I see Lennart answered your question. For more fun you could also do this with TypeFamilies, which are the new hot thing in Haskell type level logic. Since you are just getting into MPTC, FunDeps etc I figured you'd be interested.
------ START CODE ------
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, TypeSynonymInstances, FlexibleInstances, TypeFamilies #-}
data Foo = Foo Bar deriving(Show)
data Bar = Bar String deriving(Show)
-- A family of types will evaluate from one type to another.
-- Here, I chose the word 'Eval', which you could make more meaningful.
-- It is basically a function over types.
type family Eval b
-- This is three definitions for the type function 'Eval'
type instance Eval Foo = Integer
type instance Eval Bar = String
type instance Eval [x] = [Eval x]
-- And instead of a functional dependency
-- you have a type level function (Eval) that operates on the type 'a'.
class ZOT a where
zot :: a -> Eval a
instance ZOT Foo where
zot x = 17
instance ZOT Bar where
zot x = "Eighteen"
-- And don't forget that x must be an instance of ZOT to apply zot.
instance (ZOT x) => ZOT [x] where
zot xs = map zot xs
main = do print $ zot $ Foo $ Bar "Blah"
print $ zot $ Bar "Blah"
print $ zot $ [Bar "Blah", Bar "Blah"] -- No map here please
----
Hi all,
I've been trying to refactor my tree conversion code to make
better use of type classes; and I've discovered multi-parameter
type classes and functional dependencies. I have a class with a
function a2b, and I'd like "map" to be used when it's a list of
type a.
I've created a simple failing example:
data Foo = Foo Bar deriving(Show)
data Bar = Bar String deriving(Show)
class ZOT a b | a -> b where
zot :: a -> b
instance ZOT Foo Integer where
zot x = 17
instance ZOT Bar String where
zot x = "Eighteen"
instance ZOT [x] [y] where -- This bit
zot xs = map zot xs -- fails
main = do print $ zot $ Foo $ Bar "Blah"
print $ zot $ Bar "Blah"
print $ zot $ [Bar "Blah", Bar "Blah"] -- No map here please
I know this would work if the third instance of zot
explicitly took [Bar] and [String]. Can I not instead generalise
for all the ADTs in my tree in the way I've outlined? Must I
instantiate for the type of each list pair?
Cheers,
Paul
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe