brain explosion in polymorphic state monad

mathieu tenfingers@ifrance.com
Thu, 10 Oct 2002 22:42:28 +0200


Hello,

I am trying to define a polymorphic state monad using glasgow extensions and I got a brain explosion of ghc when i try to compile it.

Here is the code :

newtype StateT s m a = MkStateT (s -> m (a, s))

instance Monad m => Monad (StateT s m) where
  return x = MkStateT (\s -> return (x, s))
  MkStateT m1 >>= k =
    MkStateT
    (\s0 -> do (a, s1) <- m1 s0
               let MkStateT m2 = k a
               m2 s1 )

data Thread a = forall b . MkThread (StateT (Thread b) [] a)

instance Monad Thread where
  return = MkThread . return
  MkThread p >>= k = MkThread ( do x <- p
                                   let MkThread p' = k x 
                                   p' )

I got this error :
   My brain just exploded.
    I can't handle pattern bindings for existentially-quantified constructors.
    In the binding group
        MkThread p' = k x
    In the first argument of `MkThread', namely
        `(do
            x <- p
            let MkThread p' = k x
            p')'
    In the definition of `>>=':
        MkThread (do
                    x <- p
                    let MkThread p' = k x
                    p')

How can i define (>>=) for my thread monad ?

Thanks in advance for any piece of advice,
Mathieu

-- 
There are only 10 types of people in the world:
Those who understand binary and those who don't.