{-# LANGUAGE TupleSections, ConstraintKinds #-}

-- | Extra functions for creating processes. Specifically variants that automatically check
--   the 'ExitCode' and capture the 'stdout' \/ 'stderr' handles.
module System.Process.Extra(
    module System.Process,
    system_, systemOutput, systemOutput_
    ) where

import Control.Monad
import System.IO.Extra
import System.Process
import System.Exit
import Data.Functor
import Partial
import Prelude


-- | A version of 'system' that also captures the output, both 'stdout' and 'stderr'.
--   Returns a pair of the 'ExitCode' and the output.
systemOutput :: String -> IO (ExitCode, String)
systemOutput :: String -> IO (ExitCode, String)
systemOutput String
x = forall a. (String -> IO a) -> IO a
withTempFile forall a b. (a -> b) -> a -> b
$ \String
file -> do
    ExitCode
exit <- forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withFile String
file IOMode
WriteMode forall a b. (a -> b) -> a -> b
$ \Handle
h -> do
        (Maybe Handle
_, Maybe Handle
_, Maybe Handle
_, ProcessHandle
pid) <- CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess (String -> CreateProcess
shell String
x){std_out :: StdStream
std_out=Handle -> StdStream
UseHandle Handle
h, std_err :: StdStream
std_err=Handle -> StdStream
UseHandle Handle
h}
        ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
pid
    (ExitCode
exit,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO String
readFile' String
file


-- | A version of 'system' that throws an error if the 'ExitCode' is not 'ExitSuccess'.
system_ :: Partial => String -> IO ()
system_ :: Partial => String -> IO ()
system_ String
x = do
    ExitCode
res <- String -> IO ExitCode
system String
x
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ExitCode
res forall a. Eq a => a -> a -> Bool
/= ExitCode
ExitSuccess) forall a b. (a -> b) -> a -> b
$
        forall a. Partial => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Failed when running system command: " forall a. [a] -> [a] -> [a]
++ String
x

-- | A version of 'system' that captures the output (both 'stdout' and 'stderr')
--   and throws an error if the 'ExitCode' is not 'ExitSuccess'.
systemOutput_ :: Partial => String -> IO String
systemOutput_ :: Partial => String -> IO String
systemOutput_ String
x = do
    (ExitCode
res,String
out) <- String -> IO (ExitCode, String)
systemOutput String
x
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ExitCode
res forall a. Eq a => a -> a -> Bool
/= ExitCode
ExitSuccess) forall a b. (a -> b) -> a -> b
$
        forall a. Partial => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Failed when running system command: " forall a. [a] -> [a] -> [a]
++ String
x
    forall (f :: * -> *) a. Applicative f => a -> f a
pure String
out