Copyright | (c) 2022 Composewell Technologies |
---|---|
License | Apache-2.0 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- 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 ()
- pipeBytes :: (MonadAsync m, MonadCatch m) => String -> Stream m Word8 -> Stream m Word8
- pipeChars :: (MonadAsync m, MonadCatch m) => String -> Stream m Char -> Stream m Char
- 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)
- standalone :: Bool -> (Bool, Bool, Bool) -> (Config -> Config) -> String -> IO (Either ExitCode ProcessHandle)
- foreground :: (Config -> Config) -> String -> IO ExitCode
- daemon :: (Config -> Config) -> String -> IO ProcessHandle
- quotedWord :: MonadCatch m => Parser Char m String
- runWith :: MonadCatch m => (FilePath -> [String] -> m a) -> String -> m a
- streamWith :: MonadCatch m => (FilePath -> [String] -> Stream m a) -> String -> Stream m a
- pipeWith :: MonadCatch m => (FilePath -> [String] -> Stream m a -> Stream m b) -> String -> Stream m a -> Stream m b
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
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
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.
Standalone Processes
:: 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.
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.
Helpers
quotedWord :: MonadCatch m => Parser Char m String Source #
runWith :: MonadCatch m => (FilePath -> [String] -> m a) -> String -> m a Source #
A modifier for process running APIs in Streamly.System.Process to run command strings.
For example:
>>>
runWith Process.toString "echo hello"
"hello\n">>>
runWith Process.toStdout "echo hello"
hello
Internal
streamWith :: MonadCatch m => (FilePath -> [String] -> Stream m a) -> String -> Stream m a Source #
A modifier for stream generation APIs in Streamly.System.Process to generate streams from command strings.
For example:
>>>
streamWith Process.toBytes "echo hello" & Stdio.putBytes
hello>>>
streamWith Process.toChunks "echo hello" & Stdio.putChunks
hello
Internal
pipeWith :: MonadCatch m => (FilePath -> [String] -> Stream m a -> Stream m b) -> String -> Stream m a -> Stream m b Source #
A modifier for process piping APIs in Streamly.System.Process to pipe data through processes specified by command strings.
For example:
>>>
:{
toChunks "echo hello" & pipeWith Process.pipeChunks "tr [a-z] [A-Z]" & Stdio.putChunks :} HELLO
Internal