module System.Posix.Process (
forkProcess,
forkProcessWithUnmask,
executeFile,
exitImmediately,
getProcessID,
getParentProcessID,
getProcessGroupID,
getProcessGroupIDOf,
createProcessGroupFor,
joinProcessGroup,
setProcessGroupIDOf,
createSession,
ProcessTimes(..),
getProcessTimes,
nice,
getProcessPriority,
getProcessGroupPriority,
getUserPriority,
setProcessPriority,
setProcessGroupPriority,
setUserPriority,
ProcessStatus(..),
getProcessStatus,
getAnyProcessStatus,
getGroupProcessStatus,
createProcessGroup,
setProcessGroupID,
) where
import Foreign
import Foreign.C
import System.Posix.Process.Internals
import System.Posix.Process.Common
import System.Posix.Internals ( withFilePath )
executeFile :: FilePath
-> Bool
-> [String]
-> Maybe [(String, String)]
-> IO a
executeFile path search args Nothing = do
withFilePath path $ \s ->
withMany withFilePath (path:args) $ \cstrs ->
withArray0 nullPtr cstrs $ \arr -> do
pPrPr_disableITimers
if search
then throwErrnoPathIfMinus1_ "executeFile" path (c_execvp s arr)
else throwErrnoPathIfMinus1_ "executeFile" path (c_execv s arr)
return undefined
executeFile path search args (Just env) = do
withFilePath path $ \s ->
withMany withFilePath (path:args) $ \cstrs ->
withArray0 nullPtr cstrs $ \arg_arr ->
let env' = map (\ (name, val) -> name ++ ('=' : val)) env in
withMany withFilePath env' $ \cenv ->
withArray0 nullPtr cenv $ \env_arr -> do
pPrPr_disableITimers
if search
then throwErrnoPathIfMinus1_ "executeFile" path
(c_execvpe s arg_arr env_arr)
else throwErrnoPathIfMinus1_ "executeFile" path
(c_execve s arg_arr env_arr)
return undefined
foreign import ccall unsafe "execvp"
c_execvp :: CString -> Ptr CString -> IO CInt
foreign import ccall unsafe "execv"
c_execv :: CString -> Ptr CString -> IO CInt
foreign import ccall unsafe "execve"
c_execve :: CString -> Ptr CString -> Ptr CString -> IO CInt