New monads/MaybeT: Difference between revisions
(Import/export of Fix and State not needed yet.) |
(added MonadIO and MonadState instances) |
||
Line 4: | Line 4: | ||
<haskell> | <haskell> | ||
{-# OPTIONS_GHC -fglasgow-exts #-} | {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-} | ||
module Control.Monad.Maybe | module Control.Monad.Maybe | ||
Line 14: | Line 14: | ||
import Control.Monad | import Control.Monad | ||
import Control.Monad.Trans | import Control.Monad.Trans | ||
import Control.Monad.State | |||
newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)} | newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)} | ||
Line 35: | Line 36: | ||
-- (Add other MTL instances, and a MonadFix instance) | -- (Add other MTL instances, and a MonadFix instance) | ||
instance MonadIO m => MonadIO (maybeT m) where | |||
liftIO = lift . liftIO | |||
instance (MonadState s m) => MonadState s (MaybeT m) where | |||
get = lift get | |||
put = lift . put | |||
</haskell> | </haskell> | ||
[[Category:Code]] | [[Category:Code]] |
Revision as of 13:34, 26 July 2007
The Maybe monad deserves a transformer, just like the other classic monads.
The code
{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}
module Control.Monad.Maybe
(MaybeT(runMaybeT),
module Control.Monad,
module Control.Monad.Trans)
where
import Control.Monad
import Control.Monad.Trans
import Control.Monad.State
newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)}
instance Functor m => Functor (MaybeT m) where
fmap f x = MaybeT $ fmap (fmap f) $ runMaybeT x
instance Monad m => Monad (MaybeT m) where
return = MaybeT . return . return
x >>= f = MaybeT $ runMaybeT x >>= maybe (return Nothing) (runMaybeT . f)
fail _ = MaybeT $ return Nothing
instance Monad m => MonadPlus (MaybeT m) where
mzero = MaybeT $ return mzero
mplus x y = MaybeT $ liftM2 mplus (runMaybeT x) (runMaybeT y)
-- Provide other MTL instances, for convenience
instance MonadTrans MaybeT where
lift = MaybeT . liftM return
-- (Add other MTL instances, and a MonadFix instance)
instance MonadIO m => MonadIO (maybeT m) where
liftIO = lift . liftIO
instance (MonadState s m) => MonadState s (MaybeT m) where
get = lift get
put = lift . put