| Safe Haskell | Safe-Inferred |
|---|---|
| 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 that are not directly related to IO are made explicit in the types.
Regular Consumers, Parsers from pipes-parse and folds from
Pipes.Prelude (also folds from pipes-bytestring and pipes-text)
can be used to consume the output streams of the external processes.
- execute :: PipingPolicy Void a -> CreateProcess -> IO (ExitCode, a)
- executeFallibly :: PipingPolicy e a -> CreateProcess -> IO (Either e (ExitCode, a))
- data PipingPolicy e a
- nopiping :: PipingPolicy e ()
- pipeo :: (Show e, Typeable e) => Siphon ByteString e a -> PipingPolicy e a
- pipee :: (Show e, Typeable e) => Siphon ByteString e a -> PipingPolicy e a
- pipeoe :: (Show e, Typeable e) => Siphon ByteString e a -> Siphon ByteString e b -> PipingPolicy e (a, b)
- pipeoec :: (Show e, Typeable e) => LinePolicy e -> LinePolicy e -> Siphon Text e a -> PipingPolicy e a
- pipei :: (Show e, Typeable e) => Pump ByteString e i -> PipingPolicy e i
- pipeio :: (Show e, Typeable e) => Pump ByteString e i -> Siphon ByteString e a -> PipingPolicy e (i, a)
- pipeie :: (Show e, Typeable e) => Pump ByteString e i -> Siphon ByteString e a -> PipingPolicy e (i, a)
- pipeioe :: (Show e, Typeable e) => Pump ByteString e i -> Siphon ByteString e a -> Siphon ByteString e b -> PipingPolicy e (i, a, b)
- pipeioec :: (Show e, Typeable e) => Pump ByteString e i -> LinePolicy e -> LinePolicy e -> Siphon Text e a -> PipingPolicy e (i, a)
- newtype Pump b e a = Pump {}
- fromProducer :: Producer b IO () -> Pump b e ()
- fromSafeProducer :: Producer b (SafeT IO) () -> Pump b e ()
- fromFallibleProducer :: Producer b (ExceptT e IO) () -> Pump b e ()
- data 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 ()
- fromConsumer :: Consumer b IO () -> Siphon b e ()
- fromSafeConsumer :: Consumer b (SafeT IO) () -> Siphon b e ()
- fromFallibleConsumer :: Consumer b (ExceptT e IO) () -> Siphon b e ()
- fromParser :: Parser b IO (Either e a) -> Siphon b e a
- unwanted :: a -> Siphon b b a
- type DecodingFunction bytes text = forall r. Producer bytes IO r -> Producer text IO (Producer bytes IO r)
- encoded :: (Show e, Typeable e) => DecodingFunction bytes text -> Siphon bytes e (a -> b) -> Siphon text e a -> Siphon bytes e b
- data LinePolicy e
- linePolicy :: (Show e, Typeable e) => DecodingFunction ByteString Text -> Siphon ByteString e () -> (forall r. Producer Text IO r -> Producer Text IO r) -> LinePolicy e
- executePipeline :: PipingPolicy Void a -> CreatePipeline Void -> IO a
- executePipelineFallibly :: (Show e, Typeable e) => PipingPolicy e a -> CreatePipeline e -> IO (Either e a)
- data CreatePipeline e = CreatePipeline (Stage e) (NonEmpty (Tree (SubsequentStage e)))
- simplePipeline :: DecodingFunction ByteString Text -> CreateProcess -> NonEmpty (Tree CreateProcess) -> CreatePipeline String
- data Stage e = Stage {
- processDefinition :: CreateProcess
- stderrLinePolicy :: LinePolicy e
- exitCodePolicy :: Int -> Maybe e
- data SubsequentStage e = SubsequentStage (forall a. Pipe ByteString ByteString (ExceptT e IO) a) (Stage e)
- module System.Process
Execution
execute :: PipingPolicy Void a -> CreateProcess -> IO (ExitCode, a) Source
executeFallibly :: PipingPolicy 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 PipingPolicy argument.
This fuction 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 PipingPolicy e a Source
A PipingPolicy 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 PipingPolicy is parametrized by the type e of errors that can abort
the processing of the streams.
Instances
nopiping :: PipingPolicy e () Source
Do not pipe any standard stream.
pipeo :: (Show e, Typeable e) => Siphon ByteString e a -> PipingPolicy e a Source
Pipe stdout.
pipee :: (Show e, Typeable e) => Siphon ByteString e a -> PipingPolicy e a Source
Pipe stderr.
pipeoe :: (Show e, Typeable e) => Siphon ByteString e a -> Siphon ByteString e b -> PipingPolicy e (a, b) Source
Pipe stdout and stderr.
pipeoec :: (Show e, Typeable e) => LinePolicy e -> LinePolicy e -> Siphon Text e a -> PipingPolicy e a Source
Pipe stdout and stderr and consume them combined as Text.
pipei :: (Show e, Typeable e) => Pump ByteString e i -> PipingPolicy e i Source
Pipe stdin.
pipeio :: (Show e, Typeable e) => Pump ByteString e i -> Siphon ByteString e a -> PipingPolicy e (i, a) Source
Pipe stdin and stdout.
pipeie :: (Show e, Typeable e) => Pump ByteString e i -> Siphon ByteString e a -> PipingPolicy e (i, a) Source
Pipe stdin and stderr.
pipeioe :: (Show e, Typeable e) => Pump ByteString e i -> Siphon ByteString e a -> Siphon ByteString e b -> PipingPolicy e (i, a, b) Source
Pipe stdin, stdout and stderr.
pipeioec :: (Show e, Typeable e) => Pump ByteString e i -> LinePolicy e -> LinePolicy e -> Siphon Text e a -> PipingPolicy e (i, a) Source
Pipe stdin, stdout and stderr, consuming the last two combined as Text.
Pumping bytes into stdin
fromProducer :: Producer b IO () -> 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.
fromConsumer :: Consumer b IO () -> 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.
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 :: (Show e, Typeable e) => DecodingFunction bytes text -> Siphon bytes e (a -> b) -> Siphon text e a -> Siphon bytes e b Source
Line handling
data LinePolicy e Source
Defines how to decode a stream of bytes into text, including what to do in presence of leftovers. Also defines how to manipulate each individual line of text.
Instances
linePolicy :: (Show e, Typeable e) => DecodingFunction ByteString Text -> Siphon ByteString e () -> (forall r. Producer Text IO r -> Producer Text IO r) -> LinePolicy e Source
Constructs a LinePolicy.
The second argument is a Siphon value that specifies how to handle
decoding failures. Passing pure () will ignore any leftovers. Passing
unwanted () will abort the computation if leftovers remain.
The third argument is a function that modifies each individual line.
The line is represented as a Producer to avoid having to keep it
wholly in memory. If you want the lines unmodified, just pass id.
Line prefixes are easy to add using applicative notation:
(\x -> yield "prefix: " *> x)
Pipelines
executePipeline :: PipingPolicy Void a -> CreatePipeline Void -> IO a Source
executePipelineFallibly :: (Show e, Typeable e) => PipingPolicy e a -> CreatePipeline 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 PipingPolicy 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 CreatePipeline e Source
Constructors
| CreatePipeline (Stage e) (NonEmpty (Tree (SubsequentStage e))) |
Instances
simplePipeline :: DecodingFunction ByteString Text -> CreateProcess -> NonEmpty (Tree CreateProcess) -> CreatePipeline String Source
Builds a (possibly branching) pipeline assuming that stderr has the same
encoding in all the stages, that no computation is perfored between the stages,
and that any exit code besides ExitSuccess in a stage actually represents an
error.
An individual stage in a process pipeline.
The LinePolicy field defines how to handle stderr when stderr is
piped.
Also required is a function that determines if the returned exit code represents an error or not. This is necessary because some programs use non-standard exit codes.
Constructors
| Stage | |
Fields
| |
data SubsequentStage e Source
Any stage beyond the first in a process pipeline.
Incoming data is passed through the Pipe before being fed to the process.
Use cat (the identity Pipe from Pipes) if no pre-processing is required.
Constructors
| SubsequentStage (forall a. Pipe ByteString ByteString (ExceptT e IO) a) (Stage e) |
Instances
Re-exports
System.Process is re-exported for convenience.
module System.Process