module Polysemy.Process.Interpreter.ProcessOneshot where
import Polysemy.Conc.Effect.Race (Race)
import Polysemy.Resume (Stop, interpretScopedRWith_, type (!!))
import Polysemy.Scoped (Scoped, Scoped_)
import Polysemy.Process.Data.ProcessError (ProcessError)
import Polysemy.Process.Data.ProcessOptions (ProcessOptions)
import Polysemy.Process.Data.SystemProcessError (SystemProcessError, SystemProcessScopeError)
import Polysemy.Process.Effect.Process (Process)
import Polysemy.Process.Effect.SystemProcess (SystemProcess)
import Polysemy.Process.Interpreter.Process (ScopeEffects, handleProcessWithQueues, pscope, terminated)
import Polysemy.Process.Interpreter.ProcessIO (ProcessIO)
import Polysemy.Process.Interpreter.SystemProcess (SysProcConf, interpretSystemProcessNative)
interpretProcessOneshot ::
∀ 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
interpretProcessOneshot :: forall param proc i o (r :: EffectRow).
(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
interpretProcessOneshot ProcessOptions
options param -> Sem (Stop SystemProcessScopeError : r) proc
proc =
forall (extra :: EffectRow) param (effect :: (* -> *) -> * -> *) eo
ei (r :: EffectRow).
KnownList extra =>
(forall (q :: (* -> *) -> * -> *) x.
param
-> Sem (extra ++ (Stop eo : Opaque q : r)) x
-> Sem (Stop eo : Opaque q : r) x)
-> (forall (q :: (* -> *) -> * -> *) (r0 :: EffectRow) x.
effect (Sem r0) x
-> Sem (Stop ei : (extra ++ (Stop eo : Opaque q : r))) x)
-> InterpreterFor (Scoped param (effect !! ei) !! eo) r
interpretScopedRWith_ @(ScopeEffects i o SystemProcessError)
(\ param
p -> forall serr i o param proc err (r :: EffectRow).
(Members
'[Scoped proc (SystemProcess !! err) !! serr, Stop serr] r,
Members
'[ProcessInput i, ProcessOutput 'Stdout o, ProcessOutput 'Stderr o,
Resource, Race, Async, Embed IO]
r) =>
ProcessOptions
-> (param -> Sem r proc)
-> param
-> InterpretersFor (ScopeEffects i o err) r
pscope @SystemProcessScopeError ProcessOptions
options (Sem (Stop SystemProcessScopeError : r) proc
-> Sem (Stop SystemProcessScopeError : Opaque q : r) proc
forall (e2 :: (* -> *) -> * -> *) (e1 :: (* -> *) -> * -> *)
(r :: EffectRow) a.
Sem (e1 : r) a -> Sem (e1 : e2 : r) a
raiseUnder (Sem (Stop SystemProcessScopeError : r) proc
-> Sem (Stop SystemProcessScopeError : Opaque q : r) proc)
-> (param -> Sem (Stop SystemProcessScopeError : r) proc)
-> param
-> Sem (Stop SystemProcessScopeError : Opaque q : r) proc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. param -> Sem (Stop SystemProcessScopeError : r) proc
proc) param
p)
((forall x.
Text
-> Sem
(Stop ProcessError
: Queue (In i) : Queue (Out o) : Sync ()
: (SystemProcess !! SystemProcessError)
: Stop SystemProcessScopeError : Opaque q : r)
x)
-> Process i o (Sem r0) x
-> Sem
(Stop ProcessError
: Queue (In i) : Queue (Out o) : Sync ()
: (SystemProcess !! SystemProcessError)
: Stop SystemProcessScopeError : Opaque q : r)
x
forall i o (m :: * -> *) (r :: EffectRow) a.
Members '[Queue (In i), Queue (Out o), Stop ProcessError] r =>
(forall x. Text -> Sem r x) -> Process i o m a -> Sem r a
handleProcessWithQueues forall (r :: EffectRow) a.
Members
'[SystemProcess !! SystemProcessError, Stop ProcessError] r =>
Text -> Sem r a
forall x.
Text
-> Sem
(Stop ProcessError
: Queue (In i) : Queue (Out o) : Sync ()
: (SystemProcess !! SystemProcessError)
: Stop SystemProcessScopeError : Opaque q : r)
x
terminated)
interpretProcessOneshot_ ::
∀ 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
interpretProcessOneshot_ :: forall proc i o (r :: EffectRow).
(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
interpretProcessOneshot_ ProcessOptions
options proc
proc =
ProcessOptions
-> (() -> Sem (Stop SystemProcessScopeError : r) proc)
-> InterpreterFor
(Scoped () (Process i o !! ProcessError)
!! SystemProcessScopeError)
r
forall param proc i o (r :: EffectRow).
(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
interpretProcessOneshot ProcessOptions
options (Sem (Stop SystemProcessScopeError : r) proc
-> () -> Sem (Stop SystemProcessScopeError : r) proc
forall a b. a -> b -> a
const (proc -> Sem (Stop SystemProcessScopeError : r) proc
forall (f :: * -> *) a. Applicative f => a -> f a
pure proc
proc))
interpretProcessOneshotNative ::
∀ 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
interpretProcessOneshotNative :: forall param i o (r :: EffectRow).
(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
interpretProcessOneshotNative ProcessOptions
options param -> Sem r (Either Text SysProcConf)
proc =
(Either Text SysProcConf -> Sem r (Either Text SysProcConf))
-> InterpreterFor
(Scoped
(Either Text SysProcConf) (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
r
forall param (r :: EffectRow).
Members '[Resource, Embed IO] r =>
(param -> Sem r (Either Text SysProcConf))
-> InterpreterFor
(Scoped param (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
r
interpretSystemProcessNative Either Text SysProcConf -> Sem r (Either Text SysProcConf)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Sem
((Scoped
(Either Text SysProcConf) (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem r a)
-> (Sem
((Scoped param (Process i o !! ProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem
((Scoped
(Either Text SysProcConf) (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a)
-> Sem
((Scoped param (Process i o !! ProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem r a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ProcessOptions
-> (param
-> Sem
(Stop SystemProcessScopeError
: (Scoped
(Either Text SysProcConf) (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
(Either Text SysProcConf))
-> InterpreterFor
(Scoped param (Process i o !! ProcessError)
!! SystemProcessScopeError)
((Scoped
(Either Text SysProcConf) (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
forall param proc i o (r :: EffectRow).
(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
interpretProcessOneshot ProcessOptions
options (forall (index :: Nat) (inserted :: EffectRow) (head :: EffectRow)
(oldTail :: EffectRow) (tail :: EffectRow) (old :: EffectRow)
(full :: EffectRow) a.
(ListOfLength index head, WhenStuck index InsertAtUnprovidedIndex,
old ~ Append head oldTail, tail ~ Append inserted oldTail,
full ~ Append head tail,
InsertAtIndex index head tail oldTail full inserted) =>
Sem old a -> Sem full a
insertAt @0 (Sem r (Either Text SysProcConf)
-> Sem
(Stop SystemProcessScopeError
: (Scoped
(Either Text SysProcConf) (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
(Either Text SysProcConf))
-> (param -> Sem r (Either Text SysProcConf))
-> param
-> Sem
(Stop SystemProcessScopeError
: (Scoped
(Either Text SysProcConf) (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
(Either Text SysProcConf)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. param -> Sem r (Either Text SysProcConf)
proc) (Sem
((Scoped param (Process i o !! ProcessError)
!! SystemProcessScopeError)
: (Scoped
(Either Text SysProcConf) (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem
((Scoped
(Either Text SysProcConf) (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a)
-> (Sem
((Scoped param (Process i o !! ProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem
((Scoped param (Process i o !! ProcessError)
!! SystemProcessScopeError)
: (Scoped
(Either Text SysProcConf) (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a)
-> Sem
((Scoped param (Process i o !! ProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem
((Scoped
(Either Text SysProcConf) (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Sem
((Scoped param (Process i o !! ProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem
((Scoped param (Process i o !! ProcessError)
!! SystemProcessScopeError)
: (Scoped
(Either Text SysProcConf) (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a
forall (e2 :: (* -> *) -> * -> *) (e1 :: (* -> *) -> * -> *)
(r :: EffectRow) a.
Sem (e1 : r) a -> Sem (e1 : e2 : r) a
raiseUnder
interpretProcessOneshotNative_ ::
∀ 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
interpretProcessOneshotNative_ :: forall i o (r :: EffectRow).
(Members (ProcessIO i o) r,
Members '[Resource, Race, Async, Embed IO] r) =>
ProcessOptions
-> SysProcConf
-> InterpreterFor
(Scoped_ (Process i o !! ProcessError) !! SystemProcessScopeError)
r
interpretProcessOneshotNative_ ProcessOptions
options SysProcConf
proc =
(SysProcConf -> Sem r (Either Text SysProcConf))
-> InterpreterFor
(Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
r
forall param (r :: EffectRow).
Members '[Resource, Embed IO] r =>
(param -> Sem r (Either Text SysProcConf))
-> InterpreterFor
(Scoped param (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
r
interpretSystemProcessNative (Either Text SysProcConf -> Sem r (Either Text SysProcConf)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either Text SysProcConf -> Sem r (Either Text SysProcConf))
-> (SysProcConf -> Either Text SysProcConf)
-> SysProcConf
-> Sem r (Either Text SysProcConf)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SysProcConf -> Either Text SysProcConf
forall a b. b -> Either a b
Right) (Sem
((Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem r a)
-> (Sem
((Scoped () (Process i o !! ProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem
((Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a)
-> Sem
((Scoped () (Process i o !! ProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem r a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
ProcessOptions
-> (()
-> Sem
(Stop SystemProcessScopeError
: (Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
SysProcConf)
-> InterpreterFor
(Scoped () (Process i o !! ProcessError)
!! SystemProcessScopeError)
((Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
forall param proc i o (r :: EffectRow).
(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
interpretProcessOneshot ProcessOptions
options (Sem
(Stop SystemProcessScopeError
: (Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
SysProcConf
-> ()
-> Sem
(Stop SystemProcessScopeError
: (Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
SysProcConf
forall a b. a -> b -> a
const (SysProcConf
-> Sem
(Stop SystemProcessScopeError
: (Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
SysProcConf
forall (f :: * -> *) a. Applicative f => a -> f a
pure SysProcConf
proc)) (Sem
((Scoped () (Process i o !! ProcessError)
!! SystemProcessScopeError)
: (Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem
((Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a)
-> (Sem
((Scoped () (Process i o !! ProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem
((Scoped () (Process i o !! ProcessError)
!! SystemProcessScopeError)
: (Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a)
-> Sem
((Scoped () (Process i o !! ProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem
((Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Sem
((Scoped () (Process i o !! ProcessError)
!! SystemProcessScopeError)
: r)
a
-> Sem
((Scoped () (Process i o !! ProcessError)
!! SystemProcessScopeError)
: (Scoped SysProcConf (SystemProcess !! SystemProcessError)
!! SystemProcessScopeError)
: r)
a
forall (e2 :: (* -> *) -> * -> *) (e1 :: (* -> *) -> * -> *)
(r :: EffectRow) a.
Sem (e1 : r) a -> Sem (e1 : e2 : r) a
raiseUnder