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

Benja Fallenstein benja.fallenstein at gmail.com
Fri Dec 7 13:35:09 EST 2007


On Dec 7, 2007 6:57 PM, Peter Padawitz <peter.padawitz at udo.edu> wrote:
> Jules Bean wrote:
> > Peter Padawitz wrote:
> >> Cause I don't see why the instantiation conflicts pointed out by
> >> others would vanish then.
> >
> > They would.
> >
> > If it's really true that there is only one possible choice of b,c,d
> > for any particular a, then there are no conflicts, so you'd get no
> > errors.
>
> How can ghci know this even if no instance has been defined?

Because "there is only one possible choice of b,c,d for any particular
a" is what the fundep means :-)

> If I omit the comp functions (see below), everything works. If I add
> them, all proposed solutions fail with error messages of the form
>
> Could not deduce (Java block1 ....) from the context (Java block ....)
> arising from use of `prod' at ...
>
> (see also Ben Franksen's comment from yesterday).

If you add the cyclic functional dependencies to your code, it
compiles just fine:

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)

Best,
- Benja


More information about the Haskell-Cafe mailing list