polysemy-process-0.5.1.1: Polysemy Effects for System Processes
Safe HaskellNone
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.

The values produced by the constructors are chunks of the process' output when using the default interpreter.

Effect

data Process i o e :: Effect 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 =
 withProcess do
   resumeAs "failed" do
     send "input"
     recv

main :: IO ()
main = do
  out <- runConc $ interpretProcessNative (System.proc "cat" []) prog
  putStrLn out

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 err r. Member (Scoped resource (Process i o e !! err)) r => InterpreterFor (Process i o e !! err) r Source #

Create a scoped resource for Process.

Interpreters

interpretProcessNative :: forall resource i o e err stdin stdout stderr r. Members [Resource, Race, Async, Embed IO] r => ProcessConfig stdin stdout stderr -> (forall x. Process stdin stdout stderr -> (resource -> Sem r x) -> Sem r x) -> (resource -> InterpreterFor (Process i o e !! err) r) -> InterpreterFor (Scoped resource (Process i o e !! err)) r Source #

Interpret Process with a system process resource.

interpretProcessIOE :: Members [Resource, Race, Async, Embed IO] r => Bool -> Int -> ProcessConfig () () () -> InterpreterFor (Scoped ProcessQueues (Process ByteString ByteString ByteString !! ProcessError)) r Source #

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