managed-1.0.1: A monad for managed values

Safe HaskellSafe-Inferred
LanguageHaskell98

Control.Monad.Managed

Contents

Description

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.

Synopsis

Managed

data Managed a Source

A managed resource that you acquire using with

managed :: (forall r. (a -> IO r) -> IO r) -> Managed a Source

Build a Managed value

managed_ :: (forall r. IO r -> IO r) -> Managed () Source

Like managed but for resource-less operations.

with :: Managed a -> (a -> IO r) -> IO r Source

Acquire a Managed value

runManaged :: Managed () -> IO () Source

Run a Managed computation, enforcing that no acquired resources leak

Re-exports