Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Please see the README.md file for information on using this package at https://www.stackage.org/package/unliftio-core.
- 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)
- 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: 0.1.0.0
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 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: 0.1.0.0
MonadUnliftIO IO Source # | |
MonadUnliftIO m => MonadUnliftIO (IdentityT * m) Source # | |
MonadUnliftIO m => MonadUnliftIO (ReaderT * r m) Source # | |
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: 0.1.0.0
askRunInIO :: MonadUnliftIO m => m (m a -> IO a) Source #
Same ask 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: 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: 0.1.0.0
toIO :: MonadUnliftIO m => m a -> m (IO a) Source #
Convert an action in m
to an action in IO
.
Since: 0.1.0.0