servant-0.9: A family of combinators for defining webservices APIs

Safe HaskellNone
LanguageHaskell2010

Servant.Utils.Enter

Contents

Synopsis

Documentation

class Enter typ arg ret | typ arg -> ret, typ ret -> arg where Source #

Minimal complete definition

enter

Methods

enter :: arg -> typ -> ret Source #

Instances

Enter (m a) ((:~>) m n) (n a) Source # 

Methods

enter :: (m :~> n) -> m a -> n a Source #

Enter b arg ret => Enter (a -> b) arg (a -> ret) Source # 

Methods

enter :: arg -> (a -> b) -> a -> ret Source #

(Enter typ1 arg1 ret1, Enter typ2 arg2 ret2, (~) * arg1 arg2) => Enter ((:<|>) typ1 typ2) arg1 ((:<|>) ret1 ret2) Source # 

Methods

enter :: arg1 -> (typ1 :<|> typ2) -> ret1 :<|> ret2 Source #

Servant combinators

Useful instances

newtype m :~> n Source #

A natural transformation from m to n. Used to enter particular datatypes.

Constructors

Nat 

Fields

  • unNat :: forall a. m a -> n a
     

Instances

Enter (m a) ((:~>) m n) (n a) Source # 

Methods

enter :: (m :~> n) -> m a -> n a Source #

Category (* -> *) (:~>) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

liftNat :: (MonadTrans t, Monad m) => m :~> t m Source #

Like lift.

evalStateTLNat :: Monad m => s -> StateT s m :~> m Source #

evalStateTSNat :: Monad m => s -> StateT s 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.

hoistNat :: (MFunctor t, Monad m) => (m :~> n) -> t m :~> t n Source #

Like mmorph's hoist.

embedNat :: (MMonad t, Monad n) => (m :~> t n) -> t m :~> t n Source #

Like mmorph's embed.

squashNat :: (Monad m, MMonad t) => t (t m) :~> t m Source #

Like mmorph's squash.