polysemy-process-0.10.0.0: Polysemy effects for system processes
Safe HaskellSafe-Inferred
LanguageHaskell2010

Polysemy.Process.Effect.Process

Description

 
Synopsis

Documentation

data Process i o :: Effect where 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

Constructors

Recv :: Process i o m o 
Send :: i -> Process i o 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 r. Member (Process i o) r => Sem r o Source #

Obtain a chunk of output.

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

Send data to stdin.

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

Create a scoped_ resource for Process. The process configuration may depend on the provided value of type param. This variant models daemon processes that are expected to run forever, with Stop being sent to this function, if at all.

withProcessOneshot :: forall param i o err r. Member (Scoped param (Process i o !! err)) r => param -> InterpreterFor (Process i o !! err) r Source #

Create a scoped_ resource for Process. The process configuration may depend on the provided value of type param. This variant models processes that are expected to terminate, with Stop being sent to individual actions within the scope.

withProcess_ :: forall i o r. Member (Scoped_ (Process i o)) r => InterpreterFor (Process i o) r Source #

Create a scoped_ resource for Process. The process configuration is provided to the interpreter statically. This variant models daemon processes that are expected to run forever, with Stop being sent to this function, if at all.

withProcessOneshot_ :: forall i o err r. Member (Scoped_ (Process i o !! err)) r => InterpreterFor (Process i o !! err) r Source #

Create a scoped_ resource for Process. The process configuration is provided to the interpreter statically. This variant models processes that are expected to terminate, with Stop being sent to individual actions within the scope.

runProcessIO :: forall i o r. Member (Process i o) r => InterpretersFor [Output i, Input o] r Source #

Convert Output and Input to Process for a daemon process.

runProcessOneshotIO :: forall i o err r. Member (Process i o !! err) r => InterpretersFor [Output i !! err, Input o !! err] r Source #

Convert Output and Input to Process for a oneshot process.