Without going too deep into the details of my type classes, I have
written the following code (focusing on compile1):

  {-# OPTIONS -fglasgow-exts #-}

  compile1 :: (Builder b box) => t -> Name -> Ir.ANF -> b t
  compile1 f x body = do env <- compile body empty
                         wire (Arg W) (env x)
                         return f

  compile :: (Builder b box) => Ir.ANF -> Env box -> b (Env box)

  class (Monad b) => Builder b box where
    wire            :: Source box -> Sink box -> b ()
    ...

  type Env box = Name -> Sink box

This program is rejected by GHC with the following message:

Ccomp.hs:54:23:
    Could not deduce (Builder b box1) from the context (Builder b box)
      arising from use of `wire' at Ccomp.hs:54:23-42
    Possible fix:
      add (Builder b box1) to the type signature(s) for `compile1'
    In the expression: wire (Arg W) (env x)
    In a 'do' expression: wire (Arg W) (env x)
    In the expression:
        do env <- compile body empty
           wire (Arg W) (env x)
           return f

Note that compile1 has an explicit type signature much along the lines
suggested by GHC.  If I *remove* this type signature, the function
compiles successfully, and ghci reporets this type for compile1:

  compile1 :: (Builder t box) => t1 -> Name -> Ir.ANF -> t t1

I believe this signature is isomorphic to the explicit signature I had
attempted to use.

Am I misusing the type-class system in some way, or should I be
reporting a bug in GHC?


Norman

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

Reply via email to