module Ribosome.Host.Interpreter.Process.Stdio where import Data.Serialize (Serialize) import Polysemy.Process (Process, interpretProcessCurrent) import Ribosome.Host.Data.BootError (BootError (BootError)) import Ribosome.Host.IOStack (IOStack) import Ribosome.Host.Interpreter.Process.Cereal (interpretProcessInputCereal, interpretProcessOutputCereal) interpretProcessCerealStdio :: Serialize a => Members IOStack r => InterpreterFor (Process a (Either Text a)) r interpretProcessCerealStdio :: forall a (r :: EffectRow). (Serialize a, Members IOStack r) => InterpreterFor (Process a (Either Text a)) r interpretProcessCerealStdio = Sem (ProcessOutput 'Stdout (Either Text a) : r) a -> Sem r a forall a (r :: EffectRow). Serialize a => InterpreterFor (ProcessOutput 'Stdout (Either Text a)) r interpretProcessOutputCereal (Sem (ProcessOutput 'Stdout (Either Text a) : r) a -> Sem r a) -> (Sem (Process a (Either Text a) : r) a -> Sem (ProcessOutput 'Stdout (Either Text a) : r) a) -> Sem (Process a (Either Text a) : r) a -> Sem r a forall b c a. (b -> c) -> (a -> b) -> a -> c . Sem (ProcessInput a : ProcessOutput 'Stdout (Either Text a) : r) a -> Sem (ProcessOutput 'Stdout (Either Text a) : r) a forall a (r :: EffectRow). Serialize a => InterpreterFor (ProcessInput a) r interpretProcessInputCereal (Sem (ProcessInput a : ProcessOutput 'Stdout (Either Text a) : r) a -> Sem (ProcessOutput 'Stdout (Either Text a) : r) a) -> (Sem (Process a (Either Text a) : r) a -> Sem (ProcessInput a : ProcessOutput 'Stdout (Either Text a) : r) a) -> Sem (Process a (Either Text a) : r) a -> Sem (ProcessOutput 'Stdout (Either Text a) : r) a forall b c a. (b -> c) -> (a -> b) -> a -> c . ProcessOptions -> InterpreterFor (Resumable ProcessError (Process a (Either Text a))) (ProcessInput a : ProcessOutput 'Stdout (Either Text a) : r) forall i o (r :: EffectRow). Members '[ProcessInput i, ProcessOutput 'Stdout o, Resource, Race, Async, Embed IO] r => ProcessOptions -> InterpreterFor (Process i o !! ProcessError) r interpretProcessCurrent ProcessOptions forall a. Default a => a def (Sem (Resumable ProcessError (Process a (Either Text a)) : ProcessInput a : ProcessOutput 'Stdout (Either Text a) : r) a -> Sem (ProcessInput a : ProcessOutput 'Stdout (Either Text a) : r) a) -> (Sem (Process a (Either Text a) : r) a -> Sem (Resumable ProcessError (Process a (Either Text a)) : ProcessInput a : ProcessOutput 'Stdout (Either Text a) : r) a) -> Sem (Process a (Either Text a) : r) a -> Sem (ProcessInput a : ProcessOutput 'Stdout (Either Text a) : r) a forall b c a. (b -> c) -> (a -> b) -> a -> c . Sem (Resumable ProcessError (Process a (Either Text a)) : r) a -> Sem (Resumable ProcessError (Process a (Either Text a)) : ProcessInput a : ProcessOutput 'Stdout (Either Text a) : r) a forall (e2 :: (* -> *) -> * -> *) (e3 :: (* -> *) -> * -> *) (e1 :: (* -> *) -> * -> *) (r :: EffectRow) a. Sem (e1 : r) a -> Sem (e1 : e2 : e3 : r) a raiseUnder2 (Sem (Resumable ProcessError (Process a (Either Text a)) : r) a -> Sem (Resumable ProcessError (Process a (Either Text a)) : ProcessInput a : ProcessOutput 'Stdout (Either Text a) : r) a) -> (Sem (Process a (Either Text a) : r) a -> Sem (Resumable ProcessError (Process a (Either Text a)) : r) a) -> Sem (Process a (Either Text a) : r) a -> Sem (Resumable ProcessError (Process a (Either Text a)) : ProcessInput a : ProcessOutput 'Stdout (Either Text a) : r) a forall b c a. (b -> c) -> (a -> b) -> a -> c . (ProcessError -> BootError) -> Sem (Process a (Either Text a) : Resumable ProcessError (Process a (Either Text a)) : r) a -> Sem (Resumable ProcessError (Process a (Either Text a)) : r) a forall err (eff :: (* -> *) -> * -> *) err' (r :: EffectRow) a. Members '[Resumable err eff, Error err'] r => (err -> err') -> Sem (eff : r) a -> Sem r a resumeHoistError (Text -> BootError BootError (Text -> BootError) -> (ProcessError -> Text) -> ProcessError -> BootError forall b c a. (b -> c) -> (a -> b) -> a -> c . forall b a. (Show a, IsString b) => a -> b show @Text) (Sem (Process a (Either Text a) : Resumable ProcessError (Process a (Either Text a)) : r) a -> Sem (Resumable ProcessError (Process a (Either Text a)) : r) a) -> (Sem (Process a (Either Text a) : r) a -> Sem (Process a (Either Text a) : Resumable ProcessError (Process a (Either Text a)) : r) a) -> Sem (Process a (Either Text a) : r) a -> Sem (Resumable ProcessError (Process a (Either Text a)) : r) a forall b c a. (b -> c) -> (a -> b) -> a -> c . Sem (Process a (Either Text a) : r) a -> Sem (Process a (Either Text a) : Resumable ProcessError (Process a (Either Text a)) : r) a forall (e2 :: (* -> *) -> * -> *) (e1 :: (* -> *) -> * -> *) (r :: EffectRow) a. Sem (e1 : r) a -> Sem (e1 : e2 : r) a raiseUnder