process-streaming-0.6.7.0: Streaming interface to system processes.

Safe HaskellNone
LanguageHaskell2010

System.Process.Streaming

Contents

Description

This module contains helper functions and types built on top of System.Process and Pipes.

They provide concurrent, streaming access to the inputs and outputs of system processes.

Error conditions not directly related to IO are made explicit in the types.

Regular Consumers, Parsers from pipes-parse and various folds can be used to consume the output streams of the external processes.

Synopsis

Execution

executeFallibly :: Piping e a -> CreateProcess -> IO (Either e (ExitCode, a)) Source

Executes an external process. The standard streams are piped and consumed in a way defined by the Piping argument.

This function re-throws any IOExceptions it encounters.

If the consumption of the standard streams fails with e, the whole computation is immediately aborted and e is returned. (An exception is not thrown in this case.).

If an error e or an exception happens, the external process is terminated.

Piping Policies

data Piping e a Source

A Piping determines what standard streams will be piped and what to do with them.

The user doesn't need to manually set the std_in, std_out and std_err fields of the CreateProcess record to CreatePipe, this is done automatically.

A Piping is parametrized by the type e of errors that can abort the processing of the streams.

Instances

nopiping :: Piping e () Source

Do not pipe any standard stream.

pipeo :: Siphon ByteString e a -> Piping e a Source

Pipe stdout.

pipee :: Siphon ByteString e a -> Piping e a Source

Pipe stderr.

pipeoe :: Siphon ByteString e a -> Siphon ByteString e b -> Piping e (a, b) Source

Pipe stdout and stderr.

pipeoec :: Lines e -> Lines e -> Siphon Text e a -> Piping e a Source

Pipe stdout and stderr and consume them combined as Text.

pipei :: Pump ByteString e i -> Piping e i Source

Pipe stdin.

pipeio :: Pump ByteString e i -> Siphon ByteString e a -> Piping e (i, a) Source

Pipe stdin and stdout.

pipeie :: Pump ByteString e i -> Siphon ByteString e a -> Piping e (i, a) Source

Pipe stdin and stderr.

pipeioe :: Pump ByteString e i -> Siphon ByteString e a -> Siphon ByteString e b -> Piping e (i, a, b) Source

Pipe stdin, stdout and stderr.

pipeioec :: Pump ByteString e i -> Lines e -> Lines e -> Siphon Text e a -> Piping e (i, a) Source

Pipe stdin, stdout and stderr, consuming the last two combined as Text.

Pumping bytes into stdin

newtype Pump b e a Source

Constructors

Pump 

Fields

runPump :: Consumer b IO () -> IO (Either e a)
 

Instances

Bifunctor (Pump b) 
Functor (Pump b e) 
Applicative (Pump b e) 
Monoid a => Monoid (Pump b e a) 

fromProducerM :: MonadIO m => (m () -> IO (Either e a)) -> Producer b m r -> Pump b e a Source

fromFoldable :: Foldable f => f b -> Pump b e () Source

fromEnumerable :: Enumerable t => t IO b -> Pump b e () Source

Siphoning bytes out of stdout/stderr

data Siphon b e a Source

A Siphon represents a computation that completely drains a producer, but may fail early with an error of type e.

pure creates a Siphon that does nothing besides draining the Producer.

<*> executes its arguments concurrently. The Producer is forked so that each argument receives its own copy of the data.

Instances

Bifunctor (Siphon b) 
Functor (Siphon b e) 
Applicative (Siphon b e) 
Monoid a => Monoid (Siphon b e a) 

newtype SiphonOp e a b Source

Constructors

SiphonOp 

Fields

getSiphonOp :: Siphon b e a
 

Instances

Monoid a => Divisible (SiphonOp e a)

divide builds a SiphonOp for a composite out of the SiphonOps for the parts.

Monoid a => Decidable (SiphonOp e a)

choose builds a SiphonOp for a sum out of the SiphonOps for the branches.

Contravariant (SiphonOp e a)

contramap carn turn a SiphonOp for bytes into a SiphonOp for text.

siphon :: (Producer b IO () -> IO (Either e a)) -> Siphon b e a Source

Builds a Siphon out of a computation that does something with a Producer, but may fail with an error of type e.

Even if the original computation doesn't completely drain the Producer, the constructed Siphon will.

siphon' :: (forall r. Producer b IO r -> IO (Either e (a, r))) -> Siphon b e a Source

Builds a Siphon out of a computation that drains a Producer completely, but may fail with an error of type e.

fromFold :: (Producer b IO () -> IO a) -> Siphon b e a Source

