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

Peter Padawitz peter.padawitz at udo.edu
Fri Dec 7 12:57:12 EST 2007


Jules Bean wrote:

> Peter Padawitz wrote:
>
>> Jules Bean wrote:
>>
>>> Peter Padawitz wrote:
>>>
>>>> Functional dependencies don't work in my case. Actually, I don't 
>>>> see why they should.
>>>
>>>
>>>
>>> Ah well, it's cruel to say that without explaining to us why!
>>
>>
>> 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?

> So the fundep would solve the problem.

But, actually, it doesn't :-(

>>> class Java (a,b,c,d) where ....
>>
>>
>> Yeah... but ghc accepts only type variables here, not arbitrary 
>> polymorphic types.
>
>
> Indeed, but there is a workaround:
>
> class Java all a b c d |
>    all -> a, all -> b, all -> c, all -> d, a,b,c,d -> all

Same problem.

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

***************

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



More information about the Haskell-Cafe mailing list