{-# LINE 1 "libraries/unix/System/Posix/Process.hsc" #-}

{-# LINE 2 "libraries/unix/System/Posix/Process.hsc" #-}
{-# LANGUAGE Safe #-}

{-# LINE 6 "libraries/unix/System/Posix/Process.hsc" #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  System.Posix.Process
-- Copyright   :  (c) The University of Glasgow 2002
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  provisional
-- Portability :  non-portable (requires POSIX)
--
-- POSIX process support.  See also the System.Cmd and System.Process
-- modules in the process package.
--
-----------------------------------------------------------------------------

module System.Posix.Process (
    -- * Processes

    -- ** Forking and executing
    forkProcess,
    forkProcessWithUnmask,
    executeFile,

    -- ** Exiting
    exitImmediately,

    -- ** Process environment
    getProcessID,
    getParentProcessID,

    -- ** Process groups
    getProcessGroupID,
    getProcessGroupIDOf,
    createProcessGroupFor,
    joinProcessGroup,
    setProcessGroupIDOf,

    -- ** Sessions
    createSession,

    -- ** Process times
    ProcessTimes(..),
    getProcessTimes,

    -- ** Scheduling priority
    nice,
    getProcessPriority,
    getProcessGroupPriority,
    getUserPriority,
    setProcessPriority,
    setProcessGroupPriority,
    setUserPriority,

    -- ** Process status
    ProcessStatus(..),
    getProcessStatus,
    getAnyProcessStatus,
    getGroupProcessStatus,

    -- ** Deprecated
    createProcessGroup,
    setProcessGroupID,

 ) where



import Foreign
import Foreign.C
import System.Posix.Process.Internals
import System.Posix.Process.Common
import System.Posix.Internals ( withFilePath )

-- | @'executeFile' cmd args env@ calls one of the
--   @execv*@ family, depending on whether or not the current
--   PATH is to be searched for the command, and whether or not an
--   environment is provided to supersede the process's current
--   environment.  The basename (leading directory names suppressed) of
--   the command is passed to @execv*@ as @arg[0]@;
--   the argument list passed to 'executeFile' therefore
--   begins with @arg[1]@.
executeFile :: FilePath                     -- ^ Command
            -> Bool                         -- ^ Search PATH?
            -> [String]                     -- ^ Arguments
            -> Maybe [(String, String)]     -- ^ Environment
            -> IO a
executeFile :: FilePath
-> Bool -> [FilePath] -> Maybe [(FilePath, FilePath)] -> IO a
executeFile FilePath
path Bool
search [FilePath]
args Maybe [(FilePath, FilePath)]
Nothing = do
  FilePath -> (CString -> IO a) -> IO a
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
path ((CString -> IO a) -> IO a) -> (CString -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \CString
s ->
    (FilePath -> (CString -> IO a) -> IO a)
-> [FilePath] -> ([CString] -> IO a) -> IO a
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany FilePath -> (CString -> IO a) -> IO a
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath (FilePath
pathFilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:[FilePath]
args) (([CString] -> IO a) -> IO a) -> ([CString] -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \[CString]
cstrs ->
      CString -> [CString] -> (Ptr CString -> IO a) -> IO a
forall a b. Storable a => a -> [a] -> (Ptr a -> IO b) -> IO b
withArray0 CString
forall a. Ptr a
nullPtr [CString]
cstrs ((Ptr CString -> IO a) -> IO a) -> (Ptr CString -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr CString
arr -> do
        IO ()
pPrPr_disableITimers
        if Bool
search
           then FilePath -> FilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => FilePath -> FilePath -> IO a -> IO ()
throwErrnoPathIfMinus1_ FilePath
"executeFile" FilePath
path (CString -> Ptr CString -> IO CInt
c_execvp CString
s Ptr CString
arr)
           else FilePath -> FilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => FilePath -> FilePath -> IO a -> IO ()
throwErrnoPathIfMinus1_ FilePath
"executeFile" FilePath
path (CString -> Ptr CString -> IO CInt
c_execv CString
s Ptr CString
arr)
        a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. HasCallStack => a
undefined -- never reached

executeFile FilePath
path Bool
search [FilePath]
args (Just [(FilePath, FilePath)]
env) = do
  FilePath -> (CString -> IO a) -> IO a
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath FilePath
path ((CString -> IO a) -> IO a) -> (CString -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \CString
s ->
    (FilePath -> (CString -> IO a) -> IO a)
-> [FilePath] -> ([CString] -> IO a) -> IO a
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany FilePath -> (CString -> IO a) -> IO a
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath (FilePath
pathFilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:[FilePath]
args) (([CString] -> IO a) -> IO a) -> ([CString] -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \[CString]
cstrs ->
      CString -> [CString] -> (Ptr CString -> IO a) -> IO a
forall a b. Storable a => a -> [a] -> (Ptr a -> IO b) -> IO b
withArray0 CString
forall a. Ptr a
nullPtr [CString]
cstrs ((Ptr CString -> IO a) -> IO a) -> (Ptr CString -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr CString
arg_arr ->
    let env' :: [FilePath]
env' = ((FilePath, FilePath) -> FilePath)
-> [(FilePath, FilePath)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (\ (FilePath
name, FilePath
val) -> FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ (Char
'=' Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: FilePath
val)) [(FilePath, FilePath)]
env in
    (FilePath -> (CString -> IO a) -> IO a)
-> [FilePath] -> ([CString] -> IO a) -> IO a
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withMany FilePath -> (CString -> IO a) -> IO a
forall a. FilePath -> (CString -> IO a) -> IO a
withFilePath [FilePath]
env' (([CString] -> IO a) -> IO a) -> ([CString] -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \[CString]
cenv ->
      CString -> [CString] -> (Ptr CString -> IO a) -> IO a
forall a b. Storable a => a -> [a] -> (Ptr a -> IO b) -> IO b
withArray0 CString
forall a. Ptr a
nullPtr [CString]
cenv ((Ptr CString -> IO a) -> IO a) -> (Ptr CString -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr CString
env_arr -> do
        IO ()
pPrPr_disableITimers
        if Bool
search
           then FilePath -> FilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => FilePath -> FilePath -> IO a -> IO ()
throwErrnoPathIfMinus1_ FilePath
"executeFile" FilePath
path
                   (CString -> Ptr CString -> Ptr CString -> IO CInt
c_execvpe CString
s Ptr CString
arg_arr Ptr CString
env_arr)
           else FilePath -> FilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => FilePath -> FilePath -> IO a -> IO ()
throwErrnoPathIfMinus1_ FilePath
"executeFile" FilePath
path
                   (CString -> Ptr CString -> Ptr CString -> IO CInt
c_execve CString
s Ptr CString
arg_arr Ptr CString
env_arr)
        a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. HasCallStack => a
undefined -- never reached

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