Copyright | (c) 2025 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | released |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Streamly.Control.Exception
Contents
Description
Exception handling and resource managment operations complementing the Control.Exception module in base package.
Setup
To execute the code examples provided in this module in ghci, please run the following commands first.
>>>
:m
>>>
import Control.Monad (when)
>>>
import Control.Concurrent (threadDelay)
>>>
import Data.Function ((&))
>>>
import System.IO (hClose, IOMode(..), openFile)
>>>
import Streamly.Data.Stream (Stream)
>>>
import qualified Streamly.Data.Fold as Fold
>>>
import qualified Streamly.Data.Stream as Stream
>>>
import qualified Streamly.Control.Exception as Exception
AcquireIO
is used to acquire a resource safely such that it is
automatically released if not released manually.
See withAcquireIO
.
withAcquireIO :: (MonadIO m, MonadMask m) => (AcquireIO -> m a) -> m a Source #
withAcquireIO action
runs the given action
, providing it with a
an AcquireIO
reference called ref
as argument. ref
is used for resource
acquisition or hook registeration within the scope of action
. An acquire
ref alloc free
call can be used within action
any number of times to
acquire resources that are automatically freed when the scope of action
ends or if an exception occurs at any time. alloc
is a function supplied
by the user to allocate a resource and free
is supplied to free the
allocated resource. acquire
returns (resource, release)
-- the acquired
resource
and a release
action to release it.
acquire
allocates a resource in an exception safe manner and sets up its
automatic release on exception or when the scope of action
ends. The
release
function returned by acquire
can be used to free the resource
manually at any time. release
is guaranteed to free the resource once and
only once even if it is called concurrently or multiple times.
Here is an example to allocate resources that are guaranteed to be released automatically, and can be released manually as well:
>>>
:{
close x h = do putStrLn $ "closing: " ++ x hClose h :}
>>>
:{
action ref = Stream.fromList ["file1", "file2"] & Stream.mapM (\x -> do (h, release) <- Exception.acquire ref (openFile x ReadMode) (close x) -- use h here threadDelay 1000000 when (x == "file1") $ do putStrLn $ "Manually releasing: " ++ x release return x ) & Stream.trace print & Stream.fold Fold.drain :}
>>>
run = Exception.withAcquireIO action
In the above code, you should see the "closing:" message for both the files, and only once for each file. Even if you interrupt the program with CTRL-C you should still see the "closing:" message for the files opened before the interrupt. Make sure you create "file1" and "file2" before running this code snippet.
Cleanup is guaranteed to happen as soon as the scope of action
finishes or if an exception occurs.
Here is an example for just registering hooks to be called eventually:
>>>
:{
action ref = Stream.fromList ["file1", "file2"] & Stream.mapM (\x -> do Exception.register ref $ putStrLn $ "saw: " ++ x threadDelay 1000000 return x ) & Stream.trace print & Stream.fold Fold.drain :}
>>>
run = Exception.withAcquireIO action
In the above code, even if you interrupt the program with CTRL-C you should still see the "saw:" message for the elements seen before the interrupt.
The registered hooks are guaranteed to be invoked as soon as the scope of
action
finishes or if an exception occurs.
This function provides functionality similar to the bracket
function
available in the base library. However, it is more powerful as any number of
resources can be allocated and released within the scope of action
.
Exception safe, thread safe.
acquire :: AcquireIO -> IO b -> (b -> IO c) -> IO (b, IO ()) Source #
acquire ref alloc free
is used in bracket-style safe resource allocation
functions, where alloc
is a function supplied by the user to allocate a
resource and free
is supplied to free it. acquire
returns a tuple
(resource, release)
where resource
is the allocated resource and
release
is an action that can be called later to release the resource.
Both alloc
and free
are invoked with async signals masked. You can use
allowInterrupt
from base package for allowing interrupts if required.
The release
action can be called multiple times or even concurrently from
multiple threads, but it will release the resource only once. If release
is never called by the programmer it will be automatically called at the end
of the bracket scope.
register :: AcquireIO -> IO () -> IO () Source #
Register a hook to be executed at the end of a bracket.
hook :: AcquireIO -> IO () -> IO (IO ()) Source #
Like register
but returns a hook release function as well. When the
returned hook release function is called, the hook is invoked and removed.
If the returned function is never called by the programmer then it is
automatically invoked at the end of the bracket. The hook is invoked once
and only once.