monad-unlift-0.2.0: Typeclasses for representing monad transformer unlifting

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.Unlift

Contents

Description

See overview in the README.md

Synopsis

Trans

class (MonadTransControl t, Forall (Identical t)) => MonadTransUnlift t Source #

A monad transformer which can be unlifted, obeying the monad morphism laws.

Since 0.1.0

Instances

(MonadTransControl t, Forall * (Identical t)) => MonadTransUnlift t Source # 

newtype Unlift t Source #

A function which can move an action down the monad transformer stack, by providing any necessary environment to the action.

Note that, if ImpredicativeTypes worked reliably, this type wouldn't be necessary, and askUnlift would simply include a more generalized type.

Since 0.1.0

Constructors

Unlift 

Fields

askUnlift :: forall t m. (MonadTransUnlift t, Monad m) => t m (Unlift t) Source #

Get the Unlift action for the current transformer layer.

Since 0.1.0

askRun :: (MonadTransUnlift t, Monad (t m), Monad m) => t m (t m a -> m a) Source #

A simplified version of askUnlift which addresses the common case where polymorphism isn't necessary.

Since 0.1.0

Base

class (MonadBaseControl b m, Forall (IdenticalBase m)) => MonadBaseUnlift b m | m -> b Source #

A monad transformer stack which can be unlifted, obeying the monad morphism laws.

Since 0.1.0

Instances

(MonadBaseControl b m, Forall * (IdenticalBase m)) => MonadBaseUnlift b m Source # 

newtype UnliftBase b m Source #

Similar to Unlift, but instead of moving one layer down the stack, moves the action to the base monad.

Since 0.1.0

Constructors

UnliftBase 

Fields

askUnliftBase :: forall b m. MonadBaseUnlift b m => m (UnliftBase b m) Source #

Get the UnliftBase action for the current transformer stack.

Since 0.1.0

askRunBase :: MonadBaseUnlift b m => m (m a -> b a) Source #

A simplified version of askUnliftBase which addresses the common case where polymorphism isn't necessary.

Since 0.1.0

Reexports

class MonadTrans t where #

The class of monad transformers. Instances should satisfy the following laws, which state that lift is a monad transformation:

Minimal complete definition

lift

Methods

lift :: Monad m => m a -> t m a #

Lift a computation from the argument monad to the constructed monad.

Instances

MonadTrans ListT 

Methods

lift :: Monad m => m a -> ListT m a #

MonadTrans MaybeT 

Methods

lift :: Monad m => m a -> MaybeT m a #

MonadTrans (ErrorT e) 

Methods

lift :: Monad m => m a -> ErrorT e m a #

MonadTrans (ExceptT e) 

Methods

lift :: Monad m => m a -> ExceptT e m a #

MonadTrans (StateT s) 

Methods

lift :: Monad m => m a -> StateT s m a #

MonadTrans (StateT s) 

Methods

lift :: Monad m => m a -> StateT s m a #

Monoid w => MonadTrans (WriterT w) 

Methods

lift :: Monad m => m a -> WriterT w m a #

Monoid w => MonadTrans (WriterT w) 

Methods

lift :: Monad m => m a -> WriterT w m a #

MonadTrans (IdentityT *) 

Methods

lift :: Monad m => m a -> IdentityT * m a #

MonadTrans (ContT * r) 

Methods

lift :: Monad m => m a -> ContT * r m a #

MonadTrans (ReaderT * r) 

Methods

lift :: Monad m => m a -> ReaderT * r m a #

Monoid w => MonadTrans (RWST r w s) 

Methods

lift :: Monad m => m a -> RWST r w s m a #

Monoid w => MonadTrans (RWST r w s) 

Methods

lift :: Monad m => m a -> RWST r w s m a #

class (Applicative b, Applicative m, Monad b, Monad m) => MonadBase b m | m -> b where #

Minimal complete definition

liftBase

Methods

liftBase :: b α -> m α #

Lift a computation from the base monad

Instances

MonadBase [] [] 

Methods

liftBase :: [α] -> [α] #

MonadBase Maybe Maybe 

Methods

liftBase :: Maybe α -> Maybe α #

MonadBase IO IO 

Methods

liftBase :: IO α -> IO α #

MonadBase Identity Identity 

Methods

liftBase :: Identity α -> Identity α #

MonadBase STM STM 

Methods

liftBase :: STM α -> STM α #

MonadBase b m => MonadBase b (MaybeT m) 

Methods

liftBase :: b α -> MaybeT m α #

MonadBase b m => MonadBase b (ListT m) 

Methods

liftBase :: b α -> ListT m α #

(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) 

Methods

liftBase :: b α -> WriterT w m α #

(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) 

Methods

liftBase :: b α -> WriterT w m α #

MonadBase b m => MonadBase b (StateT s m) 

Methods

liftBase :: b α -> StateT s m α #

MonadBase b m => MonadBase b (StateT s m) 

Methods

liftBase :: b α -> StateT s m α #

MonadBase b m => MonadBase b (IdentityT * m) 

Methods

liftBase :: b α -> IdentityT * m α #

MonadBase b m => MonadBase b (ExceptT e m) 

