{-# LANGUAGE CPP #-}
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
{-# LANGUAGE ForeignFunctionInterface #-}
#if defined(i386_HOST_ARCH)
#define WINDOWS_CCONV stdcall
#elif defined(x86_64_HOST_ARCH)
#define WINDOWS_CCONV ccall
#else
#error Unknown mingw32 arch
#endif
#endif
module Config.Dyre.Compat ( customExec, getPIDString ) where
import Config.Dyre.Options ( customOptions )
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
import System.Win32
import System.Process
import System.Exit
import System.Mem
foreign import WINDOWS_CCONV unsafe "winbase.h GetCurrentProcessId"
c_GetCurrentProcessID :: IO DWORD
getPIDString = fmap show c_GetCurrentProcessID
customExec binary mArgs = do
args <- customOptions mArgs
(_,_,_,child) <- createProcess $ proc binary args
performGC
waitForProcess child >>= exitWith
#else
import System.Posix.Process ( executeFile, getProcessID )
#ifdef darwin_HOST_OS
import System.Posix.Process
( exitImmediately , forkProcess, getProcessStatus, ProcessStatus(..) )
import System.Posix.Signals ( raiseSignal, sigTSTP )
import System.Exit ( ExitCode(ExitSuccess) )
customExec binary mArgs = do
args <- customOptions mArgs
childPID <- forkProcess $ executeFile binary False args Nothing
forever $ do
childStatus <- getProcessStatus True True childPID
case childStatus of
Nothing -> error "executeFile: couldn't get child process status"
Just (Exited code) -> exitImmediately code
#if MIN_VERSION_unix(2,7,0)
Just (Terminated _ _) -> exitImmediately ExitSuccess
#else
Just (Terminated _) -> exitImmediately ExitSuccess
#endif
Just (Stopped _) -> raiseSignal sigTSTP
where forever a = a >> forever a
#else
customExec :: FilePath -> Maybe [FilePath] -> IO a
customExec FilePath
binary Maybe [FilePath]
mArgs = do
[FilePath]
args <- Maybe [FilePath] -> IO [FilePath]
customOptions Maybe [FilePath]
mArgs
FilePath
-> Bool -> [FilePath] -> Maybe [(FilePath, FilePath)] -> IO a
forall a.
FilePath
-> Bool -> [FilePath] -> Maybe [(FilePath, FilePath)] -> IO a
executeFile FilePath
binary Bool
False [FilePath]
args Maybe [(FilePath, FilePath)]
forall a. Maybe a
Nothing
#endif
getPIDString :: IO FilePath
getPIDString = (ProcessID -> FilePath) -> IO ProcessID -> IO FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ProcessID -> FilePath
forall a. Show a => a -> FilePath
show IO ProcessID
getProcessID
#endif
customExec :: FilePath -> Maybe [String] -> IO a
getPIDString :: IO String