| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
System.Process.Typed.Internal
Description
This module is internal and its contents may change without a warning or announcement. It is not subject to the PVP.
Synopsis
- data ProcessConfig stdin stdout stderr = ProcessConfig {
- pcCmdSpec :: !CmdSpec
- pcStdin :: !(StreamSpec 'STInput stdin)
- pcStdout :: !(StreamSpec 'STOutput stdout)
- pcStderr :: !(StreamSpec 'STOutput stderr)
- pcWorkingDir :: !(Maybe FilePath)
- pcEnv :: !(Maybe [(String, String)])
- pcCloseFds :: !Bool
- pcCreateGroup :: !Bool
- pcDelegateCtlc :: !Bool
- pcDetachConsole :: !Bool
- pcCreateNewConsole :: !Bool
- pcNewSession :: !Bool
- pcChildGroup :: !(Maybe GroupID)
- pcChildUser :: !(Maybe UserID)
- data StreamType
- data StreamSpec (streamType :: StreamType) a = StreamSpec {}
- newtype Cleanup a = Cleanup {
- runCleanup :: IO (a, IO ())
- defaultProcessConfig :: ProcessConfig () () ()
- proc :: FilePath -> [String] -> ProcessConfig () () ()
- setProc :: FilePath -> [String] -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- shell :: String -> ProcessConfig () () ()
- setShell :: String -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setStdin :: StreamSpec 'STInput stdin -> ProcessConfig stdin0 stdout stderr -> ProcessConfig stdin stdout stderr
- setStdout :: StreamSpec 'STOutput stdout -> ProcessConfig stdin stdout0 stderr -> ProcessConfig stdin stdout stderr
- setStderr :: StreamSpec 'STOutput stderr -> ProcessConfig stdin stdout stderr0 -> ProcessConfig stdin stdout stderr
- setWorkingDir :: FilePath -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setWorkingDirInherit :: ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setEnv :: [(String, String)] -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setEnvInherit :: ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setCloseFds :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setCreateGroup :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setDelegateCtlc :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setDetachConsole :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setCreateNewConsole :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setNewSession :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setChildGroup :: GroupID -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setChildGroupInherit :: ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setChildUser :: UserID -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setChildUserInherit :: ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- mkStreamSpec :: StdStream -> (ProcessConfig () () () -> Maybe Handle -> IO (a, IO ())) -> StreamSpec streamType a
- mkPipeStreamSpec :: (ProcessConfig () () () -> Handle -> IO (a, IO ())) -> StreamSpec streamType a
- mkManagedStreamSpec :: (forall b. (StdStream -> IO b) -> IO b) -> (ProcessConfig () () () -> Maybe Handle -> IO (a, IO ())) -> StreamSpec streamType a
- inherit :: StreamSpec anyStreamType ()
- nullStream :: StreamSpec anyStreamType ()
- closed :: StreamSpec anyStreamType ()
- byteStringInput :: ByteString -> StreamSpec 'STInput ()
- byteStringOutput :: StreamSpec 'STOutput (STM ByteString)
- byteStringFromHandle :: ProcessConfig () () () -> Handle -> IO (STM ByteString, IO ())
- createPipe :: StreamSpec anyStreamType Handle
- useHandleOpen :: Handle -> StreamSpec anyStreamType ()
- useHandleClose :: Handle -> StreamSpec anyStreamType ()
- data ExitCodeException = ExitCodeException {
- eceExitCode :: ExitCode
- eceProcessConfig :: ProcessConfig () () ()
- eceStdout :: ByteString
- eceStderr :: ByteString
- data ByteStringOutputException = ByteStringOutputException SomeException (ProcessConfig () () ())
- bracket :: MonadUnliftIO m => IO a -> (a -> IO b) -> (a -> m c) -> m c
- finally :: MonadUnliftIO m => m a -> IO () -> m a
- nullDevice :: FilePath
Documentation
data ProcessConfig stdin stdout stderr Source #
An abstract configuration for a process, which can then be
launched into an actual running Process. Takes three type
parameters, providing the types of standard input, standard output,
and standard error, respectively.
There are three ways to construct a value of this type:
- With the
procsmart constructor, which takes a command name and a list of arguments. - With the
shellsmart constructor, which takes a shell string - With the
IsStringinstance via OverloadedStrings. If you provide it a string with no spaces (e.g.,"date"), it will treat it as a raw command with no arguments (e.g.,proc "date" []). If it has spaces, it will useshell.
In all cases, the default for all three streams is to inherit the streams from the parent process. For other settings, see the setters below for default values.
Once you have a ProcessConfig you can launch a process from it
using the functions in the section Launch a
process.
Since: 0.1.0.0
Constructors
| ProcessConfig | |
Fields
| |
Instances
| (stdin ~ (), stdout ~ (), stderr ~ ()) => IsString (ProcessConfig stdin stdout stderr) Source # | |
Defined in System.Process.Typed.Internal Methods fromString :: String -> ProcessConfig stdin stdout stderr # | |
| Show (ProcessConfig stdin stdout stderr) Source # | |
Defined in System.Process.Typed.Internal Methods showsPrec :: Int -> ProcessConfig stdin stdout stderr -> ShowS # show :: ProcessConfig stdin stdout stderr -> String # showList :: [ProcessConfig stdin stdout stderr] -> ShowS # | |
data StreamType Source #
Whether a stream is an input stream or output stream. Note that
this is from the perspective of the child process, so that a
child's standard input stream is an STInput, even though the
parent process will be writing to it.
Since: 0.1.0.0
data StreamSpec (streamType :: StreamType) a Source #
A specification for how to create one of the three standard child
streams, stdin, stdout and stderr. A StreamSpec can be
thought of as containing
- A type safe version of
StdStreamfrom System.Process. This determines whether the stream should be inherited from the parent process, piped to or from aHandle, etc. - A means of accessing the stream as a value of type
a - A cleanup action which will be run on the stream once the process terminates
To create a StreamSpec see the section Stream
specs.
Since: 0.1.0.0
Constructors
| StreamSpec | |
Instances
| Functor (StreamSpec streamType) Source # | |
Defined in System.Process.Typed.Internal Methods fmap :: (a -> b) -> StreamSpec streamType a -> StreamSpec streamType b # (<$) :: a -> StreamSpec streamType b -> StreamSpec streamType a # | |
| (streamType ~ 'STInput, res ~ ()) => IsString (StreamSpec streamType res) Source # | This instance uses Since: 0.1.0.0 |
Defined in System.Process.Typed.Internal Methods fromString :: String -> StreamSpec streamType res # | |
Internal type, to make for easier composition of cleanup actions.
Since: 0.1.0.0
Constructors
| Cleanup | |
Fields
| |
defaultProcessConfig :: ProcessConfig () () () Source #
Internal helper
proc :: FilePath -> [String] -> ProcessConfig () () () Source #
Create a ProcessConfig from the given command and arguments.
Since: 0.1.0.0
setProc :: FilePath -> [String] -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr Source #
Internal helper
shell :: String -> ProcessConfig () () () Source #
Create a ProcessConfig from the given shell command.
Since: 0.1.0.0
setShell :: String -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr Source #
Internal helper
Arguments
| :: StreamSpec 'STInput stdin | |
| -> ProcessConfig stdin0 stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Arguments
| :: StreamSpec 'STOutput stdout | |
| -> ProcessConfig stdin stdout0 stderr | |
| -> ProcessConfig stdin stdout stderr |
Arguments
| :: StreamSpec 'STOutput stderr | |
| -> ProcessConfig stdin stdout stderr0 | |
| -> ProcessConfig stdin stdout stderr |
Arguments
| :: FilePath | |
| -> ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Set the working directory of the child process.
Default: current process's working directory.
Since: 0.1.0.0
Arguments
| :: ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Inherit the working directory from the parent process.
Since: 0.2.2.0
Arguments
| :: [(String, String)] | |
| -> ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Set the environment variables of the child process.
Default: current process's environment.
Since: 0.1.0.0
Arguments
| :: ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Inherit the environment variables from the parent process.
Since: 0.2.2.0
Arguments
| :: Bool | |
| -> ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Should we close all file descriptors besides stdin, stdout, and
stderr? See close_fds for more information.
Default: False
Since: 0.1.0.0
Arguments
| :: Bool | |
| -> ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Should we create a new process group?
Default: False
Since: 0.1.0.0
Arguments
| :: Bool | |
| -> ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Delegate handling of Ctrl-C to the child. For more information,
see delegate_ctlc.
Default: False
Since: 0.1.0.0
Arguments
| :: Bool | |
| -> ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Arguments
| :: Bool | |
| -> ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Arguments
| :: Bool | |
| -> ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Set a new session with the POSIX setsid syscall, does nothing
on non-POSIX. See new_session.
Default: False
Since: 0.1.0.0
Arguments
| :: GroupID | |
| -> ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Set the child process's group ID with the POSIX setgid syscall,
does nothing on non-POSIX. See child_group.
Default: False
Since: 0.1.0.0
Arguments
| :: ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Inherit the group from the parent process.
Since: 0.2.2.0
Arguments
| :: UserID | |
| -> ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Set the child process's user ID with the POSIX setuid syscall,
does nothing on non-POSIX. See child_user.
Default: False
Since: 0.1.0.0
Arguments
| :: ProcessConfig stdin stdout stderr | |
| -> ProcessConfig stdin stdout stderr |
Inherit the user from the parent process.
Since: 0.2.2.0
Arguments
| :: StdStream | |
| -> (ProcessConfig () () () -> Maybe Handle -> IO (a, IO ())) | |
| -> StreamSpec streamType a |
Create a new StreamSpec from the given StdStream and a
helper function. This function:
- Takes as input the raw
Maybe Handlereturned by thecreateProcessfunction. The handle will beJustHandleif theStdStreamargument isCreatePipeandNothingotherwise. SeecreateProcessfor more details. - Returns the actual stream value
a, as well as a cleanup function to be run when callingstopProcess.
If making a StreamSpec with CreatePipe, prefer mkPipeStreamSpec,
which encodes the invariant that a Handle is created.
Since: 0.1.0.0
Arguments
| :: (ProcessConfig () () () -> Handle -> IO (a, IO ())) | |
| -> StreamSpec streamType a |
Create a new CreatePipe StreamSpec from the given function.
This function:
- Takes as input the
Handlereturned by thecreateProcessfunction. SeecreateProcessfor more details. - Returns the actual stream value
a, as well as a cleanup function to be run when callingstopProcess.
Since: 0.2.10.0
Arguments
| :: (forall b. (StdStream -> IO b) -> IO b) | |
| -> (ProcessConfig () () () -> Maybe Handle -> IO (a, IO ())) | |
| -> StreamSpec streamType a |
Create a new StreamSpec from a function that accepts a
StdStream and a helper function. This function is the same as
the helper in mkStreamSpec
inherit :: StreamSpec anyStreamType () Source #
A stream spec which simply inherits the stream of the parent process.
Since: 0.1.0.0
nullStream :: StreamSpec anyStreamType () Source #
A stream spec which is empty when used for for input and discards output. Note this requires your platform's null device to be available when the process is started.
Since: 0.2.5.0
closed :: StreamSpec anyStreamType () Source #
A stream spec which will close the stream for the child process.
You usually do not want to use this, as it will leave the
corresponding file descriptor unassigned and hence available for
re-use in the child process. Prefer nullStream unless you're
certain you want this behavior.
Since: 0.1.0.0
byteStringInput :: ByteString -> StreamSpec 'STInput () Source #
An input stream spec which sets the input to the given
ByteString. A separate thread will be forked to write the
contents to the child process.
Since: 0.1.0.0
byteStringOutput :: StreamSpec 'STOutput (STM ByteString) Source #
Capture the output of a process in a ByteString.
This function will fork a separate thread to consume all input from
the process, and will only make the results available when the
underlying Handle is closed. As this is provided as an STM
action, you can either check if the result is available, or block
until it's ready.
In the event of any exception occurring when reading from the
Handle, the STM action will throw a
ByteStringOutputException.
Since: 0.1.0.0
Arguments
| :: ProcessConfig () () () | |
| -> Handle | reader handle |
| -> IO (STM ByteString, IO ()) |
Helper function (not exposed) for both byteStringOutput and
withProcessInterleave. This will consume all of the output from
the given Handle in a separate thread and provide access to the
resulting ByteString via STM. Second action will close the
reader handle.
createPipe :: StreamSpec anyStreamType Handle Source #
Create a new pipe between this process and the child, and return
a Handle to communicate with the child.
Since: 0.1.0.0
useHandleOpen :: Handle -> StreamSpec anyStreamType () Source #
Use the provided Handle for the child process, and when the
process exits, do not close it. This is useful if, for example,
you want to have multiple processes write to the same log file
sequentially.
Since: 0.1.0.0
useHandleClose :: Handle -> StreamSpec anyStreamType () Source #
Use the provided Handle for the child process, and when the
process exits, close it. If you have no reason to keep the Handle
open, you should use this over useHandleOpen.
Since: 0.1.0.0
data ExitCodeException Source #
Exception thrown by checkExitCode in the event of a non-success
exit code. Note that checkExitCode is called by other functions
as well, like runProcess_ or readProcess_.
Note that several functions that throw an ExitCodeException intentionally do not populate eceStdout or eceStderr.
This prevents unbounded memory usage for large stdout and stderrs.
Since: 0.1.0.0
Constructors
| ExitCodeException | |
Fields
| |
Instances
| Exception ExitCodeException Source # | |
Defined in System.Process.Typed.Internal Methods toException :: ExitCodeException -> SomeException # | |
| Show ExitCodeException Source # | |
Defined in System.Process.Typed.Internal Methods showsPrec :: Int -> ExitCodeException -> ShowS # show :: ExitCodeException -> String # showList :: [ExitCodeException] -> ShowS # | |
data ByteStringOutputException Source #
Wrapper for when an exception is thrown when reading from a child
process, used by byteStringOutput.
Since: 0.1.0.0
Constructors
| ByteStringOutputException SomeException (ProcessConfig () () ()) |
Instances
| Exception ByteStringOutputException Source # | |
Defined in System.Process.Typed.Internal | |
| Show ByteStringOutputException Source # | |
Defined in System.Process.Typed.Internal Methods showsPrec :: Int -> ByteStringOutputException -> ShowS # show :: ByteStringOutputException -> String # showList :: [ByteStringOutputException] -> ShowS # | |
finally :: MonadUnliftIO m => m a -> IO () -> m a Source #
nullDevice :: FilePath Source #
The name of the system null device