{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module What4.Utils.Process
( withProcessHandles
, resolveSolverPath
, findSolverPath
, filterAsync
, startProcess
, cleanupProcess
) where
import Control.Exception
import Control.Monad (void)
import qualified Data.Map as Map
import qualified Data.Text as T
import System.IO
import System.Exit (ExitCode)
import System.Process hiding (cleanupProcess)
import What4.BaseTypes
import What4.Config
import qualified What4.Utils.Environment as Env
import What4.Panic
resolveSolverPath :: FilePath
-> IO FilePath
resolveSolverPath path = do
Env.findExecutable =<< Env.expandEnvironmentPath Map.empty path
findSolverPath :: ConfigOption (BaseStringType Unicode) -> Config -> IO FilePath
findSolverPath o cfg =
do v <- getOpt =<< getOptionSetting o cfg
resolveSolverPath (T.unpack v)
withProcessHandles :: FilePath
-> [String]
-> Maybe FilePath
-> ((Handle, Handle, Handle, ProcessHandle) -> IO a)
-> IO a
withProcessHandles path args mcwd action = do
let onError (_,_,_,ph) = do
catchJust filterAsync (terminateProcess ph) (\(ex :: SomeException) ->
hPutStrLn stderr $ displayException ex)
bracket (startProcess path args mcwd)
(void . cleanupProcess)
(\hs -> onException (action hs) (onError hs))
cleanupProcess :: (Handle, Handle, Handle, ProcessHandle) -> IO ExitCode
cleanupProcess (h_in, h_out, h_err, ph) =
do catchJust filterAsync
(hClose h_in >> hClose h_out >> hClose h_err)
(\(_ :: SomeException) -> return ())
waitForProcess ph
startProcess ::
FilePath ->
[String] ->
Maybe FilePath ->
IO (Handle, Handle, Handle, ProcessHandle)
startProcess path args mcwd =
do let create_proc
= (proc path args)
{ std_in = CreatePipe
, std_out = CreatePipe
, std_err = CreatePipe
, create_group = False
, cwd = mcwd
}
createProcess create_proc >>= \case
(Just in_h, Just out_h, Just err_h, ph) -> return (in_h, out_h, err_h, ph)
_ -> panic "startProcess" $
[ "Failed to exec: " ++ show path
, "With the following arguments:"
] ++ args
filterAsync :: SomeException -> Maybe SomeException
filterAsync e
| Just (_ :: AsyncException) <- fromException e = Nothing
| otherwise = Just e