| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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.
- execute :: CreateProcess -> Streams Void a -> IO a
- executeFallibly :: CreateProcess -> Streams e a -> IO (Either e a)
- executeInteractive :: CreateProcess -> Streams Void a -> IO a
- executeInteractiveFallibly :: CreateProcess -> Streams e a -> IO (Either e a)
- piped :: CreateProcess -> CreateProcess
- data Streams e r
- feedBytes :: Foldable f => f ByteString -> Streams e ()
- feedLazyBytes :: ByteString -> Streams e ()
- feedUtf8 :: Foldable f => f Text -> Streams e ()
- feedLazyUtf8 :: Text -> Streams e ()
- feedProducer :: Producer ByteString IO () -> Streams e ()
- feedProducerM :: MonadIO m => (m () -> IO (Either e a)) -> Producer ByteString m r -> Streams e a
- feedSafeProducer :: Producer ByteString (SafeT IO) () -> Streams e ()
- feedFallibleProducer :: Producer ByteString (ExceptT e IO) () -> Streams e ()
- feedCont :: (Consumer ByteString IO () -> IO (Either e a)) -> Streams e a
- foldOut :: Fold1 ByteString e r -> Streams e r
- foldErr :: Fold1 ByteString e r -> Streams e r
- intoLazyBytes :: Fold1 ByteString e ByteString
- foldOutErr :: Fold2 ByteString ByteString e r -> Streams e r
- exitCode :: Streams e ExitCode
- validateExitCode :: Streams Int ()
- withExitCode :: (ExitCode -> IO (Either e a)) -> Streams e a
- module System.Process
- module Pipes.Transduce
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")) exitCodeExitSuccess
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")) validateExitCodeLeft 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 #
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
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 # |
|
| Functor (Streams e) Source # | |
| Applicative (Streams e) Source # |
|
| Semigroup a => Semigroup (Streams e a) Source # | |
| (Monoid a, Semigroup a) => Monoid (Streams e a) Source # | |
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.
feedProducer :: Producer ByteString IO () -> Streams e () Source #
feedProducerM :: MonadIO m => (m () -> IO (Either e a)) -> Producer ByteString m r -> Streams e a Source #
feedSafeProducer :: Producer ByteString (SafeT IO) () -> Streams e () Source #
feedFallibleProducer :: Producer ByteString (ExceptT e IO) () -> Streams e () Source #
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.
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
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
module System.Process
module Pipes.Transduce