| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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.
- execute :: Piping Void a -> CreateProcess -> IO (ExitCode, a)
 - executeFallibly :: Piping e a -> CreateProcess -> IO (Either e (ExitCode, a))
 - data Piping e a
 - nopiping :: Piping e ()
 - pipeo :: Siphon ByteString e a -> Piping e a
 - pipee :: Siphon ByteString e a -> Piping e a
 - pipeoe :: Siphon ByteString e a -> Siphon ByteString e b -> Piping e (a, b)
 - pipeoec :: Lines e -> Lines e -> Siphon Text e a -> Piping e a
 - pipei :: Pump ByteString e i -> Piping e i
 - pipeio :: Pump ByteString e i -> Siphon ByteString e a -> Piping e (i, a)
 - pipeie :: Pump ByteString e i -> Siphon ByteString e a -> Piping e (i, a)
 - pipeioe :: Pump ByteString e i -> Siphon ByteString e a -> Siphon ByteString e b -> Piping e (i, a, b)
 - pipeioec :: Pump ByteString e i -> Lines e -> Lines e -> Siphon Text e a -> Piping e (i, a)
 - newtype Pump b e a = Pump {}
 - fromProducer :: Producer b IO r -> Pump b e ()
 - fromProducerM :: MonadIO m => (m () -> IO (Either e a)) -> Producer b m r -> Pump b e a
 - fromSafeProducer :: Producer b (SafeT IO) r -> Pump b e ()
 - fromFallibleProducer :: Producer b (ExceptT e IO) r -> Pump b e ()
 - data Siphon b e a
 - newtype SiphonOp e a b = SiphonOp {
- getSiphonOp :: Siphon b e a
 
 - siphon :: (Producer b IO () -> IO (Either e a)) -> Siphon b e a
 - siphon' :: (forall r. Producer b IO r -> IO (Either e (a, r))) -> Siphon b e a
 - fromFold :: (Producer b IO () -> IO a) -> Siphon b e a
 - fromFold' :: (forall r. Producer b IO r -> IO (a, r)) -> Siphon b e a
 - fromFold'_ :: (forall r. Producer b IO r -> IO r) -> Siphon b e ()
 - fromFoldl :: Fold b a -> Siphon b e a
 - fromFoldlIO :: FoldM IO b a -> Siphon b e a
 - fromFoldlM :: MonadIO m => (forall r. m (a, r) -> IO (Either e (c, r))) -> FoldM m b a -> Siphon b e c
 - fromConsumer :: Consumer b IO r -> Siphon b e ()
 - fromConsumerM :: MonadIO m => (m () -> IO (Either e a)) -> Consumer b m r -> Siphon b e a
 - fromSafeConsumer :: Consumer b (SafeT IO) r -> Siphon b e ()
 - fromFallibleConsumer :: Consumer b (ExceptT e IO) r -> Siphon b e ()
 - fromParser :: Parser b IO (Either e a) -> Siphon b e a
 - fromParserM :: MonadIO m => (forall r. m (a, r) -> IO (Either e (c, r))) -> Parser b m a -> Siphon b e c
 - unwanted :: a -> Siphon b b a
 - type DecodingFunction bytes text = forall r. Producer bytes IO r -> Producer text IO (Producer bytes IO r)
 - encoded :: DecodingFunction bytes text -> Siphon bytes e (a -> b) -> Siphon text e a -> Siphon bytes e b
 - data Lines e
 - toLines :: DecodingFunction ByteString Text -> Siphon ByteString e () -> Lines e
 - tweakLines :: (forall r. Producer Text IO r -> Producer Text IO r) -> Lines e -> Lines e
 - executePipeline :: Piping Void a -> Tree (Stage Void) -> IO a
 - executePipelineFallibly :: Piping e a -> Tree (Stage e) -> IO (Either e a)
 - data Stage e
 - stage :: Lines e -> (ExitCode -> Either e ()) -> CreateProcess -> Stage e
 - pipefail :: ExitCode -> Either Int ()
 - inbound :: (forall r. Producer ByteString (ExceptT e IO) r -> Producer ByteString (ExceptT e IO) r) -> Stage e -> Stage e
 - module System.Process
 - type PipingPolicy e a = Piping e a
 - type LinePolicy e = Lines e
 - linePolicy :: DecodingFunction ByteString Text -> Siphon ByteString e () -> Lines e
 
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
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.
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
fromProducer :: Producer b IO r -> Pump b e () Source
fromSafeProducer :: Producer b (SafeT IO) r -> Pump b e () Source
fromFallibleProducer :: Producer b (ExceptT e IO) r -> Pump b e () Source
Siphoning bytes out of stdout/stderr
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.
Constructors
| SiphonOp | |
Fields 
  | |
Instances
| Contravariant (SiphonOp e a) | 
  | 
| Monoid a => Divisible (SiphonOp e a) | 
  | 
| Monoid a => Decidable (SiphonOp e a) | 
  | 
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.
fromConsumer :: Consumer b IO r -> Siphon b e () Source
fromSafeConsumer :: Consumer b (SafeT IO) r -> Siphon b e () Source
fromFallibleConsumer :: Consumer b (ExceptT e IO) r -> Siphon b e () 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
Line handling
A configuration parameter used in functions that combine lines from multiple streams.
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)
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.
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.
module System.Process
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