Safe Haskell | Safe |
---|---|
Language | Haskell98 |
An example Haskell program to copy data from one handle to another might look like this:
main = withFile "inFile.txt" ReadMode $ \inHandle -> withFile "outFile.txt" WriteMode $ \outHandle -> copy inHandle outHandle -- A hypothetical function that copies data from one handle to another copy :: Handle -> Handle -> IO ()
withFile
is one of many functions that acquire some resource in
an exception-safe way. These functions take a callback function as an
argument and they invoke the callback on the resource when it becomes
available, guaranteeing that the resource is properly disposed if the
callback throws an exception.
These functions usually have a type that ends with the following pattern:
Callback -- ----------- withXXX :: ... -> (a -> IO r) -> IO r
Here are some examples of this pattern from the base
libraries:
withArray :: Storable a => [a] -> (Ptr a -> IO r) -> IO r withBuffer :: Buffer e -> (Ptr e -> IO r) -> IO r withCAString :: String -> (CString -> IO r) -> IO r withForeignPtr :: ForeignPtr a -> (Ptr a -> IO r) -> IO r withMVar :: Mvar a -> (a -> IO r) -> IO r withPool :: (Pool -> IO r) -> IO r
Acquiring multiple resources in this way requires nesting callbacks.
However, you can wrap anything of the form ((a -> IO r) -> IO r)
in the
Managed
monad, which translates binds to callbacks for you:
import Control.Monad.Managed import System.IO inFile :: FilePath -> Managed Handle inFile filePath = managed (withFile filePath ReadMode) outFile :: FilePath -> Managed Handle outFile filePath = managed (withFile filePath WriteMode) main = runManaged $ do inHandle <- inFile "inFile.txt" outHandle <- outFile "outFile.txt" liftIO (copy inHandle outHandle)
... or you can just wrap things inline:
main = runManaged $ do inHandle <- managed (withFile "inFile.txt" ReadMode) outHandle <- managed (withFile "outFile.txt" WriteMode) liftIO (copy inHandle outHandle)
Additionally, since Managed
is a Monad
, you can take advantage of all
your favorite combinators from Control.Monad. For example, the
withMany
function from Foreign.Marshal.Utils
becomes a trivial wrapper around mapM
:
withMany :: (a -> (b -> IO r) -> IO r) -> [a] -> ([b] -> IO r) -> IO r withMany f = with . mapM (Managed . f)
Another reason to use Managed
is that if you wrap a Monoid
value in
Managed
you get back a new Monoid
:
instance Monoid a => Monoid (Managed a)
This lets you combine managed resources transparently. You can also lift
operations from some numeric type classes this way, too, such as the Num
type class.
NOTE: Managed
may leak space if used in an infinite loop like this
example:
import Control.Monad import Control.Monad.Managed main = runManaged (forever (liftIO (print 1)))
If you need to acquire a resource for a long-lived loop, you can instead
acquire the resource first and run the loop in IO
, using either of the
following two equivalent idioms:
with resource (\r -> forever (useThe r)) do r <- resource liftIO (forever (useThe r))
Managed
A managed resource that you acquire using with
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)
MonadManaged Managed Source | |
MonadManaged m => MonadManaged (MaybeT m) Source | |
MonadManaged m => MonadManaged (IdentityT m) Source | |
(Monoid w, MonadManaged m) => MonadManaged (WriterT w m) Source | |
(Monoid w, MonadManaged m) => MonadManaged (WriterT w m) Source | |
MonadManaged m => MonadManaged (ExceptT e m) Source | |
MonadManaged m => MonadManaged (StateT s m) Source | |
MonadManaged m => MonadManaged (StateT s m) Source | |
MonadManaged m => MonadManaged (ReaderT r 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_ :: (forall r. IO r -> IO r) -> Managed () Source
Like managed
but for resource-less operations.
runManaged :: Managed () -> IO () Source
Run a Managed
computation, enforcing that no acquired resources leak
Re-exports
Control.Monad.IO.Class re-exports MonadIO
module Control.Monad.IO.Class