streaming-process-0.1.0.0: Streaming support for running system process

Copyright(c) Ivan Lazar Miljenovic
LicenseMIT
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell2010

Streaming.Process.Lifted

Contents

Description

This module defines variants of those in Streaming.Process for use with the Withable class, found in the streaming-with package.

WARNING: If using this module, you will need to have ghc-options -threaded in your .cabal file otherwise it will likely hang!

These functions will all throw ProcessExitedUnsuccessfully if the process/command itself fails.

Synopsis

High level functions

withStreamingProcess :: (Withable w, MonadBaseControl IO (WithMonad w), MonadBase IO n) => CreateProcess -> ByteString (WithMonad w) v -> w (StdOutErr n ()) Source #

Feeds the provided data into the specified process, then concurrently streams stdout and stderr into the provided continuation.

Note that the monad used in the StdOutErr argument to the continuation can be different from the final result, as it's up to the caller to make sure the result is reached.

withStreamingCommand :: (Withable w, MonadBaseControl IO (WithMonad w), MonadBase IO n) => String -> ByteString (WithMonad w) v -> w (StdOutErr n ()) Source #

As with withStreamingProcess, but run the specified command in a shell.

streamInput :: Withable w => CreateProcess -> ByteString (WithMonad w) r -> w r Source #

Feed input into a process with no expected output.

streamInputCommand :: Withable w => String -> ByteString (WithMonad w) r -> w r Source #

As with streamInput but run the specified command in a shell.

withStreamingOutput :: (Withable w, MonadIO n) => CreateProcess -> w (ByteString n ()) Source #

Obtain the output of a process with no input (ignoring error output).

withStreamingOutputCommand :: (Withable w, MonadIO n) => String -> w (ByteString n ()) Source #

As with withStreamingOutput but run the specified command in a shell.

Lower level

data StreamProcess stdin stdout stderr Source #

Represents the input and outputs for a streaming process.

Constructors

StreamProcess 

Fields

Instances

(Eq stderr, Eq stdout, Eq stdin) => Eq (StreamProcess stdin stdout stderr) Source # 

Methods

(==) :: StreamProcess stdin stdout stderr -> StreamProcess stdin stdout stderr -> Bool #

(/=) :: StreamProcess stdin stdout stderr -> StreamProcess stdin stdout stderr -> Bool #

(Show stderr, Show stdout, Show stdin) => Show (StreamProcess stdin stdout stderr) Source # 

Methods

showsPrec :: Int -> StreamProcess stdin stdout stderr -> ShowS #

show :: StreamProcess stdin stdout stderr -> String #

showList :: [StreamProcess stdin stdout stderr] -> ShowS #

switchOutputs :: StreamProcess stdin stdout stderr -> StreamProcess stdin stderr stdout Source #

Switch the two outputs. Useful for example if using withStreamProcess and withProcessHandles but wanting to deal with any potential output from stderr before stdout.

newtype WithStream n m Source #

A wrapper for something taking a continuation with a stream of bytes as input.

Constructors

WithStream (forall r. (ByteString n () -> m r) -> m r) 

Instances

type WithStream' m = WithStream m m Source #

An alias for the common case of n ~ m.

withStream :: Withable w => WithStream n (WithMonad w) -> w (ByteString n ()) Source #

Please note that - unlike the version in Streaming.Process - this is not a record selector.

newtype SupplyStream m Source #

A wrapper for being able to provide a stream of bytes.

Constructors

SupplyStream (forall r. ByteString m r -> m r) 

supplyStream :: Withable w => SupplyStream (WithMonad w) -> ByteString (WithMonad w) r -> w r Source #

Please note that - unlike the version in Streaming.Process - this is not a record selector.

withStreamProcess :: (InputSource stdin, OutputSink stdout, OutputSink stderr, Withable w) => CreateProcess -> w (StreamProcess stdin stdout stderr) Source #

A variant of withCheckedProcess that will on an exception kill the child process and attempt to perform cleanup (though you should also attempt to do so in your own code).

Will throw ProcessExitedUnsuccessfully on a non-successful exit code.

Compared to withCheckedProcessCleanup from conduit-extra, this has the three parameters grouped into StreamProcess to make it more of a continuation.

withStreamCommand :: (InputSource stdin, OutputSink stdout, OutputSink stderr, Withable w) => String -> w (StreamProcess stdin stdout stderr) Source #

A variant of withStreamProcess that runs the provided command in a shell.

withProcessHandles :: (Withable w, m ~ WithMonad w, MonadBaseControl IO m, MonadBase IO n) => ByteString m v -> StreamProcess (SupplyStream m) (WithStream' m) (WithStream' m) -> w (StdOutErr n ()) Source #

Feeds the provided data into the input handle, then concurrently streams stdout and stderr into the provided continuation.

Note that the monad used in the StdOutErr argument to the continuation can be different from the final result, as it's up to the caller to make sure the result is reached.

processInput :: Withable w => StreamProcess (SupplyStream (WithMonad w)) ClosedStream ClosedStream -> ByteString (WithMonad w) r -> w r Source #

Stream input into a process, ignoring any output.

withProcessOutput :: (Withable w, MonadIO n) => StreamProcess ClosedStream (WithStream n (WithMonad w)) ClosedStream -> w (ByteString n ()) Source #

Read the output from a process, ignoring stdin and stderr.

Interleaved stdout and stderr

type StdOutErr m r = ByteString (ByteString m) r Source #

A representation of the concurrent streaming of both stdout and stderr (contrast to hGet).

Note that if for example you wish to completely discard stderr, you can do so with hoist effects (or just process the stdout, then run effects at the end to discard the stderr).

withStreamOutputs :: (Withable w, m ~ WithMonad w, MonadBaseControl IO m, MonadBase IO n) => StreamProcess stdin (WithStream' m) (WithStream' m) -> w (StdOutErr n ()) Source #

Get both stdout and stderr concurrently.

Re-exports

All of Data.Streaming.Process is available for you to use.

The concurrently function will probably be useful if manually handling process inputs and outputs.

concurrently :: MonadBaseControl IO m => m a -> m b -> m (a, b) #

Generalized version of concurrently.