| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Control.Monad.IO.Unlift
Description
Please see the README.md file for information on using this package at https://www.stackage.org/package/unliftio-core.
Synopsis
- class MonadIO m => MonadUnliftIO m where
- newtype UnliftIO m = UnliftIO {}
- askRunInIO :: MonadUnliftIO m => m (m a -> IO a)
- withUnliftIO :: MonadUnliftIO m => (UnliftIO m -> IO a) -> m a
- toIO :: MonadUnliftIO m => m a -> m (IO a)
- wrappedWithRunInIO :: MonadUnliftIO n => (n b -> m b) -> (forall a. m a -> n a) -> ((forall a. m a -> IO a) -> IO b) -> m b
- class Monad m => MonadIO (m :: * -> *) where
Documentation
class MonadIO m => MonadUnliftIO m where Source #
Monads which allow their actions to be run in IO.
While MonadIO allows an IO action to be lifted into another
 monad, this class captures the opposite concept: allowing you to
 capture the monadic context. Note that, in order to meet the laws
 given below, the intuition is that a monad must have no monadic
 state, but may have monadic context. This essentially limits
 MonadUnliftIO to ReaderT and IdentityT transformers on top of
 IO.
Laws. For any value u returned by askUnliftIO, it must meet the
 monad transformer laws as reformulated for MonadUnliftIO:
- unliftIO u . return = return 
- unliftIO u (m >>= f) = unliftIO u m >>= unliftIO u . f 
The third is a currently nameless law which ensures that the current context is preserved.
- askUnliftIO >>= (u -> liftIO (unliftIO u m)) = m 
If you have a name for this, please submit it in a pull request for great glory.
Since: unliftio-core-0.1.0.0
Minimal complete definition
Methods
askUnliftIO :: m (UnliftIO m) Source #
Capture the current monadic context, providing the ability to
 run monadic actions in IO.
See UnliftIO for an explanation of why we need a helper
 datatype here.
Since: unliftio-core-0.1.0.0
withRunInIO :: ((forall a. m a -> IO a) -> IO b) -> m b Source #
Convenience function for capturing the monadic context and running an IO
 action with a runner function. The runner function is used to run a monadic
 action m in IO.
Since: unliftio-core-0.1.0.0
Instances
| MonadUnliftIO IO Source # | |
| Defined in Control.Monad.IO.Unlift | |
| MonadUnliftIO m => MonadUnliftIO (IdentityT m) Source # | |
| Defined in Control.Monad.IO.Unlift | |
| MonadUnliftIO m => MonadUnliftIO (ReaderT r m) Source # | |
| Defined in Control.Monad.IO.Unlift | |
The ability to run any monadic action m a as IO a.
This is more precisely a natural transformation. We need to new
 datatype (instead of simply using a forall) due to lack of
 support in GHC for impredicative types.
Since: unliftio-core-0.1.0.0
askRunInIO :: MonadUnliftIO m => m (m a -> IO a) Source #
Same as askUnliftIO, but returns a monomorphic function
 instead of a polymorphic newtype wrapper. If you only need to apply
 the transformation on one concrete type, this function can be more
 convenient.
Since: unliftio-core-0.1.0.0
withUnliftIO :: MonadUnliftIO m => (UnliftIO m -> IO a) -> m a Source #
Convenience function for capturing the monadic context and running
 an IO action. The UnliftIO newtype wrapper is rarely needed, so
 prefer withRunInIO to this function.
Since: unliftio-core-0.1.0.0
toIO :: MonadUnliftIO m => m a -> m (IO a) Source #
Convert an action in m to an action in IO.
Since: unliftio-core-0.1.0.0
Arguments
| :: MonadUnliftIO n | |
| => (n b -> m b) | The wrapper, for instance  | 
| -> (forall a. m a -> n a) | The inverse, for instance  | 
| -> ((forall a. m a -> IO a) -> IO b) | The actual function to invoke  | 
| -> m b | 
A helper function for implementing MonadUnliftIO instances.
Useful for the common case where you want to simply delegate to the
underlying transformer.
Example
newtype AppT m a = AppT { unAppT :: ReaderT Int (ResourceT m) a }
  deriving (Functor, Applicative, Monad, MonadIO)
  -- Unfortunately, deriving MonadUnliftIO does not work.
instance MonadUnliftIO m => MonadUnliftIO (AppT m) where
  withRunInIO = wrappedWithRunInIO AppT unAppTSince: unliftio-core-0.1.2.0
class Monad m => MonadIO (m :: * -> *) where #
Monads in which IO computations may be embedded.
 Any monad built by applying a sequence of monad transformers to the
 IO monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
 is a transformer of monads:
Minimal complete definition
Instances
| MonadIO IO | Since: base-4.9.0.0 | 
| Defined in Control.Monad.IO.Class | |
| MonadIO m => MonadIO (IdentityT m) | |
| Defined in Control.Monad.Trans.Identity | |
| MonadIO m => MonadIO (ReaderT r m) | |
| Defined in Control.Monad.Trans.Reader | |