Useful in combination with toLazyM from pipes-text and toLazyM from pipes-bytestring, when the user wants to collect all the output.

fromFold' :: (forall r. Producer b IO r -> IO (a, r)) -> Siphon b e a Source

Builds a Siphon out of a computation that folds a Producer and drains it completely.

fromFold'_ :: (forall r. Producer b IO r -> IO r) -> Siphon b e () Source

fromFoldl :: Fold b a -> Siphon b e a Source

Builds a Siphon out of a pure fold from the foldl package.

fromFoldlIO :: FoldM IO b a -> Siphon b e a Source

Builds a Siphon out of a monadic fold from the foldl package that works in the IO monad.

fromFoldlM :: MonadIO m => (forall r. m (a, r) -> IO (Either e (c, r))) -> FoldM m b a -> Siphon b e c Source

Builds a Siphon out of a monadic fold from the foldl package.

fromConsumerM :: MonadIO m => (m () -> IO (Either e a)) -> Consumer b m r -> Siphon b e a Source

fromParser :: Parser b IO (Either e a) -> Siphon b e a Source

Turn a Parser from pipes-parse into a Sihpon.

fromParserM :: MonadIO m => (forall r. m (a, r) -> IO (Either e (c, r))) -> Parser b m a -> Siphon b e c Source

Turn a Parser from pipes-parse into a Sihpon.

unwanted :: a -> Siphon b b a Source

Constructs a Siphon that aborts the computation if the underlying Producer produces anything.

type DecodingFunction bytes text = forall r. Producer bytes IO r -> Producer text IO (Producer bytes IO r) Source

See the section Non-lens decoding functions in the documentation for the pipes-text package.

encoded :: DecodingFunction bytes text -> Siphon bytes e (a -> b) -> Siphon text e a -> Siphon bytes e b Source

Constructs a Siphon that works on encoded values out of a Siphon that works on decoded values.

The two first arguments are a decoding function and a Siphon that determines how to handle leftovers. Pass pure id to ignore leftovers. Pass unwanted id to abort the computation if leftovers remain.

Line handling

data Lines e Source

A configuration parameter used in functions that combine lines from multiple streams.

Instances

Functor Lines

fmap maps over the encoding error.

toLines :: DecodingFunction ByteString Text -> Siphon ByteString e () -> Lines e Source

Constructs a Lines out of a DecodingFunction and a Siphon that specifies how to handle decoding failures. Passing pure () as the Siphon will ignore any leftovers. Passing unwanted () will abort the computation if leftovers remain.

tweakLines :: (forall r. Producer Text IO r -> Producer Text IO r) -> Lines e -> Lines e Source

Specifies a transformation that will be applied to each line of text, represented as a Producer.

Line prefixes are easy to add using applicative notation:

(\x -> yield "prefix: " *> x)

prefixLines :: IO Text -> Lines e -> Lines e Source

Specifies a prefix that will be calculated and appended for each line of text.

Pipelines

executePipelineFallibly :: Piping e a -> Tree (Stage e) -> IO (Either e a) Source

Similar to executeFallibly, but instead of a single process it executes a (possibly branching) pipeline of external processes.

The Piping argument views the pipeline as a synthetic process for which stdin is the stdin of the first stage, stdout is the stdout of the leftmost terminal stage among those closer to the root, and stderr is a combination of the stderr streams of all the stages.

The combined stderr stream always has UTF-8 encoding.

This function has a limitation compared to the standard UNIX pipelines. If a downstream process terminates early without error, the upstream processes are not notified and keep going. There is no SIGPIPE-like functionality, in other words.

data Stage e Source

An individual stage in a process pipeline.

Instances

stage :: Lines e -> (ExitCode -> Either e ()) -> CreateProcess -> Stage e Source

Builds a Stage out of a Lines that specifies how to handle stderr when piped, a function that determines whether an ExitCode represents an error (some programs return non-standard exit codes) and a process definition.

pipefail :: ExitCode -> Either Int () Source

Converts any ExitFailure to the left side of an Either.

inbound :: (forall r. Producer ByteString (ExceptT e IO) r -> Producer ByteString (ExceptT e IO) r) -> Stage e -> Stage e Source

Applies a transformation to the stream of bytes flowing into a stage from previous stages.

This function is ignored for first stages.

Re-exports

System.Process is re-exported for convenience.

Deprecated

 

type PipingPolicy e a = Piping e a Source

Deprecated: Use Piping instead

type LinePolicy e = Lines e Source

Deprecated: Use Lines instead

linePolicy :: DecodingFunction ByteString Text -> Siphon ByteString e () -> Lines e Source

Deprecated: Use toLines instead