[Haskell-cafe] type class question

Peter Padawitz peter.padawitz at udo.edu
Mon Dec 3 07:43:14 EST 2007


What is wrong here? ghci tries (and fails) to deduce certain types for 
the comp functions that I did not expect.

|type Block   = [Command]
data Command = Skip | Assign String IntE | Cond BoolE Block Block |
               Loop BoolE Block
data IntE    = IntE Int | Var String | Sub IntE IntE | Sum [IntE] | Prod 
[IntE]
data BoolE   = BoolE Bool | Greater IntE IntE | Not BoolE

class Java block command intE boolE
   where block_ :: [command] -> block
         skip :: command
         assign :: String -> intE -> command
         cond :: boolE -> block -> block -> command
         loop :: boolE -> block -> command
         intE_ :: Int -> intE
         var :: String -> intE
         sub :: intE -> intE -> intE
         sum_ :: [intE] -> intE
         prod :: [intE] -> intE
         boolE_ :: Bool -> boolE
         greater :: intE -> intE -> boolE
         not_ :: boolE -> boolE

         compBlock :: Block -> block
         compBlock = block_ . map compCommand

         compCommand :: Command -> command
         compCommand Skip           = skip
         compCommand (Assign x e)   = assign x (compIntE e)
         compCommand (Cond be c c') = cond (compBoolE be) (compCommand c)
                                                          (compCommand c')
         compCommand (Loop be c)    = loop (compBoolE be) (compCommand c)-}

         compIntE :: IntE -> intE
         compIntE (IntE i)   = intE_ i
         compIntE (Var x)    = var x
         compIntE (Sub e e') = sub (compIntE e) (compIntE e')
         compIntE (Sum es)   = sum_ (map compIntE es)
         compIntE (Prod es)  = prod (map compIntE es)
         
         compBoolE :: BoolE -> boolE
         compBoolE (BoolE b)      = boolE_ b
         compBoolE (Greater e e') = greater (compIntE e) (compIntE e')
         compBoolE (Not be)       = not_ (compBoolE be)
|
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20071203/b797ca5b/attachment.htm


More information about the Haskell-Cafe mailing list