| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Polysemy.Process.Effect.Process
Description
Synopsis
- data Process i o :: Effect where
- 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
- withProcessOneshot :: forall param i o err r. Member (Scoped param (Process i o !! err)) r => param -> InterpreterFor (Process i o !! err) r
- withProcess_ :: forall i o r. Member (Scoped_ (Process i o)) r => InterpreterFor (Process i o) r
- withProcessOneshot_ :: forall i o err r. Member (Scoped_ (Process i o !! err)) r => InterpreterFor (Process i o !! err) r
- runProcessIO :: forall i o r. Member (Process i o) r => InterpretersFor [Output i, Input o] r
- runProcessOneshotIO :: forall i o err r. Member (Process i o !! err) r => InterpretersFor [Output i !! err, Input o !! err] r
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
withProcess :: forall param i o r. Member (Scoped param (Process i o)) r => param -> 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 #
withProcess_ :: forall i o r. Member (Scoped_ (Process i o)) r => InterpreterFor (Process i o) r Source #
withProcessOneshot_ :: forall i o err r. Member (Scoped_ (Process i o !! err)) r => InterpreterFor (Process i o !! err) r Source #
runProcessIO :: forall i o r. Member (Process i o) r => InterpretersFor [Output i, Input o] r Source #