Methods

liftBase :: b α -> ExceptT e m α #

(Error e, MonadBase b m) => MonadBase b (ErrorT e m) 

Methods

liftBase :: b α -> ErrorT e m α #

MonadBase b m => MonadBase b (ReaderT * r m) 

Methods

liftBase :: b α -> ReaderT * r m α #

MonadBase b m => MonadBase b (ContT * r m) 

Methods

liftBase :: b α -> ContT * r m α #

(Monoid w, MonadBase b m) => MonadBase b (RWST r w s m) 

Methods

liftBase :: b α -> RWST r w s m α #

(Monoid w, MonadBase b m) => MonadBase b (RWST r w s m) 

Methods

liftBase :: b α -> RWST r w s m α #

MonadBase ((->) r) ((->) r) 

Methods

liftBase :: (r -> α) -> r -> α #

MonadBase (Either e) (Either e) 

Methods

liftBase :: Either e α -> Either e α #

MonadBase (ST s) (ST s) 

Methods

liftBase :: ST s α -> ST s α #

MonadBase (ST s) (ST s) 

Methods

liftBase :: ST s α -> ST s α #

class MonadTrans t => MonadTransControl t where #

Minimal complete definition

liftWith, restoreT

Associated Types

type StT (t :: (* -> *) -> * -> *) a :: * #

Monadic state of t.

Methods

liftWith :: Monad m => (Run t -> m a) -> t m a #

liftWith is similar to lift in that it lifts a computation from the argument monad to the constructed monad.

Instances should satisfy similar laws as the MonadTrans laws:

liftWith . const . return = return
liftWith (const (m >>= f)) = liftWith (const m) >>= liftWith . const . f

The difference with lift is that before lifting the m computation liftWith captures the state of t. It then provides the m computation with a Run function that allows running t n computations in n (for all n) on the captured state.

restoreT :: Monad m => m (StT t a) -> t m a #

Construct a t computation from the monadic state of t that is returned from a Run function.

Instances should satisfy:

liftWith (\run -> run t) >>= restoreT . return = t

Instances

MonadTransControl ListT 

Associated Types

type StT (ListT :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run ListT -> m a) -> ListT m a #

restoreT :: Monad m => m (StT ListT a) -> ListT m a #

MonadTransControl MaybeT 

Associated Types

type StT (MaybeT :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run MaybeT -> m a) -> MaybeT m a #

restoreT :: Monad m => m (StT MaybeT a) -> MaybeT m a #

Error e => MonadTransControl (ErrorT e) 

Associated Types

type StT (ErrorT e :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (ErrorT e) -> m a) -> ErrorT e m a #

restoreT :: Monad m => m (StT (ErrorT e) a) -> ErrorT e m a #

MonadTransControl (ExceptT e) 

Associated Types

type StT (ExceptT e :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (ExceptT e) -> m a) -> ExceptT e m a #

restoreT :: Monad m => m (StT (ExceptT e) a) -> ExceptT e m a #

MonadTransControl (StateT s) 

Associated Types

type StT (StateT s :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (StateT s) -> m a) -> StateT s m a #

restoreT :: Monad m => m (StT (StateT s) a) -> StateT s m a #

MonadTransControl (StateT s) 

Associated Types

type StT (StateT s :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (StateT s) -> m a) -> StateT s m a #

restoreT :: Monad m => m (StT (StateT s) a) -> StateT s m a #

Monoid w => MonadTransControl (WriterT w) 

Associated Types

type StT (WriterT w :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (WriterT w) -> m a) -> WriterT w m a #

restoreT :: Monad m => m (StT (WriterT w) a) -> WriterT w m a #

Monoid w => MonadTransControl (WriterT w) 

Associated Types

type StT (WriterT w :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (WriterT w) -> m a) -> WriterT w m a #

restoreT :: Monad m => m (StT (WriterT w) a) -> WriterT w m a #

MonadTransControl (IdentityT *) 

Associated Types

type StT (IdentityT * :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (IdentityT *) -> m a) -> IdentityT * m a #

restoreT :: Monad m => m (StT (IdentityT *) a) -> IdentityT * m a #

MonadTransControl (ReaderT * r) 

Associated Types

type StT (ReaderT * r :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (ReaderT * r) -> m a) -> ReaderT * r m a #

restoreT :: Monad m => m (StT (ReaderT * r) a) -> ReaderT * r m a #

Monoid w => MonadTransControl (RWST r w s) 

Associated Types

type StT (RWST r w s :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (RWST r w s) -> m a) -> RWST r w s m a #

restoreT :: Monad m => m (StT (RWST r w s) a) -> RWST r w s m a #

Monoid w => MonadTransControl (RWST r w s) 

Associated Types

type StT (RWST r w s :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (RWST r w s) -> m a) -> RWST r w s m a #

restoreT :: Monad m => m (StT (RWST r w s) a) -> RWST r w s m a #

class MonadBase b m => MonadBaseControl b m | m -> b where #

Minimal complete definition

liftBaseWith, restoreM

Associated Types

type StM (m :: * -> *) a :: * #

Monadic state of m.

Methods

liftBaseWith :: (RunInBase m b -> b a) -> m a #

