I have no time now to answer completely, but I would say that type families could help.


2013/12/2 TP <paratribulations@free.fr>
Hi,

Let us consider the following example:

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

instance FooClass Bar where

    foo1 b = case b of
        Bar1 i     -> Bar1 (foo1 i)
        Exp1 b1 b2 -> Exp1 (foo1 b1) (foo1 b2)
        Exp2 b1 b2 -> Exp2 (foo1 b1) (foo1 b2)

    foo2 b = case b of
        Bar1 i     -> Bar1 (foo2 i)
        Exp1 b1 b2 -> Exp1 (foo2 b1) (foo2 b2)
        Exp2 b1 b2 -> Exp2 (foo2 b1) (foo2 b2)

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

We obtain as expected:

$ runghc propagate_with_duplicated_code.hs
Exp1 (Exp2 (Bar1 3) (Bar1 4)) (Bar1 4)
Exp1 (Exp2 (Bar1 1) (Bar1 1)) (Bar1 1)
Exp1 (Exp2 (Bar1 2) (Bar1 2)) (Bar1 2)

My question is related to the code inside the Fooclass instance definition
for Bar: we have repeated code where only "foo1" or "foo2" changes.
So the first idea is to write a higher-order function, but it does not work:

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

propagate :: FooClass a => a -> (a->a) -> a
propagate v f = case v of
        Bar1 i     -> Bar1 (f i)
        Exp1 b1 b2 -> Exp1 (f b1) (f b2)
        Exp2 b1 b2 -> Exp2 (f b1) (f b2)

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

The problem is that the type variable `a` in the definition of `propagate`
cannot match both the type of i, i.e. an integer, and the type of b1 and b2,
i.e. Bar.
Putting the function propagate in the typeclass does not help. How to
factorize my code?

Thanks in advance,

TP

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe