Copyright | (c) 2022 Dominik Peteler |
---|---|
License | BSD-3-Clause |
Stability | stable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module provides effectful bindings for typed-process.
Synopsis
- type TypedProcess = Process
- runTypedProcess :: IOE :> es => Eff (TypedProcess : es) a -> Eff es a
- startProcess :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> Eff es (Process stdin stdout stderr)
- stopProcess :: TypedProcess :> es => Process stdin stdout stderr -> Eff es ()
- withProcessWait :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> Eff es a) -> Eff es a
- withProcessWait_ :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> Eff es a) -> Eff es a
- withProcessTerm :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> Eff es a) -> Eff es a
- withProcessTerm_ :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> Eff es a) -> Eff es a
- readProcess :: TypedProcess :> es => ProcessConfig stdin stdoutIgnored stderrIgnored -> Eff es (ExitCode, ByteString, ByteString)
- readProcess_ :: TypedProcess :> es => ProcessConfig stdin stdoutIgnored stderrIgnored -> Eff es (ByteString, ByteString)
- runProcess :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> Eff es ExitCode
- runProcess_ :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> Eff es ()
- readProcessStdout :: TypedProcess :> es => ProcessConfig stdin stdoutIgnored stderr -> Eff es (ExitCode, ByteString)
- readProcessStdout_ :: TypedProcess :> es => ProcessConfig stdin stdoutIgnored stderr -> Eff es ByteString
- readProcessStderr :: TypedProcess :> es => ProcessConfig stdin stdout stderrIgnored -> Eff es (ExitCode, ByteString)
- readProcessStderr_ :: TypedProcess :> es => ProcessConfig stdin stdout stderrIgnored -> Eff es ByteString
- readProcessInterleaved :: TypedProcess :> es => ProcessConfig stdin stdoutIgnored stderrIgnored -> Eff es (ExitCode, ByteString)
- readProcessInterleaved_ :: TypedProcess :> es => ProcessConfig stdin stdoutIgnored stderrIgnored -> Eff es ByteString
- waitExitCode :: TypedProcess :> es => Process stdin stdout stderr -> Eff es ExitCode
- getExitCode :: TypedProcess :> es => Process stdin stdout stderr -> Eff es (Maybe ExitCode)
- checkExitCode :: TypedProcess :> es => Process stdin stdout stderr -> Eff es ()
- data ExitCode
- data StdStream
- data Process stdin stdout stderr
- data ByteStringOutputException = ByteStringOutputException SomeException (ProcessConfig () () ())
- data ExitCodeException = ExitCodeException {
- eceExitCode :: ExitCode
- eceProcessConfig :: ProcessConfig () () ()
- eceStdout :: ByteString
- eceStderr :: ByteString
- data StreamSpec (streamType :: StreamType) a
- data StreamType
- data ProcessConfig stdin stdout stderr
- setEnv :: [(String, String)] -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- proc :: FilePath -> [String] -> ProcessConfig () () ()
- shell :: String -> ProcessConfig () () ()
- createPipe :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType Handle
- 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
- 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 :: forall a (streamType :: StreamType). StdStream -> (ProcessConfig () () () -> Maybe Handle -> IO (a, IO ())) -> StreamSpec streamType a
- mkPipeStreamSpec :: forall a (streamType :: StreamType). (ProcessConfig () () () -> Handle -> IO (a, IO ())) -> StreamSpec streamType a
- inherit :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType ()
- nullStream :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType ()
- closed :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType ()
- byteStringInput :: ByteString -> StreamSpec 'STInput ()
- byteStringOutput :: StreamSpec 'STOutput (STM ByteString)
- useHandleOpen :: forall (anyStreamType :: StreamType). Handle -> StreamSpec anyStreamType ()
- useHandleClose :: forall (anyStreamType :: StreamType). Handle -> StreamSpec anyStreamType ()
- withProcess :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a
- withProcess_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a
- waitExitCodeSTM :: Process stdin stdout stderr -> STM ExitCode
- getExitCodeSTM :: Process stdin stdout stderr -> STM (Maybe ExitCode)
- checkExitCodeSTM :: Process stdin stdout stderr -> STM ()
- getStdin :: Process stdin stdout stderr -> stdin
- getStdout :: Process stdin stdout stderr -> stdout
- getStderr :: Process stdin stdout stderr -> stderr
- unsafeProcessHandle :: Process stdin stdout stderr -> ProcessHandle
Process effect
type TypedProcess = Process Source #
runTypedProcess :: IOE :> es => Eff (TypedProcess : es) a -> Eff es a Source #
This is merely an alias for runProcess
since that name
clashes with runProcess
, i.e.:
runTypedProcess = Effectful.Process.runProcess
Launch a process
startProcess :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> Eff es (Process stdin stdout stderr) Source #
Lifted startProcess
.
stopProcess :: TypedProcess :> es => Process stdin stdout stderr -> Eff es () Source #
Lifted stopProcess
.
withProcessWait :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> Eff es a) -> Eff es a Source #
Lifted withProcessWait
.
withProcessWait_ :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> Eff es a) -> Eff es a Source #
Lifted withProcessWait_
.
withProcessTerm :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> Eff es a) -> Eff es a Source #
Lifted withProcessTerm
.
withProcessTerm_ :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> Eff es a) -> Eff es a Source #
Lifted withProcessTerm_
.
readProcess :: TypedProcess :> es => ProcessConfig stdin stdoutIgnored stderrIgnored -> Eff es (ExitCode, ByteString, ByteString) Source #
Lifted readProcess
.
readProcess_ :: TypedProcess :> es => ProcessConfig stdin stdoutIgnored stderrIgnored -> Eff es (ByteString, ByteString) Source #
Lifted readProcess_
.
runProcess :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> Eff es ExitCode Source #
Lifted runProcess
.
runProcess_ :: TypedProcess :> es => ProcessConfig stdin stdout stderr -> Eff es () Source #
Lifted runProcess_
.
readProcessStdout :: TypedProcess :> es => ProcessConfig stdin stdoutIgnored stderr -> Eff es (ExitCode, ByteString) Source #
Lifted readProcessStdout
.
readProcessStdout_ :: TypedProcess :> es => ProcessConfig stdin stdoutIgnored stderr -> Eff es ByteString Source #
Lifted readProcessStdout_
.
readProcessStderr :: TypedProcess :> es => ProcessConfig stdin stdout stderrIgnored -> Eff es (ExitCode, ByteString) Source #
Lifted readProcessStderr
.
readProcessStderr_ :: TypedProcess :> es => ProcessConfig stdin stdout stderrIgnored -> Eff es ByteString Source #
Lifted readProcessStderr_
.
readProcessInterleaved :: TypedProcess :> es => ProcessConfig stdin stdoutIgnored stderrIgnored -> Eff es (ExitCode, ByteString) Source #
Lifted readProcessInterleaved
.
readProcessInterleaved_ :: TypedProcess :> es => ProcessConfig stdin stdoutIgnored stderrIgnored -> Eff es ByteString Source #
Lifted readProcessInterleaved_
.
Process exit code
waitExitCode :: TypedProcess :> es => Process stdin stdout stderr -> Eff es ExitCode Source #
Lifted waitExitCode
.
getExitCode :: TypedProcess :> es => Process stdin stdout stderr -> Eff es (Maybe ExitCode) Source #
Lifted getExitCode
.
checkExitCode :: TypedProcess :> es => Process stdin stdout stderr -> Eff es () Source #
Lifted checkExitCode
.
Re-exports from System.Process.Typed
Defines the exit codes that a program can return.
ExitSuccess | indicates successful termination; |
ExitFailure Int | indicates program failure with an exit code. The exact interpretation of the code is operating-system dependent. In particular, some values may be prohibited (e.g. 0 on a POSIX-compliant system). |
Instances
Exception ExitCode | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception toException :: ExitCode -> SomeException # fromException :: SomeException -> Maybe ExitCode # displayException :: ExitCode -> String # | |
Generic ExitCode | |
Read ExitCode | |
Show ExitCode | |
Eq ExitCode | |
Ord ExitCode | |
Defined in GHC.IO.Exception | |
type Rep ExitCode | |
Defined in GHC.IO.Exception type Rep ExitCode = D1 ('MetaData "ExitCode" "GHC.IO.Exception" "base" 'False) (C1 ('MetaCons "ExitSuccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExitFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
Inherit | Inherit Handle from parent |
UseHandle Handle | Use the supplied Handle |
CreatePipe | Create a new pipe. The returned
|
NoStream | Close the stream's file descriptor without
passing a Handle. On POSIX systems this may
lead to strange behavior in the child process
because attempting to read or write after the
file has been closed throws an error. This
should only be used with child processes that
don't use the file descriptor at all. If you
wish to ignore the child process's output you
should either create a pipe and drain it
manually or pass a |
data Process stdin stdout stderr #
A running process. The three type parameters provide the type of the standard input, standard output, and standard error streams.
To interact with a Process
use the functions from the section
Interact with a process.
Since: typed-process-0.1.0.0
data ByteStringOutputException #
Wrapper for when an exception is thrown when reading from a child
process, used by byteStringOutput
.
Since: typed-process-0.1.0.0
ByteStringOutputException SomeException (ProcessConfig () () ()) |
Instances
data ExitCodeException #
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: typed-process-0.1.0.0
ExitCodeException | |
|
Instances
Exception ExitCodeException | |
Defined in System.Process.Typed.Internal | |
Show ExitCodeException | |
Defined in System.Process.Typed.Internal showsPrec :: Int -> ExitCodeException -> ShowS # show :: ExitCodeException -> String # showList :: [ExitCodeException] -> ShowS # |
data StreamSpec (streamType :: StreamType) a #
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
StdStream
from 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: typed-process-0.1.0.0
Instances
Functor (StreamSpec streamType) | |
Defined in System.Process.Typed.Internal fmap :: (a -> b) -> StreamSpec streamType a -> StreamSpec streamType b # (<$) :: a -> StreamSpec streamType b -> StreamSpec streamType a # | |
(streamType ~ 'STInput, res ~ ()) => IsString (StreamSpec streamType res) | This instance uses Since: typed-process-0.1.0.0 |
Defined in System.Process.Typed.Internal fromString :: String -> StreamSpec streamType res # |
data StreamType #
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: typed-process-0.1.0.0
data ProcessConfig stdin stdout stderr #
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
proc
smart constructor, which takes a command name and a list of arguments. - With the
shell
smart constructor, which takes a shell string - With the
IsString
instance 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: typed-process-0.1.0.0
Instances
(stdin ~ (), stdout ~ (), stderr ~ ()) => IsString (ProcessConfig stdin stdout stderr) | |
Defined in System.Process.Typed.Internal fromString :: String -> ProcessConfig stdin stdout stderr # | |
Show (ProcessConfig stdin stdout stderr) | |
Defined in System.Process.Typed.Internal showsPrec :: Int -> ProcessConfig stdin stdout stderr -> ShowS # show :: ProcessConfig stdin stdout stderr -> String # showList :: [ProcessConfig stdin stdout stderr] -> ShowS # |
:: [(String, String)] | |
-> ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Set the environment variables of the child process.
Default: current process's environment.
Since: typed-process-0.1.0.0
proc :: FilePath -> [String] -> ProcessConfig () () () #
Create a ProcessConfig
from the given command and arguments.
Since: typed-process-0.1.0.0
shell :: String -> ProcessConfig () () () #
Create a ProcessConfig
from the given shell command.
Since: typed-process-0.1.0.0
createPipe :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType Handle #
Create a new pipe between this process and the child, and return
a Handle
to communicate with the child.
Since: typed-process-0.1.0.0
:: StreamSpec 'STInput stdin | |
-> ProcessConfig stdin0 stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Set the child's standard input stream to the given StreamSpec
.
Default: inherit
Since: typed-process-0.1.0.0
:: StreamSpec 'STOutput stdout | |
-> ProcessConfig stdin stdout0 stderr | |
-> ProcessConfig stdin stdout stderr |
Set the child's standard output stream to the given StreamSpec
.
Default: inherit
Since: typed-process-0.1.0.0
:: StreamSpec 'STOutput stderr | |
-> ProcessConfig stdin stdout stderr0 | |
-> ProcessConfig stdin stdout stderr |
Set the child's standard error stream to the given StreamSpec
.
Default: inherit
Since: typed-process-0.1.0.0
:: FilePath | |
-> ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Set the working directory of the child process.
Default: current process's working directory.
Since: typed-process-0.1.0.0
:: ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Inherit the working directory from the parent process.
Since: typed-process-0.2.2.0
:: ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Inherit the environment variables from the parent process.
Since: typed-process-0.2.2.0
:: 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: typed-process-0.1.0.0
:: Bool | |
-> ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Should we create a new process group?
Default: False
Since: typed-process-0.1.0.0
:: 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: typed-process-0.1.0.0
:: Bool | |
-> ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
:: Bool | |
-> ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
:: 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: typed-process-0.1.0.0
:: 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: typed-process-0.1.0.0
:: ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Inherit the group from the parent process.
Since: typed-process-0.2.2.0
:: 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: typed-process-0.1.0.0
:: ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Inherit the user from the parent process.
Since: typed-process-0.2.2.0
:: forall a (streamType :: StreamType). 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 Handle
returned by thecreateProcess
function. The handle will beJust
Handle
if theStdStream
argument isCreatePipe
andNothing
otherwise. SeecreateProcess
for 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: typed-process-0.1.0.0
:: forall a (streamType :: StreamType). (ProcessConfig () () () -> Handle -> IO (a, IO ())) | |
-> StreamSpec streamType a |
Create a new CreatePipe
StreamSpec
from the given function.
This function:
- Takes as input the
Handle
returned by thecreateProcess
function. SeecreateProcess
for more details. - Returns the actual stream value
a
, as well as a cleanup function to be run when callingstopProcess
.
Since: typed-process-0.2.10.0
inherit :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType () #
A stream spec which simply inherits the stream of the parent process.
Since: typed-process-0.1.0.0
nullStream :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType () #
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: typed-process-0.2.5.0
closed :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType () #
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: typed-process-0.1.0.0
byteStringInput :: ByteString -> StreamSpec 'STInput () #
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: typed-process-0.1.0.0
byteStringOutput :: StreamSpec 'STOutput (STM ByteString) #
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: typed-process-0.1.0.0
useHandleOpen :: forall (anyStreamType :: StreamType). Handle -> StreamSpec anyStreamType () #
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: typed-process-0.1.0.0
useHandleClose :: forall (anyStreamType :: StreamType). Handle -> StreamSpec anyStreamType () #
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: typed-process-0.1.0.0
withProcess :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a #
Deprecated synonym for withProcessTerm
.
Since: typed-process-0.1.0.0
withProcess_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a #
Deprecated synonym for withProcessTerm_
.
Since: typed-process-0.1.0.0
waitExitCodeSTM :: Process stdin stdout stderr -> STM ExitCode #
Same as waitExitCode
, but in STM
.
Since: typed-process-0.1.0.0
getExitCodeSTM :: Process stdin stdout stderr -> STM (Maybe ExitCode) #
Same as getExitCode
, but in STM
.
Since: typed-process-0.1.0.0
checkExitCodeSTM :: Process stdin stdout stderr -> STM () #
Same as checkExitCode
, but in STM
.
Since: typed-process-0.1.0.0
getStdin :: Process stdin stdout stderr -> stdin #
Get the child's standard input stream value.
Since: typed-process-0.1.0.0
getStdout :: Process stdin stdout stderr -> stdout #
Get the child's standard output stream value.
Since: typed-process-0.1.0.0
getStderr :: Process stdin stdout stderr -> stderr #
Get the child's standard error stream value.
Since: typed-process-0.1.0.0
unsafeProcessHandle :: Process stdin stdout stderr -> ProcessHandle #
Take ProcessHandle
out of the Process
.
This method is needed in cases one need to use low level functions
from the process
package. Use cases for this method are:
- Send a special signal to the process.
- Terminate the process group instead of terminating single process.
- Use platform specific API on the underlying process.
This method is considered unsafe because the actions it performs on
the underlying process may overlap with the functionality that
typed-process
provides. For example the user should not call
waitForProcess
on the process handle as either
waitForProcess
or stopProcess
will lock.
Additionally, even if process was terminated by the
terminateProcess
or by sending signal,
stopProcess
should be called either way in order to cleanup resources
allocated by the typed-process
.
Since: typed-process-0.1.1