| Copyright | Ivan Lazar Miljenovic | 
|---|---|
| License | MIT | 
| Maintainer | Ivan.Miljenovic@gmail.com | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Streaming.With.Lifted
Description
Both the ContT and Managed (which is a specialised variant of
   ContT) monads can help with writing heavily nested bracketed
   code, by being able to pass around the argument to each continuation.
This module - through the use of the Withable class - provides
   lifted variants of Streaming.With to be able to automatically use
   these functions for resource management in your choice of monad.
Note that you still need to use the specific monad's running
   function, as it is not possible to encapsulate those in a generic
   fashion (unless we wanted to constrain the ContT instance to
   ContT ()).
To ensure resources don't leak out, it is preferred that if using
   ContT, you keep the final result type to () (which is what
   Managed recommends with its runManaged function).
As an example using Managed, this function will copy the contents
   of two files into a third.:
copyBoth :: FilePath -> FilePath -> FilePath -> IO () copyBoth inF1 inF2 outF = runManaged $ do bs1 <- withBinaryFileContents inF1 bs2 <- withBinaryFileContents inF2 writeBinaryFile outF bs1 appendBinaryFile outF bs2
- class (Monad w, MonadMask (WithMonad w), MonadIO (WithMonad w)) => Withable w where
- class Withable w => RunWithable w where
- within :: Withable w => w a -> (a -> WithMonad w b) -> w b
- liftActionIO :: Withable w => IO a -> w a
- withFile :: Withable w => FilePath -> IOMode -> w Handle
- withBinaryFile :: Withable w => FilePath -> IOMode -> w Handle
- writeBinaryFile :: Withable w => FilePath -> ByteString (WithMonad w) r -> w r
- appendBinaryFile :: Withable w => FilePath -> ByteString (WithMonad w) r -> w r
- withBinaryFileContents :: (Withable w, MonadIO n) => FilePath -> w (ByteString n ())
- withSystemTempFile :: Withable w => String -> w (FilePath, Handle)
- withTempFile :: Withable w => FilePath -> String -> w (FilePath, Handle)
- withSystemTempDirectory :: Withable w => String -> w FilePath
- withTempDirectory :: Withable w => FilePath -> String -> w FilePath
- class MonadCatch m => MonadMask (m :: * -> *)
- bracket :: MonadMask m => m a -> (a -> m c) -> (a -> m b) -> m b
Documentation
class (Monad w, MonadMask (WithMonad w), MonadIO (WithMonad w)) => Withable w where Source #
How to automatically lift bracket-style expressions into a monad.
The constraints are common ones found throughout this module, and as such incorporated into this class to avoid repetition in all the type signatures.
It is highly recommended that you do not try and layer extra transformers on top of this; the intent of this class is just to make writing all the underlying continuations in a nicer fashion without explicit nesting, rather than as the basis of lower-level code.
Minimal complete definition
class Withable w => RunWithable w where Source #
Safely run the provided continuation.
A result of type '()' is required to ensure no resources are leaked.
Note that you cannot write something like:
copyBoth :: FilePath -> FilePath -> FilePath -> IO () copyBoth inF1 inF2 outF = runWith $ do bs1 <- withBinaryFileContents inF1 bs2 <- withBinaryFileContents inF2 writeBinaryFile outF bs1 appendBinaryFile outF bs2
as the RunWithable instance cannot be inferred.  As such, you
   will need to specify a type somewhere.
Since: 0.2.1.0
Minimal complete definition
within :: Withable w => w a -> (a -> WithMonad w b) -> w b Source #
A helper function to run a computation within a lifted resource management expression.
within w f = w >>= liftAction . f
Since: 0.2.1.0
liftActionIO :: Withable w => IO a -> w a Source #
A helper function for the common case of lifting an IO
   computation into a Withable.
liftActionIO = liftAction . liftIO.
Since: 0.2.1.0
File-handling
withFile :: Withable w => FilePath -> IOMode -> w Handle Source #
A lifted variant of withFile.
You almost definitely don't want to use this; instead, use
   withBinaryFile in conjunction with Data.ByteString.Streaming.
withBinaryFile :: Withable w => FilePath -> IOMode -> w Handle Source #
A lifted variant of withBinaryFile.
Common file-handling cases
writeBinaryFile :: Withable w => FilePath -> ByteString (WithMonad w) r -> w r Source #
Write to the specified file.
appendBinaryFile :: Withable w => FilePath -> ByteString (WithMonad w) r -> w r Source #
Append to the specified file.
withBinaryFileContents :: (Withable w, MonadIO n) => FilePath -> w (ByteString n ()) Source #
Apply a function to the contents of the file.
Note that a different monadic stack is allowed for the
   ByteString input, as long as it later gets resolved to the
   required output type (e.g. remove transformer).
Temporary files
Arguments
| :: Withable w | |
| => String | File name template.  See
    | 
