Copyright | (c) 2023 Composewell Technologies |
---|---|
License | Apache-2.0 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module provides a way to invoke external executables and use them seamlessly in a Haskell program, in a streaming fashion. This enables you to write high-level Haskell scripts to perform tasks similar to shell scripts without requiring the shell. Moreover, Haskell scripts provide C-like performance.
Please see the Streamly.System.Process for basics. This module is a wrapper over that module. Streamly.System.Process requires specifying a command executable name and its arguments separately (e.g. "ls" "-al") whereas using this module we can specify the executable and its arguments more conveniently as a single command string e.g. we can execute "ls -al".
A command string is parsed in the same way as a posix shell would parse it.
A command string consists of whitespace separated tokens with the first
token treated as the executable name and the rest as arguments. Whitespace
can be escaped using \
. Alternatively, double quotes or single quotes can
be used to enclose tokens with whitespaces. Quotes can be escaped using \
.
Single quotes inside double quotes or vice-versa are treated as normal
characters.
You can use the string quasiquoter str
to write
commands conveniently, it allows Haskell variable expansion as well e.g.:
>>>
f = "file name"
>>>
[str|ls -al "#{f} with spaces"|]
"ls -al \"file name with spaces\""
With the Streamly.System.Command module you can write the examples in the Streamly.System.Process module more conveniently.
Executables as functions
The shell command echo "hello world" | tr [a-z] [A-Z]
can be written as
follows using this module:
>>>
:{
Command.toBytes [str|echo "hello world"|] & Command.pipeBytes [str|tr [a-z] [A-Z]|] & Stream.fold Stdio.write :} HELLO WORLD
Shell commands as functions
We recommend using streamly to compose commands natively in Haskell rather than using the shell as shown in the previous example. However, if for some reason you want to execute commands using the shell:
>>>
:{
Command.toBytes [str|sh "-c" "echo 'hello world' | tr [a-z] [A-Z]"|] & Stream.fold Stdio.write :} HELLO WORLD
Running Commands Concurrently
This example shows the power of composing in Haskell rather than using the
shell. Running grep
concurrently on many files:
>>>
:{
grep file = Command.toBytes [str|grep -H "pattern" #{file}|] & Stream.handle (\(_ :: Command.ProcessFailure) -> Stream.nil) & Stream.foldMany (Fold.takeEndBy (== 10) Array.write) :}
>>>
:{
pgrep = Dir.readFiles "." & Stream.parConcatMap id grep & Stream.fold Stdio.writeChunks :}
Experimental APIs
See Streamly.Internal.System.Command for unreleased APIs.
Synopsis
- newtype ProcessFailure = ProcessFailure Int
- data Config
- setCwd :: Maybe FilePath -> Config -> Config
- setEnv :: Maybe [(String, String)] -> Config -> Config
- closeFiles :: Bool -> Config -> Config
- newProcessGroup :: Bool -> Config -> Config
- data Session
- setSession :: Session -> Config -> Config
- interruptChildOnly :: Bool -> Config -> Config
- setUserId :: Maybe Word32 -> Config -> Config
- setGroupId :: Maybe Word32 -> Config -> Config
- waitForDescendants :: Bool -> Config -> Config
- toBytes :: (MonadAsync m, MonadCatch m) => String -> Stream m Word8
- toChunks :: (MonadAsync m, MonadCatch m) => String -> Stream m (Array Word8)
- toChunksWith :: (MonadCatch m, MonadAsync m) => (Config -> Config) -> String -> Stream m (Array Word8)
- toChars :: (MonadAsync m, MonadCatch m) => String -> Stream m Char
- toLines :: (MonadAsync m, MonadCatch m) => Fold m Char a -> String -> Stream m a
- toString :: (MonadAsync m, MonadCatch m) => String -> m String
- toStdout :: (MonadAsync m, MonadCatch m) => String -> m ()
- toNull :: (MonadAsync m, MonadCatch m) => String -> m ()
- pipeChunks :: (MonadAsync m, MonadCatch m) => String -> Stream m (Array Word8) -> Stream m (Array Word8)
- pipeChunksWith :: (MonadCatch m, MonadAsync m) => (Config -> Config) -> String -> Stream m (Array Word8) -> Stream m (Array Word8)
- pipeBytes :: (MonadAsync m, MonadCatch m) => String -> Stream m Word8 -> Stream m Word8
- pipeChars :: (MonadAsync m, MonadCatch m) => String -> Stream m Char -> Stream m Char
- foreground :: (Config -> Config) -> String -> IO ExitCode
- daemon :: (Config -> Config) -> String -> IO ProcessHandle
- standalone :: Bool -> (Bool, Bool, Bool) -> (Config -> Config) -> String -> IO (Either ExitCode ProcessHandle)
Setup
To execute the code examples provided in this module in ghci, please run the following commands first.
>>>
:set -XFlexibleContexts
>>>
:set -XQuasiQuotes
>>>
import Data.Char (toUpper)
>>>
import Data.Function ((&))
>>>
import Streamly.Unicode.String (str)
>>>
import qualified Streamly.Console.Stdio as Stdio
>>>
import qualified Streamly.Data.Array as Array
>>>
import qualified Streamly.Data.Fold as Fold
>>>
import qualified Streamly.Data.Stream.Prelude as Stream
>>>
import qualified Streamly.System.Command as Command
>>>
import qualified Streamly.Unicode.Stream as Unicode
For APIs that have not been released yet.
>>>
import qualified Streamly.Internal.Console.Stdio as Stdio (putBytes, putChars, putChunks)
>>>
import qualified Streamly.Internal.FileSystem.Dir as Dir (readFiles)
>>>
import qualified Streamly.Internal.System.Process as Process
Exceptions
newtype ProcessFailure Source #
An exception that is raised when a process fails.
Since: 0.1.0
ProcessFailure Int | The exit code of the process. |
Instances
Exception ProcessFailure Source # | |
Defined in Streamly.Internal.System.Process | |
Show ProcessFailure Source # | |
Defined in Streamly.Internal.System.Process showsPrec :: Int -> ProcessFailure -> ShowS # show :: ProcessFailure -> String # showList :: [ProcessFailure] -> ShowS # |
Process Configuration
Use the config modifiers to modify the default config.
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 Modifiers
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.
InheritSession
makes the new process inherit the terminal session from the
parent process. This is the default.
NewSession
makes the new process start with a new session without a
controlling terminal. On POSIX,
setsid
is used to create a new process
group and session, the pid of the new process is the session id and process
group id as well. On Windows DETACHED_PROCESS
flag is used to detach the
process from inherited console session.
NewConsole
creates a new terminal and attaches the process to the new
terminal on Windows, using the CREATE_NEW_CONSOLE flag. On POSIX this does
nothing.
For Windows see
- https://learn.microsoft.com/en-us/windows/win32/procthread/process-creation-flags
- https://learn.microsoft.com/en-us/windows/console/creation-of-a-console .
For POSIX see, setsid man page.
InheritSession | Inherit the parent session |
NewSession | Detach process from the current session |
NewConsole | Windows only, CREATE_NEW_CONSOLE flag |
setSession :: Session -> Config -> Config Source #
Define the terminal session behavior for the new process.
Default is InheritSession
.
Posix Only Modifiers
These options have no effect on Windows.
interruptChildOnly :: 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
.
Windows Only Modifiers
These options have no effect on Posix.
waitForDescendants :: Bool -> Config -> Config Source #
On Windows, the parent waits for the entire descendant tree of process i.e. including processes that are spawned by the child process.
Default is True
.
Generation
toBytes :: (MonadAsync m, MonadCatch m) => String -> Stream m Word8 Source #
>>>
toBytes "echo hello world" & Stdio.putBytes
hello world>>>
toBytes "echo hello\\ world" & Stdio.putBytes
hello world>>>
toBytes "echo 'hello world'" & Stdio.putBytes
hello world>>>
toBytes "echo \"hello world\"" & Stdio.putBytes
hello world
Pre-release
toChunks :: (MonadAsync m, MonadCatch m) => String -> Stream m (Array Word8) Source #
>>>
toChunks "echo hello world" & Stdio.putChunks
hello world
Pre-release
:: (MonadCatch m, MonadAsync m) | |
=> (Config -> Config) | Config modifier |
-> String | Command |
-> Stream m (Array Word8) | Output stream |
Like toChunks
but use the specified configuration to run the process.
toChars :: (MonadAsync m, MonadCatch m) => String -> Stream m Char Source #
>>>
toChars "echo hello world" & Stdio.putChars
hello world
Pre-release
:: (MonadAsync m, MonadCatch m) | |
=> Fold m Char a | |
-> String | Command |
-> Stream m a | Output Stream |
>>>
toLines Fold.toList "echo -e hello\\\\nworld" & Stream.fold Fold.toList
["hello","world"]
Pre-release
Effects
:: (MonadAsync m, MonadCatch m) | |
=> String | Command |
-> m String |
>>>
toString "echo hello world"
"hello world\n"
Pre-release
:: (MonadAsync m, MonadCatch m) | |
=> String | Command |
-> m () |
>>>
toStdout "echo hello world"
hello world
Pre-release
:: (MonadAsync m, MonadCatch m) | |
=> String | Command |
-> m () |
>>>
toNull "echo hello world"
Pre-release
Transformation
pipeChunks :: (MonadAsync m, MonadCatch m) => String -> Stream m (Array Word8) -> Stream m (Array Word8) Source #
pipeChunks command input
runs the executable with arguments specified by
command
and supplying input
stream as its standard input. Returns the
standard output of the executable as a stream of byte arrays.
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]
:
>>>
:{
toChunks "echo hello world" & pipeChunks "tr [a-z] [A-Z]" & Stdio.putChunks :} HELLO WORLD
Pre-release
:: (MonadCatch m, MonadAsync m) | |
=> (Config -> Config) | Config modifier |
-> String | Command |
-> Stream m (Array Word8) | Input stream |
-> Stream m (Array Word8) | Output stream |
Like pipeChunks
but use the specified configuration to run the process.
pipeBytes :: (MonadAsync m, MonadCatch m) => String -> Stream m Word8 -> Stream m Word8 Source #
Like pipeChunks
except that it works on a stream of bytes instead of
a stream of chunks.
>>>
:{
toBytes "echo hello world" & pipeBytes "tr [a-z] [A-Z]" & Stdio.putBytes :} HELLO WORLD
Pre-release
pipeChars :: (MonadAsync m, MonadCatch m) => String -> Stream m Char -> Stream m Char Source #
Like pipeChunks
except that it works on a stream of chars instead of
a stream of chunks.
>>>
:{
toChars "echo hello world" & pipeChars "tr [a-z] [A-Z]" & Stdio.putChars :} HELLO WORLD
Pre-release
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.
, toBytesEither
, toChunksEither
, toChunksEitherWith
, pipeBytesEither
, pipeChunksEither
, pipeChunksEitherWith
Non-streaming Processes
These processes do not attach the IO streams with other processes.
Launch a process interfacing with the user. User interrupts are sent to
the launched process and ignored by the parent process. The launched process
inherits stdin, stdout, and stderr from the parent, so that the user can
interact with the process. The parent waits for the child process to exit,
an ExitCode
is returned when the process finishes.
This is the 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.
:: (Config -> Config) | |
-> String | Command |
-> IO ProcessHandle |
Launch a daemon process. Closes stdin, stdout and stderr, creates a new session, detached from the terminal, the parent does not wait for the process to finish.
The ProcessHandle
returned can be used to terminate the daemon or send
signals to it.
:: Bool | Wait for process to finish? |
-> (Bool, Bool, Bool) | close (stdin, stdout, stderr) |
-> (Config -> Config) | |
-> String | Command |
-> IO (Either ExitCode ProcessHandle) |
Launch a standlone process i.e. the process does not have a way to attach the IO streams with other processes. The IO streams stdin, stdout, stderr can either be inherited from the parent or closed.
This API is more powerful than interactive
and daemon
and can be used to
implement both of these. However, it should be used carefully e.g. if you
inherit the IO streams and parent is not waiting for the child process to
finish then both parent and child may use the IO streams resulting in
garbled IO if both are reading/writing simultaneously.
If the parent chooses to wait for the process an ExitCode
is returned
otherwise a ProcessHandle
is returned which can be used to terminate the
process, send signals to it or wait for it to finish.