At 13:22 2000-04-29 +0200, you wrote:
>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

To be a Monad, the type constructor TracingEv needs to work with _all_ types.
   -----------------
You can work around this, with overlapping instances. 

  class MightPrint a where
    pr :: Int -> a -> IO ()
  instance MightPrint a where
    pr i c = return ()
  instance (Show a) => MightPrint a where
    pr i c = do print c; putChar ':'; print i; putChar '\n'

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

  instance Monad TracingEv where
    return i = TE (\c -> do pr c i
                            return (c+1,i))
    m >>= f  = TE (\c -> do (c',v) <- (unTE m) c
                            (unTE (f v)) c')

But Hugs is not happy with the overlap unless you use -98 +m,
and the +m is an experimental feature.

--
Scott Turner
[EMAIL PROTECTED]       http://www.ma.ultranet.com/~pkturner

Reply via email to