Multi-parameter type classes are more flexible. Here is how you can
write your old code:

> {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
>
> class (ClassA a, ClassB b) => ClassC a b where
>   from :: a -> [b]
>   to   :: a -> [b]
>
> data H = H
>
> class ClassA a where toInt :: a -> Int
> class ClassB b where fromInt :: Int -> b
>
> instance ClassB H where fromInt _ = H
>
> data Test = Test { m :: H }
> instance ClassA Test where toInt _ = 0
>
> instance ClassC Test H where
>   from = (:[]) . m
>   to   = (:[]) . m


The constraints in the ClassC a b declaration specify that in all
instances of ClassC, the type a must be in ClassA and the type b must
be in ClassB. This is the case for the "ClassC Test H" instance.

You can also specify that for some particular 'a' the function 'from'
can produce the value of the type [b] for any b in ClassB. The caller
will determine which b it wants. This is similar to your original
intention, as I understand.

> instance ClassA Int where toInt = id
>
> instance ClassB b => ClassC Int b where
>   from x = [fromInt x]
>
> t1:: [H]
> t1 = from (5::Int)



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

Reply via email to