liftBaseWith is similar to liftIO and liftBase in that it lifts a base computation to the constructed monad.

Instances should satisfy similar laws as the MonadIO and MonadBase laws:

liftBaseWith . const . return = return
liftBaseWith (const (m >>= f)) = liftBaseWith (const m) >>= liftBaseWith . const . f

The difference with liftBase is that before lifting the base computation liftBaseWith captures the state of m. It then provides the base computation with a RunInBase function that allows running m computations in the base monad on the captured state.

restoreM :: StM m a -> m a #

Construct a m computation from the monadic state of m that is returned from a RunInBase function.

Instances should satisfy:

liftBaseWith (\runInBase -> runInBase m) >>= restoreM = m

Instances

MonadBaseControl [] [] 

Associated Types

type StM ([] :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase [] [] -> [a]) -> [a] #

restoreM :: StM [] a -> [a] #

MonadBaseControl Maybe Maybe 

Associated Types

type StM (Maybe :: * -> *) a :: * #

MonadBaseControl IO IO 

Associated Types

type StM (IO :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase IO IO -> IO a) -> IO a #

restoreM :: StM IO a -> IO a #

MonadBaseControl Identity Identity 

Associated Types

type StM (Identity :: * -> *) a :: * #

MonadBaseControl STM STM 

Associated Types

type StM (STM :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase STM STM -> STM a) -> STM a #

restoreM :: StM STM a -> STM a #

MonadBaseControl b m => MonadBaseControl b (MaybeT m) 

Associated Types

type StM (MaybeT m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (MaybeT m) b -> b a) -> MaybeT m a #

restoreM :: StM (MaybeT m) a -> MaybeT m a #

MonadBaseControl b m => MonadBaseControl b (ListT m) 

Associated Types

type StM (ListT m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (ListT m) b -> b a) -> ListT m a #

restoreM :: StM (ListT m) a -> ListT m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (WriterT w m) 

Associated Types

type StM (WriterT w m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (WriterT w m) b -> b a) -> WriterT w m a #

restoreM :: StM (WriterT w m) a -> WriterT w m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (WriterT w m) 

Associated Types

type StM (WriterT w m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (WriterT w m) b -> b a) -> WriterT w m a #

restoreM :: StM (WriterT w m) a -> WriterT w m a #

MonadBaseControl b m => MonadBaseControl b (StateT s m) 

Associated Types

type StM (StateT s m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (StateT s m) b -> b a) -> StateT s m a #

restoreM :: StM (StateT s m) a -> StateT s m a #

MonadBaseControl b m => MonadBaseControl b (StateT s m) 

Associated Types

type StM (StateT s m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (StateT s m) b -> b a) -> StateT s m a #

restoreM :: StM (StateT s m) a -> StateT s m a #

MonadBaseControl b m => MonadBaseControl b (IdentityT * m) 

Associated Types

type StM (IdentityT * m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (IdentityT * m) b -> b a) -> IdentityT * m a #

restoreM :: StM (IdentityT * m) a -> IdentityT * m a #

MonadBaseControl b m => MonadBaseControl b (ExceptT e m) 

Associated Types

type StM (ExceptT e m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (ExceptT e m) b -> b a) -> ExceptT e m a #

restoreM :: StM (ExceptT e m) a -> ExceptT e m a #

(Error e, MonadBaseControl b m) => MonadBaseControl b (ErrorT e m) 

Associated Types

type StM (ErrorT e m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (ErrorT e m) b -> b a) -> ErrorT e m a #

restoreM :: StM (ErrorT e m) a -> ErrorT e m a #

MonadBaseControl b m => MonadBaseControl b (ReaderT * r m) 

Associated Types

type StM (ReaderT * r m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (ReaderT * r m) b -> b a) -> ReaderT * r m a #

restoreM :: StM (ReaderT * r m) a -> ReaderT * r m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (RWST r w s m) 

Associated Types

type StM (RWST r w s m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (RWST r w s m) b -> b a) -> RWST r w s m a #

restoreM :: StM (RWST r w s m) a -> RWST r w s m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (RWST r w s m) 

Associated Types

type StM (RWST r w s m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (RWST r w s m) b -> b a) -> RWST r w s m a #

restoreM :: StM (RWST r w s m) a -> RWST r w s m a #

MonadBaseControl ((->) r) ((->) r) 

Associated Types

type StM ((->) r :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase ((->) r) ((->) r) -> r -> a) -> r -> a #

restoreM :: StM ((->) r) a -> r -> a #

MonadBaseControl (Either e) (Either e) 

Associated Types

type StM (Either e :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (Either e) (Either e) -> Either e a) -> Either e a #

restoreM :: StM (Either e) a -> Either e a #

MonadBaseControl (ST s) (ST s) 

Associated Types

type StM (ST s :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (ST s) (ST s) -> ST s a) -> ST s a #

restoreM :: StM (ST s) a -> ST s a #

MonadBaseControl (ST s) (ST s) 

Associated Types

type StM (ST s :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (ST s) (ST s) -> ST s a) -> ST s a #

restoreM :: StM (ST s) a -> ST s a #