| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Effectful.Process
Description
Lifted System.Process.
Synopsis
- data Process :: Effect
- runProcess :: IOE :> es => Eff (Process ': es) a -> Eff es a
- createProcess :: Process :> es => CreateProcess -> Eff es (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
- createProcess_ :: Process :> es => String -> CreateProcess -> Eff es (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
- shell :: String -> CreateProcess
- proc :: FilePath -> [String] -> CreateProcess
- data CreateProcess = CreateProcess {
- cmdspec :: CmdSpec
- cwd :: Maybe FilePath
- env :: Maybe [(String, String)]
- std_in :: StdStream
- std_out :: StdStream
- std_err :: StdStream
- close_fds :: Bool
- create_group :: Bool
- delegate_ctlc :: Bool
- detach_console :: Bool
- create_new_console :: Bool
- new_session :: Bool
- child_group :: Maybe GroupID
- child_user :: Maybe UserID
- use_process_jobs :: Bool
- data CmdSpec
- data StdStream
- data ProcessHandle
- callProcess :: Process :> es => FilePath -> [String] -> Eff es ()
- callCommand :: Process :> es => String -> Eff es ()
- spawnProcess :: Process :> es => FilePath -> [String] -> Eff es ProcessHandle
- spawnCommand :: Process :> es => String -> Eff es ProcessHandle
- readCreateProcess :: Process :> es => CreateProcess -> String -> Eff es String
- readProcess :: Process :> es => FilePath -> [String] -> String -> Eff es String
- readCreateProcessWithExitCode :: Process :> es => CreateProcess -> String -> Eff es (ExitCode, String, String)
- readProcessWithExitCode :: Process :> es => FilePath -> [String] -> String -> Eff es (ExitCode, String, String)
- withCreateProcess :: Process :> es => CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> Eff es a) -> Eff es a
- cleanupProcess :: Process :> es => (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> Eff es ()
- showCommandForUser :: FilePath -> [String] -> String
- type Pid = CPid
- getPid :: Process :> es => ProcessHandle -> Eff es (Maybe Pid)
- waitForProcess :: Process :> es => ProcessHandle -> Eff es ExitCode
- getProcessExitCode :: Process :> es => ProcessHandle -> Eff es (Maybe ExitCode)
- terminateProcess :: Process :> es => ProcessHandle -> Eff es ()
- interruptProcessGroupOf :: Process :> es => ProcessHandle -> Eff es ()
- createPipe :: Process :> es => Eff es (Handle, Handle)
- createPipeFd :: Process :> es => Eff es (FD, FD)
Effect
data Process :: Effect Source #
An effect for running child processes using the process library.
Instances
| data StaticRep Process Source # | |
Defined in Effectful.Process | |
| type DispatchOf Process Source # | |
Defined in Effectful.Process | |
Handlers
Running sub-processes
createProcess :: Process :> es => CreateProcess -> Eff es (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) Source #
Lifted createProcess.
createProcess_ :: Process :> es => String -> CreateProcess -> Eff es (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) Source #
Lifted createProcess_.
shell :: String -> CreateProcess #
Construct a CreateProcess record for passing to createProcess,
representing a command to be passed to the shell.
proc :: FilePath -> [String] -> CreateProcess #
Construct a CreateProcess record for passing to createProcess,
representing a raw command with arguments.
See RawCommand for precise semantics of the specified FilePath.
data CreateProcess #
Constructors
| CreateProcess | |
Fields
| |
Instances
| Eq CreateProcess | |
Defined in System.Process.Common Methods (==) :: CreateProcess -> CreateProcess -> Bool # (/=) :: CreateProcess -> CreateProcess -> Bool # | |
| Show CreateProcess | |
Defined in System.Process.Common Methods showsPrec :: Int -> CreateProcess -> ShowS # show :: CreateProcess -> String # showList :: [CreateProcess] -> ShowS # | |
Constructors
| ShellCommand String | A command line to execute using the shell |
| RawCommand FilePath [String] | The name of an executable with a list of arguments The
|
Instances
| Eq CmdSpec | |
| Show CmdSpec | |
| IsString CmdSpec | construct a Since: process-1.2.1.0 |
Defined in System.Process.Common Methods fromString :: String -> CmdSpec # | |
Constructors
| 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 |
Instances
data ProcessHandle #
Simpler functions for common tasks
callProcess :: Process :> es => FilePath -> [String] -> Eff es () Source #
Lifted callProcess.
callCommand :: Process :> es => String -> Eff es () Source #
Lifted callCommand.
spawnProcess :: Process :> es => FilePath -> [String] -> Eff es ProcessHandle Source #
Lifted spawnProcess.
spawnCommand :: Process :> es => String -> Eff es ProcessHandle Source #
Lifted spawnCommand.
readCreateProcess :: Process :> es => CreateProcess -> String -> Eff es String Source #
Lifted readCreateProcess.
readProcess :: Process :> es => FilePath -> [String] -> String -> Eff es String Source #
Lifted readProcess.
readCreateProcessWithExitCode :: Process :> es => CreateProcess -> String -> Eff es (ExitCode, String, String) Source #
Lifted readCreateProcessWithExitCode.
readProcessWithExitCode :: Process :> es => FilePath -> [String] -> String -> Eff es (ExitCode, String, String) Source #
Lifted readProcessWithExitCode.
withCreateProcess :: Process :> es => CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> Eff es a) -> Eff es a Source #
Lifted withCreateProcess.
cleanupProcess :: Process :> es => (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> Eff es () Source #
Lifted cleanupProcess.
Related utilities
showCommandForUser :: FilePath -> [String] -> String #
Given a program p and arguments args,
showCommandForUser p args returns a string suitable for pasting
into /bin/sh (on Unix systems) or CMD.EXE (on Windows).
The platform specific type for a process identifier.
This is always an integral type. Width and signedness are platform specific.
Since: process-1.6.3.0
Process completion
waitForProcess :: Process :> es => ProcessHandle -> Eff es ExitCode Source #
Lifted waitForProcess.
getProcessExitCode :: Process :> es => ProcessHandle -> Eff es (Maybe ExitCode) Source #
Lifted getProcessExitCode.
terminateProcess :: Process :> es => ProcessHandle -> Eff es () Source #
Lifted terminateProcess.
interruptProcessGroupOf :: Process :> es => ProcessHandle -> Eff es () Source #
Lifted interruptProcessGroupOf.
Interprocess communication
createPipe :: Process :> es => Eff es (Handle, Handle) Source #
Lifted createPipe.
createPipeFd :: Process :> es => Eff es (FD, FD) Source #
Lifted createPipeFd.