New monads/MaybeT

From HaskellWiki
< New monads
Revision as of 13:34, 26 July 2007 by Antoine (talk | contribs) (added MonadIO and MonadState instances)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

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