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

From: Aran Donohue
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

Hi John I'm not sure about making Binding polymorphic to get Functor, Traversable, Foldable... While I think you're correct that partitionEithers might not be a useful example to draw from in this case, I'd assume that Binding would be part of a larger syntax-tree, thus there might not be a appropriate single leaf to make the tree polymorphic on. Felipe Lessa's point - to use Uniplate or one of the Generics packages - might be a better candidate for implementing traversals. Best wishes Stephen

One way or the other, this has been a very productive question for getting
good pointers on what to read about next...
Thanks again.
Aran
On Sat, Feb 6, 2010 at 8:18 AM, Stephen Tetley
Hi John
I'm not sure about making Binding polymorphic to get Functor, Traversable, Foldable...
While I think you're correct that partitionEithers might not be a useful example to draw from in this case, I'd assume that Binding would be part of a larger syntax-tree, thus there might not be a appropriate single leaf to make the tree polymorphic on. Felipe Lessa's point - to use Uniplate or one of the Generics packages - might be a better candidate for implementing traversals.
Best wishes
Stephen _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Aran Donohue
-
John Lato
-
Stephen Tetley