Hi Ryan,

Think of AssignCap as an extra argument packaged up with the Assign 
constructor. When
you pattern match against Assign you make the AssignCap constraint *available* 
for use in
the RHS of the pattern; so there's no need for quantification, you already have 
the constraint
you want packaged inside your argument. (Back in the old times when GHC did not 
implement
implication constraints maybe you'd get the type you say). Does that help?

Thanks
d-


From: haskell-cafe-boun...@haskell.org 
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Ryan Newton
Sent: 12 July 2011 16:02
To: Haskell Cafe
Subject: [Haskell-cafe] Type checking oddity -- maybe my own confusion

Hi all,

Is there something wrong with the code below?  My anticipation was that the 
type of "test" would include the class constraint, because it uses the Assign 
constructor.  But if you load this code in GHCI you can see that the inferred 
type was "test :: E m -> E m".

Thanks,
  -Ryan


{-# LANGUAGE GADTs #-}

class AssignCap m
data PureT
data IOT
instance AssignCap IOT

data E m where
  Assign  :: AssignCap m => V -> E m -> E m -> E m
  Varref  :: V -> E m
-- ...

type V = String

-- I expected the following type but am not getting it:
-- test :: AssignCap m => E m -> E m
test x =
  case x of
   Assign v e1 e2 -> Assign v e1 e2
-- And this is the same:
   Assign v e1 e2 -> x

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to