[Haskell-cafe] Re: GATD and pattern matching

Dupont Corentin corentin.dupont at gmail.com
Fri Jun 11 18:13:14 EDT 2010


Thanks all, it works fine (see below).

I lamentably try to make the same for show:
> showTypeable :: (Typeable a) => a -> String
> showTypeable x = case cast x of
>                      Just x' -> show x'
>                      Nothing -> ""

Because it really upsets me to add this show constraints to the Equ
constructor ;)
what if i want to make an Obs instance with non showable elements, with no
intention to show it of course?

Corentin

> instance Typeable1 Obs where
>    typeOf1 _ = mkTyConApp (mkTyCon "Obs") []

> (===) :: (Typeable a, Typeable b, Eq b) => a -> b -> Bool
> (===) x y = cast x == Just y


> data Obs a where
>     Player   :: Obs Player
>     Official :: Obs Bool
>     Equ      :: (Eq a, Show a, Typeable a) => Obs a -> Obs a -> Obs Bool
>     Plus     :: (Num a) => Obs a -> Obs a -> Obs a
>     Time     :: (Num a) => Obs a -> Obs a -> Obs a
>     Minus    :: (Num a) => Obs a -> Obs a -> Obs a
>     And      :: Obs Bool -> Obs Bool -> Obs Bool
>     Or       :: Obs Bool -> Obs Bool -> Obs Bool
>     Not      :: Obs Bool -> Obs Bool
>     Konst    :: (Show a, Eq a) => a -> Obs a



> instance Show t => Show (Obs t) where
>     show Player      = "Player"
>     show Official    = "Official"
>     show (Equ a b)   = (show a) ++ " Eq " ++ (show b)
>     show (Plus a b)  = (show a) ++ " Plus " ++ (show b)
>     show (Minus a b) = (show a) ++ " Minus " ++ (show b)
>     show (Time a b)  = (show a) ++ " Time " ++ (show b)
>     show (Konst a)   = " (Konst " ++ (show a) ++ ")"
>     show (And a b)   = (show a) ++ " And " ++ (show b)
>     show (Or a b)    = (show a) ++ " Or " ++ (show b)
>     show (Not a)     = " (Not " ++ (show a) ++ ")"


> instance Eq t => Eq (Obs t) where
>     Player == Player       = True
>     Official == Official   = True
>     Equ a b == Equ c d     = (a,b) === (c,d)
>     Plus a b == Plus c d   = (a == c) && (b == d)
>     Minus a b == Minus c d = (a == c) && (b == d)
>     Time a b == Time c d   = (a == c) && (b == d)
>     And a b == And c d     = (a == c) && (b == d)
>     Or a b == Or c d       = (a == c) && (b == d)
>     Not a == Not b         = (a == b)
>     Konst a == Konst b     = a == b
>     _ == _                 = False
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100611/f8387902/attachment.html


More information about the Haskell-Cafe mailing list