[Haskell-cafe] Converting -fglasgow-exts into LANGUAGE pragmas

Martijn van Steenbergen martijn at van.steenbergen.nl
Tue Mar 31 06:24:41 EDT 2009


Hello café,

I want to replace the -fglasgow-exts in the snippet below by LANGUAGE 
pragmas. Rank2Types alone doesn't suffice. Which do I need to get the 
snippet to compile?

> {-# OPTIONS -fglasgow-exts #-}
> 
> module RunMud where
> 
> import Control.Monad.State
> 
> type Mud      = StateT MudState IO
> data MudState = MudState { mRunMud :: RunMud }
> type RunMud   = forall a. Mud a -> IO a
> 
> getRunMud :: Mud RunMud
> getRunMud = do
>   s <- get
>   return (mRunMud s)

Thanks in advance,

Martijn.


More information about the Haskell-Cafe mailing list