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 stdcall unsafe "winbase.h GetCurrentProcessId"
c_GetCurrentProcessID :: IO DWORD
getPIDString = fmap show c_GetCurrentProcessID
customExec binary mArgs = do
args <- customOptions mArgs
(_,_,_,child) <- createProcess $ CreateProcess
{ cmdspec = RawCommand binary args
, cwd = Nothing
, env = Nothing
, std_in = Inherit
, std_out = Inherit
, std_err = Inherit
, close_fds = True
, create_group = False
}
performGC
exitCode <- waitForProcess child
case exitCode of
ExitSuccess -> c_ExitProcess 0
ExitFailure c -> c_ExitProcess (fromIntegral c)
foreign import stdcall unsafe "winbase.h ExitProcess"
c_ExitProcess :: UINT -> IO ()
#else
import System.Posix.Process ( executeFile, getProcessID, exitImmediately
, forkProcess, getProcessStatus, ProcessStatus(..) )
import System.Posix.Signals ( raiseSignal, sigTSTP )
import System.Exit ( ExitCode(..) )
getPIDString = fmap show getProcessID
#ifdef darwin_HOST_OS
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 binary mArgs = do
args <- customOptions mArgs
executeFile binary False args Nothing
#endif
#endif
customExec :: FilePath -> Maybe [String] -> IO ()
getPIDString :: IO String