Copyright | (c) Dong Han 2018-2020 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provides process utilities.
import Control.Concurrent.MVar import Z.IO.Process > readProcessText defaultProcessOptions{processFile = "cat"} "hello world" ("hello world","",ExitSuccess)
Synopsis
- initProcess :: ProcessOptions -> Resource (Maybe UVStream, Maybe UVStream, Maybe UVStream, TVar ProcessState)
- readProcess :: HasCallStack => ProcessOptions -> Bytes -> IO (Bytes, Bytes, ExitCode)
- readProcessText :: HasCallStack => ProcessOptions -> Text -> IO (Text, Text, ExitCode)
- data ProcessOptions = ProcessOptions {}
- defaultProcessOptions :: ProcessOptions
- data ProcessStdStream
- data ProcessState
- data ExitCode
- waitProcessExit :: TVar ProcessState -> IO ExitCode
- getProcessPID :: TVar ProcessState -> IO (Maybe PID)
- killPID :: HasCallStack => PID -> Signal -> IO ()
- getPriority :: HasCallStack => PID -> IO Priority
- setPriority :: HasCallStack => PID -> Priority -> IO ()
- spawn :: HasCallStack => ProcessOptions -> IO (Maybe UVStream, Maybe UVStream, Maybe UVStream, TVar ProcessState)
- type ProcessFlag = CUInt
- pattern PROCESS_SETUID :: ProcessFlag
- pattern PROCESS_SETGID :: ProcessFlag
- pattern PROCESS_WINDOWS_VERBATIM_ARGUMENTS :: ProcessFlag
- pattern PROCESS_DETACHED :: ProcessFlag
- pattern PROCESS_WINDOWS_HIDE_CONSOLE :: ProcessFlag
- pattern PROCESS_WINDOWS_HIDE_GUI :: ProcessFlag
- type Signal = CInt
- pattern SIGTERM :: Signal
- pattern SIGINT :: Signal
- pattern SIGKILL :: Signal
- pattern SIGHUP :: Signal
- type Priority = CInt
- pattern PRIORITY_LOW :: Priority
- pattern PRIORITY_BELOW_NORMAL :: Priority
- pattern PRIORITY_NORMAL :: Priority
- pattern PRIORITY_ABOVE_NORMAL :: Priority
- pattern PRIORITY_HIGH :: Priority
- pattern PRIORITY_HIGHEST :: Priority
Documentation
initProcess :: ProcessOptions -> Resource (Maybe UVStream, Maybe UVStream, Maybe UVStream, TVar ProcessState) Source #
Resource spawn processes.
Return a resource spawn processes, when initiated return the (stdin, stdout, stderr, pstate)
tuple,
std streams are created when pass ProcessCreate
option, otherwise will be Nothing
,
pstate
will be updated to ProcessExited
automatically when the process exits.
A cleanup thread will be started when you finish using the process resource, to close any std stream created during spawn.
initProcess defaultProcessOptions{ processFile="your program" , processStdStreams = (ProcessCreate, ProcessCreate, ProcessCreate) } $ (stdin, stdout, stderr, pstate) -> do ... -- read or write from child process's std stream, will clean up automatically waitProcessExit pstate -- wait for process exit on current thread.
:: HasCallStack | |
=> ProcessOptions | processStdStreams options are ignored |
-> Bytes | stdin |
-> IO (Bytes, Bytes, ExitCode) | stdout, stderr, exit code |
Spawn a processe with given input.
Child process's stdout and stderr output are collected, return with exit code.
:: HasCallStack | |
=> ProcessOptions | processStdStreams options are ignored |
-> Text | stdin |
-> IO (Text, Text, ExitCode) | stdout, stderr, exit code |
Spawn a processe with given UTF8 textual input.
Child process's stdout and stderr output are collected as UTF8 bytes, return with exit code.
data ProcessOptions Source #
ProcessOptions | |
|
Instances
defaultProcessOptions :: ProcessOptions Source #
Default process options, start "./main"
with no arguments, redirect all std streams to /dev/null
.
data ProcessStdStream Source #
ProcessIgnore | redirect process std stream to /dev/null |
ProcessCreate | create a new std stream |
ProcessInherit FD | pass an existing FD to child process as std stream |
Instances
data ProcessState Source #
Process state
Instances
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
Eq ExitCode | |
Ord ExitCode | |
Defined in GHC.IO.Exception | |
Read ExitCode | |
Show ExitCode | |
Generic ExitCode | |
JSON ExitCode | |
Print ExitCode | |
Defined in Z.Data.Text.Print toUTF8BuilderP :: Int -> ExitCode -> Builder () # | |
Exception ExitCode | Since: base-4.1.0.0 |
Defined in GHC.IO.Exception toException :: ExitCode -> SomeException # fromException :: SomeException -> Maybe ExitCode # displayException :: ExitCode -> String # | |
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))) |
waitProcessExit :: TVar ProcessState -> IO ExitCode Source #
Wait until process exit and return the ExitCode
.
getProcessPID :: TVar ProcessState -> IO (Maybe PID) Source #
Get process PID
if process is running.
getPriority :: HasCallStack => PID -> IO Priority Source #
Retrieves the scheduling priority of the process specified by pid.
The returned value of priority is between -20 (high priority) and 19 (low priority). On Windows, the returned priority will equal one of the PRIORITY constants.
setPriority :: HasCallStack => PID -> Priority -> IO () Source #
Sets the scheduling priority of the process specified by pid.
The priority value range is between -20 (high priority) and 19 (low priority).
The constants PRIORITY_LOW
, PRIORITY_BELOW_NORMAL
, PRIORITY_NORMAL
,
PRIORITY_ABOVE_NORMAL
, PRIORITY_HIGH
, and PRIORITY_HIGHEST
are also provided for convenience.
internal
spawn :: HasCallStack => ProcessOptions -> IO (Maybe UVStream, Maybe UVStream, Maybe UVStream, TVar ProcessState) Source #
Spawn a new thread
Please manually close child process's std stream(if any) after process exits.
Constant
ProcessFlag
type ProcessFlag = CUInt Source #
pattern PROCESS_SETUID :: ProcessFlag Source #
Set the child process' user id.
This is not supported on Windows, uv_spawn() will fail and set the error to UV_ENOTSUP.
pattern PROCESS_SETGID :: ProcessFlag Source #
Set the child process' user id.
This is not supported on Windows, uv_spawn() will fail and set the error to UV_ENOTSUP.
pattern PROCESS_WINDOWS_VERBATIM_ARGUMENTS :: ProcessFlag Source #
Do not wrap any arguments in quotes, or perform any other escaping, when converting the argument list into a command line string.
This option is only meaningful on Windows systems. On Unix it is silently ignored.
pattern PROCESS_DETACHED :: ProcessFlag Source #
Spawn the child process in a detached state
This will make it a process group leader, and will effectively enable the child to keep running after the parent exits.
pattern PROCESS_WINDOWS_HIDE_CONSOLE :: ProcessFlag Source #
Hide the subprocess console window that would normally be created.
This option is only meaningful on Windows systems. On Unix it is silently ignored.
pattern PROCESS_WINDOWS_HIDE_GUI :: ProcessFlag Source #
Hide the subprocess GUI window that would normally be created.
This option is only meaningful on Windows systems. On Unix it is silently ignored.
Signal
Priority
pattern PRIORITY_LOW :: Priority Source #
pattern PRIORITY_BELOW_NORMAL :: Priority Source #
pattern PRIORITY_NORMAL :: Priority Source #
pattern PRIORITY_ABOVE_NORMAL :: Priority Source #
pattern PRIORITY_HIGH :: Priority Source #
pattern PRIORITY_HIGHEST :: Priority Source #