module Ribosome.Host.Interpreter.Process.Embed where import Data.Serialize (Serialize) import Polysemy.Process (Process, ProcessOptions, withProcess_) import System.Process.Typed (ProcessConfig, proc) import Ribosome.Host.Data.BootError (BootError (BootError)) import Ribosome.Host.Interpreter.Process.Cereal (interpretProcessCerealNative) nvimArgs :: [String] nvimArgs :: [String] nvimArgs = [Item [String] "--embed", Item [String] "-n", Item [String] "-u", Item [String] "NONE", Item [String] "-i", Item [String] "NONE", Item [String] "--clean", Item [String] "--headless"] nvimProc :: ProcessConfig () () () nvimProc :: ProcessConfig () () () nvimProc = String -> [String] -> ProcessConfig () () () proc String "nvim" [String] nvimArgs interpretProcessCerealNvimEmbed :: Serialize a => Members [Error BootError, Log, Resource, Race, Async, Embed IO] r => Maybe ProcessOptions -> Maybe (ProcessConfig () () ()) -> InterpreterFor (Process a (Either Text a)) r interpretProcessCerealNvimEmbed :: forall a (r :: EffectRow). (Serialize a, Members '[Error BootError, Log, Resource, Race, Async, Embed IO] r) => Maybe ProcessOptions -> Maybe (ProcessConfig () () ()) -> InterpreterFor (Process a (Either Text a)) r interpretProcessCerealNvimEmbed Maybe ProcessOptions options Maybe (ProcessConfig () () ()) conf = ProcessOptions -> ProcessConfig () () () -> InterpreterFor (Resumable ProcessError (Scoped () (Process a (Either Text a)))) r forall a (r :: EffectRow). (Serialize a, Members '[Log, Resource, Race, Async, Embed IO] r) => ProcessOptions -> ProcessConfig () () () -> InterpreterFor (Scoped () (Process a (Either Text a)) !! ProcessError) r interpretProcessCerealNative (ProcessOptions -> Maybe ProcessOptions -> ProcessOptions forall a. a -> Maybe a -> a fromMaybe ProcessOptions forall a. Default a => a def Maybe ProcessOptions options) (ProcessConfig () () () -> Maybe (ProcessConfig () () ()) -> ProcessConfig () () () forall a. a -> Maybe a -> a fromMaybe ProcessConfig () () () nvimProc Maybe (ProcessConfig () () ()) conf) (Sem (Resumable ProcessError (Scoped () (Process a (Either Text a))) : r) a -> Sem r a) -> (Sem (Process a (Either Text a) : r) a -> Sem (Resumable ProcessError (Scoped () (Process a (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 . (ProcessError -> BootError) -> Sem (Scoped () (Process a (Either Text a)) : Resumable ProcessError (Scoped () (Process a (Either Text a))) : r) a -> Sem (Resumable ProcessError (Scoped () (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 . ProcessError -> Text forall b a. (Show a, IsString b) => a -> b show) (Sem (Scoped () (Process a (Either Text a)) : Resumable ProcessError (Scoped () (Process a (Either Text a))) : r) a -> Sem (Resumable ProcessError (Scoped () (Process a (Either Text a))) : r) a) -> (Sem (Process a (Either Text a) : r) a -> Sem (Scoped () (Process a (Either Text a)) : Resumable ProcessError (Scoped () (Process a (Either Text a))) : r) a) -> Sem (Process a (Either Text a) : r) a -> Sem (Resumable ProcessError (Scoped () (Process a (Either Text a))) : r) a forall b c a. (b -> c) -> (a -> b) -> a -> c . forall resource i o (r :: EffectRow). Member (Scoped resource (Process i o)) r => InterpreterFor (Process i o) r withProcess_ @() (Sem (Process a (Either Text a) : Scoped () (Process a (Either Text a)) : Resumable ProcessError (Scoped () (Process a (Either Text a))) : r) a -> Sem (Scoped () (Process a (Either Text a)) : Resumable ProcessError (Scoped () (Process a (Either Text a))) : r) a) -> (Sem (Process a (Either Text a) : r) a -> Sem (Process a (Either Text a) : Scoped () (Process a (Either Text a)) : Resumable ProcessError (Scoped () (Process a (Either Text a))) : r) a) -> Sem (Process a (Either Text a) : r) a -> Sem (Scoped () (Process a (Either Text a)) : Resumable ProcessError (Scoped () (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) : Scoped () (Process a (Either Text a)) : Resumable ProcessError (Scoped () (Process a (Either Text a))) : r) a forall (e2 :: (* -> *) -> * -> *) (e3 :: (* -> *) -> * -> *) (e1 :: (* -> *) -> * -> *) (r :: EffectRow) a. Sem (e1 : r) a -> Sem (e1 : e2 : e3 : r) a raiseUnder2