[Haskell-cafe] how to factorize propagation of a function over a data type

Andras Slemmer 0slemi0 at gmail.com
Mon Dec 2 16:21:25 UTC 2013


There are several ways to approach this problem. What you are basically
trying to do is map a function over the leaves of your datastructure. So
naturally a function that comes to mind is:

mapBar :: (Integer -> Integer) -> (Float -> Float) -> Bar -> Bar
mapBar f _ (Bar1 i) = Bar1 (f i)
mapBar _ g (Bar2 r) = Bar2 (g r)
mapBar f g (Exp1 e1 e2) = Exp1 (mapBar f g e1) (mapBar f g e2)
mapBar f g (Exp2 e1 e2) = Exp2 (mapBar f g e1) (mapBar f g e2)

And the Bar instance becomes

instance FooClass Bar where
    foo1 = mapBar foo1 foo1
    foo2 = mapBar foo2 foo2

As far as I understand this is not what you're looking for, as you want the
mapBar function to be agnostic wrt what type the leaves contain. The
minimal assumption that this requires is that the leaf types are a member
of FooClass, and indeed you can write such a map:

mapBar :: (forall a. FooClass a => a -> a) -> Bar -> Bar
mapBar f (Bar1 i) = Bar1 (f i)
mapBar f (Bar2 r) = Bar2 (f r)
mapBar f (Exp1 e1 e2) = Exp1 (mapBar f e1) (mapBar f e2)
mapBar f (Exp2 e1 e2) = Exp2 (mapBar f e1) (mapBar f e2)

instance FooClass Bar where
    foo1 = mapBar foo1
    foo2 = mapBar foo2

I think this is closer to what you were looking for. The above map requires
-XRankNTypes, because mapBar requires a function that is fully polymorphic
('a' will instantiate to Integer and Float respectively). If you haven't
used higher ranked types before I think it is instructive to think about
why the above signature works and the one you wrote doesn't. In particular
think about at which point the polymorphic type 'a' is instantiated in both
cases, or rather what the "scope" of 'a' is.


On 2 December 2013 19:37, TP <paratribulations at free.fr> wrote:

> Vo Minh Thu wrote:
>
> > You can replace your `propagate` function by this one:
> >
> >     propagate :: Bar -> (Integer -> Integer) -> Bar
> >     propagate v f = case v of
> >         Bar1 i     -> Bar1 (f i)
> >         Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f)
> >         Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f)
> >
> > In your code, you were applying the same (w.r.t. to its type) `f` to
> > Bar and Integer.
> > Also, your Bar data type contains, at its leaf, an Intger, not a `a`.
>
> You are right, I made a stupid error in my code. The following version
> indeed works:
>
> ----------------
> class FooClass a where
>     foo1 :: a -> a
>     foo2 :: a -> a
>
> instance FooClass Integer where
>
>     foo1 v = 1
>     foo2 v = 2
>
> data Bar = Bar1 Integer
>          | Exp1 Bar Bar
>          | Exp2 Bar Bar
>     deriving Show
>
> -- The following line works because there are only integers in the leaves.
> propagate :: Bar -> (Integer -> Integer) -> Bar
> propagate v f = case v of
>         Bar1 i     -> Bar1 (f i)
>         Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f)
>         Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f)
>
> instance FooClass Bar where
>
>     foo1 b = propagate b foo1
>     foo2 b = propagate b foo2
>
> main = do
>
> let a = Bar1 3
> let b = Bar1 4
> let c = Exp1 (Exp2 a b) b
>
> print c
> print $ foo1 c
> print $ foo2 c
> ----------------
>
> However, if we add another type in the leaves, we cannot use the solution
> above.
>
> ----------------
> class FooClass a where
>     foo1 :: a -> a
>     foo2 :: a -> a
>
> instance FooClass Integer where
>
>     foo1 v = 1
>     foo2 v = 2
>
> instance FooClass Float where
>
>     foo1 v = 0.25
>     foo2 v = 0.5
>
> data Bar = Bar1 Integer
>          | Bar2 Float
>          | Exp1 Bar Bar
>          | Exp2 Bar Bar
>     deriving Show
>
> -- This time the following line does not work.
> propagate :: Bar -> (Integer -> Integer) -> Bar
> -- The following line does not work either.
> -- propagate :: FooClass a => Bar -> (a->a) -> Bar
> propagate v f = case v of
>         Bar1 i     -> Bar1 (f i)
>         Bar2 i     -> Bar2 (f i)
>         Exp1 b1 b2 -> Exp1 (propagate b1 f) (propagate b2 f)
>         Exp2 b1 b2 -> Exp2 (propagate b1 f) (propagate b2 f)
>
> instance FooClass Bar where
>
>     foo1 b = propagate b foo1
>     foo2 b = propagate b foo2
>
> main = do
>
> let a = Bar1 3
> let b = Bar1 4
> let c = Exp1 (Exp2 a b) b
>
> print c
> print $ foo1 c
> print $ foo2 c
> ----------------
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131202/60bb3559/attachment.html>


More information about the Haskell-Cafe mailing list