[Haskell-cafe] Type checking oddity -- maybe my own confusion

Ryan Newton rrnewton at gmail.com
Tue Jul 12 17:01:36 CEST 2011


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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110712/b775aa97/attachment.htm>


More information about the Haskell-Cafe mailing list