{-# LANGUAGE CPP #-}
-- | Lifted "System.Process".
module Effectful.Process
  ( -- * Effect
    Process

    -- ** Handlers
  , runProcess

    -- * Running sub-processes
  , createProcess
  , createProcess_
  , P.shell
  , P.proc
  , P.CreateProcess(..)
  , P.CmdSpec(..)
  , P.StdStream(..)
  , P.ProcessHandle

    -- ** Simpler functions for common tasks
  , callProcess
  , callCommand
  , spawnProcess
  , spawnCommand
  , readCreateProcess
  , readProcess
  , readCreateProcessWithExitCode
  , readProcessWithExitCode
  , withCreateProcess
  , cleanupProcess

    -- ** Related utilities
  , P.showCommandForUser
  , P.Pid
  , getPid
#if MIN_VERSION_process(1,6,12)
  , getCurrentPid
#endif

    -- * Process completion
  , waitForProcess
  , getProcessExitCode
  , terminateProcess
  , interruptProcessGroupOf

    -- * Interprocess communication
  , createPipe
  , createPipeFd
  ) where

import System.Exit (ExitCode)
import System.IO (Handle)
import System.Posix.Internals (FD)
import qualified System.Process as P

import Effectful
import Effectful.Dispatch.Static

-- | An effect for running child processes using the @process@ library.
data Process :: Effect

type instance DispatchOf Process = Static WithSideEffects
data instance StaticRep Process = Process

runProcess :: IOE :> es => Eff (Process : es) a -> Eff es a
runProcess :: forall (es :: [Effect]) a.
(IOE :> es) =>
Eff (Process : es) a -> Eff es a
runProcess = forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect])
       a.
(DispatchOf e ~ 'Static sideEffects, MaybeIOE sideEffects es) =>
StaticRep e -> Eff (e : es) a -> Eff es a
evalStaticRep StaticRep Process
Process

----------------------------------------
-- Running sub-processes

-- | Lifted 'P.createProcess'.
createProcess
  :: Process :> es
  => P.CreateProcess
  -> Eff es (Maybe Handle, Maybe Handle, Maybe Handle, P.ProcessHandle)
createProcess :: forall (es :: [Effect]).
(Process :> es) =>
CreateProcess
-> Eff es (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
P.createProcess

-- | Lifted 'P.createProcess_'.
createProcess_
  :: Process :> es
  => String
  -> P.CreateProcess
  -> Eff es (Maybe Handle, Maybe Handle, Maybe Handle, P.ProcessHandle)
createProcess_ :: forall (es :: [Effect]).
(Process :> es) =>
String
-> CreateProcess
-> Eff es (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess_ String
msg = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. String
-> CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
P.createProcess_ String
msg

----------------------------------------
-- Simpler functions for common tasks

-- | Lifted 'P.callProcess'.
callProcess :: Process :> es => FilePath -> [String] -> Eff es ()
callProcess :: forall (es :: [Effect]).
(Process :> es) =>
String -> [String] -> Eff es ()
callProcess String
fp = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String] -> IO ()
P.callProcess String
fp

-- | Lifted 'P.callCommand'.
callCommand :: Process :> es => String -> Eff es ()
callCommand :: forall (es :: [Effect]). (Process :> es) => String -> Eff es ()
callCommand = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ()
P.callCommand

-- | Lifted 'P.spawnProcess'.
spawnProcess :: Process :> es => FilePath -> [String] -> Eff es P.ProcessHandle
spawnProcess :: forall (es :: [Effect]).
(Process :> es) =>
String -> [String] -> Eff es ProcessHandle
spawnProcess String
fp = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String] -> IO ProcessHandle
P.spawnProcess String
fp

-- | Lifted 'P.spawnCommand'.
spawnCommand :: Process :> es => String -> Eff es P.ProcessHandle
spawnCommand :: forall (es :: [Effect]).
(Process :> es) =>
String -> Eff es ProcessHandle
spawnCommand = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ProcessHandle
P.spawnCommand

-- | Lifted 'P.readCreateProcess'.
readCreateProcess :: Process :> es => P.CreateProcess -> String -> Eff es String
readCreateProcess :: forall (es :: [Effect]).
(Process :> es) =>
CreateProcess -> String -> Eff es String
readCreateProcess CreateProcess
cp = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. CreateProcess -> String -> IO String
P.readCreateProcess CreateProcess
cp

-- | Lifted 'P.readProcess'.
readProcess :: Process :> es => FilePath -> [String] -> String -> Eff es String
readProcess :: forall (es :: [Effect]).
(Process :> es) =>
String -> [String] -> String -> Eff es String
readProcess String
fp [String]
args = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String] -> String -> IO String
P.readProcess String
fp [String]
args

-- | Lifted 'P.readCreateProcessWithExitCode'.
readCreateProcessWithExitCode
  :: Process :> es
  => P.CreateProcess
  -> String
  -> Eff es (ExitCode, String, String)
readCreateProcessWithExitCode :: forall (es :: [Effect]).
(Process :> es) =>
CreateProcess -> String -> Eff es (ExitCode, String, String)
readCreateProcessWithExitCode CreateProcess
cp = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. CreateProcess -> String -> IO (ExitCode, String, String)
P.readCreateProcessWithExitCode CreateProcess
cp

