[Haskell-cafe] existential type problem

oleg at pobox.com oleg at pobox.com
Fri Oct 15 22:54:46 EDT 2004


Andrew Pimlott wrote:
> I want values in my existential type to denote, for some monad, a
> monadic operation and a way to run the monad.  Except, I want it mix
> the operation with operations in another monad, so it use a monad
> transformer.

I'm afraid, that phrase was a little misleading. It seems that you
meant:
	- encapsulate one _specific_ monad transformer
	- to be able to apply it to _any_ (not some!) monad

That is, the transformer must be existentially quantified, and the
monad must be universally quantified. Once that is clear, the solution
is straightforward.

> {-# OPTIONS -fglasgow-exts #-}
> module P where
>
> import Control.Monad.Trans
> import Control.Monad.State
>
> data Bar a m = forall t. (MonadTrans t, Monad (t m)) =>
> 	         Bar (t m a -> m a) (t m Int)
>
> data Foo = Foo (forall a m. Monad m => Bar a m)
>
> prog :: Foo -> IO Int
> prog (Foo x) = case x of Bar run op -> 
> 			       run $ do
> 				     lift $ putStrLn "Running prog"
> 				     op
>
> test:: IO Int
> test = prog (Foo x) where
> 	   -- to be used in a higher-ranked type: signature required
> 	   x:: Monad m => Bar a m
> 	   x = Bar (flip evalStateT 0) get
>
>
> myFoo :: Int -> Foo
> myFoo i = Foo (Bar 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
>
>
> test1 = prog (myFoo 10)


More information about the Haskell-Cafe mailing list