-- | Extend a monad with a read-only environment module Mini.Transformers.ReaderT ( -- * Type ReaderT ( ReaderT ), -- * Runner runReaderT, -- * Operations ask, local, ) where import Control.Applicative ( Alternative ( empty, (<|>) ), ) import Control.Monad ( ap, liftM, ) import Mini.Transformers.Class ( MonadTrans ( lift ), ) {- - Type -} -- | A transformer with read-only /r/, inner monad /m/, return /a/ newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a -- ^ Unwrap a 'ReaderT' computation with an initial read-only value } instance (Monad m) => Functor (ReaderT r m) where fmap = liftM instance (Monad m) => Applicative (ReaderT r m) where pure = ReaderT . const . pure (<*>) = ap instance (Monad m, Alternative m) => Alternative (ReaderT r m) where empty = ReaderT . const $ empty m <|> n = ReaderT $ \r -> runReaderT m r <|> runReaderT n r instance (Monad m) => Monad (ReaderT r m) where m >>= k = ReaderT $ \r -> runReaderT m r >>= (`runReaderT` r) . k instance MonadTrans (ReaderT r) where lift = ReaderT . const {- - Operations -} -- | Fetch the read-only environment ask :: (Monad m) => ReaderT r m r ask = ReaderT pure -- | Run a computation in a modified environment local :: (r -> r') -> ReaderT r' m a -> ReaderT r m a local f m = ReaderT $ runReaderT m . f