| Copyright | (C) XT et al. 2017 - 2024 | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | e@xtendo.org | 
| Stability | stable | 
| Portability | POSIX | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
RawFilePath.Process
Description
Welcome to RawFilePath.Process, a small part of the Haskell community's
 effort to replace String for the Greater Good.
With this module, you can create (and interact with) sub-processes without
 the encoding problem of String. The command and its arguments, all
 ByteStrings, never get converted from/to String internally on its way
 to the actual syscall. It also avoids the time/space waste of String.
The interface, unlike the original process package, uses types to prevent
 unnecessary runtime errors when obtaining Handles. This is
 inspired by the typed-process package which is awesome, although this
 module is much simpler; it doesn't introduce any new requirement of language
 extension or library package (for the sake of portability).
Handle (accessible with processStdin, processStdout, and
 processStderr) is what you can use to interact with the sub-process. For
 example, use hGetContents from Data.ByteString to read
 from a Handle as a ByteString.
Fast and brief example
If you have experience with Unix pipes, this example should be pretty straightforward. In fact it is so simple that you don't need any type theory or PL knowledge. It demonstrates how you can create a child process and interact with it.
{-# language OverloadedStrings #-}
import RawFilePath.Process
import System.IO
import qualified Data.ByteString as B
main :: IO ()
main = do
  p <- startProcess $ proc "sed" ["-e", "s/\\>/!/g"]
    `setStdin` CreatePipe
    `setStdout` CreatePipe
  B.hPut (processStdin p) "Lorem ipsum dolor sit amet"
  hClose (processStdin p)
  result <- B.hGetContents (processStdout p)
  print result
  -- "Lorem! ipsum! dolor! sit! amet!"
That's it! You can totally skip the verbose explanation below.
Verbose explanation of the example
We launch sed as a child process. As we know, it is a regular expression
 search and replacement tool. In the example, sed is a simple Unix pipe
 utility: Take some text from stdin and output the processed text to
 stdout.
In sed regex, \> means "the end of the word." So, "s/\\>/!/g"
 means "substitute all ends of the words with an exclamation mark." Then, we
 feed some text to its stdin, close stdin (to send EOF to sed's
 stdin), and read what it wrote to stdout.
The interesting part is proc. It is a simple function that takes a
 command and its arguments and returns a ProcessConf which defines the
 properties of the child process you want to create. You can use
 functions like setStdin or setStdout to change those properties.
The advantage of this interface is type safety. Take stdout for example.
 There are four options: Inherit, UseHandle, CreatePipe, and
 NoStream. If you want to read stdout of the child process, you must set
 it to CreatePipe. With the process package, this is done by giving a
 proper argument to createProcess. The trouble is, regardless of the
 argument, createProcess returns Maybe Handle as stdout.
 You may or may not get a Handle.
This is not what we want with Haskell. We want to ensure that
- We use CreatePipeand certainly get thestdoutHandle(without having to write unncessary handling for theNothingcase that never happens).
- If we don't use CreatePipebut still request thestdoutHandle, it is an error, detected compile-time.
So that's what RawFilePath.Process does. In the above example, we use
 functions like setStdout. Later, you use the processStdout family of
 functions to get the process's standard stream handles. This requires that
 the process was created with CreatePipe appropriately set for that
 stream.
It sounds all complicated, but all you really need to do is as simple as:
startProcess$proc"..." [...] `setStdout`CreatePipe
... If you want to create a new pipe for the child process's stdin. Then
 you can later use processStdout to get the Handle. If you
 don't put the `setStdout` CreatePipe part or set it to something other
 than CreatePipe, it will be a compile-time error to use processStdout on
 this process object.
In short, it makes the correct code easy and the wrong code impossible.
 This approach was inspired by the typed-process package. Then why not
 just typed-process? rawfilepath offers
- RawFilePath!
- A lot less dependency (only three packages)
- A lot more portability (doesn't require any language extension).
Enjoy.
Synopsis
- type RawFilePath = ByteString
- data ProcessConf stdin stdout stderr
- proc :: RawFilePath -> [ByteString] -> ProcessConf Inherit Inherit Inherit
- class StreamType c
- data CreatePipe = CreatePipe
- data Inherit = Inherit
- data NoStream = NoStream
- data UseHandle = UseHandle Handle
- setStdin :: StreamType newStdin => ProcessConf oldStdin stdout stderr -> newStdin -> ProcessConf newStdin stdout stderr
- setStdout :: StreamType newStdout => ProcessConf stdin oldStdout stderr -> newStdout -> ProcessConf stdin newStdout stderr
- setStderr :: StreamType newStderr => ProcessConf stdin stdout oldStderr -> newStderr -> ProcessConf stdin stdout newStderr
- data Process stdin stdout stderr
- startProcess :: (StreamType stdin, StreamType stdout, StreamType stderr) => ProcessConf stdin stdout stderr -> IO (Process stdin stdout stderr)
- processStdin :: Process CreatePipe stdout stderr -> Handle
- processStdout :: Process stdin CreatePipe stderr -> Handle
- processStderr :: Process stdin stdout CreatePipe -> Handle
- stopProcess :: Process stdin stdout stderr -> IO ExitCode
- terminateProcess :: Process stdin stdout stderr -> IO ()
- waitForProcess :: Process stdin stdout stderr -> IO ExitCode
- data UnknownStream
- untypeProcess :: Process stdin stdout stderr -> Process UnknownStream UnknownStream UnknownStream
- untypeProcessStdin :: Process stdin stdout stderr -> Process UnknownStream stdout stderr
- untypeProcessStdout :: Process stdin stdout stderr -> Process stdin UnknownStream stderr
- untypeProcessStderr :: Process stdin stdout stderr -> Process stdin stdout UnknownStream
- processStdinUnknown :: Process UnknownStream stdout stderr -> Maybe Handle
- processStdoutUnknown :: Process stdin UnknownStream stderr -> Maybe Handle
- processStderrUnknown :: Process stdin stdout UnknownStream -> Maybe Handle
- callProcess :: ProcessConf stdin stdout stderr -> IO ExitCode
- readProcessWithExitCode :: ProcessConf stdin stdout stderr -> IO (ExitCode, ByteString, ByteString)
Documentation
type RawFilePath = ByteString #
A literal POSIX file path
Configuring process
Configuration of how a new sub-process will be launched.
data ProcessConf stdin stdout stderr Source #
The process configuration that is needed for creating new processes. Use
 proc to make one.
Arguments
| :: RawFilePath | Command to run | 
| -> [ByteString] | Arguments to the command | 
| -> ProcessConf Inherit Inherit Inherit | 
Create a process configuration with the default settings.
Configuring process standard streams
class StreamType c Source #
The class of types that determine the standard stream of a sub-process. You can decide how to initialize the standard streams (stdin, stdout, and stderr) of a sub-process with the instances of this class.
Instances
| StreamType CreatePipe Source # | |
| Defined in RawFilePath.Process.Common | |
| StreamType Inherit Source # | |
| Defined in RawFilePath.Process.Common | |
| StreamType NoStream Source # | |
| Defined in RawFilePath.Process.Common | |
| StreamType UseHandle Source # | |
| Defined in RawFilePath.Process.Common | |
data CreatePipe Source #
Create a new pipe for the stream. You get a new Handle.
Constructors
| CreatePipe | 
Instances
| Show CreatePipe Source # | |
| Defined in RawFilePath.Process.Common Methods showsPrec :: Int -> CreatePipe -> ShowS # show :: CreatePipe -> String # showList :: [CreatePipe] -> ShowS # | |
| StreamType CreatePipe Source # | |
| Defined in RawFilePath.Process.Common | |
Inherit the parent (current) process handle. The child will share the stream. For example, if the child writes anything to stdout, it will all go to the parent's stdout.
Constructors
| Inherit | 
Instances
| Show Inherit Source # | |
| StreamType Inherit Source # | |
| Defined in RawFilePath.Process.Common | |
No stream handle will be passed. Use when you don't want to communicate with a stream. For example, to run something silently.
Constructors
| NoStream | 
Instances
| Show NoStream Source # | |
| StreamType NoStream Source # | |
| Defined in RawFilePath.Process.Common | |
Use the supplied Handle.
Instances
| Show UseHandle Source # | |
| StreamType UseHandle Source # | |
| Defined in RawFilePath.Process.Common | |
setStdin :: StreamType newStdin => ProcessConf oldStdin stdout stderr -> newStdin -> ProcessConf newStdin stdout stderr infixl 4 Source #
Control how the standard input of the process will be initialized.
setStdout :: StreamType newStdout => ProcessConf stdin oldStdout stderr -> newStdout -> ProcessConf stdin newStdout stderr infixl 4 Source #
Control how the standard output of the process will be initialized.
setStderr :: StreamType newStderr => ProcessConf stdin stdout oldStderr -> newStderr -> ProcessConf stdin stdout newStderr infixl 4 Source #
Control how the standard error of the process will be initialized.
Running process
data Process stdin stdout stderr Source #
The process type. The three type variables denote how its standard streams were initialized.
startProcess :: (StreamType stdin, StreamType stdout, StreamType stderr) => ProcessConf stdin stdout stderr -> IO (Process stdin stdout stderr) Source #
Start a new sub-process with the given configuration.
Obtaining process streams
As the type signature suggests, these functions only work on processes whose
 stream in configured to CreatePipe. This is the type-safe way of obtaining
 Handles instead of returning Maybe Handles like
 the process package does.
processStdin :: Process CreatePipe stdout stderr -> Handle Source #
Take a process and return its standard input handle.
processStdout :: Process stdin CreatePipe stderr -> Handle Source #
Take a process and return its standard output handle.
processStderr :: Process stdin stdout CreatePipe -> Handle Source #
Take a process and return its standard error handle.
Process completion
stopProcess :: Process stdin stdout stderr -> IO ExitCode Source #
Stop a sub-process. For now it simply calls terminateProcess and then
 waitForProcess.
terminateProcess :: Process stdin stdout stderr -> IO () Source #
Terminate a sub-process by sending SIGTERM to it.
waitForProcess :: Process stdin stdout stderr -> IO ExitCode Source #
Wait (block) for a sub-process to exit and obtain its exit code.
Untyped process
Type safety is awesome, and having types like Process NoStream
 CreatePipe Inherit is the whole point of this module.
However, after we've dealt with many sub-processes and their stream
 Handles, we may have
- Process- Inherit- CreatePipe- Inherit
- Process- CreatePipe- Inherit- Inherit
- Process- CreatePipe- CreatePipe- CreatePipe
- Process- NoStream- Inherit- Inherit
- Process- NoStream- CreatePipe- Inherit
- Process- Inherit- CreatePipe- CreatePipe
- ...
You get the point. It gets out of hand! There are \( 4^3 = 64 \) combinations and they are all "different process types." You can't put them in a same basket. There are realistic reasons you'd want this:
- To keep track of many sub-processes you create, and later properly clean them up.
- To have a group of partially typed sub-processes: For example, if you
    have one Process NoStreamand oneCreatePipeInheritProcess CreatePipe, both are guaranteed to have stdout. You'd want to put them into a list, and later loop over them to collect the stdoutCreatePipeCreatePipeHandles.
(Maybe you can use extensions like ExistentialQuantification for this
 but... It's like you're trying to safeguard your house by installing iron
 walls in front of the gate, then bringing in a tunnel boring machine to
 construct an underground passage. Also, we advertised rawfilepath with
 "minimal dependencies" and "high portability.")
This is why rawfilepath now provides UnknownStream and its related
 functions. So,
ProcessUnknownStreamUnknownStreamUnknownStream
... is much like the traditional, un-typed process. You can get a Maybe
 Handle for an UnknownStream. This is useful when you
- ... Are done with any standard stream I/O
- ... No longer need the compile-time guarantee of getting (or being
      prevented to get) Handles.
- ... But still need the Process
Since: 1.1.1
data UnknownStream Source #
Represents a stream whose creation information is unknown; We don't have
 any type system guarantee of the Handle's existence.
Since: 1.1.1
Functions to untype process streams
untypeProcess :: Process stdin stdout stderr -> Process UnknownStream UnknownStream UnknownStream Source #
untypeProcessStdin :: Process stdin stdout stderr -> Process UnknownStream stdout stderr Source #
Deliberately "un-type" the standard input stream (stdin) type parameter of
 a process. After this, use processStdinUnknown to access Maybe
 Handle.
Since: 1.1.1
untypeProcessStdout :: Process stdin stdout stderr -> Process stdin UnknownStream stderr Source #
Deliberately "un-type" the standard output stream (stdout) type parameter of
 a process. After this, use processStdinUnknown to access Maybe
 Handle.
Since: 1.1.1
untypeProcessStderr :: Process stdin stdout stderr -> Process stdin stdout UnknownStream Source #
Deliberately "un-type" the standard error stream (stderr) type parameter
 of a process. After this, use processStdinUnknown to access Maybe
 Handle.
Since: 1.1.1
Functions to obtain Maybe Handle from UnknownStream
processStdinUnknown :: Process UnknownStream stdout stderr -> Maybe Handle Source #
processStdoutUnknown :: Process stdin UnknownStream stderr -> Maybe Handle Source #
processStderrUnknown :: Process stdin stdout UnknownStream -> Maybe Handle Source #
Utility functions
These are utility functions; they can be implemented with the primary functions above. They are provided for convenience.
callProcess :: ProcessConf stdin stdout stderr -> IO ExitCode Source #
Create a new process with the given configuration, and wait for it to
 finish. Note that this will set all streams to NoStream, so the process
 will be completely silent. If you need the output data from the process, use
 readProcessWithExitCode instead.
readProcessWithExitCode :: ProcessConf stdin stdout stderr -> IO (ExitCode, ByteString, ByteString) Source #
Fork an external process, read its standard output and standard error strictly, blocking until the process terminates, and return them with the process exit code.