process-streaming-0.7.2.2: 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 other than IOExceptions 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.

Besides exceptions, if the consumption of the standard streams fails with e, the whole computation is immediately aborted and e is returned.

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

execute :: Piping Void a -> CreateProcess -> IO (ExitCode, a) Source

A simplified version of executeFallibly for when the error type unifies with Void. Note however that this function may still throw exceptions.

Piping the standard streams

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

Bifunctor Piping

first is useful to massage errors.

Functor (Piping e) 

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

data Pump b e a Source

Pumps are actions that write data into a process' stdin.

Instances

Bifunctor (Pump b)

first is useful to massage errors.

Functor (Pump b e) 
Applicative (Pump b e)

pure writes nothing to stdin.

<*> sequences the writes to stdin.

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 which may fail early with an error of type e.

Instances

Bifunctor (Siphon b)

first is useful to massage errors.

Functor (Siphon b e) 
Applicative (Siphon b 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.

Monoid a => Monoid (Siphon b e a) 

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.

This functions incurs in less overhead than siphon.

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

Useful in combination with folds from the pipes prelude, or more specialized folds like toLazyM from pipes-text and toLazyM from pipes-bytestring.

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

fromConsumer' :: Consumer b IO Void -> Siphon b e () Source

Builds a Siphon out of a Consumer with a polymorphic return type (one example is toHandle from pipes-bytestring).

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

fromConsumerM' :: MonadIO m => (forall r. m r -> IO (Either e (a, r))) -> Consumer b m Void -> 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 Siphon.

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

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.

intoLazyBytes :: Siphon ByteString e ByteString Source

Collects incoming ByteString values into a lazy ByteString.

intoLazyText :: Siphon Text e Text Source

Collects incoming Text values into a lazy Text.

unwanted :: a -> Siphon b b a Source

Constructs a Siphon that aborts the computation with an explicit error 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 Source

Arguments

:: DecodingFunction bytes text

A decoding function.

-> Siphon bytes e (a -> b)

A Siphon that determines how to handle decoding leftovers. Pass pure id to ignore leftovers. Pass unwanted id to abort the computation with an explicit error if leftovers remain. Pass _leftoverX to throw a LeftoverException if leftovers remain.

-> Siphon text e a 
-> Siphon bytes e b 

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

newtype SiphonOp e a b Source

A newtype wrapper with functions for working on the inputs of a Siphon, instead of the outputs.

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.

contramapFoldable :: Foldable f => (a -> f b) -> SiphonOp e r b -> SiphonOp e r a Source

Useful to weed out unwanted inputs to a Siphon, by returning [].

contramapEnumerable :: Enumerable t => (a -> t IO b) -> SiphonOp e r b -> SiphonOp e r a Source

contraproduce :: (forall r. Producer a IO r -> Producer b IO r) -> SiphonOp e r b -> SiphonOp e r a Source

contraencoded Source

Arguments

:: DecodingFunction bytes text

A decoding function.

-> Siphon bytes e (a -> b)

A Siphon that determines how to handle decoding leftovers. Pass pure id to ignore leftovers. Pass unwanted id to abort the computation with an explicit error if leftovers remain. Pass _leftoverX to throw a LeftoverException if leftovers remain.

-> SiphonOp e a text 
-> SiphonOp e b bytes 

Like encoded, but works on SiphonOps.

splitter :: (forall r. Producer b IO r -> FreeT (Producer b IO) IO r) -> Splitter b Source

Build a Splitter out of a function that splits a Producer while preserving streaming.

See the section FreeT Transformations in the documentation for the pipes-text package, and also the documentation for the pipes-group package.

tweakSplits :: (forall r. Producer b IO r -> Producer b IO r) -> Splitter b -> Splitter b Source

Specifies a transformation that will be applied to each individual split, represented as a Producer.

rejoin :: forall b r. Splitter b -> Producer b IO r -> Producer b IO r Source

Flattens the Splitter, returning a function from Producer to Producer which can be passed to functions like contraproduce.

nest :: Splitter b -> Siphon b Void a -> SiphonOp e r a -> SiphonOp e r b Source

Process each individual split created by a Splitter using a Siphon.

Handling lines

data Lines e Source

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

Instances

Functor Lines

fmap maps over the encoding error.

toLines Source

Arguments

:: DecodingFunction ByteString Text

A decoding function for lines of text.

-> Siphon ByteString e (() -> ())

A Siphon that determines how to handle decoding leftovers. Pass pure id to ignore leftovers. Pass unwanted id to abort the computation with an explicit error if leftovers remain. Pass _leftoverX to throw a LeftoverException if leftovers remain.

-> Lines e 

Constructs a Lines value.

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.

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

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

Throwing exceptions

unwantedX :: Exception ex => (b -> ex) -> a -> Siphon b e a Source

Like unwanted, but throws an exception instead of using the explicit error type.

data LeftoverException b Source

Exception that carries a message and a sample of the leftover data.

Constructors

LeftoverException String b 

leftoverX Source

Arguments

:: String

Error message

-> Siphon ByteString e (a -> a) 

Throws LeftoverException if any data comes out of the underlying producer, and returns id otherwise.

_leftoverX :: Siphon ByteString e (a -> a) Source

Like leftoverX, but doesn't take an error message.

Pipelines

executePipelineFallibly Source

Arguments

:: Piping e a

Views the pipeline as a single process for which stdin is the stdin of the first stage and stdout is the stdout of the leftmost terminal stage closer to the root. stderr is a combination of the stderr streams of all the stages. The combined stderr stream always has UTF-8 encoding.

-> Tree (Stage e)

A (possibly branching) pipeline of processes. Each process' stdin is fed with the stdout of its parent in the tree.

-> IO (Either e a) 

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

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.

executePipeline :: Piping Void a -> Tree (Stage Void) -> IO a Source

A simplified version of executePipelineFallibly for when the error type unifies with Void. Note however that this function may still throw exceptions.

data Stage e Source

An individual stage in a process pipeline.

Instances

stage Source

Arguments

:: Lines e

How to handle lines coming from stderr for this Stage.

-> (ExitCode -> Either e ())

Does the ExitCode for this Stage represent an error? (Some programs return non-standard exit codes.)

-> CreateProcess

A process definition.

-> Stage e 

Builds a Stage.

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.

decodeAscii :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r)

Reduce a byte stream to a corresponding stream of ascii chars, returning the unused ByteString upon hitting an un-ascii byte.

decodeIso8859_1 :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r)

Reduce a byte stream to a corresponding stream of ascii chars, returning the unused ByteString upon hitting the rare un-latinizable byte.