polysemy-process-0.8.0.0: Polysemy Effects for System Processes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Polysemy.Process

Description

 
Synopsis

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 e :: Effect where Source #

Abstraction of a process with stdinstdoutstderr.

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 resource (Process Text Text e !! 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

Constructors

Recv :: Process i o e m o 
RecvError :: Process i o e m e 
Send :: i -> Process i o e m () 

Instances

Instances details
type DefiningModule Process Source # 
Instance details

Defined in Polysemy.Process.Effect.Process

type DefiningModule Process = "Polysemy.Process.Effect.Process"

recv :: forall i o e r. Member (Process i o e) r => Sem r o Source #

Obtain a chunk of stdout.

recvError :: forall i o e r. Member (Process i o e) r => Sem r e Source #

Obtain a chunk of stderr.

send :: forall i o e r. Member (Process i o e) r => i -> Sem r () Source #

Send data to stdin.

withProcess :: forall resource i o e r. Member (Scoped resource (Process i o e)) r => InterpreterFor (Process i o e) r Source #

Create a scoped resource for Process.

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

Instances details
Show ProcessKill Source # 
Instance details

Defined in Polysemy.Process.Data.ProcessKill

Eq ProcessKill Source # 
Instance details

Defined in Polysemy.Process.Data.ProcessKill

ProcessOutput

data ProcessOutput 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.

Instances

Instances details
type DefiningModule ProcessOutput Source # 
Instance details

Defined in Polysemy.Process.Effect.ProcessOutput

type DefiningModule ProcessOutput = "Polysemy.Process.Effect.ProcessOutput"

SystemProcess

data SystemProcess :: Effect Source #

Low-level interface for a process, operating on raw chunks of bytes. Interface is modeled after System.Process.

Instances

Instances details
type DefiningModule SystemProcess Source # 
Instance details

Defined in Polysemy.Process.Effect.SystemProcess

type DefiningModule SystemProcess = "Polysemy.Process.Effect.SystemProcess"

withSystemProcess :: forall resource err r. Member (Scoped resource (SystemProcess !! err)) r => InterpreterFor (SystemProcess !! err) r Source #

Create a scoped resource for SystemProcess.

Pty

data Pty :: Effect Source #

A pseudo terminal, to be scoped with withPty.

Instances

Instances details
type DefiningModule Pty Source # 
Instance details

Defined in Polysemy.Process.Effect.Pty

type DefiningModule Pty = "Polysemy.Process.Effect.Pty"

withPty :: forall resource r. Member (Scoped resource Pty) r => InterpreterFor Pty r Source #

Bracket an action with the creation and destruction of a pseudo terminal.

Interpreters

Process

interpretProcessByteStringNative Source #

Arguments

:: Members [Resource, Race, Async, Embed IO] r 
=> ProcessOptions

Whether to discard output chunks if the queue is full.

-> ProcessConfig () () () 
-> InterpreterFor (Scoped () (Process ByteString ByteString ByteString) !! ProcessError) r 

Interpret Process as a native SystemProcess, producing unaccumulated chunks of ByteString.

interpretProcessByteStringLinesNative Source #

Arguments

:: Members [Resource, Race, Async, Embed IO] r 
=> ProcessOptions 
-> ProcessConfig () () ()

Basic config. The pipes will be changed to Handle by the interpreter.

-> InterpreterFor (Scoped () (Process ByteString ByteString ByteString) !! ProcessError) r 

Interpret Process as a native SystemProcess, producing lines of ByteString.

interpretProcessTextNative Source #

Arguments

:: Members [Resource, Race, Async, Embed IO] r 
=> ProcessOptions 
-> ProcessConfig () () ()

Basic config. The pipes will be changed to Handle by the interpreter.

-> InterpreterFor (Scoped () (Process ByteString Text Text) !! ProcessError) r 

Interpret Process as a native SystemProcess, producing unaccumulated chunks of Text.

interpretProcessTextLinesNative Source #

Arguments

:: Members [Resource, Race, Async, Embed IO] r 
=> ProcessOptions 
-> ProcessConfig () () ()

Basic config. The pipes will be changed to Handle by the interpreter.

-> InterpreterFor (Scoped () (Process ByteString Text Text) !! ProcessError) r 

Interpret Process as a native SystemProcess, producing lines of Text.

interpretProcess :: forall resource err o e r. Member (Scoped resource (SystemProcess !! err)) r => Members [ProcessOutput o, ProcessOutput e, Resource, Race, Async, Embed IO] r => ProcessOptions -> InterpreterFor (Scoped () (Process ByteString o e) !! 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.

interpretProcessByteString :: forall resource err r. Members [Scoped resource (SystemProcess !! err), Resource, Race, Async, Embed IO] r => ProcessOptions -> InterpreterFor (Scoped () (Process ByteString ByteString ByteString) !! ProcessError) r Source #

Interpret Process with a system process resource whose file descriptors are connected to three TBMQueues, producing ByteStrings.

interpretProcessByteStringLines :: forall resource err r. Members [Scoped resource (SystemProcess !! err), Resource, Race, Async, Embed IO] r => ProcessOptions -> InterpreterFor (Scoped () (Process ByteString ByteString ByteString) !! ProcessError) r Source #

Interpret Process with a system process resource whose file descriptors are connected to three TBMQueues, producing chunks of lines of ByteStrings.

interpretProcessText :: forall resource err r. Members [Scoped resource (SystemProcess !! err), Resource, Race, Async, Embed IO] r => ProcessOptions -> InterpreterFor (Scoped () (Process ByteString Text Text) !! ProcessError) r Source #

Interpret Process with a system process resource whose file descriptors are connected to three TBMQueues, producing Texts.

interpretProcessTextLines :: forall resource err r. Members [Scoped resource (SystemProcess !! err), Resource, Race, Async, Embed IO] r => ProcessOptions -> InterpreterFor (Scoped () (Process ByteString Text Text) !! ProcessError) r Source #

Interpret Process with a system process resource whose file descriptors are connected to three TBMQueues, producing chunks of lines of Texts.

ProcessOutput

interpretProcessOutputId :: InterpreterFor (ProcessOutput ByteString) r Source #

Interpret ProcessOutput by immediately emitting raw ByteStrings without accumulation.

interpretProcessOutputLines :: InterpreterFor (ProcessOutput ByteString) r Source #

Interpret ProcessOutput by emitting individual ByteString lines of output.

interpretProcessOutputText :: InterpreterFor (ProcessOutput Text) r Source #

Interpret ProcessOutput by immediately emitting Text without accumulation.

interpretProcessOutputTextLines :: InterpreterFor (ProcessOutput Text) r Source #

Interpret ProcessOutput by emitting individual Text lines of output.

SystemProcess

interpretSystemProcessNativeSingle :: forall r. Members [Resource, Embed IO] r => ProcessConfig () () () -> InterpreterFor (SystemProcess !! SystemProcessError) r Source #

Interpret SystemProcess as a single global Process that's started immediately.

interpretSystemProcessNative :: forall r. Members [Resource, Embed IO] r => ProcessConfig () () () -> InterpreterFor (Scoped PipesProcess (SystemProcess !! SystemProcessError)) r Source #

Interpret SystemProcess as a scoped Process that's started wherever withSystemProcess is called and terminated when the wrapped action finishes.

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 connected pipes.

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 (Process i o e) (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

Tools

resolveExecutable Source #

Arguments

:: Member (Embed IO) r 
=> Path Rel File

Executable name, for $PATH lookup and error messages

-> Maybe (Path Abs File)

Explicit override to be checked for adequate permissions

-> Sem r (Either Text (Path Abs File)) 

Find a file in $PATH, verifying that it is executable by this process.