[Haskell-cafe] Multi-parameter Type Class

Alexander Dunlap alexander.dunlap at gmail.com
Fri Dec 12 00:06:33 EST 2008


2008/12/11 Thomas DuBuisson <thomas.dubuisson at gmail.com>:
> 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


More information about the Haskell-Cafe mailing list