module System.Process.Typed
(
ProcessConfig
, StreamSpec
, StreamType (..)
, Process
, proc
, shell
, setStdin
, setStdout
, setStderr
, setWorkingDir
, setEnv
, setCloseFds
, setCreateGroup
, setDelegateCtlc
#if MIN_VERSION_process(1, 3, 0)
, setDetachConsole
, setCreateNewConsole
, setNewSession
#endif
#if MIN_VERSION_process(1, 4, 0) && !WINDOWS
, setChildGroup
, setChildUser
#endif
, mkStreamSpec
, inherit
, closed
, byteStringInput
, byteStringOutput
, createPipe
, useHandleOpen
, useHandleClose
, startProcess
, stopProcess
, withProcess
, withProcess_
, readProcess
, readProcess_
, runProcess
, runProcess_
, readProcessStdout
, readProcessStdout_
, readProcessStderr
, readProcessStderr_
, waitExitCode
, waitExitCodeSTM
, getExitCode
, getExitCodeSTM
, checkExitCode
, checkExitCodeSTM
, getStdin
, getStdout
, getStderr
, ExitCodeException (..)
, ByteStringOutputException (..)
, unsafeProcessHandle
) where
import qualified Data.ByteString as S
import Data.ByteString.Lazy.Internal (defaultChunkSize)
import Control.Exception (assert, evaluate, throwIO, Exception, SomeException, finally, bracket, onException, catch)
import Control.Monad (void)
import Control.Monad.IO.Class
import qualified System.Process as P
import Data.Typeable (Typeable)
import System.IO (Handle, hClose)
import Control.Concurrent.Async (async, cancel, waitCatch)
import Control.Concurrent.STM (newEmptyTMVarIO, atomically, putTMVar, TMVar, readTMVar, tryReadTMVar, STM, tryPutTMVar, throwSTM, catchSTM)
import System.Exit (ExitCode (ExitSuccess))
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Char8 as L8
import Data.String (IsString (fromString))
#if MIN_VERSION_process(1, 4, 0) && !WINDOWS
import System.Posix.Types (GroupID, UserID)
#endif
#if !MIN_VERSION_base(4, 8, 0)
import Control.Applicative (Applicative (..), (<$>), (<$))
#endif
#if !MIN_VERSION_process(1, 3, 0)
import qualified System.Process.Internals as P (createProcess_)
#endif
data ProcessConfig stdin stdout stderr = ProcessConfig
{ pcCmdSpec :: !P.CmdSpec
, pcStdin :: !(StreamSpec 'STInput stdin)
, pcStdout :: !(StreamSpec 'STOutput stdout)
, pcStderr :: !(StreamSpec 'STOutput stderr)
, pcWorkingDir :: !(Maybe FilePath)
, pcEnv :: !(Maybe [(String, String)])
, pcCloseFds :: !Bool
, pcCreateGroup :: !Bool
, pcDelegateCtlc :: !Bool
#if MIN_VERSION_process(1, 3, 0)
, pcDetachConsole :: !Bool
, pcCreateNewConsole :: !Bool
, pcNewSession :: !Bool
#endif
#if MIN_VERSION_process(1, 4, 0) && !WINDOWS
, pcChildGroup :: !(Maybe GroupID)
, pcChildUser :: !(Maybe UserID)
#endif
}
instance Show (ProcessConfig stdin stdout stderr) where
show pc = concat
[ case pcCmdSpec pc of
P.ShellCommand s -> "Shell command: " ++ s
P.RawCommand x xs -> "Raw command: " ++ unwords (map escape (x:xs))
, "\n"
, case pcWorkingDir pc of
Nothing -> ""
Just wd -> concat
[ "Run from: "
, wd
, "\n"
]
, case pcEnv pc of
Nothing -> ""
Just e -> unlines
$ "Modified environment:"
: map (\(k, v) -> concat [k, "=", v]) e
]
where
escape x
| any (`elem` " \\\"'") x = show x
| otherwise = x
instance (stdin ~ (), stdout ~ (), stderr ~ ())
=> IsString (ProcessConfig stdin stdout stderr) where
fromString s
| any (== ' ') s = shell s
| otherwise = proc s []
data StreamType = STInput | STOutput
data StreamSpec (streamType :: StreamType) a = StreamSpec
{ ssStream :: !P.StdStream
, ssCreate :: !(ProcessConfig () () () -> Maybe Handle -> Cleanup a)
}
deriving Functor
instance (streamType ~ 'STInput, res ~ ())
=> IsString (StreamSpec streamType res) where
fromString = byteStringInput . fromString
newtype Cleanup a = Cleanup { runCleanup :: IO (a, IO ()) }
deriving Functor
instance Applicative Cleanup where
pure x = Cleanup (return (x, return ()))
Cleanup f <*> Cleanup x = Cleanup $ do
(f', c1) <- f
(`onException` c1) $ do
(x', c2) <- x
return (f' x', c1 `finally` c2)
data Process stdin stdout stderr = Process
{ pConfig :: !(ProcessConfig () () ())
, pCleanup :: !(IO ())
, pStdin :: !stdin
, pStdout :: !stdout
, pStderr :: !stderr
, pHandle :: !P.ProcessHandle
, pExitCode :: !(TMVar ExitCode)
}
instance Show (Process stdin stdout stderr) where
show p = "Running process: " ++ show (pConfig p)
defaultProcessConfig :: ProcessConfig () () ()
defaultProcessConfig = ProcessConfig
{ pcCmdSpec = P.ShellCommand ""
, pcStdin = inherit
, pcStdout = inherit
, pcStderr = inherit
, pcWorkingDir = Nothing
, pcEnv = Nothing
, pcCloseFds = False
, pcCreateGroup = False
, pcDelegateCtlc = False
#if MIN_VERSION_process(1, 3, 0)
, pcDetachConsole = False
, pcCreateNewConsole = False
, pcNewSession = False
#endif
#if MIN_VERSION_process(1, 4, 0) && !WINDOWS
, pcChildGroup = Nothing
, pcChildUser = Nothing
#endif
}
proc :: FilePath -> [String] -> ProcessConfig () () ()
proc cmd args = setProc cmd args defaultProcessConfig
setProc :: FilePath -> [String]
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setProc cmd args p = p { pcCmdSpec = P.RawCommand cmd args }
shell :: String -> ProcessConfig () () ()
shell cmd = setShell cmd defaultProcessConfig
setShell :: String
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setShell cmd p = p { pcCmdSpec = P.ShellCommand cmd }
setStdin :: StreamSpec 'STInput stdin
-> ProcessConfig stdin0 stdout stderr
-> ProcessConfig stdin stdout stderr
setStdin spec pc = pc { pcStdin = spec }
setStdout :: StreamSpec 'STOutput stdout
-> ProcessConfig stdin stdout0 stderr
-> ProcessConfig stdin stdout stderr
setStdout spec pc = pc { pcStdout = spec }
setStderr :: StreamSpec 'STOutput stderr
-> ProcessConfig stdin stdout stderr0
-> ProcessConfig stdin stdout stderr
setStderr spec pc = pc { pcStderr = spec }
setWorkingDir :: FilePath
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setWorkingDir dir pc = pc { pcWorkingDir = Just dir }
setEnv :: [(String, String)]
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setEnv env pc = pc { pcEnv = Just env }
setCloseFds
:: Bool
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setCloseFds x pc = pc { pcCloseFds = x }
setCreateGroup
:: Bool
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setCreateGroup x pc = pc { pcCreateGroup = x }
setDelegateCtlc
:: Bool
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setDelegateCtlc x pc = pc { pcDelegateCtlc = x }
#if MIN_VERSION_process(1, 3, 0)
setDetachConsole
:: Bool
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setDetachConsole x pc = pc { pcDetachConsole = x }
setCreateNewConsole
:: Bool
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setCreateNewConsole x pc = pc { pcCreateNewConsole = x }
setNewSession
:: Bool
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setNewSession x pc = pc { pcNewSession = x }
#endif
#if MIN_VERSION_process(1, 4, 0) && !WINDOWS
setChildGroup
:: GroupID
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setChildGroup x pc = pc { pcChildGroup = Just x }
setChildUser
:: UserID
-> ProcessConfig stdin stdout stderr
-> ProcessConfig stdin stdout stderr
setChildUser x pc = pc { pcChildUser = Just x }
#endif
mkStreamSpec :: P.StdStream
-> (ProcessConfig () () () -> Maybe Handle -> IO (a, IO ()))
-> StreamSpec streamType a
mkStreamSpec ss f = StreamSpec ss (\pc mh -> Cleanup (f pc mh))
inherit :: StreamSpec anyStreamType ()
inherit = mkStreamSpec P.Inherit (\_ Nothing -> pure ((), return ()))
closed :: StreamSpec anyStreamType ()
#if MIN_VERSION_process(1, 4, 0)
closed = mkStreamSpec P.NoStream (\_ Nothing -> pure ((), return ()))
#else
closed = mkStreamSpec P.CreatePipe (\_ (Just h) -> (((), return ()) <$ hClose h))
#endif
byteStringInput :: L.ByteString -> StreamSpec 'STInput ()
byteStringInput lbs = mkStreamSpec P.CreatePipe $ \_ (Just h) -> do
void $ async $ do
L.hPut h lbs
hClose h
return ((), hClose h)
byteStringOutput :: StreamSpec 'STOutput (STM L.ByteString)
byteStringOutput = mkStreamSpec P.CreatePipe $ \pc (Just h) -> do
mvar <- newEmptyTMVarIO
void $ async $ do
let loop front = do
bs <- S.hGetSome h defaultChunkSize
if S.null bs
then atomically $ putTMVar mvar $ Right $ L.fromChunks $ front []
else loop $ front . (bs:)
loop id `catch` \e -> do
atomically $ void $ tryPutTMVar mvar $ Left $ ByteStringOutputException e pc
throwIO e
return (readTMVar mvar >>= either throwSTM return, hClose h)
createPipe :: StreamSpec anyStreamType Handle
createPipe = mkStreamSpec P.CreatePipe $ \_ (Just h) -> return (h, hClose h)
useHandleOpen :: Handle -> StreamSpec anyStreamType ()
useHandleOpen h = mkStreamSpec (P.UseHandle h) $ \_ Nothing -> return ((), return ())
useHandleClose :: Handle -> StreamSpec anyStreamType ()
useHandleClose h = mkStreamSpec (P.UseHandle h) $ \_ Nothing -> return ((), hClose h)
startProcess :: MonadIO m
=> ProcessConfig stdin stdout stderr
-> m (Process stdin stdout stderr)
startProcess pConfig'@ProcessConfig {..} = liftIO $ do
let cp0 =
case pcCmdSpec of
P.ShellCommand cmd -> P.shell cmd
P.RawCommand cmd args -> P.proc cmd args
cp = cp0
{ P.std_in = ssStream pcStdin
, P.std_out = ssStream pcStdout
, P.std_err = ssStream pcStderr
, P.cwd = pcWorkingDir
, P.env = pcEnv
, P.close_fds = pcCloseFds
, P.create_group = pcCreateGroup
, P.delegate_ctlc = pcDelegateCtlc
#if MIN_VERSION_process(1, 3, 0)
, P.detach_console = pcDetachConsole
, P.create_new_console = pcCreateNewConsole
, P.new_session = pcNewSession
#endif
#if MIN_VERSION_process(1, 4, 0) && !WINDOWS
, P.child_group = pcChildGroup
, P.child_user = pcChildUser
#endif
}
(minH, moutH, merrH, pHandle) <- P.createProcess_ "startProcess" cp
((pStdin, pStdout, pStderr), pCleanup1) <- runCleanup $ (,,)
<$> ssCreate pcStdin pConfig minH
<*> ssCreate pcStdout pConfig moutH
<*> ssCreate pcStderr pConfig merrH
pExitCode <- newEmptyTMVarIO
waitingThread <- async $ do
ec <- P.waitForProcess pHandle
atomically $ putTMVar pExitCode ec
return ec
let pCleanup = pCleanup1 `finally` do
cancel waitingThread
eec <- waitCatch waitingThread
case eec of
Right _ec -> return ()
Left _ -> do
P.terminateProcess pHandle
ec <- P.waitForProcess pHandle
success <- atomically $ tryPutTMVar pExitCode ec
evaluate $ assert success ()
return Process {..}
where
pConfig = clearStreams pConfig'
stopProcess :: MonadIO m
=> Process stdin stdout stderr
-> m ()
stopProcess = liftIO . pCleanup
withProcess :: ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a)
-> IO a
withProcess config = bracket (startProcess config) stopProcess
withProcess_ :: ProcessConfig stdin stdout stderr
-> (Process stdin stdout stderr -> IO a)
-> IO a
withProcess_ config = bracket
(startProcess config)
(\p -> stopProcess p `finally` checkExitCode p)
readProcess :: MonadIO m
=> ProcessConfig stdin stdoutIgnored stderrIgnored
-> m (ExitCode, L.ByteString, L.ByteString)
readProcess pc =
liftIO $ withProcess pc' $ \p -> atomically $ (,,)
<$> waitExitCodeSTM p
<*> getStdout p
<*> getStderr p
where
pc' = setStdout byteStringOutput
$ setStderr byteStringOutput pc
readProcess_ :: MonadIO m
=> ProcessConfig stdin stdoutIgnored stderrIgnored
-> m (L.ByteString, L.ByteString)
readProcess_ pc =
liftIO $ withProcess pc' $ \p -> atomically $ do
stdout <- getStdout p
stderr <- getStderr p
checkExitCodeSTM p `catchSTM` \ece -> throwSTM ece
{ eceStdout = stdout
, eceStderr = stderr
}
return (stdout, stderr)
where
pc' = setStdout byteStringOutput
$ setStderr byteStringOutput pc
readProcessStdout
:: MonadIO m
=> ProcessConfig stdin stdoutIgnored stderr
-> m (ExitCode, L.ByteString)
readProcessStdout pc =
liftIO $ withProcess pc' $ \p -> atomically $ (,)
<$> waitExitCodeSTM p
<*> getStdout p
where
pc' = setStdout byteStringOutput pc
readProcessStdout_
:: MonadIO m
=> ProcessConfig stdin stdoutIgnored stderr
-> m L.ByteString
readProcessStdout_ pc =
liftIO $ withProcess pc' $ \p -> atomically $ do
stdout <- getStdout p
checkExitCodeSTM p `catchSTM` \ece -> throwSTM ece
{ eceStdout = stdout
}
return stdout
where
pc' = setStdout byteStringOutput pc
readProcessStderr
:: MonadIO m
=> ProcessConfig stdin stderrIgnored stderr
-> m (ExitCode, L.ByteString)
readProcessStderr pc =
liftIO $ withProcess pc' $ \p -> atomically $ (,)
<$> waitExitCodeSTM p
<*> getStderr p
where
pc' = setStderr byteStringOutput pc
readProcessStderr_
:: MonadIO m
=> ProcessConfig stdin stderrIgnored stderr
-> m L.ByteString
readProcessStderr_ pc =
liftIO $ withProcess pc' $ \p -> atomically $ do
stderr <- getStderr p
checkExitCodeSTM p `catchSTM` \ece -> throwSTM ece
{ eceStderr = stderr
}
return stderr
where
pc' = setStderr byteStringOutput pc
runProcess :: MonadIO m
=> ProcessConfig stdin stdout stderr
-> m ExitCode
runProcess pc = liftIO $ withProcess pc waitExitCode
runProcess_ :: MonadIO m
=> ProcessConfig stdin stdout stderr
-> m ()
runProcess_ pc = liftIO $ withProcess pc checkExitCode
waitExitCode :: MonadIO m => Process stdin stdout stderr -> m ExitCode
waitExitCode = liftIO . atomically . waitExitCodeSTM
waitExitCodeSTM :: Process stdin stdout stderr -> STM ExitCode
waitExitCodeSTM = readTMVar . pExitCode
getExitCode :: MonadIO m => Process stdin stdout stderr -> m (Maybe ExitCode)
getExitCode = liftIO . atomically . getExitCodeSTM
getExitCodeSTM :: Process stdin stdout stderr -> STM (Maybe ExitCode)
getExitCodeSTM = tryReadTMVar . pExitCode
checkExitCode :: MonadIO m => Process stdin stdout stderr -> m ()
checkExitCode = liftIO . atomically . checkExitCodeSTM
checkExitCodeSTM :: Process stdin stdout stderr -> STM ()
checkExitCodeSTM p = do
ec <- readTMVar (pExitCode p)
case ec of
ExitSuccess -> return ()
_ -> throwSTM ExitCodeException
{ eceExitCode = ec
, eceProcessConfig = clearStreams (pConfig p)
, eceStdout = L.empty
, eceStderr = L.empty
}
clearStreams :: ProcessConfig stdin stdout stderr -> ProcessConfig () () ()
clearStreams pc = pc
{ pcStdin = inherit
, pcStdout = inherit
, pcStderr = inherit
}
getStdin :: Process stdin stdout stderr -> stdin
getStdin = pStdin
getStdout :: Process stdin stdout stderr -> stdout
getStdout = pStdout
getStderr :: Process stdin stdout stderr -> stderr
getStderr = pStderr
data ExitCodeException = ExitCodeException
{ eceExitCode :: ExitCode
, eceProcessConfig :: ProcessConfig () () ()
, eceStdout :: L.ByteString
, eceStderr :: L.ByteString
}
deriving Typeable
instance Exception ExitCodeException
instance Show ExitCodeException where
show ece = concat
[ "Received "
, show (eceExitCode ece)
, " when running\n"
, show (eceProcessConfig ece) { pcEnv = Nothing }
, if L.null (eceStdout ece)
then ""
else "Standard output:\n\n" ++ L8.unpack (eceStdout ece)
, if L.null (eceStderr ece)
then ""
else "Standard error:\n\n" ++ L8.unpack (eceStderr ece)
]
data ByteStringOutputException = ByteStringOutputException SomeException (ProcessConfig () () ())
deriving (Show, Typeable)
instance Exception ByteStringOutputException
unsafeProcessHandle :: Process stdin stdout stderr -> P.ProcessHandle
unsafeProcessHandle = pHandle