streaming-with-0.2.1.0: with/bracket-style idioms for use with streaming

CopyrightIvan Lazar Miljenovic
LicenseMIT
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell2010

Streaming.With.Lifted

Contents

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

Synopsis

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

liftWith, liftAction

Associated Types

type WithMonad w :: * -> * Source #

Methods

liftWith :: (forall r. (a -> WithMonad w r) -> WithMonad w r) -> w a Source #

liftAction :: WithMonad w a -> w a Source #

Instances

Withable Managed Source # 

Associated Types

type WithMonad (Managed :: * -> *) :: * -> * Source #

Methods

liftWith :: (forall r. (a -> WithMonad Managed r) -> WithMonad Managed r) -> Managed a Source #

liftAction :: WithMonad Managed a -> Managed a Source #

(MonadMask m, MonadIO m) => Withable (ContT * r m) Source # 

Associated Types

type WithMonad (ContT * r m :: * -> *) :: * -> * Source #

Methods

liftWith :: (forall a. (a -> WithMonad (ContT * r m) a) -> WithMonad (ContT * r m) a) -> ContT * r m a Source #

liftAction :: WithMonad (ContT * r m) a -> ContT * r m a Source #

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

runWith

Methods

runWith :: w () -> WithMonad w () Source #

Instances

RunWithable Managed Source # 
(MonadMask m, MonadIO m) => RunWithable (ContT * () m) Source # 

Methods

runWith :: ContT * () m () -> WithMonad (ContT * () m) () Source #

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

withSystemTempFile Source #

Arguments

:: Withable w 
=> String

File name template. See openTempFile.

-> 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

withTempFile Source #

Arguments

:: Withable w 
=> FilePath

Temp dir to create the file in

-> String

File name template. See openTempFile.

-> 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 openTempFile.

-> 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

withTempDirectory Source #

Arguments

:: Withable w 
=> FilePath

Temp directory to create the directory in

-> String

Directory name template. See openTempFile.

-> 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, and stacks such as ErrorT e IO which provide for multiple failure modes, are invalid instances of this class.

Note that this package does provide a MonadMask instance for CatchT. This instance is only valid if the base monad provides no ability to provide multiple exit. For example, IO or Either would be invalid base monads, but Reader or State would be acceptable.

Instances should ensure that, in the following code:

f `finally` g

The action g is called regardless of what occurs within f, including async exceptions.

Minimal complete definition

mask, uninterruptibleMask

Instances

MonadMask IO 

Methods

mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

(~) * e SomeException => MonadMask (Either e)

Since: 0.8.3

Methods

mask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

uninterruptibleMask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

MonadMask m => MonadMask (StateT s m) 

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

MonadMask m => MonadMask (StateT s m) 

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

MonadMask m => MonadMask (IdentityT * m) 

Methods

mask :: ((forall a. IdentityT * m a -> IdentityT * m a) -> IdentityT * m b) -> IdentityT * m b #

uninterruptibleMask :: ((forall a. IdentityT * m a -> IdentityT * m a) -> IdentityT * m b) -> IdentityT * m b #

MonadMask m => MonadMask (ReaderT * r m) 

Methods

mask :: ((forall a. ReaderT * r m a -> ReaderT * r m a) -> ReaderT * r m b) -> ReaderT * r m b #

uninterruptibleMask :: ((forall a. ReaderT * r m a -> ReaderT * r m a) -> ReaderT * r m b) -> ReaderT * r m b #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

bracket :: MonadMask m => m a -> (a -> m b) -> (a -> m c) -> m c #

Generalized abstracted pattern of safe resource acquisition and release in the face of exceptions. 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 exception occurs during the use, the release still happens before the exception is rethrown.