Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class Enter typ arg ret | typ arg -> ret, typ ret -> arg where
- newtype m :~> n = Nat {
- unNat :: forall a. m a -> n a
- liftNat :: (MonadTrans t, Monad m) => m :~> t m
- runReaderTNat :: r -> ReaderT r m :~> m
- evalStateTLNat :: Monad m => s -> StateT s m :~> m
- evalStateTSNat :: Monad m => s -> StateT s m :~> m
- logWriterTSNat :: MonadIO m => (w -> IO ()) -> WriterT w m :~> m
- logWriterTLNat :: MonadIO m => (w -> IO ()) -> WriterT w m :~> m
- hoistNat :: (MFunctor t, Monad m) => (m :~> n) -> t m :~> t n
- embedNat :: (MMonad t, Monad n) => (m :~> t n) -> t m :~> t n
- squashNat :: (Monad m, MMonad t) => t (t m) :~> t m
- generalizeNat :: Applicative m => Identity :~> m
Documentation
Servant combinators
Useful instances
A natural transformation from m
to n
. Used to enter
particular
datatypes.
runReaderTNat :: r -> ReaderT r m :~> m Source #
logWriterTSNat :: MonadIO m => (w -> IO ()) -> WriterT w m :~> m Source #
Log the contents of WriterT
with the function provided as the
first argument, and return the value of the WriterT
computation
logWriterTLNat :: MonadIO m => (w -> IO ()) -> WriterT w m :~> m Source #
Like logWriterTSNat
, but for strict WriterT
.
generalizeNat :: Applicative m => Identity :~> m Source #
Like mmorph
's generalize
.