[Haskell-cafe] existential type problem

Andrew Pimlott andrew at pimlott.net
Fri Oct 15 21:58:13 EDT 2004


On Sat, Oct 16, 2004 at 10:19:14AM +0900, Koji Nakahara wrote:
> On Fri, 15 Oct 2004 19:55:02 -0400
> Andrew Pimlott <andrew at pimlott.net> wrote:
> 
> >     data Foo = forall t. (MonadTrans t) => Foo
> >                     ((Monad m, Monad (t m)) => t m a -> m a)    -- run
> >                     ((Monad m, Monad (t m)) => t m Int)         -- op
> > 
> >     prog :: Foo -> IO Int
> >     prog (Foo run op) = run $ do
> >       lift $ putStrLn "Running prog"
> >       op
> > 
> > ghci gives the error
> > 
> >     Could not deduce (Monad (t IO)) from the context (MonadTrans t)
> >       arising from use of `op' at try.hs:22
> 
> 
> Your prog leaks m (= IO) out of Foo.  I guess you mean:
> 
> > data Foo m = forall t. (MonadTrans t, Monad (t m)) =>
> >       Foo (forall a. t m a -> m a) (t m Int)
> > 
> > prog :: Foo IO -> IO Int
> > prog (Foo run op) = run $ do
> >       lift $ putStrLn "Running prog"
> >       op
> > 
> > test = prog (Foo (flip evalStateT 0) get)

But my implementation may look like

    myFoo :: Int -> Foo
    myFoo i = Foo run op where
      run :: Monad m => StateT Int m a -> m a
      run prog  = do  (a, s) <- runStateT prog i
                      return a
      op :: Monad m => StateT Int m Int
      op        = get

which works for all monads, not just IO (that is the idea of using a
tranformer).  So I really don't want to encode that type in Foo.

Andrew


More information about the Haskell-Cafe mailing list