
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