-- | Lifted 'P.readProcessWithExitCode'.
readProcessWithExitCode
  :: Process :> es
  => FilePath
  -> [String]
  -> String
  -> Eff es (ExitCode, String, String)
readProcessWithExitCode :: forall (es :: [Effect]).
(Process :> es) =>
String -> [String] -> String -> Eff es (ExitCode, String, String)
readProcessWithExitCode String
fp [String]
args = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String] -> String -> IO (ExitCode, String, String)
P.readProcessWithExitCode String
fp [String]
args

-- | Lifted 'P.withCreateProcess'.
withCreateProcess
  :: Process :> es
  => P.CreateProcess
  -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> P.ProcessHandle -> Eff es a)
  -> Eff es a
withCreateProcess :: forall (es :: [Effect]) a.
(Process :> es) =>
CreateProcess
-> (Maybe Handle
    -> Maybe Handle -> Maybe Handle -> ProcessHandle -> Eff es a)
-> Eff es a
withCreateProcess CreateProcess
cp Maybe Handle
-> Maybe Handle -> Maybe Handle -> ProcessHandle -> Eff es a
cb = forall (es :: [Effect]) a.
HasCallStack =>
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
unsafeSeqUnliftIO forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
  forall a.
CreateProcess
-> (Maybe Handle
    -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a)
-> IO a
P.withCreateProcess CreateProcess
cp forall a b. (a -> b) -> a -> b
$ \Maybe Handle
inh Maybe Handle
outh Maybe Handle
errh ProcessHandle
ph -> forall r. Eff es r -> IO r
unlift forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> Maybe Handle -> Maybe Handle -> ProcessHandle -> Eff es a
cb Maybe Handle
inh Maybe Handle
outh Maybe Handle
errh ProcessHandle
ph

-- | Lifted 'P.cleanupProcess'.
cleanupProcess
  :: Process :> es
  => (Maybe Handle, Maybe Handle, Maybe Handle, P.ProcessHandle)
  -> Eff es ()
cleanupProcess :: forall (es :: [Effect]).
(Process :> es) =>
(Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-> Eff es ()
cleanupProcess = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO ()
P.cleanupProcess

----------------------------------------
-- Related utilities

-- | Lifted 'P.getPid'.
getPid :: Process :> es => P.ProcessHandle -> Eff es (Maybe P.Pid)
getPid :: forall (es :: [Effect]).
(Process :> es) =>
ProcessHandle -> Eff es (Maybe Pid)
getPid = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessHandle -> IO (Maybe Pid)
P.getPid

#if MIN_VERSION_process(1,6,12)
-- | Lifted 'P.getCurrentPid'.
getCurrentPid :: Process :> es => Eff es P.Pid
getCurrentPid :: forall (es :: [Effect]). (Process :> es) => Eff es Pid
getCurrentPid = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ IO Pid
P.getCurrentPid
#endif

----------------------------------------
-- Process completion

-- | Lifted 'P.waitForProcess'.
waitForProcess :: Process :> es => P.ProcessHandle -> Eff es ExitCode
waitForProcess :: forall (es :: [Effect]).
(Process :> es) =>
ProcessHandle -> Eff es ExitCode
waitForProcess = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessHandle -> IO ExitCode
P.waitForProcess

-- | Lifted 'P.getProcessExitCode'.
getProcessExitCode :: Process :> es => P.ProcessHandle -> Eff es (Maybe ExitCode)
getProcessExitCode :: forall (es :: [Effect]).
(Process :> es) =>
ProcessHandle -> Eff es (Maybe ExitCode)
getProcessExitCode = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessHandle -> IO (Maybe ExitCode)
P.getProcessExitCode

-- | Lifted 'P.terminateProcess'.
terminateProcess :: Process :> es => P.ProcessHandle -> Eff es ()
terminateProcess :: forall (es :: [Effect]).
(Process :> es) =>
ProcessHandle -> Eff es ()
terminateProcess = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessHandle -> IO ()
P.terminateProcess

-- | Lifted 'P.interruptProcessGroupOf'.
interruptProcessGroupOf :: Process :> es => P.ProcessHandle -> Eff es ()
interruptProcessGroupOf :: forall (es :: [Effect]).
(Process :> es) =>
ProcessHandle -> Eff es ()
interruptProcessGroupOf = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProcessHandle -> IO ()
P.interruptProcessGroupOf

----------------------------------------
-- Interprocess communication

-- | Lifted 'P.createPipe'.
createPipe :: Process :> es => Eff es (Handle, Handle)
createPipe :: forall (es :: [Effect]). (Process :> es) => Eff es (Handle, Handle)
createPipe = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ IO (Handle, Handle)
P.createPipe

-- | Lifted 'P.createPipeFd'.
createPipeFd :: Process :> es => Eff es (FD, FD)
createPipeFd :: forall (es :: [Effect]). (Process :> es) => Eff es (FD, FD)
createPipeFd = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ IO (FD, FD)
P.createPipeFd