Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module is a safer subset of Control.Monad.Managed that only lets you
unwrap the Managed
type using runManaged
. This enforces that you never
leak acquired resources from a Managed
computation.
In general, you should strive to propagate the Managed
type as much as
possible and use runManaged
when you are done with acquired resources.
However, there are legitimate circumstances where you want to return a value
other than acquired resource from the bracketed computation, which requires
using with
.
This module is not the default because you can also use the Managed
type
for callback-based code that is completely unrelated to resources.
Synopsis
- data Managed a
- class MonadIO m => MonadManaged m where
- managed :: MonadManaged m => (forall r. (a -> IO r) -> IO r) -> m a
- managed_ :: MonadManaged m => (forall r. IO r -> IO r) -> m ()
- defer :: MonadManaged m => IO r -> m ()
- runManaged :: Managed () -> IO ()
- class Monad m => MonadIO (m :: Type -> Type) where
Managed
A managed resource that you acquire using with
Instances
class MonadIO m => MonadManaged m where Source #
You can embed a Managed
action within any Monad
that implements
MonadManaged
by using the using
function
All instances must obey the following two laws:
using (return x) = return x using (m >>= f) = using m >>= \x -> using (f x)
Instances
MonadManaged Managed Source # | |
MonadManaged m => MonadManaged (MaybeT m) Source # | |
MonadManaged m => MonadManaged (ExceptT e m) Source # | |
MonadManaged m => MonadManaged (IdentityT m) Source # | |
MonadManaged m => MonadManaged (ReaderT r m) Source # | |
MonadManaged m => MonadManaged (StateT s m) Source # | |
MonadManaged m => MonadManaged (StateT s m) Source # | |
(Monoid w, MonadManaged m) => MonadManaged (WriterT w m) Source # | |
(Monoid w, MonadManaged m) => MonadManaged (WriterT w m) Source # | |
MonadManaged m => MonadManaged (ContT r m) Source # | |
(Monoid w, MonadManaged m) => MonadManaged (RWST r w s m) Source # | |
(Monoid w, MonadManaged m) => MonadManaged (RWST r w s m) Source # | |
managed_ :: MonadManaged m => (forall r. IO r -> IO r) -> m () Source #
Like managed
but for resource-less operations.
defer :: MonadManaged m => IO r -> m () Source #
Defer running an action until exit (via runManaged
).
For example, the following code will print "Hello" followed by "Goodbye":
runManaged $ do defer $ liftIO $ putStrLn "Goodbye" liftIO $ putStrLn "Hello"
runManaged :: Managed () -> IO () Source #
Run a Managed
computation, enforcing that no acquired resources leak
Re-exports
Control.Monad.IO.Class re-exports MonadIO
class Monad m => MonadIO (m :: Type -> Type) 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:
Lift a computation from the IO
monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO
is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted
, we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO ()
and
.IO
()
Luckily, we know of a function that takes an
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
Instances
MonadIO IO | Since: base-4.9.0.0 |
Defined in Control.Monad.IO.Class | |
MonadIO Managed Source # | |
Defined in Control.Monad.Managed | |
MonadIO m => MonadIO (MaybeT m) | |
Defined in Control.Monad.Trans.Maybe | |
MonadIO m => MonadIO (ExceptT e m) | |
Defined in Control.Monad.Trans.Except | |
MonadIO m => MonadIO (IdentityT m) | |
Defined in Control.Monad.Trans.Identity | |
MonadIO m => MonadIO (ReaderT r m) | |
Defined in Control.Monad.Trans.Reader | |
MonadIO m => MonadIO (StateT s m) | |
Defined in Control.Monad.Trans.State.Lazy | |
MonadIO m => MonadIO (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Lazy | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Strict | |
MonadIO m => MonadIO (ContT r m) | |
Defined in Control.Monad.Trans.Cont | |
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.Lazy | |
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.Strict |