{-# LINE 1 "System/Posix/Process/PosixString.hsc" #-}{-# LANGUAGE PackageImports #-}------------------------------------------------------------------------------- |-- Module : System.Posix.Process.PosixString-- 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.PosixString(-- * 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 ,)whereimportForeignimportSystem.Posix.Process.Internals importSystem.Posix.Process (ProcessTimes (..),setProcessGroupID ,createProcessGroup ,getGroupProcessStatus ,getAnyProcessStatus ,getProcessStatus ,setUserPriority ,setProcessGroupPriority ,setProcessPriority ,getUserPriority ,getProcessGroupPriority ,getProcessPriority ,nice ,getProcessTimes ,createSession ,setProcessGroupIDOf ,joinProcessGroup ,createProcessGroupFor ,getProcessGroupIDOf ,getProcessGroupID ,getParentProcessID ,getProcessID ,exitImmediately ,forkProcessWithUnmask ,forkProcess )importForeign.Chiding(throwErrnoPath,throwErrnoPathIf,throwErrnoPathIf_,throwErrnoPathIfNull,throwErrnoPathIfMinus1,throwErrnoPathIfMinus1_)importSystem.OsPath.TypesimportSystem.OsString.Internal.Types(PosixString(..)){-# LINE 86 "System/Posix/Process/PosixString.hsc" #-}importqualified"filepath"System.OsPath.Data.ByteString.ShortasBC{-# LINE 88 "System/Posix/Process/PosixString.hsc" #-}importSystem.Posix.PosixPath.FilePath -- | @'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 ::PosixPath-- ^ Command->Bool-- ^ Search PATH?->[PosixString]-- ^ Arguments->Maybe[(PosixString,PosixString)]-- ^ Environment->IOa executeFile :: forall a.
PosixPath
-> Bool -> [PosixPath] -> Maybe [(PosixPath, PosixPath)] -> IO a
executeFile PosixPath
path Bool
search [PosixPath]
args Maybe [(PosixPath, PosixPath)]
Nothing=doPosixPath -> (Ptr CChar -> IO a) -> IO a
forall a. PosixPath -> (Ptr CChar -> IO a) -> IO a
withFilePath PosixPath
path ((Ptr CChar -> IO a) -> IO a) -> (Ptr CChar -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\Ptr CChar
s ->(PosixPath -> (Ptr CChar -> IO a) -> IO a)
-> [PosixPath] -> ([Ptr CChar] -> IO a) -> IO a
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withManyPosixPath -> (Ptr CChar -> IO a) -> IO a
forall a. PosixPath -> (Ptr CChar -> IO a) -> IO a
withFilePath (PosixPath
path PosixPath -> [PosixPath] -> [PosixPath]
forall a. a -> [a] -> [a]
:[PosixPath]
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 thenString -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"executeFile"PosixPath
path (Ptr CChar -> Ptr (Ptr CChar) -> IO CInt
c_execvp Ptr CChar
s Ptr (Ptr CChar)
arr )elseString -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"executeFile"PosixPath
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 PosixPath
path Bool
search [PosixPath]
args (Just[(PosixPath, PosixPath)]
env )=doPosixPath -> (Ptr CChar -> IO a) -> IO a
forall a. PosixPath -> (Ptr CChar -> IO a) -> IO a
withFilePath PosixPath
path ((Ptr CChar -> IO a) -> IO a) -> (Ptr CChar -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$\Ptr CChar
s ->(PosixPath -> (Ptr CChar -> IO a) -> IO a)
-> [PosixPath] -> ([Ptr CChar] -> IO a) -> IO a
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withManyPosixPath -> (Ptr CChar -> IO a) -> IO a
forall a. PosixPath -> (Ptr CChar -> IO a) -> IO a
withFilePath (PosixPath
path PosixPath -> [PosixPath] -> [PosixPath]
forall a. a -> [a] -> [a]
:[PosixPath]
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' :: [PosixPath]
env' =((PosixPath, PosixPath) -> PosixPath)
-> [(PosixPath, PosixPath)] -> [PosixPath]
forall a b. (a -> b) -> [a] -> [b]
map(\(PosixStringShortByteString
name ,PosixStringShortByteString
val )->ShortByteString -> PosixPath
PosixString(ShortByteString -> PosixPath) -> ShortByteString -> PosixPath
forall a b. (a -> b) -> a -> b
$ShortByteString
name ShortByteString -> ShortByteString -> ShortByteString
`BC.append`(Word8
_equal Word8 -> ShortByteString -> ShortByteString
`BC.cons`ShortByteString
val ))[(PosixPath, PosixPath)]
env in(PosixPath -> (Ptr CChar -> IO a) -> IO a)
-> [PosixPath] -> ([Ptr CChar] -> IO a) -> IO a
forall a b res.
(a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
withManyPosixPath -> (Ptr CChar -> IO a) -> IO a
forall a. PosixPath -> (Ptr CChar -> IO a) -> IO a
withFilePath [PosixPath]
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 thenString -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"executeFile"PosixPath
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 )elseString -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"executeFile"PosixPath
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_equal ::Word8_equal :: Word8
_equal =Word8
0x3d

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