Yes, the recursive calls of compCommand are supposed to be calls of compBlock.

The intention of the program is a generic evaluator comp... of Sigma-terms in arbitrary Sigma-algebras. The signature Sigma is given by the first 4 types (and the corresponding functions in the class declaration), the terms are the objects of the types, and the algebras are the class instances.

The problem with my implementation in terms of multiple-parameter classes seems to be - I conclude this from Ryan's comment - that the intended dependency among the parameters is not reflected here. But what are the alternatives? Roughly said, I need a construct that allows me gather several type variables such that an instance is always an instance of all of them.


On Dec 3, 2007 7:43 AM, Peter Padawitz <[EMAIL PROTECTED] <mailto:[EMAIL PROTECTED]>> wrote:

    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)
    |


Well, first of all, the definition of compCommand should use calls to compBlock, not recursive calls to compCommand. But that's not the main source of your problems.

What exactly are you trying to accomplish? And why do you need a type class?

-Brent

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

Reply via email to