Copyright | (c) 2020 Composewell Technologies |
---|---|
License | Apache-2.0 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Streamly.Internal.System.Process
Description
Synopsis
- data Config
- setCwd :: Maybe FilePath -> Config -> Config
- setEnv :: Maybe [(String, String)] -> Config -> Config
- closeFiles :: Bool -> Config -> Config
- newProcessGroup :: Bool -> Config -> Config
- setSession :: Session -> Config -> Config
- parentIgnoresInterrupt :: Bool -> Config -> Config
- setUserId :: Maybe Word32 -> Config -> Config
- setGroupId :: Maybe Word32 -> Config -> Config
- waitForChildTree :: Bool -> Config -> Config
- inheritStdin :: Config -> Config
- inheritStdout :: Config -> Config
- pipeStdErr :: Config -> Config
- newtype ProcessFailure = ProcessFailure Int
- toBytes :: (MonadAsync m, MonadCatch m) => FilePath -> [String] -> Stream m Word8
- toChunks :: (MonadAsync m, MonadCatch m) => FilePath -> [String] -> Stream m (Array Word8)
- toChunksWith :: (MonadCatch m, MonadAsync m) => (Config -> Config) -> FilePath -> [String] -> Stream m (Array Word8)
- toChars :: (MonadAsync m, MonadCatch m) => FilePath -> [String] -> Stream m Char
- toLines :: (MonadAsync m, MonadCatch m) => Fold m Char a -> FilePath -> [String] -> Stream m a
- toString :: (MonadAsync m, MonadCatch m) => FilePath -> [String] -> m String
- toStdout :: (MonadAsync m, MonadCatch m) => FilePath -> [String] -> m ()
- toNull :: (MonadAsync m, MonadCatch m) => FilePath -> [String] -> m ()
- pipeBytes :: (MonadCatch m, MonadAsync m) => FilePath -> [String] -> Stream m Word8 -> Stream m Word8
- pipeChunks :: (MonadCatch m, MonadAsync m) => FilePath -> [String] -> Stream m (Array Word8) -> Stream m (Array Word8)
- pipeChunksWith :: (MonadCatch m, MonadAsync m) => (Config -> Config) -> FilePath -> [String] -> Stream m (Array Word8) -> Stream m (Array Word8)
- pipeChars :: (MonadCatch m, MonadAsync m) => FilePath -> [String] -> Stream m Char -> Stream m Char
- toBytesEither :: (MonadAsync m, MonadCatch m) => FilePath -> [String] -> Stream m (Either Word8 Word8)
- toChunksEither :: (MonadAsync m, MonadCatch m) => FilePath -> [String] -> Stream m (Either (Array Word8) (Array Word8))
- toChunksEitherWith :: (MonadCatch m, MonadAsync m) => (Config -> Config) -> FilePath -> [String] -> Stream m (Either (Array Word8) (Array Word8))
- pipeBytesEither :: (MonadCatch m, MonadAsync m) => FilePath -> [String] -> Stream m Word8 -> Stream m (Either Word8 Word8)
- pipeChunksEither :: (MonadCatch m, MonadAsync m) => FilePath -> [String] -> Stream m (Array Word8) -> Stream m (Either (Array Word8) (Array Word8))
- pipeChunksEitherWith :: (MonadCatch m, MonadAsync m) => (Config -> Config) -> FilePath -> [String] -> Stream m (Array Word8) -> Stream m (Either (Array Word8) (Array Word8))
- standalone :: Bool -> (Bool, Bool, Bool) -> (Config -> Config) -> FilePath -> [String] -> IO (Either ExitCode ProcessHandle)
- interactive :: (Config -> Config) -> FilePath -> [String] -> IO ExitCode
- daemon :: (Config -> Config) -> FilePath -> [String] -> IO ProcessHandle
- processBytes :: (MonadCatch m, MonadAsync m) => FilePath -> [String] -> Stream m Word8 -> Stream m Word8
- processChunks :: (MonadCatch m, MonadAsync m) => FilePath -> [String] -> Stream m (Array Word8) -> Stream m (Array Word8)
Process Configuration
Process configuration used for creating a new process.
By default the process config is setup to inherit the following attributes from the parent process:
- Current working directory
- Environment variables
- Open file descriptors
- Process group
- Terminal session
On POSIX:
- Process uid and gid
- Signal handlers
On Windows by default the parent process waits for the entire child process tree to finish.
Common Config Options
These options apply to both POSIX and Windows.
closeFiles :: Bool -> Config -> Config Source #
Close all open file descriptors inherited from the parent process. Note, this does not apply to stdio descriptors - the behavior of those is determined by other configuration settings.
Default is False
.
Note: if the number of open descriptors is large, it may take a while closing them.
setSession :: Session -> Config -> Config Source #
Define the terminal session behavior for the new process.
Default is InheritSession
.
Posix Only Options
These options have no effect on Windows.
parentIgnoresInterrupt :: Bool -> Config -> Config Source #
When this is True
, the parent process ignores user interrupt signals
SIGINT
and SIGQUIT
delivered to it until the child process exits. If
multiple child processes are started then the default handling in the parent
is restored only after the last one exits.
When a user presses CTRL-C or CTRL- on the terminal, a SIGINT or SIGQUIT is sent to all the foreground processes in the terminal session, this includes both the child and the parent. By default, on receiving these signals, the parent process would cleanup and exit, to avoid that and let the child handle these signals we can choose to ignore these signals in the parent until the child exits.
POSIX only. Default is False
.
setUserId :: Maybe Word32 -> Config -> Config Source #
Use the POSIX setuid
call to set the user id of the new process before
executing the command. The parent process must have sufficient privileges to
set the user id.
POSIX only. See the POSIX setuid
man page.
Default is Nothing
- inherit from the parent.
setGroupId :: Maybe Word32 -> Config -> Config Source #
Use the POSIX setgid
call to set the group id of the new process before
executing the command. The parent process must have sufficient privileges to
set the group id.
POSIX only. See the POSIX setgid
man page.
Default is Nothing
- inherit from the parent.
Windows Only Options
These options have no effect on Posix.
waitForChildTree :: Bool -> Config -> Config Source #
On Windows, the parent waits for the entire tree of process i.e. including processes that are spawned by the child process.
Default is True
.
Internal
inheritStdin :: Config -> Config Source #
inheritStdout :: Config -> Config Source #
pipeStdErr :: Config -> Config Source #
Exceptions
newtype ProcessFailure Source #
An exception that is raised when a process fails.
Since: 0.1.0
Constructors
ProcessFailure Int | The exit code of the process. |
Instances
Exception ProcessFailure Source # | |
Defined in Streamly.Internal.System.Process Methods toException :: ProcessFailure -> SomeException # | |
Show ProcessFailure Source # | |
Defined in Streamly.Internal.System.Process Methods showsPrec :: Int -> ProcessFailure -> ShowS # show :: ProcessFailure -> String # showList :: [ProcessFailure] -> ShowS # |
Generation
stdout of the process is redirected to output stream.
Arguments
:: (MonadAsync m, MonadCatch m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m Word8 | Output Stream |
The following code is equivalent to the shell command echo "hello
world"
:
>>>
:{
Process.toBytes "echo" ["hello world"] & Stream.fold Stdio.write :} hello world
Since: 0.1.0
Arguments
:: (MonadAsync m, MonadCatch m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m (Array Word8) | Output Stream |
The following code is equivalent to the shell command echo "hello
world"
:
>>>
:{
Process.toChunks "echo" ["hello world"] & Stream.fold Stdio.writeChunks :} hello world
>>>
toChunks = toChunksWith id
Since: 0.1.0
Arguments
:: (MonadCatch m, MonadAsync m) | |
=> (Config -> Config) | Config modifier |
-> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m (Array Word8) | Output stream |
Arguments
:: (MonadAsync m, MonadCatch m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m Char | Output Stream |
>>>
toChars path args = toBytes path args & Unicode.decodeUtf8
Arguments
:: (MonadAsync m, MonadCatch m) | |
=> Fold m Char a | |
-> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m a | Output Stream |
>>>
toLines path args f = toChars path args & Unicode.lines f
Arguments
:: (MonadAsync m, MonadCatch m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> m String |
>>>
toString path args = toChars path args & Stream.fold Fold.toList
Arguments
:: (MonadAsync m, MonadCatch m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> m () |
>>>
toStdout path args = toChunks path args & Stdio.putChunks
Arguments
:: (MonadAsync m, MonadCatch m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> m () |
>>>
toNull path args = toChunks path args & Stream.fold Fold.drain
Transformation
The input stream is redirected to the stdin of the process, stdout of the process is redirected to the output stream.
Arguments
:: (MonadCatch m, MonadAsync m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m Word8 | Input Stream |
-> Stream m Word8 | Output Stream |
Like pipeChunks
except that it works on a stream of bytes instead of
a stream of chunks.
We can write the example in pipeChunks
as follows.
>>>
:{
Process.toBytes "echo" ["hello world"] & Process.pipeBytes "tr" ["[a-z]", "[A-Z]"] & Stream.fold Stdio.write :} HELLO WORLD
pre-release
Arguments
:: (MonadCatch m, MonadAsync m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m (Array Word8) | Input stream |
-> Stream m (Array Word8) | Output stream |
pipeChunks file args input
runs the executable file
specified by
its name or path using args
as arguments and input
stream as its
standard input. Returns the standard output of the executable as a stream.
If only the name of an executable file is specified instead of its path then the file name is searched in the directories specified by the PATH environment variable.
If the input stream throws an exception or if the output stream is garbage collected before it could finish then the process is terminated with SIGTERM.
If the process terminates with a non-zero exit code then a ProcessFailure
exception is raised.
The following code is equivalent to the shell command echo "hello world" |
tr [a-z] [A-Z]
:
>>>
:{
Process.toChunks "echo" ["hello world"] & Process.pipeChunks "tr" ["[a-z]", "[A-Z]"] & Stream.fold Stdio.writeChunks :} HELLO WORLD
pre-release
Arguments
:: (MonadCatch m, MonadAsync m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m Char | Input Stream |
-> Stream m Char | Output Stream |
Like pipeChunks
except that it works on a stream of chars instead of
a stream of chunks.
>>>
:{
Process.toChars "echo" ["hello world"] & Process.pipeChars "tr" ["[a-z]", "[A-Z]"] & Stdio.putChars :} HELLO WORLD
We can seamlessly replace the tr
process with the Haskell toUpper
function:
>>>
:{
Process.toChars "echo" ["hello world"] & fmap toUpper & Stdio.putChars :} HELLO WORLD
pre-release
Stderr
Like other Generation routines but along with stdout, stderr is also
included in the output stream. stdout is converted to Right
values in
the output stream and stderr is converted to Left
values.
Arguments
:: (MonadAsync m, MonadCatch m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m (Either Word8 Word8) | Output Stream |
toBytesEither path args
runs the executable at path
using args
as
arguments and returns a stream of Either
bytes. The Left
values are from
stderr
and the Right
values are from stdout
of the executable.
Raises ProcessFailure
exception in case of failure.
The following example uses echo
to write hello
to stdout
and world
to stderr
, then uses folds from Streamly.Console.Stdio to write them
back to stdout
and stderr
respectively:
>>>
:{
Process.toBytesEither "/bin/bash" ["-c", "echo 'hello'; echo 'world' 1>&2"] & Stream.fold (Fold.partition Stdio.writeErr Stdio.write) :} world hello ((),())
Since: 0.1.0
Arguments
:: (MonadAsync m, MonadCatch m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m (Either (Array Word8) (Array Word8)) | Output Stream |
Like toBytes
but generates a stream of Array Word8
instead of a stream
of Word8
.
>>>
:{
toChunksEither "bash" ["-c", "echo 'hello'; echo 'world' 1>&2"] & Stream.fold (Fold.partition Stdio.writeErrChunks Stdio.writeChunks) :} world hello ((),())
>>>
toChunksEither = toChunksEitherWith id
Prefer 'toChunksEither over 'toBytesEither when performance matters.
Pre-release
Arguments
:: (MonadCatch m, MonadAsync m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m Word8 | Input Stream |
-> Stream m (Either Word8 Word8) | Output Stream |
pipeBytesEither path args input
runs the executable at path
using args
as arguments and input
stream as its standard input. The error stream of
the executable is presented as Left
values in the resulting stream and
output stream as Right
values.
Raises ProcessFailure
exception in case of failure.
For example, the following is equivalent to the shell command echo "hello
world" | tr [:lower:] [:upper:]
:
>>>
:{
pipeBytesEither "echo" ["hello world"] Stream.nil & Stream.catRights & pipeBytesEither "tr" ["[:lower:]", "[:upper:]"] & Stream.catRights & Stream.fold Stdio.write :} HELLO WORLD
Since: 0.1.0
Standalone Processes
Inherits stdin, stdout, and stderr from the parent, so that the user can interact with the process, user interrupts are handled by the child process, the parent waits for the child process to exit.
This is same as the common system
function found in other libraries used
to execute commands.
On Windows you can pass setSession NewConsole
to create a new console.
Arguments
:: (Config -> Config) | |
-> FilePath | Executable name or path |
-> [String] | Arguments |
-> IO ProcessHandle |
Closes stdin, stdout and stderr, creates a new session, detached from the terminal, the parent does not wait for the process to finish.
Deprecated
Arguments
:: (MonadCatch m, MonadAsync m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m Word8 | Input Stream |
-> Stream m Word8 | Output Stream |
Deprecated: Please use pipeBytes instead.
Arguments
:: (MonadCatch m, MonadAsync m) | |
=> FilePath | Executable name or path |
-> [String] | Arguments |
-> Stream m (Array Word8) | Input stream |
-> Stream m (Array Word8) | Output stream |
Deprecated: Please use pipeChunks instead.