| -> w (FilePath, Handle) | 
Create and use a temporary file in the system standard temporary directory.
Behaves exactly the same as withTempFile, except that the
   parent temporary directory will be that returned by
   getCanonicalTemporaryDirectory.
Since: 0.1.1.0
Arguments
| :: Withable w | |
| => FilePath | Temp dir to create the file in | 
| -> String | File name template.  See
    | 
| -> w (FilePath, Handle) | 
Use a temporary filename that doesn't already exist.
Creates a new temporary file inside the given directory, making use of the template. The temp file is deleted after use. For example:
withTempFile "src" "sdist." >>= \(tmpFile, hFile) -> ...
The tmpFile will be file in the given directory, e.g.
   src/sdist.342.
Since: 0.1.1.0
withSystemTempDirectory Source #
Arguments
| :: Withable w | |
| => String | Directory name template. See
    | 
| -> w FilePath | 
Create and use a temporary directory in the system standard temporary directory.
Behaves exactly the same as withTempDirectory, except that the
   parent temporary directory will be that returned by
   getCanonicalTemporaryDirectory.
Since: 0.1.1.0
Arguments
| :: Withable w | |
| => FilePath | Temp directory to create the directory in | 
| -> String | Directory name template. See
    | 
| -> w FilePath | 
Create and use a temporary directory.
Creates a new temporary directory inside the given directory, making use of the template. The temp directory is deleted after use. For example:
withTempDirectory "src" "sdist." >>= \tmpDir -> ...
The tmpDir will be a new subdirectory of the given directory, e.g.
   src/sdist.342.
Since: 0.1.1.0
Re-exports
These may assist in writing your own bracket-style functions.
Note that not everything is re-exported: for example, Handle isn't
re-exported for use with withFile as it's unlikely that you will
write another wrapper around it, and furthermore it wouldn't be a
common enough extension to warrant it.
class MonadCatch m => MonadMask (m :: * -> *) #
A class for monads which provide for the ability to account for all possible exit points from a computation, and to mask asynchronous exceptions. Continuation-based monads are invalid instances of this class.
Instances should ensure that, in the following code:
fg = f `finally` g
The action g is called regardless of what occurs within f, including
 async exceptions. Some monads allow f to abort the computation via other
 effects than throwing an exception. For simplicity, we will consider aborting
 and throwing an exception to be two forms of "throwing an error".
If f and g both throw an error, the error thrown by fg depends on which
 errors we're talking about. In a monad transformer stack, the deeper layers
 override the effects of the inner layers; for example, ExceptT e1 (Except
 e2) a represents a value of type Either e2 (Either e1 a), so throwing both
 an e1 and an e2 will result in Left e2. If f and g both throw an
 error from the same layer, instances should ensure that the error from g
 wins.
Effects other than throwing an error are also overriden by the deeper layers.
 For example, StateT s Maybe a represents a value of type s -> Maybe (a,
 s), so if an error thrown from f causes this function to return Nothing,
 any changes to the state which f also performed will be erased. As a
 result, g will see the state as it was before f. Once g completes,
 f's error will be rethrown, so g' state changes will be erased as well.
 This is the normal interaction between effects in a monad transformer stack.
By contrast, lifted-base's
 version of finally always discards all of g's non-IO effects, and g
 never sees any of f's non-IO effects, regardless of the layer ordering and
 regardless of whether f throws an error. This is not the result of
 interacting effects, but a consequence of MonadBaseControl's approach.
Minimal complete definition
Instances
| MonadMask IO | |
| (~) * e SomeException => MonadMask (Either e) | Since: 0.8.3 | 
| MonadMask m => MonadMask (MaybeT m) | Since: 0.10.0 | 
| MonadMask m => MonadMask (ExceptT e m) | Since: 0.9.0 | 
| (Error e, MonadMask m) => MonadMask (ErrorT e m) | |
| MonadMask m => MonadMask (StateT s m) | |
| MonadMask m => MonadMask (StateT s m) | |
| (MonadMask m, Monoid w) => MonadMask (WriterT w m) | |
| (MonadMask m, Monoid w) => MonadMask (WriterT w m) | |
| MonadMask m => MonadMask (IdentityT * m) | |
| MonadMask m => MonadMask (ReaderT * r m) | |
| (MonadMask m, Monoid w) => MonadMask (RWST r w s m) | |
| (MonadMask m, Monoid w) => MonadMask (RWST r w s m) | |
bracket :: MonadMask m => m a -> (a -> m c) -> (a -> m b) -> m b #
Generalized abstracted pattern of safe resource acquisition and release
 in the face of errors. The first action "acquires" some value, which
 is "released" by the second action at the end. The third action "uses"
 the value and its result is the result of the bracket.
If an error is thrown during the use, the release still happens before the error is rethrown.
Note that this is essentially a type-specialized version of
 generalBracket. This function has a more common signature (matching the
 signature from Control.Exception), and is often more convenient to use. By
 contrast, generalBracket is more expressive, allowing us to implement
 other functions like bracketOnError.