[Haskell-cafe] Fighting the monad stack, MonadIO

Antoine Latter aslatter at gmail.com
Thu Apr 10 13:44:32 EDT 2008


On Thu, Apr 10, 2008 at 9:50 AM, Adam Smyczek <adam.smyczek at gmail.com> wrote:
> For a small webapi binding I try to implement a session like monad
>  by building a stack including BrowserAction from Network.Browser
>  module as following:
>
>  newtype RBAction a = RBAction
>     { exec :: ErrorT String (StateT RBState BrowserAction) a }
>     deriving (Functor, Monad, MonadState RBState)
>
>  I would like the RBAction to implement MonadIO as well,
>  but fight with the liftIO function for hours now, without success.
>  Any idea how the implementation of liftIO could look like?
>

Adam,

The following worked for me:

+++++
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Control.Monad.Trans
import Control.Monad.State
import Control.Monad.Error

type BrowserAction = IO  -- or something else which is in MondaIO
data RBState = RBState

newtype RBAction a = RBAction
   { exec :: ErrorT String (StateT RBState BrowserAction) a }
   deriving (Functor, Monad, MonadState RBState)

instance MonadIO RBAction where
    liftIO = RBAction . liftIO
+++++

Because everything inside the newtype wrapper already supports MondIO,
you just need to call the version of liftIO underneath the newtype
wrapper.

Is that clear at all?

-Antoine


More information about the Haskell-Cafe mailing list