[Haskell-cafe] Re: Re: type class question

Luke Palmer lrpalmer at gmail.com
Fri Dec 7 13:21:36 EST 2007


On Dec 7, 2007 5:57 PM, Peter Padawitz <peter.padawitz at udo.edu> wrote:
> 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 cs cs') = cond (compBoolE be) (compBlock
> cs) (compBlock cs')
>          compCommand (Loop be cs)    = loop (compBoolE be) (compBlock cs)
>
>          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 kcompIntE es)
>
>          compBoolE :: BoolE -> boolE
>          compBoolE (BoolE b)      = boolE_ b
>          compBoolE (Greater e e') = greater (compIntE e) (compIntE e')
>          compBoolE (Not be)       = not_ (compBoolE be)

I'm not sure what this is worth, since you seem to have your mind set
on using this strange four-parameter type class.

You can keep most of the design advantages of using this type at the
"cost" of being more explicit if you factor it into a data type
yourself:

> data Java block command intE boolE
>   = Java { block_ :: [command] -> block
>          , skip   :: command
>          , assign :: String -> intE -> command
>          , ...
>          , compBlock :: Block -> block
>          , ...
>          }

For your default implementations:

> defCompBlock :: Java block command intE boolE -> Block -> block
> defCompBlock self = block_ self . map (compCommand self)
>
> .. etc

Then to define an example instance:

> javaAST :: Java Block Command IntE BoolE
> javaAST
>   = Java { block_ = Block
>          , ...
>          , compBlock = defCompBlock javaAST
>          , ...
>          }

Your type errors will be resolved because you are saying explicitly
which instance to use by passing the instance data structure you want
explicitly.

Luke


More information about the Haskell-Cafe mailing list