-- | Extend a monad with the ability to terminate a computation without a value module Mini.Transformers.MaybeT ( -- * Type MaybeT ( MaybeT ), -- * Runner runMaybeT, -- * Operations nothing, anticipate, ) where import Control.Applicative ( Alternative, empty, (<|>), ) import Control.Monad ( ap, liftM, (>=>), ) import Control.Monad.IO.Class ( MonadIO, liftIO, ) import Mini.Transformers.Class ( MonadTrans, lift, ) import Prelude ( Applicative, Functor, Maybe ( Just, Nothing ), Monad, MonadFail, fail, fmap, maybe, pure, ($), (.), (<$>), (<*>), (>>=), ) {- - Type -} -- | A terminable transformer with inner monad /m/, return /a/ newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) -- ^ Unwrap a 'MaybeT' computation } instance (Monad m) => Functor (MaybeT m) where fmap = liftM instance (Monad m) => Applicative (MaybeT m) where pure = MaybeT . pure . Just (<*>) = ap instance (Monad m) => Alternative (MaybeT m) where empty = MaybeT $ pure Nothing m <|> n = MaybeT $ runMaybeT m >>= maybe (runMaybeT n) (pure . Just) instance (Monad m) => Monad (MaybeT m) where m >>= k = MaybeT $ runMaybeT m >>= maybe (pure Nothing) (runMaybeT . k) instance MonadTrans MaybeT where lift = MaybeT . fmap Just instance (Monad m) => MonadFail (MaybeT m) where fail _ = empty instance (MonadIO m) => MonadIO (MaybeT m) where liftIO = lift . liftIO {- - Operations -} -- | Terminate the computation without a value nothing :: (Monad m) => MaybeT m a nothing = empty -- | Run a computation and get its result anticipate :: (Monad m) => MaybeT m a -> MaybeT m (Maybe a) anticipate = lift . runMaybeT . (Just <$>) >=> maybe (pure Nothing) pure