| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
System.Process.Streaming.Internal
- data Piping e a
- = PPNone a
- | PPOutput (Producer ByteString IO () -> IO (Either e a))
- | PPError (Producer ByteString IO () -> IO (Either e a))
- | PPOutputError ((Producer ByteString IO (), Producer ByteString IO ()) -> IO (Either e a))
- | PPInput ((Consumer ByteString IO (), IO ()) -> IO (Either e a))
- | PPInputOutput ((Consumer ByteString IO (), IO (), Producer ByteString IO ()) -> IO (Either e a))
- | PPInputError ((Consumer ByteString IO (), IO (), Producer ByteString IO ()) -> IO (Either e a))
- | PPInputOutputError ((Consumer ByteString IO (), IO (), Producer ByteString IO (), Producer ByteString IO ()) -> IO (Either e a))
- newtype Piap e a = Piap {
- runPiap :: (Consumer ByteString IO (), IO (), Producer ByteString IO (), Producer ByteString IO ()) -> IO (Either e a)
- newtype Pump b e a = Pump {}
- newtype Siphon b e a = Siphon (Lift (Siphon_ b e) a)
- runSiphon :: Siphon b e a -> Producer b IO r -> IO (Either e (a, r))
- runSiphonDumb :: Siphon b e a -> Producer b IO () -> IO (Either e a)
- data Siphon_ b e a
- = Exhaustive (forall r. Producer b IO r -> IO (Either e (a, r)))
- | Nonexhaustive (Producer b IO () -> IO (Either e a))
- exhaustive :: Siphon_ b e a -> Producer b IO r -> IO (Either e (a, r))
- data Lines e = Lines {}
- newtype Splitter b = Splitter {}
- combined :: Lines e -> Lines e -> (Producer Text IO () -> IO (Either e a)) -> Producer ByteString IO () -> Producer ByteString IO () -> IO (Either e a)
- manyCombined :: [(FreeT (Producer Text IO) IO (Producer ByteString IO ()) -> IO (Producer ByteString IO ())) -> IO (Either e ())] -> (Producer Text IO () -> IO (Either e a)) -> IO (Either e a)
- data Stage e = Stage {
- _processDefinition :: CreateProcess
- _stderrLines :: Lines e
- _exitCodePolicy :: ExitCode -> Either e ()
- _inbound :: forall r. Producer ByteString IO r -> Producer ByteString (ExceptT e IO) r
Documentation
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.
Constructors
| PPNone a | |
| PPOutput (Producer ByteString IO () -> IO (Either e a)) | |
| PPError (Producer ByteString IO () -> IO (Either e a)) | |
| PPOutputError ((Producer ByteString IO (), Producer ByteString IO ()) -> IO (Either e a)) | |
| PPInput ((Consumer ByteString IO (), IO ()) -> IO (Either e a)) | |
| PPInputOutput ((Consumer ByteString IO (), IO (), Producer ByteString IO ()) -> IO (Either e a)) | |
| PPInputError ((Consumer ByteString IO (), IO (), Producer ByteString IO ()) -> IO (Either e a)) | |
| PPInputOutputError ((Consumer ByteString IO (), IO (), Producer ByteString IO (), Producer ByteString IO ()) -> IO (Either e a)) |
An alternative to Piping for defining what to do with the
standard streams. Piap is an instance of Applicative, unlike
Piping.
With Piap, the standard streams are always piped. The values of
std_in, std_out and std_err in the CreateProcess record are
ignored.
Constructors
| Piap | |
Fields
| |
Pumps are actions that write data into a process' stdin.
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) |
|
| Functor (Siphon b e) | |
| Applicative (Siphon b e) |
|
| Monoid a => Monoid (Siphon b e a) |
Constructors
| Exhaustive (forall r. Producer b IO r -> IO (Either e (a, r))) | |
| Nonexhaustive (Producer b IO () -> IO (Either e a)) |
A configuration parameter used in functions that combine lines of text from multiple streams.
Constructors
| Lines | |
combined :: Lines e -> Lines e -> (Producer Text IO () -> IO (Either e a)) -> Producer ByteString IO () -> Producer ByteString IO () -> IO (Either e a) Source
manyCombined :: [(FreeT (Producer Text IO) IO (Producer ByteString IO ()) -> IO (Producer ByteString IO ())) -> IO (Either e ())] -> (Producer Text IO () -> IO (Either e a)) -> IO (Either e a) Source
An individual stage in a process pipeline.
Constructors
| Stage | |
Fields
| |