Safe Haskell | None |
---|---|
Language | Haskell2010 |
RIO.Process
Description
Interacting with external processes.
This module provides a layer on top of System.Process.Typed, with the following additions:
- For efficiency, it will cache
PATH
lookups. - For convenience, you can set the working directory and env vars
overrides in a
RIO
environment instead of on the individual calls to the process. - Built-in support for logging at the debug level.
In order to switch over to this API, the main idea is:
- Like most of the rio library, you need to create an environment
value (this time
ProcessContext
), and include it in yourRIO
environment. SeemkProcessContext
. - Instead of using the
proc
function from System.Process.Typed for creating aProcessConfig
, use the locally definedproc
function, which will handle overriding environment variables, looking up paths, performing logging, etc.
Once you have your ProcessConfig
, use the standard functions from
Typed
(reexported here for convenient) for running
the ProcessConfig
.
Since: 0.0.3.0
Synopsis
- data ProcessContext
- class HasProcessContext env where
- processContextL :: Lens' env ProcessContext
- type EnvVars = Map Text Text
- mkProcessContext :: MonadIO m => EnvVars -> m ProcessContext
- mkDefaultProcessContext :: MonadIO m => m ProcessContext
- modifyEnvVars :: MonadIO m => ProcessContext -> (EnvVars -> EnvVars) -> m ProcessContext
- withModifyEnvVars :: (HasProcessContext env, MonadReader env m, MonadIO m) => (EnvVars -> EnvVars) -> m a -> m a
- lookupEnvFromContext :: (MonadReader env m, HasProcessContext env) => Text -> m (Maybe Text)
- withWorkingDir :: (HasProcessContext env, MonadReader env m, MonadIO m) => FilePath -> m a -> m a
- workingDirL :: HasProcessContext env => Lens' env (Maybe FilePath)
- envVarsL :: HasProcessContext env => SimpleGetter env EnvVars
- envVarsStringsL :: HasProcessContext env => SimpleGetter env [(String, String)]
- exeSearchPathL :: HasProcessContext env => SimpleGetter env [FilePath]
- resetExeCache :: (MonadIO m, MonadReader env m, HasProcessContext env) => m ()
- proc :: (HasProcessContext env, HasLogFunc env, MonadReader env m, MonadIO m, HasCallStack) => FilePath -> [String] -> (ProcessConfig () () () -> m a) -> m a
- 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
- withProcessWait :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a
- withProcessWait_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a
- withProcessTerm :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a
- withProcessTerm_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a
- exec :: (HasProcessContext env, HasLogFunc env) => String -> [String] -> RIO env b
- execSpawn :: (HasProcessContext env, HasLogFunc env) => String -> [String] -> RIO env a
- data LoggedProcessContext = LoggedProcessContext ProcessContext LogFunc
- withProcessContextNoLogging :: MonadIO m => RIO LoggedProcessContext a -> m a
- data ProcessException
- doesExecutableExist :: (MonadIO m, MonadReader env m, HasProcessContext env) => String -> m Bool
- findExecutable :: (MonadIO m, MonadReader env m, HasProcessContext env) => String -> m (Either ProcessException FilePath)
- exeExtensions :: (MonadIO m, MonadReader env m, HasProcessContext env) => m [String]
- augmentPath :: [FilePath] -> Maybe Text -> Either ProcessException Text
- augmentPathMap :: [FilePath] -> EnvVars -> Either ProcessException EnvVars
- showProcessArgDebug :: String -> Text
- data ProcessConfig stdin stdout stderr
- data StreamSpec (streamType :: StreamType) a
- data StreamType
- data Process 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
- 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
- setChildUser :: UserID -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- mkStreamSpec :: forall a (streamType :: StreamType). StdStream -> (ProcessConfig () () () -> Maybe Handle -> IO (a, IO ())) -> StreamSpec streamType a
- inherit :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType ()
- closed :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType ()
- byteStringInput :: ByteString -> StreamSpec 'STInput ()
- byteStringOutput :: StreamSpec 'STOutput (STM ByteString)
- createPipe :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType Handle
- useHandleOpen :: forall (anyStreamType :: StreamType). Handle -> StreamSpec anyStreamType ()
- useHandleClose :: forall (anyStreamType :: StreamType). Handle -> StreamSpec anyStreamType ()
- startProcess :: MonadIO m => ProcessConfig stdin stdout stderr -> m (Process stdin stdout stderr)
- stopProcess :: MonadIO m => Process stdin stdout stderr -> m ()
- readProcess :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m (ExitCode, ByteString, ByteString)
- readProcess_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m (ByteString, ByteString)
- runProcess :: MonadIO m => ProcessConfig stdin stdout stderr -> m ExitCode
- runProcess_ :: MonadIO m => ProcessConfig stdin stdout stderr -> m ()
- readProcessStdout :: MonadIO m => ProcessConfig stdin stdoutIgnored stderr -> m (ExitCode, ByteString)
- readProcessStdout_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderr -> m ByteString
- readProcessStderr :: MonadIO m => ProcessConfig stdin stdout stderrIgnored -> m (ExitCode, ByteString)
- readProcessStderr_ :: MonadIO m => ProcessConfig stdin stdout stderrIgnored -> m ByteString
- waitExitCode :: MonadIO m => Process stdin stdout stderr -> m ExitCode
- waitExitCodeSTM :: Process stdin stdout stderr -> STM ExitCode
- getExitCode :: MonadIO m => Process stdin stdout stderr -> m (Maybe ExitCode)
- getExitCodeSTM :: Process stdin stdout stderr -> STM (Maybe ExitCode)
- checkExitCode :: MonadIO m => Process stdin stdout stderr -> m ()
- checkExitCodeSTM :: Process stdin stdout stderr -> STM ()
- getStdin :: Process stdin stdout stderr -> stdin
- getStdout :: Process stdin stdout stderr -> stdout
- getStderr :: Process stdin stdout stderr -> stderr
- data ExitCodeException = ExitCodeException {
- eceExitCode :: ExitCode
- eceProcessConfig :: ProcessConfig () () ()
- eceStdout :: ByteString
- eceStderr :: ByteString
- data ByteStringOutputException = ByteStringOutputException SomeException (ProcessConfig () () ())
- unsafeProcessHandle :: Process stdin stdout stderr -> ProcessHandle
Process context
data ProcessContext Source #
Context in which to run processes.
Since: 0.0.3.0
Instances
HasProcessContext ProcessContext Source # | |
Defined in RIO.Process Methods processContextL :: Lens' ProcessContext ProcessContext Source # |
class HasProcessContext env where Source #
Get the ProcessContext
from the environment.
Since: 0.0.3.0
Methods
processContextL :: Lens' env ProcessContext Source #
Instances
HasProcessContext LoggedProcessContext Source # | |
Defined in RIO.Process | |
HasProcessContext ProcessContext Source # | |
Defined in RIO.Process Methods processContextL :: Lens' ProcessContext ProcessContext Source # | |
HasProcessContext SimpleApp Source # | |
Defined in RIO.Prelude.Simple Methods |
mkProcessContext :: MonadIO m => EnvVars -> m ProcessContext Source #
Create a new ProcessContext
from the given environment variable map.
Since: 0.0.3.0
mkDefaultProcessContext :: MonadIO m => m ProcessContext Source #
Same as mkProcessContext
but uses the system environment (from
getEnvironment
).
Since: 0.0.3.0
modifyEnvVars :: MonadIO m => ProcessContext -> (EnvVars -> EnvVars) -> m ProcessContext Source #
Modify the environment variables of a ProcessContext
. This will not
change the working directory.
Note that this requires MonadIO
, as it will create a new IORef
for the cache.
Since: 0.0.3.0
withModifyEnvVars :: (HasProcessContext env, MonadReader env m, MonadIO m) => (EnvVars -> EnvVars) -> m a -> m a Source #
Use modifyEnvVars
to create a new ProcessContext
, and then
use it in the provided action.
Since: 0.0.3.0
lookupEnvFromContext :: (MonadReader env m, HasProcessContext env) => Text -> m (Maybe Text) Source #
Look into the ProcessContext
and return the specified environmet variable if one is
available.
Since: 0.1.14.0
withWorkingDir :: (HasProcessContext env, MonadReader env m, MonadIO m) => FilePath -> m a -> m a Source #
Set the working directory to be used by child processes.
Since: 0.0.3.0
Lenses
workingDirL :: HasProcessContext env => Lens' env (Maybe FilePath) Source #
Override the working directory processes run in. Nothing
means
the current process's working directory.
Since: 0.0.3.0
envVarsL :: HasProcessContext env => SimpleGetter env EnvVars Source #
Get the environment variables. We cannot provide a Lens
here,
since updating the environment variables requires an IO
action to
allocate a new IORef
for holding the executable path cache.
Since: 0.0.3.0
envVarsStringsL :: HasProcessContext env => SimpleGetter env [(String, String)] Source #
exeSearchPathL :: HasProcessContext env => SimpleGetter env [FilePath] Source #
Get the list of directories searched for executables (the PATH
).
Similar to envVarMapL
, this cannot be a full Lens
.
Since: 0.0.3.0
Actions
resetExeCache :: (MonadIO m, MonadReader env m, HasProcessContext env) => m () Source #
Reset the executable cache.
Since: 0.0.3.0
Configuring
Arguments
:: (HasProcessContext env, HasLogFunc env, MonadReader env m, MonadIO m, HasCallStack) | |
=> FilePath | command to run |
-> [String] | command line arguments |
-> (ProcessConfig () () () -> m a) | |
-> m a |
Provide a ProcessConfig
based on the ProcessContext
in
scope. Deals with resolving the full path, setting the child
process's environment variables, setting the working directory, and
wrapping the call with withProcessTimeLog
for debugging output.
This is intended to be analogous to the proc
function provided by
the System.Process.Typed
module, but has a different type
signature to (1) allow it to perform IO
actions for looking up
paths, and (2) allow logging and timing of the running action.
Since: 0.0.3.0
Spawning (run child process)
withProcess :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a Source #
Deprecated: Please consider using withProcessWait, or instead use withProcessTerm
Same as withProcess
, but generalized to MonadUnliftIO
.
Since: 0.0.3.0
withProcess_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a Source #
Deprecated: Please consider using withProcessWait, or instead use withProcessTerm
Same as withProcess_
, but generalized to MonadUnliftIO
.
Since: 0.0.3.0
withProcessWait :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a Source #
Same as withProcessWait
, but generalized to MonadUnliftIO
.
Since: 0.1.10.0
withProcessWait_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a Source #
Same as withProcessWait_
, but generalized to MonadUnliftIO
.
Since: 0.1.10.0
withProcessTerm :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a Source #
Same as withProcessTerm
, but generalized to MonadUnliftIO
.
Since: 0.1.10.0
withProcessTerm_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a Source #
Same as withProcessTerm_
, but generalized to MonadUnliftIO
.
Since: 0.1.10.0
Exec (replacing current process)
exec :: (HasProcessContext env, HasLogFunc env) => String -> [String] -> RIO env b Source #
Execute a process within the configured environment.
Execution will not return, because either:
1) On non-windows, execution is taken over by execv of the sub-process. This allows signals to be propagated (#527)
2) On windows, an ExitCode
exception will be thrown.
Since: 0.0.3.0
execSpawn :: (HasProcessContext env, HasLogFunc env) => String -> [String] -> RIO env a Source #
Like exec
, but does not use execv
on non-windows. This way,
there is a sub-process, which is helpful in some cases
(https://github.com/commercialhaskell/stack/issues/1306).
This function only exits by throwing ExitCode
.
Since: 0.0.3.0
Environment helper
data LoggedProcessContext Source #
A convenience environment combining a LogFunc
and a ProcessContext
Since: 0.0.3.0
Constructors
LoggedProcessContext ProcessContext LogFunc |
Instances
HasLogFunc LoggedProcessContext Source # | |
Defined in RIO.Process | |
HasProcessContext LoggedProcessContext Source # | |
Defined in RIO.Process |
withProcessContextNoLogging :: MonadIO m => RIO LoggedProcessContext a -> m a Source #
Run an action using a LoggedProcessContext
with default
settings and no logging.
Since: 0.0.3.0
Exceptions
data ProcessException Source #
Exception type which may be generated in this module.
NOTE Other exceptions may be thrown by underlying libraries!
Since: 0.0.3.0
Constructors
NoPathFound | |
ExecutableNotFound String [FilePath] | |
ExecutableNotFoundAt FilePath | |
PathsInvalidInPath [FilePath] |
Instances
Show ProcessException Source # | |
Defined in RIO.Process Methods showsPrec :: Int -> ProcessException -> ShowS show :: ProcessException -> String # showList :: [ProcessException] -> ShowS | |
Exception ProcessException Source # | |
Defined in RIO.Process Methods toException :: ProcessException -> SomeException fromException :: SomeException -> Maybe ProcessException |
Utilities
Arguments
:: (MonadIO m, MonadReader env m, HasProcessContext env) | |
=> String | Name of executable |
-> m Bool |
Check if the given executable exists on the given PATH.
Since: 0.0.3.0
Arguments
:: (MonadIO m, MonadReader env m, HasProcessContext env) | |
=> String | Name of executable |
-> m (Either ProcessException FilePath) | Full path to that executable on success |
Find the complete path for the given executable name.
On POSIX systems, filenames that match but are not exectuables are excluded.
On Windows systems, the executable names tried, in turn, are the supplied
name (only if it has an extension) and that name extended by each of the
exeExtensions
. Also, this function may behave differently from
findExecutable
. The latter excludes as executables filenames
without a .bat
, .cmd
, .com
or .exe
extension (case-insensitive).
Since: 0.0.3.0
exeExtensions :: (MonadIO m, MonadReader env m, HasProcessContext env) => m [String] Source #
Get the filename extensions for executable files, including the dot (if any).
On POSIX systems, this is [""]
.
On Windows systems, the list is determined by the value of the PATHEXT
environment variable, if it present in the environment. If the variable is
absent, this is its default value on a Windows system. This function may,
therefore, behave differently from exeExtension
,
which returns only ".exe"
.
Since: 0.1.13.0
augmentPath :: [FilePath] -> Maybe Text -> Either ProcessException Text Source #
Augment the PATH environment variable with the given extra paths.
Since: 0.0.3.0
augmentPathMap :: [FilePath] -> EnvVars -> Either ProcessException EnvVars Source #
Apply augmentPath
on the PATH value in the given EnvVars
.
Since: 0.0.3.0
showProcessArgDebug :: String -> Text Source #
Show a process arg including speechmarks when necessary. Just for debugging purposes, not functionally important.
Since: 0.0.3.0
Reexports
data ProcessConfig stdin stdout stderr #
Instances
Show (ProcessConfig stdin stdout stderr) | |
Defined in System.Process.Typed Methods showsPrec :: Int -> ProcessConfig stdin stdout stderr -> ShowS show :: ProcessConfig stdin stdout stderr -> String # showList :: [ProcessConfig stdin stdout stderr] -> ShowS | |
(stdin ~ (), stdout ~ (), stderr ~ ()) => IsString (ProcessConfig stdin stdout stderr) | |
Defined in System.Process.Typed Methods fromString :: String -> ProcessConfig stdin stdout stderr # | |
Display (ProcessConfig a b c) Source # | Since: 0.1.0.0 |
Defined in RIO.Prelude.Display Methods display :: ProcessConfig a b c -> Utf8Builder Source # textDisplay :: ProcessConfig a b c -> Text Source # |
data StreamSpec (streamType :: StreamType) a #
Instances
Functor (StreamSpec streamType) | |
Defined in System.Process.Typed Methods fmap :: (a -> b) -> StreamSpec streamType a -> StreamSpec streamType b # (<$) :: a -> StreamSpec streamType b -> StreamSpec streamType a # | |
(streamType ~ 'STInput, res ~ ()) => IsString (StreamSpec streamType res) | |
Defined in System.Process.Typed Methods fromString :: String -> StreamSpec streamType res # |
data StreamType #
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 #
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 #
setChildUser :: UserID -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr #
mkStreamSpec :: forall a (streamType :: StreamType). StdStream -> (ProcessConfig () () () -> Maybe Handle -> IO (a, IO ())) -> StreamSpec streamType a #
inherit :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType () #
closed :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType () #
byteStringInput :: ByteString -> StreamSpec 'STInput () #
byteStringOutput :: StreamSpec 'STOutput (STM ByteString) #
createPipe :: forall (anyStreamType :: StreamType). StreamSpec anyStreamType Handle #
useHandleOpen :: forall (anyStreamType :: StreamType). Handle -> StreamSpec anyStreamType () #
useHandleClose :: forall (anyStreamType :: StreamType). Handle -> StreamSpec anyStreamType () #
startProcess :: MonadIO m => ProcessConfig stdin stdout stderr -> m (Process stdin stdout stderr) #
stopProcess :: MonadIO m => Process stdin stdout stderr -> m () #
readProcess :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m (ExitCode, ByteString, ByteString) #
readProcess_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m (ByteString, ByteString) #
runProcess :: MonadIO m => ProcessConfig stdin stdout stderr -> m ExitCode #
runProcess_ :: MonadIO m => ProcessConfig stdin stdout stderr -> m () #
readProcessStdout :: MonadIO m => ProcessConfig stdin stdoutIgnored stderr -> m (ExitCode, ByteString) #
readProcessStdout_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderr -> m ByteString #
readProcessStderr :: MonadIO m => ProcessConfig stdin stdout stderrIgnored -> m (ExitCode, ByteString) #
readProcessStderr_ :: MonadIO m => ProcessConfig stdin stdout stderrIgnored -> m ByteString #
waitExitCode :: MonadIO m => Process stdin stdout stderr -> m ExitCode #
waitExitCodeSTM :: Process stdin stdout stderr -> STM ExitCode #
getExitCode :: MonadIO m => Process stdin stdout stderr -> m (Maybe ExitCode) #
getExitCodeSTM :: Process stdin stdout stderr -> STM (Maybe ExitCode) #
checkExitCode :: MonadIO m => Process stdin stdout stderr -> m () #
checkExitCodeSTM :: Process stdin stdout stderr -> STM () #
data ExitCodeException #
Constructors
ExitCodeException | |
Fields
|
Instances
Show ExitCodeException | |
Defined in System.Process.Typed Methods showsPrec :: Int -> ExitCodeException -> ShowS show :: ExitCodeException -> String # showList :: [ExitCodeException] -> ShowS | |
Exception ExitCodeException | |
Defined in System.Process.Typed Methods toException :: ExitCodeException -> SomeException fromException :: SomeException -> Maybe ExitCodeException |
data ByteStringOutputException #
Constructors
ByteStringOutputException SomeException (ProcessConfig () () ()) |
Instances
Show ByteStringOutputException | |
Defined in System.Process.Typed Methods showsPrec :: Int -> ByteStringOutputException -> ShowS show :: ByteStringOutputException -> String # showList :: [ByteStringOutputException] -> ShowS | |
Exception ByteStringOutputException | |
Defined in System.Process.Typed Methods toException :: ByteStringOutputException -> SomeException fromException :: SomeException -> Maybe ByteStringOutputException |
unsafeProcessHandle :: Process stdin stdout stderr -> ProcessHandle #