Isn't it possible to constrain instances? 

I tried the following where the idea is to implement a simple monad,
but one which can only pass and return values that are showable.

  newtype Show a => TracingEv a = TE (Int -> IO (Int,a))
  unTE :: Show a => TracingEv a -> Int -> IO (Int,a)
  unTE (TE x) = x

  instance Monad TracingEv where

    return i = TE (\c -> do print c; putChar ':'; print i; putChar '\n'
                            return (c+1,i))

    m >>= f  = TE (\c -> do (c',v) <- (unTE m) c
                            (unTE (f v)) c')

Neither GHC, nor hugs likes this.  Hugs report:

  ERROR "MonadProblem.hs" (line 9): Cannot justify constraints in
  instance member binding
  *** Expression    : return
  *** Type          : Monad TracingEv => a -> TracingEv a
  *** Given context : Monad TracingEv
  *** Constraints   : Show a

?? "Cannot justify constraints??"  Isn't the case here rather that some
constraints are lacking?

GHC offers a little more explanation, but it remains cryptic:

  MonadProblem.hs:9:
      Could not deduce `Show a' from the context: ()
      Probable cause: missing `Show a' in type signature for `return'
      arising from use of `TE' at MonadProblem.hs:9
      In the right-hand side of an equation for `return':
          TE (\ c -> do
                       print c
                       putChar ':'
                       print i
                       putChar '\n'
                       return (c + 1, i))

Sure there's a missing Show a, but I can't change the signature of
return and it seems to me that Show a should follow from the
constraint on TracingEv

Is this a fundamental limitation?  If so, why?

Regards,

  Tommy

Reply via email to