process-streaming-0.9.2.1: 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.

They provide concurrent, streaming access to the inputs and outputs of external processes.

Consumers from pipes, Parsers from pipes-parse and Folds from foldl can be used to consume the standard streams, by means of the auxiliary Fold1 datatype from pipes-transduce.

The entirety of System.Process and Pipes.Transduce is re-exported for convenience.

Synopsis

Execution

execute :: CreateProcess -> Streams Void a -> IO a Source #

Execute an external program described by the CreateProcess record.

The Streams Applicative specifies how to handle the standard streams and the exit code. Since Streams is an Applicative, a simple invocation of execute could be

>>> execute (piped (shell "echo foo")) (pure ())

which would discard the program's stdout and stderr, and ignore the exit code. To actually get the exit code:

>>> execute (piped (shell "echo foo")) exitCode
ExitSuccess

To collect stdout as a lazy ByteString along with the exit code:

>>> execute (piped (shell "echo foo")) (liftA2 (,) (foldOut intoLazyBytes) exitCode)
("foo\n",ExitSuccess)

execute respects all the fields of the CreateProcess record. If stdout is not piped, but a handler is defined for it, the handler will see an empty stream:

>>> execute ((shell "echo foo"){ std_out = Inherit }) (foldOut intoLazyBytes)
foo
""

No effort is made to catch exceptions thrown during execution:

>>> execute (piped (shell "echo foo")) (foldOut (withCont (\_ -> throwIO (userError "oops"))))
*** Exception: user error (oops)

However, care is taken to automatically terminate the external process if an exception (including asynchronous ones) or other type of error happens. This means we can terminate the external process by killing the thread that is running execute:

>>> forkIO (execute (piped (shell "sleep infinity")) (pure ())) >>= killThread

executeFallibly :: CreateProcess -> Streams e a -> IO (Either e a) Source #

Like execute, but allows the handlers in the Streams Applicative to interrupt the execution of the external process by returning a Left value, in addition to throwing exceptions. This is sometimes more convenient:

>>> executeFallibly (piped (shell "sleep infinity")) (foldOut (withFallibleCont (\_ -> pure (Left "oops"))))
Left "oops"
>>> executeFallibly (piped (shell "exit 1")) validateExitCode
Left 1

The first type parameter of Streams is the error type. If it is never used, it remains polymorphic and may unify with Void (as required by execute).

Unbuffered stdin

executeInteractive :: CreateProcess -> Streams Void a -> IO a Source #

Like execute, but std_in will be unbuffered if piped.

executeInteractiveFallibly :: CreateProcess -> Streams e a -> IO (Either e a) Source #

Like executeFallibly, but std_in will be unbuffered if piped.

CreateProcess helpers

piped :: CreateProcess -> CreateProcess Source #

Sets std_in, std_out and std_err in the CreateProcess record to CreatePipe.

Any unpiped stream will appear to the Streams handlers as empty.

The Streams Applicative

data Streams e r Source #

The type of handlers that write to piped stdin, consume piped stdout and stderr, and work with the process exit code, eventually returning a value of type r, except when an error e interrups the execution.

Example of a complex handler:

>>> :{
    execute (piped (shell "{ cat ; sleep 1 ; echo eee 1>&2 ; }")) $ 
        (\_ _ ob eb et oet c -> (ob,eb,et,oet,c)) 
        <$>
        feedBytes (Just "aaa") 
        <*> 
        feedBytes (Just "bbb") 
        <*> 
        foldOut intoLazyBytes 
        <*>
        foldErr intoLazyBytes 
        <*>
        foldErr (PT.asUtf8x PT.intoLazyText)
        <*>
        foldOutErr (PT.bothAsUtf8x (PT.combinedLines PT.intoLazyText))
        <*>
        exitCode
    :}
("aaabbb","eee\n","eee\n","aaabbb\neee\n",ExitSuccess)

Instances

Bifunctor Streams Source #

first is useful to massage errors.

Methods

bimap :: (a -> b) -> (c -> d) -> Streams a c -> Streams b d #

first :: (a -> b) -> Streams a c -> Streams b c #

second :: (b -> c) -> Streams a b -> Streams a c #

Functor (Streams e) Source # 

Methods

fmap :: (a -> b) -> Streams e a -> Streams e b #

(<$) :: a -> Streams e b -> Streams e a #

Applicative (Streams e) Source #

pure writes nothing to stdin, discards the data coming from stdout and stderr, and ignores the exit code.

<*> combines handlers by sequencing the writes to stdin, and making concurrent reads from stdout and stderr.

Methods

pure :: a -> Streams e a #

(<*>) :: Streams e (a -> b) -> Streams e a -> Streams e b #

liftA2 :: (a -> b -> c) -> Streams e a -> Streams e b -> Streams e c #

(*>) :: Streams e a -> Streams e b -> Streams e b #

(<*) :: Streams e a -> Streams e b -> Streams e a #

Monoid a => Monoid (Streams e a) Source # 

Methods

mempty :: Streams e a #

mappend :: Streams e a -> Streams e a -> Streams e a #

mconcat :: [Streams e a] -> Streams e a #

Feeding stdin

feedBytes :: Foldable f => f ByteString -> Streams e () Source #

Feed any Foldable container of strict ByteStrings to stdin.

feedLazyBytes :: ByteString -> Streams e () Source #

Feed a lazy ByteString to stdin.

feedUtf8 :: Foldable f => f Text -> Streams e () Source #

Feed any Foldable container of strict Textss to stdin, encoding the texts as UTF8.

feedLazyUtf8 :: Text -> Streams e () Source #

Feed a lazy Text to stdin, encoding it as UTF8.

feedProducerM :: MonadIO m => (m () -> IO (Either e a)) -> Producer ByteString m r -> Streams e a Source #

feedCont :: (Consumer ByteString IO () -> IO (Either e a)) -> Streams e a Source #

Feed stdin by running a pipes Consumer. This allows bracketing functions like withFile inside the handler.

Consuming stdout and stderr

These functions take as parameters the Fold1 and Fold2 datatypes defined in the pipes-transduce package.

A convenience intoLazyBytes Fold1 that collects a stream into a lazy ByteString is re-exported.

foldOut :: Fold1 ByteString e r -> Streams e r Source #

Consume standard output.

foldErr :: Fold1 ByteString e r -> Streams e r Source #

Consume standard error.

intoLazyBytes :: Fold1 ByteString e ByteString #

Collect strict ByteStrings into a lazy ByteString.

>>> PT.fold1  intoLazyBytes (mapM_ yield ["aa","bb","cc"])
("aabbcc",())

foldOutErr :: Fold2 ByteString ByteString e r -> Streams e r Source #

Consume standard output and error together. This enables combining them in a single stream. See also bothAsUtf8x and combinedLines.

Handling exit codes

exitCode :: Streams e ExitCode Source #

Simply returns the ExitCode.

validateExitCode :: Streams Int () Source #

Fails with the error code when ExitCode is not ExitSuccess.

A GHCi idiom

Within GHCi, it's easy to use this module to launch external programs.

If the program is long-running, do it in a new thread to avoid locking GHCi, and keep track of the thread id:

ghci> r <- forkIO $ execute (piped (proc "C:/Program Files (x86)/Vim/vim74/gvim.exe" [])) (pure ())

Kill the thread to kill the long-running process:

ghci> killThread r