[Haskell-cafe] a beginner question: decorate-op-undecorate

John Lato jwlato at gmail.com
Sat Feb 6 07:43:03 EST 2010


> From: Aran Donohue <aran.donohue at gmail.com>
>
> Hi Haskell-Cafe,
>
> Consider a data type such as
>
> data Binding = Binding Var (Either Value [Value])
>
> representing a variable bound either to a fixed value or that has a list of
> possible values.
>
> I'd like to perform an operation on say, the fixed-value members of a list
> of bindings. Data.Either has "partitionEithers"---I'd essentially like to
> use partitionEithers, but in a way that it "peeks" into the value field of
> the binding. For the sake of argument, let's say I can't or can't modify
> Binding to move the Either to the outside.

I think that partitionEithers is leading you down the wrong trail.  If
what you want to do is modify some values inside the binding, I would
start with this:

> mapVal :: (Either Value [Value] -> Either Value [Value]) -> Binding -> Binding
> mapVal f (Binding v e) = Binding v (f e)
>
> mapLeft :: (a -> b) -> Either a c -> Either b c
> mapLeft f = either (Left . f) Right
>
> -- mapRight is just fmap, but for symmetry
> mapRight :: (b -> c) -> Either a b -> Either a c
> mapRight = fmap
>
> modifyFixed :: (Value -> Value) -> Binding -> Binding
> modifyFixed f b = mapVal (mapLeft f) b
>
> modifyList :: ([Value] -> [Value]) -> Binding -> Binding
> modifyList f b = mapVal (mapRight f) b
>
> -- note that modifyFixed and modifyList have very nice point-free representations
> -- modifyFixed = mapVal . mapLeft
> -- modifyList = mapVal . mapRight

Now to apply this to a list:

> modifyFixedBindings :: (Value -> Value) -> [Binding] -> [Binding]
> modifyFixedBindings f binds = map (modifyFixed f) binds
> -- or point-free
> modifyFixedBindings' = map . modifyFixed

In my opinion, this would be more idiomatic if Binding were polymorphic:

> data Binding' k v = Binding' k v
>
> instance Functor (Binding' k) where
>   fmap f (Binding' k v) = Binding' k (f v)
>
> type Binding2 = Binding' Var (Either Value [Value])

now mapVal is just fmap, and these functions are:

> modifyFixed2 :: (Val -> Val) -> [Binding2] -> [Binding2]
> modifyFixed2 = fmap . fmap . mapLeft
>
> modifyList2 :: ([Val] -> [Val]) -> [Binding2] -> [Binding2]
> modifyList2 = fmap . fmap . mapRight


I've typed out all the steps for clarity, but to be honest, I wouldn't
bother with the Fixed and List variants, unless you're going to use
them frequently.  I would do just:

> mapVals :: (Either Value [Value] -> Either Value [Value]) -> [Binding] -> [Binding]
> mapVals f = map (\(Binding var val) -> Binding var (f val))

and leave it at that, using "mapVals" with the "either" function when
necessary.  I would consider making Binding polymorphic, though, so
you can write the Functor instance.

You may also want to look at Data.Traversable.

Cheers,
John


More information about the Haskell-Cafe mailing list