{-# LINE 1 "System/Posix/Process.hsc" #-}{-# LANGUAGE Safe #-}------------------------------------------------------------------------------- |-- 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.-------------------------------------------------------------------------------moduleSystem.Posix.Process(-- * Processes-- ** Forking and executingforkProcess ,forkProcessWithUnmask ,executeFile ,-- ** ExitingexitImmediately ,-- ** Process environmentgetProcessID ,getParentProcessID ,-- ** Process groupsgetProcessGroupID ,getProcessGroupIDOf ,createProcessGroupFor ,joinProcessGroup ,setProcessGroupIDOf ,-- ** SessionscreateSession ,-- ** Process timesProcessTimes (..),getProcessTimes ,-- ** Scheduling prioritynice ,getProcessPriority ,getProcessGroupPriority ,getUserPriority ,setProcessPriority ,setProcessGroupPriority ,setUserPriority ,-- ** Process statusProcessStatus (..),getProcessStatus ,getAnyProcessStatus ,getGroupProcessStatus ,-- ** DeprecatedcreateProcessGroup ,setProcessGroupID ,)whereimportForeignimportForeign.CimportSystem.Posix.Process.Internals importSystem.Posix.Process.Common importSystem.Posix.Internals(withFilePath){-# LINE 79 "System/Posix/Process.hsc" #-}-- | @'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->IOa {-# LINE 100 "System/Posix/Process.hsc" #-}executeFile :: forall a.
FilePath
-> Bool -> [FilePath] -> Maybe [(FilePath, FilePath)] -> IO a
executeFile FilePath
path Bool
search [FilePath]
args Maybe [(FilePath, FilePath)]
Nothing=doFilePath -> (Ptr CChar -> IO a) -> IO a
forall a. FilePath -> (Ptr CChar -> IO a) -> IO a
withFilePathFilePath
path ((Ptr CChar -> IO a) -> IO a) -> (Ptr CChar -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\Ptr CChar
s ->(FilePath -> (Ptr CChar -> IO a) -> IO a)
-> [FilePath] -> ([Ptr CChar] -> IO a) -> IO a
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withManyFilePath -> (Ptr CChar -> IO a) -> IO a
forall a. FilePath -> (Ptr CChar -> IO a) -> IO a
withFilePath(FilePath
path FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:[FilePath]
args )(([Ptr CChar] -> IO a) -> IO a) -> ([Ptr CChar] -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\[Ptr CChar]
cstrs ->Ptr CChar -> [Ptr CChar] -> (Ptr (Ptr CChar) -> IO a) -> IO a
forall a b. Storable a => a -> [a] -> (Ptr a -> IO b) -> IO b
withArray0Ptr CChar
forall a. Ptr a
nullPtr[Ptr CChar]
cstrs ((Ptr (Ptr CChar) -> IO a) -> IO a)
-> (Ptr (Ptr CChar) -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\Ptr (Ptr CChar)
arr ->doIO ()
pPrPr_disableITimers ifBool
search thenFilePath -> FilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => FilePath -> FilePath -> IO a -> IO ()
throwErrnoPathIfMinus1_FilePath
"executeFile"FilePath
path (Ptr CChar -> Ptr (Ptr CChar) -> IO CInt
c_execvp Ptr CChar
s Ptr (Ptr CChar)
arr )elseFilePath -> FilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => FilePath -> FilePath -> IO a -> IO ()
throwErrnoPathIfMinus1_FilePath
"executeFile"FilePath
path (Ptr CChar -> Ptr (Ptr CChar) -> IO CInt
c_execv Ptr CChar
s Ptr (Ptr CChar)
arr )a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returna
forall a. HasCallStack => a
undefined-- never reachedexecuteFile FilePath
path Bool
search [FilePath]
args (Just[(FilePath, FilePath)]
env )=doFilePath -> (Ptr CChar -> IO a) -> IO a
forall a. FilePath -> (Ptr CChar -> IO a) -> IO a
withFilePathFilePath
path ((Ptr CChar -> IO a) -> IO a) -> (Ptr CChar -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\Ptr CChar
s ->(FilePath -> (Ptr CChar -> IO a) -> IO a)
-> [FilePath] -> ([Ptr CChar] -> IO a) -> IO a
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withManyFilePath -> (Ptr CChar -> IO a) -> IO a
forall a. FilePath -> (Ptr CChar -> IO a) -> IO a
withFilePath(FilePath
path FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:[FilePath]
args )(([Ptr CChar] -> IO a) -> IO a) -> ([Ptr CChar] -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\[Ptr CChar]
cstrs ->Ptr CChar -> [Ptr CChar] -> (Ptr (Ptr CChar) -> IO a) -> IO a
forall a b. Storable a => a -> [a] -> (Ptr a -> IO b) -> IO b
withArray0Ptr CChar
forall a. Ptr a
nullPtr[Ptr CChar]
cstrs ((Ptr (Ptr CChar) -> IO a) -> IO a)
-> (Ptr (Ptr CChar) -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\Ptr (Ptr CChar)
arg_arr ->letenv' :: [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 -> (Ptr CChar -> IO a) -> IO a)
-> [FilePath] -> ([Ptr CChar] -> IO a) -> IO a
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withManyFilePath -> (Ptr CChar -> IO a) -> IO a
forall a. FilePath -> (Ptr CChar -> IO a) -> IO a
withFilePath[FilePath]
env' (([Ptr CChar] -> IO a) -> IO a) -> ([Ptr CChar] -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\[Ptr CChar]
cenv ->Ptr CChar -> [Ptr CChar] -> (Ptr (Ptr CChar) -> IO a) -> IO a
forall a b. Storable a => a -> [a] -> (Ptr a -> IO b) -> IO b
withArray0Ptr CChar
forall a. Ptr a
nullPtr[Ptr CChar]
cenv ((Ptr (Ptr CChar) -> IO a) -> IO a)
-> (Ptr (Ptr CChar) -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\Ptr (Ptr CChar)
env_arr ->doIO ()
pPrPr_disableITimers ifBool
search thenFilePath -> FilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => FilePath -> FilePath -> IO a -> IO ()
throwErrnoPathIfMinus1_FilePath
"executeFile"FilePath
path (Ptr CChar -> Ptr (Ptr CChar) -> Ptr (Ptr CChar) -> IO CInt
c_execvpe Ptr CChar
s Ptr (Ptr CChar)
arg_arr Ptr (Ptr CChar)
env_arr )elseFilePath -> FilePath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => FilePath -> FilePath -> IO a -> IO ()
throwErrnoPathIfMinus1_FilePath
"executeFile"FilePath
path (Ptr CChar -> Ptr (Ptr CChar) -> Ptr (Ptr CChar) -> IO CInt
c_execve Ptr CChar
s Ptr (Ptr CChar)
arg_arr Ptr (Ptr CChar)
env_arr )a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returna
forall a. HasCallStack => a
undefined-- never reachedforeignimportccallunsafe"execvp"c_execvp ::CString->PtrCString->IOCIntforeignimportccallunsafe"execv"c_execv ::CString->PtrCString->IOCIntforeignimportccallunsafe"execve"c_execve ::CString->PtrCString->PtrCString->IOCInt{-# LINE 136 "System/Posix/Process.hsc" #-}

AltStyle によって変換されたページ (->オリジナル) /