
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

Since your map function is calling zot to convert an x to a y you must
state that this is possible:
instance ZOT x y => ZOT [x] [y] where
zot xs = map zot xs
-- Lennart
2008/12/11 Paul Keir
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

I took your suggestion and it worked exactly as I had hoped. Thankyou. GHCI (6.8.2) was though a little concerned, and told me I had an: Illegal instance declaration for `ZOT [x] [y]' and recommended I use -fallow-undecidable-instances. I did, and it worked. What have I done though? The word "undecidable" scares me a little :) ---SNIP---

Am Donnerstag, 11. Dezember 2008 16:52 schrieb Paul Keir:
I took your suggestion and it worked exactly as I had hoped. Thankyou.
GHCI (6.8.2) was though a little concerned, and told me I had an: Illegal instance declaration for `ZOT [x] [y]' and recommended I use -fallow-undecidable-instances. I did, and it worked. What have I done though? The word "undecidable" scares me a little :)
---SNIP---
It's not dangerous. ghci told you that the Coverage Condition failed for the functional dependency, read section 8.6.3 of the user's guide for more info, so instance inference is not guaranteed to terminate, that's what 'undecidable' means. The flag says go ahead and try until either the question is decided or the recursion stack is exhausted, whichever happens first.

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
----
2008/12/11 Paul Keir
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

Thanks to you both, that also looks fantastic. I'll print it out;
put it under my pillow; let it brew overnight and then push in
tomorrow ;)
-----Original Message-----
From: Thomas DuBuisson [mailto:thomas.dubuisson@gmail.com]
Sent: Thu 11/12/2008 15:30
To: Paul Keir
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Multi-parameter Type Class[MESSAGE NOT SCANNED]
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
----
2008/12/11 Paul Keir
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

2008/12/11 Thomas DuBuisson
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 ----
I don't mean to hijack the original question, but I have a question about this code. Is this the same as saying class ZOT a where type Eval a zot :: a -> Eval a and then appropriate instance declarations? Is there any reason to have the type function inside or outside of the class? Thanks, Alex
participants (5)
-
Alexander Dunlap
-
Daniel Fischer
-
Lennart Augustsson
-
Paul Keir
-
Thomas DuBuisson