Jules Bean wrote:

Peter Padawitz wrote:

So the fundep would solve the problem.

But, actually, it doesn't :-(

But actually, it does!

Indeed... Sorry, I think I left intE out of the cycle. This might be the reason why it did not work before.

Ben Franksen's answer from yesterday compiles fine for me if I add the missing fundep, block -> command.

Your original code compiles without error, given the fundep. Exact code I compiled attached at the bottom of this document. You may have to repair long lines!

Incidentally, I question why the "compFoo" are methods. Why not just make them polymorphic functions? They don't look like you expect instances to change them. The code continues to compile if I make them functions and amend their signatures as required.

I put compFoo into the class for the same reason why /= is part of the class Eq: both functions are unique as soon as the others have been instantiated.


{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}

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 | block -> command, command -> intE, intE -> boolE, boolE -> block
  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 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)

_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to