{-# OPTIONS_GHC -fno-warn-dodgy-imports #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
module Effectful.Process.Typed
(
TypedProcess
, runTypedProcess
, startProcess
, stopProcess
, withProcessWait
, withProcessWait_
, withProcessTerm
, withProcessTerm_
, readProcess
, readProcess_
, runProcess
, runProcess_
, readProcessStdout
, readProcessStdout_
, readProcessStderr
, readProcessStderr_
, readProcessInterleaved
, readProcessInterleaved_
, waitExitCode
, getExitCode
, checkExitCode
, module Reexport
#if ! MIN_VERSION_typed_process(0,2,8)
, ExitCode(..)
#endif
) where
import System.Process.Typed as Reexport hiding
( startProcess
, stopProcess
, withProcessWait
, withProcessWait_
, withProcessTerm
, withProcessTerm_
, readProcess
, readProcess_
, runProcess
, runProcess_
, readProcessStdout
, readProcessStdout_
, readProcessStderr
, readProcessStderr_
, readProcessInterleaved
, readProcessInterleaved_
, waitExitCode
, getExitCode
, checkExitCode
)
import Data.ByteString.Lazy (ByteString)
import qualified System.Process.Typed as PT
import Effectful
import qualified Effectful.Process
import Effectful.Dispatch.Static
#if ! MIN_VERSION_typed_process(0,2,8)
import System.Exit (ExitCode(..))
#endif
type TypedProcess = Effectful.Process.Process
runTypedProcess :: IOE :> es => Eff (TypedProcess : es) a -> Eff es a
runTypedProcess :: forall (es :: [Effect]) a.
(IOE :> es) =>
Eff (TypedProcess : es) a -> Eff es a
runTypedProcess = Eff (TypedProcess : es) a -> Eff es a
forall (es :: [Effect]) a.
(IOE :> es) =>
Eff (TypedProcess : es) a -> Eff es a
Effectful.Process.runProcess
startProcess :: TypedProcess :> es
=> PT.ProcessConfig stdin stdout stderr
-> Eff es (PT.Process stdin stdout stderr)
startProcess :: forall (es :: [Effect]) stdin stdout stderr.
(TypedProcess :> es) =>
ProcessConfig stdin stdout stderr
-> Eff es (Process stdin stdout stderr)
startProcess = IO (Process stdin stdout stderr)
-> Eff es (Process stdin stdout stderr)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Process stdin stdout stderr)
-> Eff es (Process stdin stdout stderr))
-> (ProcessConfig stdin stdout stderr
-> IO (Process stdin stdout stderr))
-> ProcessConfig stdin stdout stderr
-> Eff es (Process stdin stdout stderr)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessConfig stdin stdout stderr
-> IO (Process stdin stdout stderr)
forall (m :: * -> *) stdin stdout stderr.
MonadIO m =>
ProcessConfig stdin stdout stderr
-> m (Process stdin stdout stderr)
PT.startProcess
stopProcess :: TypedProcess :> es => PT.Process stdin stdout stderr -> Eff es ()
stopProcess :: forall (es :: [Effect]) stdin stdout stderr.
(TypedProcess :> es) =>
Process stdin stdout stderr -> Eff es ()
stopProcess = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (Process stdin stdout stderr -> IO ())
-> Process stdin stdout stderr
-> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Process stdin stdout stderr -> IO ()
forall (m :: * -> *) stdin stdout stderr.
MonadIO m =>
Process stdin stdout stderr -> m ()
PT.stopProcess
withProcessWait :: TypedProcess :> es
=> PT.ProcessConfig stdin stdout stderr
-> (PT.Process stdin stdout stderr -> Eff es a)
-> Eff es a
withProcessWait :: forall (es :: [Effect]) stdin stdout stderr a.
(TypedProcess :> es) =>
ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a) -> Eff es a
withProcessWait = (ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a)
-> ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a)
-> Eff es a
forall (es :: [Effect]) stdin stdout stderr a.
(TypedProcess :> es) =>
(ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a)
-> ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a)
-> Eff es a
liftWithProcess ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a
forall (m :: * -> *) stdin stdout stderr a.
MonadUnliftIO m =>
ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> m a) -> m a
PT.withProcessWait
withProcessWait_ :: TypedProcess :> es
=> PT.ProcessConfig stdin stdout stderr
-> (PT.Process stdin stdout stderr -> Eff es a)
-> Eff es a
withProcessWait_ :: forall (es :: [Effect]) stdin stdout stderr a.
(TypedProcess :> es) =>
ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a) -> Eff es a
withProcessWait_ = (ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a)
-> ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a)
-> Eff es a
forall (es :: [Effect]) stdin stdout stderr a.
(TypedProcess :> es) =>
(ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a)
-> ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a)
-> Eff es a
liftWithProcess ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a
forall (m :: * -> *) stdin stdout stderr a.
MonadUnliftIO m =>
ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> m a) -> m a
PT.withProcessWait_
withProcessTerm :: TypedProcess :> es
=> PT.ProcessConfig stdin stdout stderr
-> (PT.Process stdin stdout stderr -> Eff es a)
-> Eff es a
withProcessTerm :: forall (es :: [Effect]) stdin stdout stderr a.
(TypedProcess :> es) =>
ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a) -> Eff es a
withProcessTerm = (ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a)
-> ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a)
-> Eff es a
forall (es :: [Effect]) stdin stdout stderr a.
(TypedProcess :> es) =>
(ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a)
-> ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a)
-> Eff es a
liftWithProcess ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a
forall (m :: * -> *) stdin stdout stderr a.
MonadUnliftIO m =>
ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> m a) -> m a
PT.withProcessTerm
withProcessTerm_ :: TypedProcess :> es
=> PT.ProcessConfig stdin stdout stderr
-> (PT.Process stdin stdout stderr -> Eff es a)
-> Eff es a
withProcessTerm_ :: forall (es :: [Effect]) stdin stdout stderr a.
(TypedProcess :> es) =>
ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a) -> Eff es a
withProcessTerm_ = (ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a)
-> ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a)
-> Eff es a
forall (es :: [Effect]) stdin stdout stderr a.
(TypedProcess :> es) =>
(ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a)
-> ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a)
-> Eff es a
liftWithProcess ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a
forall (m :: * -> *) stdin stdout stderr a.
MonadUnliftIO m =>
ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> m a) -> m a
PT.withProcessTerm_
readProcess :: TypedProcess :> es
=> PT.ProcessConfig stdin stdoutIgnored stderrIgnored
-> Eff es (ExitCode, ByteString, ByteString)
readProcess :: forall (es :: [Effect]) stdin stdoutIgnored stderrIgnored.
(TypedProcess :> es) =>
ProcessConfig stdin stdoutIgnored stderrIgnored
-> Eff es (ExitCode, ByteString, ByteString)
readProcess = IO (ExitCode, ByteString, ByteString)
-> Eff es (ExitCode, ByteString, ByteString)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (ExitCode, ByteString, ByteString)
-> Eff es (ExitCode, ByteString, ByteString))
-> (ProcessConfig stdin stdoutIgnored stderrIgnored
-> IO (ExitCode, ByteString, ByteString))
-> ProcessConfig stdin stdoutIgnored stderrIgnored
-> Eff es (ExitCode, ByteString, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessConfig stdin stdoutIgnored stderrIgnored
-> IO (ExitCode, ByteString, ByteString)
forall (m :: * -> *) stdin stdoutIgnored stderrIgnored.
MonadIO m =>
ProcessConfig stdin stdoutIgnored stderrIgnored
-> m (ExitCode, ByteString, ByteString)
PT.readProcess
readProcess_ :: TypedProcess :> es
=> PT.ProcessConfig stdin stdoutIgnored stderrIgnored
-> Eff es (ByteString, ByteString)
readProcess_ :: forall (es :: [Effect]) stdin stdoutIgnored stderrIgnored.
(TypedProcess :> es) =>
ProcessConfig stdin stdoutIgnored stderrIgnored
-> Eff es (ByteString, ByteString)
readProcess_ = IO (ByteString, ByteString) -> Eff es (ByteString, ByteString)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (ByteString, ByteString) -> Eff es (ByteString, ByteString))
-> (ProcessConfig stdin stdoutIgnored stderrIgnored
-> IO (ByteString, ByteString))
-> ProcessConfig stdin stdoutIgnored stderrIgnored
-> Eff es (ByteString, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessConfig stdin stdoutIgnored stderrIgnored
-> IO (ByteString, ByteString)
forall (m :: * -> *) stdin stdoutIgnored stderrIgnored.
MonadIO m =>
ProcessConfig stdin stdoutIgnored stderrIgnored
-> m (ByteString, ByteString)
PT.readProcess_
runProcess :: TypedProcess :> es
=> PT.ProcessConfig stdin stdout stderr
-> Eff es ExitCode
runProcess :: forall (es :: [Effect]) stdin stdout stderr.
(TypedProcess :> es) =>
ProcessConfig stdin stdout stderr -> Eff es ExitCode
runProcess = IO ExitCode -> Eff es ExitCode
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO ExitCode -> Eff es ExitCode)
-> (ProcessConfig stdin stdout stderr -> IO ExitCode)
-> ProcessConfig stdin stdout stderr
-> Eff es ExitCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessConfig stdin stdout stderr -> IO ExitCode
forall (m :: * -> *) stdin stdout stderr.
MonadIO m =>
ProcessConfig stdin stdout stderr -> m ExitCode
PT.runProcess
runProcess_ :: TypedProcess :> es
=> PT.ProcessConfig stdin stdout stderr
-> Eff es ()
runProcess_ :: forall (es :: [Effect]) stdin stdout stderr.
(TypedProcess :> es) =>
ProcessConfig stdin stdout stderr -> Eff es ()
runProcess_ = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (ProcessConfig stdin stdout stderr -> IO ())
-> ProcessConfig stdin stdout stderr
-> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessConfig stdin stdout stderr -> IO ()
forall (m :: * -> *) stdin stdout stderr.
MonadIO m =>
ProcessConfig stdin stdout stderr -> m ()
PT.runProcess_
readProcessStdout :: TypedProcess :> es
=> PT.ProcessConfig stdin stdoutIgnored stderr
-> Eff es (ExitCode, ByteString)
readProcessStdout :: forall (es :: [Effect]) stdin stdoutIgnored stderr.
(TypedProcess :> es) =>
ProcessConfig stdin stdoutIgnored stderr
-> Eff es (ExitCode, ByteString)
readProcessStdout = IO (ExitCode, ByteString) -> Eff es (ExitCode, ByteString)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (ExitCode, ByteString) -> Eff es (ExitCode, ByteString))
-> (ProcessConfig stdin stdoutIgnored stderr
-> IO (ExitCode, ByteString))
-> ProcessConfig stdin stdoutIgnored stderr
-> Eff es (ExitCode, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessConfig stdin stdoutIgnored stderr
-> IO (ExitCode, ByteString)
forall (m :: * -> *) stdin stdoutIgnored stderr.
MonadIO m =>
ProcessConfig stdin stdoutIgnored stderr
-> m (ExitCode, ByteString)
PT.readProcessStdout
readProcessStdout_ :: TypedProcess :> es
=> PT.ProcessConfig stdin stdoutIgnored stderr
-> Eff es ByteString
readProcessStdout_ :: forall (es :: [Effect]) stdin stdoutIgnored stderr.
(TypedProcess :> es) =>
ProcessConfig stdin stdoutIgnored stderr -> Eff es ByteString
readProcessStdout_ = IO ByteString -> Eff es ByteString
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO ByteString -> Eff es ByteString)
-> (ProcessConfig stdin stdoutIgnored stderr -> IO ByteString)
-> ProcessConfig stdin stdoutIgnored stderr
-> Eff es ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessConfig stdin stdoutIgnored stderr -> IO ByteString
forall (m :: * -> *) stdin stdoutIgnored stderr.
MonadIO m =>
ProcessConfig stdin stdoutIgnored stderr -> m ByteString
PT.readProcessStdout_
readProcessStderr :: TypedProcess :> es
=> PT.ProcessConfig stdin stdout stderrIgnored
-> Eff es (ExitCode, ByteString)
readProcessStderr :: forall (es :: [Effect]) stdin stdoutIgnored stderr.
(TypedProcess :> es) =>
ProcessConfig stdin stdoutIgnored stderr
-> Eff es (ExitCode, ByteString)
readProcessStderr = IO (ExitCode, ByteString) -> Eff es (ExitCode, ByteString)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (ExitCode, ByteString) -> Eff es (ExitCode, ByteString))
-> (ProcessConfig stdin stdout stderrIgnored
-> IO (ExitCode, ByteString))
-> ProcessConfig stdin stdout stderrIgnored
-> Eff es (ExitCode, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessConfig stdin stdout stderrIgnored
-> IO (ExitCode, ByteString)
forall (m :: * -> *) stdin stdoutIgnored stderr.
MonadIO m =>
ProcessConfig stdin stdoutIgnored stderr
-> m (ExitCode, ByteString)
PT.readProcessStderr
readProcessStderr_ :: TypedProcess :> es
=> PT.ProcessConfig stdin stdout stderrIgnored
-> Eff es ByteString
readProcessStderr_ :: forall (es :: [Effect]) stdin stdoutIgnored stderr.
(TypedProcess :> es) =>
ProcessConfig stdin stdoutIgnored stderr -> Eff es ByteString
readProcessStderr_ = IO ByteString -> Eff es ByteString
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO ByteString -> Eff es ByteString)
-> (ProcessConfig stdin stdout stderrIgnored -> IO ByteString)
-> ProcessConfig stdin stdout stderrIgnored
-> Eff es ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessConfig stdin stdout stderrIgnored -> IO ByteString
forall (m :: * -> *) stdin stdoutIgnored stderr.
MonadIO m =>
ProcessConfig stdin stdoutIgnored stderr -> m ByteString
PT.readProcessStderr_
readProcessInterleaved :: TypedProcess :> es
=> PT.ProcessConfig stdin stdoutIgnored stderrIgnored
-> Eff es (ExitCode, ByteString)
readProcessInterleaved :: forall (es :: [Effect]) stdin stdoutIgnored stderr.
(TypedProcess :> es) =>
ProcessConfig stdin stdoutIgnored stderr
-> Eff es (ExitCode, ByteString)
readProcessInterleaved = IO (ExitCode, ByteString) -> Eff es (ExitCode, ByteString)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (ExitCode, ByteString) -> Eff es (ExitCode, ByteString))
-> (ProcessConfig stdin stdoutIgnored stderrIgnored
-> IO (ExitCode, ByteString))
-> ProcessConfig stdin stdoutIgnored stderrIgnored
-> Eff es (ExitCode, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessConfig stdin stdoutIgnored stderrIgnored
-> IO (ExitCode, ByteString)
forall (m :: * -> *) stdin stdoutIgnored stderr.
MonadIO m =>
ProcessConfig stdin stdoutIgnored stderr
-> m (ExitCode, ByteString)
PT.readProcessInterleaved
readProcessInterleaved_ :: TypedProcess :> es
=> PT.ProcessConfig stdin stdoutIgnored stderrIgnored
-> Eff es ByteString
readProcessInterleaved_ :: forall (es :: [Effect]) stdin stdoutIgnored stderr.
(TypedProcess :> es) =>
ProcessConfig stdin stdoutIgnored stderr -> Eff es ByteString
readProcessInterleaved_ = IO ByteString -> Eff es ByteString
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO ByteString -> Eff es ByteString)
-> (ProcessConfig stdin stdoutIgnored stderrIgnored
-> IO ByteString)
-> ProcessConfig stdin stdoutIgnored stderrIgnored
-> Eff es ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessConfig stdin stdoutIgnored stderrIgnored -> IO ByteString
forall (m :: * -> *) stdin stdoutIgnored stderr.
MonadIO m =>
ProcessConfig stdin stdoutIgnored stderr -> m ByteString
PT.readProcessInterleaved_
waitExitCode :: TypedProcess :> es
=> PT.Process stdin stdout stderr
-> Eff es ExitCode
waitExitCode :: forall (es :: [Effect]) stdin stdout stderr.
(TypedProcess :> es) =>
Process stdin stdout stderr -> Eff es ExitCode
waitExitCode = IO ExitCode -> Eff es ExitCode
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO ExitCode -> Eff es ExitCode)
-> (Process stdin stdout stderr -> IO ExitCode)
-> Process stdin stdout stderr
-> Eff es ExitCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Process stdin stdout stderr -> IO ExitCode
forall (m :: * -> *) stdin stdout stderr.
MonadIO m =>
Process stdin stdout stderr -> m ExitCode
PT.waitExitCode
getExitCode :: TypedProcess :> es
=> PT.Process stdin stdout stderr
-> Eff es (Maybe ExitCode)
getExitCode :: forall (es :: [Effect]) stdin stdout stderr.
(TypedProcess :> es) =>
Process stdin stdout stderr -> Eff es (Maybe ExitCode)
getExitCode = IO (Maybe ExitCode) -> Eff es (Maybe ExitCode)
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO (Maybe ExitCode) -> Eff es (Maybe ExitCode))
-> (Process stdin stdout stderr -> IO (Maybe ExitCode))
-> Process stdin stdout stderr
-> Eff es (Maybe ExitCode)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Process stdin stdout stderr -> IO (Maybe ExitCode)
forall (m :: * -> *) stdin stdout stderr.
MonadIO m =>
Process stdin stdout stderr -> m (Maybe ExitCode)
PT.getExitCode
checkExitCode :: TypedProcess :> es
=> PT.Process stdin stdout stderr
-> Eff es ()
checkExitCode :: forall (es :: [Effect]) stdin stdout stderr.
(TypedProcess :> es) =>
Process stdin stdout stderr -> Eff es ()
checkExitCode = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ())
-> (Process stdin stdout stderr -> IO ())
-> Process stdin stdout stderr
-> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Process stdin stdout stderr -> IO ()
forall (m :: * -> *) stdin stdout stderr.
MonadIO m =>
Process stdin stdout stderr -> m ()
PT.checkExitCode
liftWithProcess :: TypedProcess :> es
=> (PT.ProcessConfig stdin stdout stderr -> (PT.Process stdin stdout stderr -> IO a) -> IO a)
-> PT.ProcessConfig stdin stdout stderr
-> (PT.Process stdin stdout stderr -> Eff es a)
-> Eff es a
liftWithProcess :: forall (es :: [Effect]) stdin stdout stderr a.
(TypedProcess :> es) =>
(ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a)
-> ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> Eff es a)
-> Eff es a
liftWithProcess ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a
k ProcessConfig stdin stdout stderr
pc Process stdin stdout stderr -> Eff es a
f = (Env es -> IO a) -> Eff es a
forall (es :: [Effect]) a. (Env es -> IO a) -> Eff es a
unsafeEff ((Env es -> IO a) -> Eff es a) -> (Env es -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \Env es
es ->
Env es -> ((forall r. Eff es r -> IO r) -> IO a) -> IO a
forall (es :: [Effect]) a.
HasCallStack =>
Env es -> ((forall r. Eff es r -> IO r) -> IO a) -> IO a
seqUnliftIO Env es
es (((forall r. Eff es r -> IO r) -> IO a) -> IO a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
runInIO ->
ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a) -> IO a
k ProcessConfig stdin stdout stderr
pc (Eff es a -> IO a
forall r. Eff es r -> IO r
runInIO (Eff es a -> IO a)
-> (Process stdin stdout stderr -> Eff es a)
-> Process stdin stdout stderr
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Process stdin stdout stderr -> Eff es a
f)