| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Polysemy.Process
Description
Synopsis
- data Process i o :: Effect
- recv :: forall i o r. Member (Process i o) r => Sem r o
- send :: forall i o r. Member (Process i o) r => i -> Sem r ()
- withProcess :: forall param i o r. Member (Scoped param (Process i o)) r => param -> InterpreterFor (Process i o) r
- withProcess_ :: forall i o r. Member (Scoped_ (Process i o)) r => InterpreterFor (Process i o) r
- withProcessOneshot :: forall param i o err r. Member (Scoped param (Process i o !! err)) r => param -> InterpreterFor (Process i o !! err) r
- withProcessOneshot_ :: forall i o err r. Member (Scoped_ (Process i o !! err)) r => InterpreterFor (Process i o !! err) r
- data ProcessOptions = ProcessOptions Bool Int ProcessKill
- data ProcessKill
- data ProcessError
- data ProcessOutput (p :: OutputPipe) a :: Effect
- data OutputPipe
- data ProcessOutputParseResult a
- data ProcessInput a :: Effect
- data SystemProcess :: Effect
- withSystemProcess :: forall param err r. Member (Scoped param (SystemProcess !! err)) r => param -> InterpreterFor (SystemProcess !! err) r
- withSystemProcess_ :: forall err r. Member (Scoped_ (SystemProcess !! err)) r => InterpreterFor (SystemProcess !! err) r
- newtype Pid = Pid {}
- currentPid :: Member (Embed IO) r => Sem r Pid
- data Pty :: Effect
- withPty :: Member (Scoped_ Pty) r => InterpreterFor Pty r
- interpretProcess :: forall param proc i o r. Members (ProcessIO i o) r => Member (Scoped proc (SystemProcess !! SystemProcessError) !! SystemProcessScopeError) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> (param -> Sem (Stop ProcessError ': r) proc) -> InterpreterFor (Scoped param (Process i o) !! ProcessError) r
- interpretProcessOneshot :: forall param proc i o r. Members (ProcessIO i o) r => Member (Scoped proc (SystemProcess !! SystemProcessError) !! SystemProcessScopeError) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> (param -> Sem (Stop SystemProcessScopeError ': r) proc) -> InterpreterFor (Scoped param (Process i o !! ProcessError) !! SystemProcessScopeError) r
- interpretProcessNative :: forall param i o r. Members (ProcessIO i o) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> (param -> Sem r (Either Text SysProcConf)) -> InterpreterFor (Scoped param (Process i o) !! ProcessError) r
- interpretProcessOneshotNative :: forall param i o r. Members (ProcessIO i o) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> (param -> Sem r (Either Text SysProcConf)) -> InterpreterFor (Scoped param (Process i o !! ProcessError) !! SystemProcessScopeError) r
- interpretProcess_ :: forall i o r. Member (Scoped_ (SystemProcess !! SystemProcessError) !! SystemProcessScopeError) r => Members [ProcessOutput 'Stdout o, ProcessOutput 'Stderr o, ProcessInput i, Resource, Race, Async, Embed IO] r => ProcessOptions -> InterpreterFor (Scoped_ (Process i o) !! ProcessError) r
- interpretProcessOneshot_ :: forall proc i o r. Members (ProcessIO i o) r => Member (Scoped proc (SystemProcess !! SystemProcessError) !! SystemProcessScopeError) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> proc -> InterpreterFor (Scoped_ (Process i o !! ProcessError) !! SystemProcessScopeError) r
- interpretProcessNative_ :: forall i o r. Members (ProcessIO i o) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> SysProcConf -> InterpreterFor (Scoped_ (Process i o) !! ProcessError) r
- interpretProcessOneshotNative_ :: forall i o r. Members (ProcessIO i o) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> SysProcConf -> InterpreterFor (Scoped_ (Process i o !! ProcessError) !! SystemProcessScopeError) r
- interpretInputOutputProcess :: forall i o r. Member (Process i o) r => InterpretersFor [Input o, Output i] r
- interpretInputHandleBuffered :: Member (Embed IO) r => Handle -> InterpreterFor (Input ByteString !! ProcessError) r
- interpretInputHandle :: Member (Embed IO) r => Handle -> InterpreterFor (Input ByteString !! ProcessError) r
- interpretOutputHandleBuffered :: Member (Embed IO) r => Handle -> InterpreterFor (Output ByteString !! ProcessError) r
- interpretOutputHandle :: Member (Embed IO) r => Handle -> InterpreterFor (Output ByteString !! ProcessError) r
- interpretProcessIO :: forall i o ie oe r. Members [Input ByteString !! ie, Output ByteString !! oe] r => Members [ProcessInput i, ProcessOutput 'Stdout o, Resource, Race, Async, Embed IO] r => ProcessOptions -> InterpreterFor (Process i o !! ProcessError) r
- interpretProcessHandles :: forall i o r. Members [ProcessInput i, ProcessOutput 'Stdout o, Resource, Race, Async, Embed IO] r => ProcessOptions -> Handle -> Handle -> InterpreterFor (Process i o !! ProcessError) r
- interpretProcessCurrent :: Members [ProcessInput i, ProcessOutput 'Stdout o, Resource, Race, Async, Embed IO] r => ProcessOptions -> InterpreterFor (Process i o !! ProcessError) r
- type ProcessIO i o = [ProcessInput i, ProcessOutput 'Stdout o, ProcessOutput 'Stderr o]
- interpretProcessByteString :: InterpretersFor (ProcessIO ByteString ByteString) r
- interpretProcessByteStringLines :: InterpretersFor (ProcessIO ByteString ByteString) r
- interpretProcessText :: InterpretersFor (ProcessIO Text Text) r
- interpretProcessTextLines :: InterpretersFor (ProcessIO Text Text) r
- interpretProcessOutputIgnore :: forall p a r. InterpreterFor (ProcessOutput p a) r
- interpretProcessOutputId :: forall p r. InterpreterFor (ProcessOutput p ByteString) r
- interpretProcessOutputLeft :: forall p a b r. Member (ProcessOutput p a) r => InterpreterFor (ProcessOutput p (Either a b)) r
- interpretProcessOutputRight :: forall p a b r. Member (ProcessOutput p b) r => InterpreterFor (ProcessOutput p (Either a b)) r
- interpretProcessOutputLines :: forall p r. InterpreterFor (ProcessOutput p ByteString) r
- interpretProcessOutputText :: forall p r. InterpreterFor (ProcessOutput p Text) r
- interpretProcessOutputTextLines :: forall p r. InterpreterFor (ProcessOutput p Text) r
- interpretProcessOutputIncremental :: forall p a r. (ByteString -> ProcessOutputParseResult a) -> InterpreterFor (ProcessOutput p (Either Text a)) r
- interpretProcessInputId :: InterpreterFor (ProcessInput ByteString) r
- interpretProcessInputText :: InterpreterFor (ProcessInput Text) r
- type SysProcConf = ProcessConfig () () ()
- type PipesProcess = Process Handle Handle Handle
- data SystemProcessError
- data SystemProcessScopeError
- interpretSystemProcessNative :: forall param r. Members [Resource, Embed IO] r => (param -> Sem r (Either Text SysProcConf)) -> InterpreterFor (Scoped param (SystemProcess !! SystemProcessError) !! SystemProcessScopeError) r
- interpretSystemProcessNative_ :: forall r. Members [Resource, Embed IO] r => SysProcConf -> InterpreterFor (Scoped_ (SystemProcess !! SystemProcessError) !! SystemProcessScopeError) r
- interpretSystemProcessWithProcess :: forall r. Member (Embed IO) r => Process Handle Handle Handle -> InterpreterFor (SystemProcess !! SystemProcessError) r
- handleSystemProcessWithProcess :: forall r r0 a. Members [Stop SystemProcessError, Embed IO] r => Process Handle Handle Handle -> SystemProcess (Sem r0) a -> Sem r a
- interpretSystemProcessNativeSingle :: forall r. Members [Stop SystemProcessScopeError, Resource, Embed IO] r => SysProcConf -> InterpreterFor (SystemProcess !! SystemProcessError) r
- interpretSystemProcessWithProcessOpaque :: forall i o e r. Member (Embed IO) r => Process i o e -> InterpreterFor (SystemProcess !! SystemProcessError) r
- interpretSystemProcessNativeOpaqueSingle :: forall i o e r. Members [Resource, Embed IO] r => ProcessConfig i o e -> InterpreterFor (SystemProcess !! SystemProcessError) r
- interpretSystemProcessNativeOpaque :: forall i o e r. Members [Resource, Embed IO] r => ProcessConfig i o e -> InterpreterFor (Scoped_ (SystemProcess !! SystemProcessError)) r
- interpretPty :: Members [Resource, Embed IO] r => InterpreterFor (Scoped_ Pty !! PtyError) r
- resolveExecutable :: Member (Embed IO) r => Path Rel File -> Maybe (Path Abs File) -> Sem r (Either Text (Path Abs File))
Introduction
This library provides an abstraction of a system process in the effect Process, whose constructors represent the
three standard file descriptors.
An intermediate effect, SystemProcess, is more concretely tied to the functionality of the System.Process
library.
See Polysemy.Process.SystemProcess for its constructors.
The utility effect ProcessOutput takes care of decoding the process output, getting called by the Process
interpreters whenever a chunk was read, while accumulating chunks until they were decoded successfully.
See Polysemy.Process.ProcessOutput for its constructors.
The effect Pty abstracts pseudo terminals.
See Polysemy.Process.Pty for its constructors.
Effects
Process
data Process i o :: Effect Source #
Abstraction of a process with input and output.
This effect is intended to be used in a scoped_ manner:
import Polysemy.Resume
import Polysemy.Conc
import Polysemy.Process
import qualified System.Process.Typed as System
prog :: Member (Scoped_ (Process Text Text !! err)) r => Sem r Text
prog =
resumeAs "failed" do
withProcess do
send "input"
recv
main :: IO ()
main = do
out <- runConc $ interpretProcessNative (System.proc "cat" []) prog
putStrLn out
withProcess :: forall param i o r. Member (Scoped param (Process i o)) r => param -> InterpreterFor (Process i o) r Source #
withProcess_ :: forall i o r. Member (Scoped_ (Process i o)) r => InterpreterFor (Process i o) r Source #
withProcessOneshot :: forall param i o err r. Member (Scoped param (Process i o !! err)) r => param -> InterpreterFor (Process i o !! err) r Source #
withProcessOneshot_ :: forall i o err r. Member (Scoped_ (Process i o !! err)) r => InterpreterFor (Process i o !! err) r Source #
data ProcessOptions Source #
Controls the behaviour of Process interpreters.
Constructors
| ProcessOptions Bool Int ProcessKill |
Instances
| Show ProcessOptions Source # | |
Defined in Polysemy.Process.Data.ProcessOptions Methods showsPrec :: Int -> ProcessOptions -> ShowS # show :: ProcessOptions -> String # showList :: [ProcessOptions] -> ShowS # | |
| Default ProcessOptions Source # | |
Defined in Polysemy.Process.Data.ProcessOptions Methods def :: ProcessOptions # | |
| Eq ProcessOptions Source # | |
Defined in Polysemy.Process.Data.ProcessOptions Methods (==) :: ProcessOptions -> ProcessOptions -> Bool # (/=) :: ProcessOptions -> ProcessOptions -> Bool # | |
data ProcessKill Source #
Indicate whether to kill a process after exiting the scope in which it was used, if it hasn't terminated.
Constructors
| KillAfter NanoSeconds | Wait for the specified interval, then kill. |
| KillImmediately | Kill immediately. |
| KillNever | Wait indefinitely for the process to terminate. |
Instances
| Show ProcessKill Source # | |
Defined in Polysemy.Process.Data.ProcessKill Methods showsPrec :: Int -> ProcessKill -> ShowS # show :: ProcessKill -> String # showList :: [ProcessKill] -> ShowS # | |
| Eq ProcessKill Source # | |
Defined in Polysemy.Process.Data.ProcessKill | |
data ProcessError Source #
Signal error for Process.
Constructors
| Unknown Text | Something broke. |
| StartFailed SystemProcessScopeError | The process failed to start. |
| Exit ExitCode | The process terminated with exit code. |
Instances
| Show ProcessError Source # | |
Defined in Polysemy.Process.Data.ProcessError Methods showsPrec :: Int -> ProcessError -> ShowS # show :: ProcessError -> String # showList :: [ProcessError] -> ShowS # | |
| Eq ProcessError Source # | |
Defined in Polysemy.Process.Data.ProcessError | |
ProcessOutput
data ProcessOutput (p :: OutputPipe) a :: Effect Source #
This effect is used by the effect Process to accumulate and decode chunks of ByteStrings, for
example using a parser.
The interpreter may be stateful or stateless, since the constructor Chunk is expected to be called with both the
accumulated unprocessed output as well as the new chunk.
data OutputPipe Source #
Kind tag for selecting the ProcessOutput handler for stdout/stderr.
Instances
| Show OutputPipe Source # | |
Defined in Polysemy.Process.Effect.ProcessOutput Methods showsPrec :: Int -> OutputPipe -> ShowS # show :: OutputPipe -> String # showList :: [OutputPipe] -> ShowS # | |
| Eq OutputPipe Source # | |
Defined in Polysemy.Process.Effect.ProcessOutput | |
data ProcessOutputParseResult a Source #
An incremental parse result, potentially a partial result containing a continuation function.
Instances
| Show a => Show (ProcessOutputParseResult a) Source # | |
Defined in Polysemy.Process.Data.ProcessOutputParseResult Methods showsPrec :: Int -> ProcessOutputParseResult a -> ShowS # show :: ProcessOutputParseResult a -> String # showList :: [ProcessOutputParseResult a] -> ShowS # | |
ProcessInput
data ProcessInput a :: Effect Source #
This effect is used by the effect Process to encode values for process input.
example using a parser.
SystemProcess
data SystemProcess :: Effect Source #
Low-level interface for a process, operating on raw chunks of bytes. Interface is modeled after System.Process.
withSystemProcess :: forall param err r. Member (Scoped param (SystemProcess !! err)) r => param -> InterpreterFor (SystemProcess !! err) r Source #
Create a scoped resource for SystemProcess.
The process configuration may depend on the provided value of type param.
withSystemProcess_ :: forall err r. Member (Scoped_ (SystemProcess !! err)) r => InterpreterFor (SystemProcess !! err) r Source #
Create a scoped resource for SystemProcess.
The process configuration is provided to the interpreter statically.
A process ID.
Pty
withPty :: Member (Scoped_ Pty) r => InterpreterFor Pty r Source #
Bracket an action with the creation and destruction of a pseudo terminal.
Interpreters
Process
interpretProcess :: forall param proc i o r. Members (ProcessIO i o) r => Member (Scoped proc (SystemProcess !! SystemProcessError) !! SystemProcessScopeError) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> (param -> Sem (Stop ProcessError ': r) proc) -> InterpreterFor (Scoped param (Process i o) !! ProcessError) r Source #
Interpret Process with a system process resource whose file descriptors are connected to three TBMQueues,
deferring decoding of stdout and stderr to the interpreters of two ProcessOutput effects.
This variant:
- Models a daemon process that is not expected to terminate, causing Stop to be sent to the scope callsite instead
of individual Process actions.
- Is for parameterized scopes, meaning that a value of arbitrary type may be passed to
withProcessOneshotParam which is then passed to the supplied function to produce a SysProcConf
for the native process.
interpretProcessOneshot :: forall param proc i o r. Members (ProcessIO i o) r => Member (Scoped proc (SystemProcess !! SystemProcessError) !! SystemProcessScopeError) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> (param -> Sem (Stop SystemProcessScopeError ': r) proc) -> InterpreterFor (Scoped param (Process i o !! ProcessError) !! SystemProcessScopeError) r Source #
Interpret Process with a system process resource whose file descriptors are connected to three
TBMQueues, deferring decoding of stdout and stderr to the interpreters of two
ProcessOutput effects.
Unlike interpretProcess, this variant sends errors inside the scope to the individual Process
actions.
This variant is for parameterized scopes, meaning that a value of arbitrary type may be passed to
withProcessOneshotParam which is then passed to the supplied function to produce a SysProcConf
for the native process.
interpretProcessNative :: forall param i o r. Members (ProcessIO i o) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> (param -> Sem r (Either Text SysProcConf)) -> InterpreterFor (Scoped param (Process i o) !! ProcessError) r Source #
Interpret Process as a native SystemProcess.
This variant:
- Models a daemon process that is not expected to terminate, causing Stop to be sent to the scope callsite instead
of individual Process actions.
- Is for parameterized scopes, meaning that a value of arbitrary type may be passed to
withProcessOneshotParam which is then passed to the supplied function to produce a SysProcConf
for the native process.
interpretProcessOneshotNative :: forall param i o r. Members (ProcessIO i o) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> (param -> Sem r (Either Text SysProcConf)) -> InterpreterFor (Scoped param (Process i o !! ProcessError) !! SystemProcessScopeError) r Source #
Interpret Process as a native SystemProcess.
This variant is for parameterized scopes, meaning that a value of arbitrary type may be passed to
withProcessOneshotParam which is then passed to the supplied function to produce a SysProcConf
for the native process.
interpretProcess_ :: forall i o r. Member (Scoped_ (SystemProcess !! SystemProcessError) !! SystemProcessScopeError) r => Members [ProcessOutput 'Stdout o, ProcessOutput 'Stderr o, ProcessInput i, Resource, Race, Async, Embed IO] r => ProcessOptions -> InterpreterFor (Scoped_ (Process i o) !! ProcessError) r Source #
Interpret Process with a system process resource whose file descriptors are connected to three TBMQueues,
deferring decoding of stdout and stderr to the interpreters of two ProcessOutput effects.
This variant:
- Models a daemon process that is not expected to terminate, causing Stop to be sent to the scope callsite instead
of individual Process actions.
- Defers process config to SystemProcess.
interpretProcessOneshot_ :: forall proc i o r. Members (ProcessIO i o) r => Member (Scoped proc (SystemProcess !! SystemProcessError) !! SystemProcessScopeError) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> proc -> InterpreterFor (Scoped_ (Process i o !! ProcessError) !! SystemProcessScopeError) r Source #
Variant of interpretProcessOneshot that takes a static SysProcConf.
interpretProcessNative_ :: forall i o r. Members (ProcessIO i o) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> SysProcConf -> InterpreterFor (Scoped_ (Process i o) !! ProcessError) r Source #
Interpret Process as a native SystemProcess.
This variant:
- Models a daemon process that is not expected to terminate, causing Stop to be sent to the scope callsite instead
of individual Process actions.
- Defers process config to SystemProcess.
interpretProcessOneshotNative_ :: forall i o r. Members (ProcessIO i o) r => Members [Resource, Race, Async, Embed IO] r => ProcessOptions -> SysProcConf -> InterpreterFor (Scoped_ (Process i o !! ProcessError) !! SystemProcessScopeError) r Source #
Interpret Process as a native SystemProcess.
This variant takes a static SysProcConf.
interpretInputOutputProcess :: forall i o r. Member (Process i o) r => InterpretersFor [Input o, Output i] r Source #
interpretInputHandleBuffered :: Member (Embed IO) r => Handle -> InterpreterFor (Input ByteString !! ProcessError) r Source #
Interpret 'Input ByteString' by polling a Handle and stopping with ProcessError when it fails.
interpretInputHandle :: Member (Embed IO) r => Handle -> InterpreterFor (Input ByteString !! ProcessError) r Source #
Interpret 'Input ByteString' by polling a Handle and stopping with ProcessError when it fails.
This variant deactivates buffering for the Handle.
interpretOutputHandleBuffered :: Member (Embed IO) r => Handle -> InterpreterFor (Output ByteString !! ProcessError) r Source #
Interpret 'Output ByteString' by writing to a Handle and stopping with ProcessError when it fails.
interpretOutputHandle :: Member (Embed IO) r => Handle -> InterpreterFor (Output ByteString !! ProcessError) r Source #
Interpret 'Output ByteString' by writing to a Handle and stopping with ProcessError when it fails.
This variant deactivates buffering for the Handle.
interpretProcessIO :: forall i o ie oe r. Members [Input ByteString !! ie, Output ByteString !! oe] r => Members [ProcessInput i, ProcessOutput 'Stdout o, Resource, Race, Async, Embed IO] r => ProcessOptions -> InterpreterFor (Process i o !! ProcessError) r Source #
Interpret Process in terms of Input and Output.
Since the i and o parameters correspond to the abstraction of stdio fds of an external system process, i is
written by Output and o is read from Input.
This is useful to abstract the current process's stdio as an external process, with input and output swapped.
interpretProcessHandles :: forall i o r. Members [ProcessInput i, ProcessOutput 'Stdout o, Resource, Race, Async, Embed IO] r => ProcessOptions -> Handle -> Handle -> InterpreterFor (Process i o !! ProcessError) r Source #
Interpret Process in terms of two Handles.
This is useful to abstract the current process's stdio as an external process, with input and output swapped.
The first Handle argument corresponds to the o parameter, the second one to i, despite the first one usually
being the current process's stdin.
This is due to Process abstracting an external process to whose stdin would be written, while the current one's
is read.
interpretProcessCurrent :: Members [ProcessInput i, ProcessOutput 'Stdout o, Resource, Race, Async, Embed IO] r => ProcessOptions -> InterpreterFor (Process i o !! ProcessError) r Source #
Interpret Process using the current process's stdin and stdout.
This mirrors the usual abstraction of an external process, to whose stdin would be written, while the current one's
is read.
ProcessIO
type ProcessIO i o = [ProcessInput i, ProcessOutput 'Stdout o, ProcessOutput 'Stderr o] Source #
The effects used by Process to send and receive chunks of bytes to and from a process.
interpretProcessByteString :: InterpretersFor (ProcessIO ByteString ByteString) r Source #
Interpret ProcessIO with plain ByteStrings without chunking.
Silently discards stderr.
interpretProcessByteStringLines :: InterpretersFor (ProcessIO ByteString ByteString) r Source #
Interpret ProcessIO with ByteStrings chunked as lines.
Silently discards stderr.
ProcessOutput
interpretProcessOutputIgnore :: forall p a r. InterpreterFor (ProcessOutput p a) r Source #
Interpret ProcessOutput by discarding any output.
interpretProcessOutputId :: forall p r. InterpreterFor (ProcessOutput p ByteString) r Source #
Interpret ProcessOutput by immediately emitting raw ByteStrings without accumulation.
interpretProcessOutputLeft :: forall p a b r. Member (ProcessOutput p a) r => InterpreterFor (ProcessOutput p (Either a b)) r Source #
Transformer for ProcessOutput that lifts results into Left, creating 'ProcessOutput p (Either a b)' from
'ProcessOutput p a'.
interpretProcessOutputRight :: forall p a b r. Member (ProcessOutput p b) r => InterpreterFor (ProcessOutput p (Either a b)) r Source #
Transformer for ProcessOutput that lifts results into Right, creating 'ProcessOutput p (Either a b)' from
'ProcessOutput p b'.
interpretProcessOutputLines :: forall p r. InterpreterFor (ProcessOutput p ByteString) r Source #
Interpret ProcessOutput by emitting individual ByteString lines of output.
interpretProcessOutputText :: forall p r. InterpreterFor (ProcessOutput p Text) r Source #
Interpret ProcessOutput by immediately emitting Text without accumulation.
interpretProcessOutputTextLines :: forall p r. InterpreterFor (ProcessOutput p Text) r Source #
Interpret ProcessOutput by emitting individual Text lines of output.
interpretProcessOutputIncremental :: forall p a r. (ByteString -> ProcessOutputParseResult a) -> InterpreterFor (ProcessOutput p (Either Text a)) r Source #
Whenever a chunk of output arrives, call the supplied incremental parser whose result must be converted to
ProcessOutputParseResult.
If a partial parse result is produced, it is stored in the state and resumed when the next chunk is available.
If parsing an a succeeds, the parser recurses until it fails.
ProcessInput
interpretProcessInputId :: InterpreterFor (ProcessInput ByteString) r Source #
Interpret ProcessInput by passing ByteString through.
interpretProcessInputText :: InterpreterFor (ProcessInput Text) r Source #
Interpret ProcessInput by UTF-8-encoding Text.
SystemProcess
type SysProcConf = ProcessConfig () () () Source #
Convenience alias for a vanilla ProcessConfig, which will usually be transformed by interpreters to use Handles.
type PipesProcess = Process Handle Handle Handle Source #
Convenience alias for the Process type used by native interpreters.
data SystemProcessError Source #
Error for SystemProcess.
Instances
| Show SystemProcessError Source # | |
Defined in Polysemy.Process.Data.SystemProcessError Methods showsPrec :: Int -> SystemProcessError -> ShowS # show :: SystemProcessError -> String # showList :: [SystemProcessError] -> ShowS # | |
| Eq SystemProcessError Source # | |
Defined in Polysemy.Process.Data.SystemProcessError Methods (==) :: SystemProcessError -> SystemProcessError -> Bool # (/=) :: SystemProcessError -> SystemProcessError -> Bool # | |
data SystemProcessScopeError Source #
Error for the scope of SystemProcess.
Instances
| Show SystemProcessScopeError Source # | |
Defined in Polysemy.Process.Data.SystemProcessError Methods showsPrec :: Int -> SystemProcessScopeError -> ShowS # show :: SystemProcessScopeError -> String # showList :: [SystemProcessScopeError] -> ShowS # | |
| Eq SystemProcessScopeError Source # | |
Defined in Polysemy.Process.Data.SystemProcessError Methods (==) :: SystemProcessScopeError -> SystemProcessScopeError -> Bool # (/=) :: SystemProcessScopeError -> SystemProcessScopeError -> Bool # | |
interpretSystemProcessNative :: forall param r. Members [Resource, Embed IO] r => (param -> Sem r (Either Text SysProcConf)) -> InterpreterFor (Scoped param (SystemProcess !! SystemProcessError) !! SystemProcessScopeError) r Source #
Interpret SystemProcess as a scoped Process that's started wherever withSystemProcess
is called and terminated when the wrapped action finishes.
This variant is for parameterized scopes, allowing the consumer to supply a value of type param to create the
process config.
interpretSystemProcessNative_ :: forall r. Members [Resource, Embed IO] r => SysProcConf -> InterpreterFor (Scoped_ (SystemProcess !! SystemProcessError) !! SystemProcessScopeError) r Source #
Interpret SystemProcess as a scoped Process that's started wherever withSystemProcess
is called and terminated when the wrapped action finishes.
This variant takes a static SysProcConf.
interpretSystemProcessWithProcess :: forall r. Member (Embed IO) r => Process Handle Handle Handle -> InterpreterFor (SystemProcess !! SystemProcessError) r Source #
Interpret SystemProcess with a concrete Process with connected pipes.
handleSystemProcessWithProcess :: forall r r0 a. Members [Stop SystemProcessError, Embed IO] r => Process Handle Handle Handle -> SystemProcess (Sem r0) a -> Sem r a Source #
Handle SystemProcess with a concrete Process with connected pipes.
interpretSystemProcessNativeSingle :: forall r. Members [Stop SystemProcessScopeError, Resource, Embed IO] r => SysProcConf -> InterpreterFor (SystemProcess !! SystemProcessError) r Source #
Interpret SystemProcess as a single global Process that's started immediately.
interpretSystemProcessWithProcessOpaque :: forall i o e r. Member (Embed IO) r => Process i o e -> InterpreterFor (SystemProcess !! SystemProcessError) r Source #
Interpret SystemProcess with a concrete Process with no connection to stdio.
interpretSystemProcessNativeOpaqueSingle :: forall i o e r. Members [Resource, Embed IO] r => ProcessConfig i o e -> InterpreterFor (SystemProcess !! SystemProcessError) r Source #
Interpret SystemProcess as a single global Process that's started immediately.
interpretSystemProcessNativeOpaque :: forall i o e r. Members [Resource, Embed IO] r => ProcessConfig i o e -> InterpreterFor (Scoped_ (SystemProcess !! SystemProcessError)) r Source #
Interpret SystemProcess as a scoped Process that's started wherever withSystemProcess
is called and terminated when the wrapped action finishes.
Pty
interpretPty :: Members [Resource, Embed IO] r => InterpreterFor (Scoped_ Pty !! PtyError) r Source #
Interpret Pty as a Pty.