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

TP paratribulations at free.fr
Mon Dec 2 19:37:14 UTC 2013


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
----------------



More information about the Haskell-Cafe mailing list