[Haskell-cafe] ANNOUNCE: monad-control-0.3
Joey Hess
joey at kitenet.net
Tue Dec 6 16:32:52 CET 2011
Bas van Dijk wrote:
> You can use the following:
>
> {-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies, MultiParamTypeClasses #-}
>
> import Control.Applicative
> import Control.Monad
> import Control.Monad.Base
> import Control.Monad.Trans.Class
> import Control.Monad.Trans.Control
> import Control.Monad.Trans.State
> import Control.Monad.IO.Class
>
> newtype Annex a = Annex { runAnnex :: StateT AnnexState IO a }
> deriving (Applicative, Functor, Monad, MonadIO)
>
> data AnnexState = AnnexState
>
> instance MonadBase IO Annex where
> liftBase = Annex . liftBase
>
> instance MonadBaseControl IO Annex where
> newtype StM Annex a = StAnnex (StM (StateT AnnexState IO) a)
> liftBaseWith f = Annex $ liftBaseWith $ \runInIO ->
> f $ liftM StAnnex . runInIO . runAnnex
>
> When I have some time I will add some better documentation to monad-control.
Hmm, very close. With -Wall, I get:
Annex.hs:54:10:
Warning: No explicit method nor default method for `restoreM'
In the instance declaration for `MonadBaseControl IO Annex'
And my program crashes at runtime (!)
No instance nor default method for class operation Control.Monad.Trans.Control.restoreM
--
see shy jo
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 828 bytes
Desc: Digital signature
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20111206/dc29f35f/attachment.pgp>
More information about the Haskell-Cafe
mailing list