{-# LINE 1 "System/Posix/Process/Common.hsc" #-}{-# LANGUAGE CApiFFI #-}{-# LANGUAGE InterruptibleFFI, RankNTypes #-}{-# LANGUAGE Trustworthy #-}------------------------------------------------------------------------------- |-- Module : System.Posix.Process.Common-- 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.Common(-- * Processes-- ** Forking and executingforkProcess ,forkProcessWithUnmask ,-- ** ExitingexitImmediately ,-- ** Process environmentgetProcessID ,getParentProcessID ,-- ** Process groupsgetProcessGroupID ,getProcessGroupIDOf ,createProcessGroupFor ,joinProcessGroup ,setProcessGroupIDOf ,-- ** SessionscreateSession ,-- ** Process timesProcessTimes (..),getProcessTimes ,clocksPerSec ,-- ** Scheduling prioritynice ,getProcessPriority ,getProcessGroupPriority ,getUserPriority ,setProcessPriority ,setProcessGroupPriority ,setUserPriority ,-- ** Process statusProcessStatus (..),getProcessStatus ,getAnyProcessStatus ,getGroupProcessStatus ,-- ** DeprecatedcreateProcessGroup ,setProcessGroupID ,)whereimportForeign.C.ErrorimportForeign.C.TypesimportForeign.Marshal.Alloc(alloca,allocaBytes)importForeign.Ptr(Ptr)importForeign.StablePtr(StablePtr,newStablePtr,freeStablePtr)importForeign.Storable(Storable(..))importSystem.ExitimportSystem.Posix.Process.Internals importSystem.Posix.TypesimportControl.MonadimportControl.Exception.Base(bracket,getMaskingState,MaskingState(..))-- used by forkProcessimportGHC.TopHandler(runIO){-# LINE 87 "System/Posix/Process/Common.hsc" #-}importGHC.IO(unsafeUnmask,uninterruptibleMask_){-# LINE 92 "System/Posix/Process/Common.hsc" #-}{-# LINE 101 "System/Posix/Process/Common.hsc" #-}-- ------------------------------------------------------------------------------- Process environment-- | 'getProcessID' calls @getpid@ to obtain the 'ProcessID' for-- the current process.getProcessID ::IOProcessIDgetProcessID :: IO CPid getProcessID =IO CPid c_getpid foreignimportccallunsafe"getpid"c_getpid ::IOCPid{-# LINE 113 "System/Posix/Process/Common.hsc" #-}{-# LINE 122 "System/Posix/Process/Common.hsc" #-}-- | 'getParentProcessID' calls @getppid@ to obtain the 'ProcessID' for-- the parent of the current process.getParentProcessID ::IOProcessIDgetParentProcessID :: IO CPid getParentProcessID =IO CPid c_getppid foreignimportccallunsafe"getppid"c_getppid ::IOCPid{-# LINE 132 "System/Posix/Process/Common.hsc" #-}{-# LINE 141 "System/Posix/Process/Common.hsc" #-}-- | 'getProcessGroupID' calls @getpgrp@ to obtain the-- 'ProcessGroupID' for the current process.getProcessGroupID ::IOProcessGroupIDgetProcessGroupID :: IO CPid getProcessGroupID =IO CPid c_getpgrp foreignimportccallunsafe"getpgrp"c_getpgrp ::IOCPid{-# LINE 151 "System/Posix/Process/Common.hsc" #-}{-# LINE 160 "System/Posix/Process/Common.hsc" #-}-- | @'getProcessGroupIDOf' pid@ calls @getpgid@ to obtain the-- 'ProcessGroupID' for process @pid@.getProcessGroupIDOf ::ProcessID->IOProcessGroupIDgetProcessGroupIDOf :: CPid -> IO CPid getProcessGroupIDOf CPid pid =String -> IO CPid -> IO CPid forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1String "getProcessGroupIDOf"(CPid -> IO CPid c_getpgid CPid pid )foreignimportccallunsafe"getpgid"c_getpgid ::CPid->IOCPid{-# LINE 171 "System/Posix/Process/Common.hsc" #-}{- To be added in the future, after the deprecation period for the existing createProcessGroup has elapsed: -- | 'createProcessGroup' calls @setpgid(0,0)@ to make -- the current process a new process group leader. createProcessGroup :: IO ProcessGroupID createProcessGroup = do throwErrnoIfMinus1_ "createProcessGroup" (c_setpgid 0 0) pgid <- getProcessGroupID return pgid -}{-# LINE 193 "System/Posix/Process/Common.hsc" #-}-- | @'createProcessGroupFor' pid@ calls @setpgid@ to make-- process @pid@ a new process group leader.createProcessGroupFor ::ProcessID->IOProcessGroupIDcreateProcessGroupFor :: CPid -> IO CPid createProcessGroupFor CPid pid =doString -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "createProcessGroupFor"(CPid -> CPid -> IO CInt c_setpgid CPid pid CPid 0)CPid -> IO CPid forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnCPid pid {-# LINE 202 "System/Posix/Process/Common.hsc" #-}{-# LINE 211 "System/Posix/Process/Common.hsc" #-}-- | @'joinProcessGroup' pgid@ calls @setpgid@ to set the-- 'ProcessGroupID' of the current process to @pgid@.joinProcessGroup ::ProcessGroupID->IO()joinProcessGroup :: CPid -> IO () joinProcessGroup CPid pgid =String -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "joinProcessGroup"(CPid -> CPid -> IO CInt c_setpgid CPid 0CPid pgid ){-# LINE 219 "System/Posix/Process/Common.hsc" #-}{- To be added in the future, after the deprecation period for the existing setProcessGroupID has elapsed: -- | @'setProcessGroupID' pgid@ calls @setpgid@ to set the -- 'ProcessGroupID' of the current process to @pgid@. setProcessGroupID :: ProcessGroupID -> IO () setProcessGroupID pgid = throwErrnoIfMinus1_ "setProcessGroupID" (c_setpgid 0 pgid) -}{-# LINE 239 "System/Posix/Process/Common.hsc" #-}-- | @'setProcessGroupIDOf' pid pgid@ calls @setpgid@ to set the-- 'ProcessGroupIDOf' for process @pid@ to @pgid@.setProcessGroupIDOf ::ProcessID->ProcessGroupID->IO()setProcessGroupIDOf :: CPid -> CPid -> IO () setProcessGroupIDOf CPid pid CPid pgid =String -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "setProcessGroupIDOf"(CPid -> CPid -> IO CInt c_setpgid CPid pid CPid pgid )foreignimportccallunsafe"setpgid"c_setpgid ::CPid->CPid->IOCInt{-# LINE 250 "System/Posix/Process/Common.hsc" #-}{-# LINE 259 "System/Posix/Process/Common.hsc" #-}-- | 'createSession' calls @setsid@ to create a new session-- with the current process as session leader.createSession ::IOProcessGroupIDcreateSession :: IO CPid createSession =String -> IO CPid -> IO CPid forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1String "createSession"IO CPid c_setsid foreignimportccallunsafe"setsid"c_setsid ::IOCPid{-# LINE 269 "System/Posix/Process/Common.hsc" #-}-- ------------------------------------------------------------------------------- Process times-- All times in clock ticks (see getClockTick)dataProcessTimes =ProcessTimes {ProcessTimes -> CClock elapsedTime ::ClockTick,ProcessTimes -> CClock userTime ::ClockTick,ProcessTimes -> CClock systemTime ::ClockTick,ProcessTimes -> CClock childUserTime ::ClockTick,ProcessTimes -> CClock childSystemTime ::ClockTick}{-# LINE 284 "System/Posix/Process/Common.hsc" #-}-- | 'getProcessTimes' calls @times@ to obtain time-accounting-- information for the current process and its children.getProcessTimes ::IOProcessTimes getProcessTimes :: IO ProcessTimes getProcessTimes =doInt -> (Ptr CTms -> IO ProcessTimes) -> IO ProcessTimes forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes(Int 32)((Ptr CTms -> IO ProcessTimes) -> IO ProcessTimes) -> (Ptr CTms -> IO ProcessTimes) -> IO ProcessTimes forall a b. (a -> b) -> a -> b $\Ptr CTms p_tms ->do{-# LINE 290 "System/Posix/Process/Common.hsc" #-}elapsed<-throwErrnoIfMinus1"getProcessTimes"(c_timesp_tms)ut<-((\hsc_ptr->peekByteOffhsc_ptr0))p_tms{-# LINE 292 "System/Posix/Process/Common.hsc" #-}st<-((\hsc_ptr->peekByteOffhsc_ptr8))p_tms{-# LINE 293 "System/Posix/Process/Common.hsc" #-}cut<-((\hsc_ptr->peekByteOffhsc_ptr16))p_tms{-# LINE 294 "System/Posix/Process/Common.hsc" #-}cst<-((\hsc_ptr->peekByteOffhsc_ptr24))p_tms{-# LINE 295 "System/Posix/Process/Common.hsc" #-}return(ProcessTimes{elapsedTime=elapsed,userTime=ut,systemTime=st,childUserTime=cut,childSystemTime=cst})data{-# CTYPE"struct tms"#-}CTms foreignimportcapiunsafe"HsUnix.h times"c_times ::PtrCTms ->IOCClock-- | Returns the value from the @CLOCK_PER_SEC@ macro, which is required by POSIX.clocksPerSec ::ClockTick{-# LINE 310 "System/Posix/Process/Common.hsc" #-}clocksPerSec=c_clocks_per_secforeignimportcapiunsafe"HsUnix.h __hsunix_clocks_per_second"c_clocks_per_sec ::CClock{-# LINE 319 "System/Posix/Process/Common.hsc" #-}{-# LINE 333 "System/Posix/Process/Common.hsc" #-}-- ------------------------------------------------------------------------------- Process scheduling priority{-# LINE 345 "System/Posix/Process/Common.hsc" #-}nice ::Int->IO()nice :: Int -> IO () nice Int prio =doIO () resetErrnoCInt res <-CInt -> IO CInt c_nice (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralInt prio )Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when(CInt res CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool ==-CInt 1)(IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $doErrno err <-IO Errno getErrnoBool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when(Errno err Errno -> Errno -> Bool forall a. Eq a => a -> a -> Bool /=Errno eOK)(String -> IO () forall a. String -> IO a throwErrnoString "nice")foreignimportccallunsafe"nice"c_nice ::CInt->IOCInt{-# LINE 358 "System/Posix/Process/Common.hsc" #-}getProcessPriority ::ProcessID->IOIntgetProcessGroupPriority ::ProcessGroupID->IOIntgetUserPriority ::UserID->IOInt{-# LINE 378 "System/Posix/Process/Common.hsc" #-}getProcessPriority :: CPid -> IO Int getProcessPriority CPid pid =doCInt r <-String -> IO CInt -> IO CInt forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1String "getProcessPriority"(IO CInt -> IO CInt) -> IO CInt -> IO CInt forall a b. (a -> b) -> a -> b $CInt -> CInt -> IO CInt c_getpriority (CInt 0)(CPid -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralCPid pid ){-# LINE 382 "System/Posix/Process/Common.hsc" #-}return(fromIntegralr)getProcessGroupPriority :: CPid -> IO Int getProcessGroupPriority CPid pid =doCInt r <-String -> IO CInt -> IO CInt forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1String "getProcessPriority"(IO CInt -> IO CInt) -> IO CInt -> IO CInt forall a b. (a -> b) -> a -> b $CInt -> CInt -> IO CInt c_getpriority (CInt 1)(CPid -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralCPid pid ){-# LINE 387 "System/Posix/Process/Common.hsc" #-}return(fromIntegralr)getUserPriority :: UserID -> IO Int getUserPriority UserID uid =doCInt r <-String -> IO CInt -> IO CInt forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1String "getUserPriority"(IO CInt -> IO CInt) -> IO CInt -> IO CInt forall a b. (a -> b) -> a -> b $CInt -> CInt -> IO CInt c_getpriority (CInt 2)(UserID -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralUserID uid ){-# LINE 392 "System/Posix/Process/Common.hsc" #-}return(fromIntegralr)foreignimportccallunsafe"getpriority"c_getpriority ::CInt->CInt->IOCInt{-# LINE 398 "System/Posix/Process/Common.hsc" #-}setProcessPriority ::ProcessID->Int->IO()setProcessGroupPriority ::ProcessGroupID->Int->IO()setUserPriority ::UserID->Int->IO(){-# LINE 418 "System/Posix/Process/Common.hsc" #-}setProcessPriority :: CPid -> Int -> IO () setProcessPriority CPid pid Int val =String -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "setProcessPriority"(IO CInt -> IO ()) -> IO CInt -> IO () forall a b. (a -> b) -> a -> b $CInt -> CInt -> CInt -> IO CInt c_setpriority (CInt 0)(CPid -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralCPid pid )(Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralInt val ){-# LINE 422 "System/Posix/Process/Common.hsc" #-}setProcessGroupPriority :: CPid -> Int -> IO () setProcessGroupPriority CPid pid Int val =String -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "setProcessPriority"(IO CInt -> IO ()) -> IO CInt -> IO () forall a b. (a -> b) -> a -> b $CInt -> CInt -> CInt -> IO CInt c_setpriority (CInt 1)(CPid -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralCPid pid )(Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralInt val ){-# LINE 426 "System/Posix/Process/Common.hsc" #-}setUserPriority :: UserID -> Int -> IO () setUserPriority UserID uid Int val =String -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "setUserPriority"(IO CInt -> IO ()) -> IO CInt -> IO () forall a b. (a -> b) -> a -> b $CInt -> CInt -> CInt -> IO CInt c_setpriority (CInt 2)(UserID -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralUserID uid )(Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralInt val ){-# LINE 430 "System/Posix/Process/Common.hsc" #-}foreignimportccallunsafe"setpriority"c_setpriority ::CInt->CInt->CInt->IOCInt{-# LINE 435 "System/Posix/Process/Common.hsc" #-}-- ------------------------------------------------------------------------------- Forking, execution{- | 'forkProcess' corresponds to the POSIX @fork@ system call. The 'IO' action passed as an argument is executed in the child process; no other threads will be copied to the child process. On success, 'forkProcess' returns the child's 'ProcessID' to the parent process; in case of an error, an exception is thrown. The exception masking state of the executed action is inherited (c.f. 'forkIO'), see also 'forkProcessWithUnmask' (/since: 2.7.0.0/). 'forkProcess' comes with a giant warning: since any other running threads are not copied into the child process, it's easy to go wrong: e.g. by accessing some shared resource that was held by another thread in the parent. GHC note: 'forkProcess' is not currently very well supported when using multiple capabilities (@+RTS -N@), although it is supported with @-threaded@ as long as only one capability is being used. -}{-# LINE 471 "System/Posix/Process/Common.hsc" #-}forkProcess ::IO()->IOProcessIDforkProcess :: IO () -> IO CPid forkProcess IO () action =do-- wrap action to re-establish caller's masking state, as-- 'forkProcessPrim' starts in 'MaskedInterruptible' state by-- default; see also #1048MaskingState mstate <-IO MaskingState getMaskingStateletaction' :: IO () action' =caseMaskingState mstate ofMaskingState Unmasked->IO () -> IO () forall a. IO a -> IO a unsafeUnmaskIO () action MaskingState MaskedInterruptible->IO () action MaskingState MaskedUninterruptible->IO () -> IO () forall a. IO a -> IO a uninterruptibleMask_IO () action IO (StablePtr (IO ())) -> (StablePtr (IO ()) -> IO ()) -> (StablePtr (IO ()) -> IO CPid) -> IO CPid forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c bracket(IO () -> IO (StablePtr (IO ())) forall a. a -> IO (StablePtr a) newStablePtr(IO () -> IO () forall a. IO a -> IO a runIOIO () action' ))StablePtr (IO ()) -> IO () forall a. StablePtr a -> IO () freeStablePtr(\StablePtr (IO ()) stable ->String -> IO CPid -> IO CPid forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1String "forkProcess"(StablePtr (IO ()) -> IO CPid forkProcessPrim StablePtr (IO ()) stable ))foreignimportccall"forkProcess"forkProcessPrim ::StablePtr(IO())->IOCPid-- | Variant of 'forkProcess' in the style of 'forkIOWithUnmask'.---- @since 2.7.0.0forkProcessWithUnmask ::((foralla .IOa ->IOa )->IO())->IOProcessIDforkProcessWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO CPid forkProcessWithUnmask (forall a. IO a -> IO a) -> IO () action =IO () -> IO CPid forkProcess ((forall a. IO a -> IO a) -> IO () action IO a -> IO a forall a. IO a -> IO a unsafeUnmask){-# LINE 497 "System/Posix/Process/Common.hsc" #-}{-# LINE 506 "System/Posix/Process/Common.hsc" #-}-- ------------------------------------------------------------------------------- Waiting for process termination-- | @'getProcessStatus' blk stopped pid@ calls @waitpid@, returning-- @'Just' tc@, the 'ProcessStatus' for process @pid@ if it is-- available, 'Nothing' otherwise. If @blk@ is 'False', then-- @WNOHANG@ is set in the options for @waitpid@, otherwise not.-- If @stopped@ is 'True', then @WUNTRACED@ is set in the-- options for @waitpid@, otherwise not.getProcessStatus ::Bool->Bool->ProcessID->IO(MaybeProcessStatus )getProcessStatus :: Bool -> Bool -> CPid -> IO (Maybe ProcessStatus) getProcessStatus Bool block Bool stopped CPid pid =(Ptr CInt -> IO (Maybe ProcessStatus)) -> IO (Maybe ProcessStatus) forall a b. Storable a => (Ptr a -> IO b) -> IO b alloca((Ptr CInt -> IO (Maybe ProcessStatus)) -> IO (Maybe ProcessStatus)) -> (Ptr CInt -> IO (Maybe ProcessStatus)) -> IO (Maybe ProcessStatus) forall a b. (a -> b) -> a -> b $\Ptr CInt wstatp ->doCPid pid' <-String -> IO CPid -> IO CPid forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1RetryString "getProcessStatus"(CPid -> Ptr CInt -> CInt -> IO CPid c_waitpid CPid pid Ptr CInt wstatp (Bool -> Bool -> CInt waitOptions Bool block Bool stopped ))caseCPid pid' ofCPid 0->Maybe ProcessStatus -> IO (Maybe ProcessStatus) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnMaybe ProcessStatus forall a. Maybe a NothingCPid _->doProcessStatus ps <-Ptr CInt -> IO ProcessStatus readWaitStatus Ptr CInt wstatp Maybe ProcessStatus -> IO (Maybe ProcessStatus) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(ProcessStatus -> Maybe ProcessStatus forall a. a -> Maybe a JustProcessStatus ps )-- safe/interruptible, because this call might blockforeignimportccallinterruptible"waitpid"c_waitpid ::CPid->PtrCInt->CInt->IOCPid{-# LINE 531 "System/Posix/Process/Common.hsc" #-}{-# LINE 543 "System/Posix/Process/Common.hsc" #-}-- | @'getGroupProcessStatus' blk stopped pgid@ calls @waitpid@,-- returning @'Just' (pid, tc)@, the 'ProcessID' and 'ProcessStatus'-- for any process in group @pgid@ if one is available, or 'Nothing'-- if there are child processes but none have exited. If there are-- no child processes, then 'getGroupProcessStatus' raises an-- 'isDoesNotExistError' exception.---- If @blk@ is 'False', then @WNOHANG@ is set in the options for-- @waitpid@, otherwise not. If @stopped@ is 'True', then-- @WUNTRACED@ is set in the options for @waitpid@, otherwise not.getGroupProcessStatus ::Bool->Bool->ProcessGroupID->IO(Maybe(ProcessID,ProcessStatus ))getGroupProcessStatus :: Bool -> Bool -> CPid -> IO (Maybe (CPid, ProcessStatus)) getGroupProcessStatus Bool block Bool stopped CPid pgid =(Ptr CInt -> IO (Maybe (CPid, ProcessStatus))) -> IO (Maybe (CPid, ProcessStatus)) forall a b. Storable a => (Ptr a -> IO b) -> IO b alloca((Ptr CInt -> IO (Maybe (CPid, ProcessStatus))) -> IO (Maybe (CPid, ProcessStatus))) -> (Ptr CInt -> IO (Maybe (CPid, ProcessStatus))) -> IO (Maybe (CPid, ProcessStatus)) forall a b. (a -> b) -> a -> b $\Ptr CInt wstatp ->doCPid pid <-String -> IO CPid -> IO CPid forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1RetryString "getGroupProcessStatus"(CPid -> Ptr CInt -> CInt -> IO CPid c_waitpid (-CPid pgid )Ptr CInt wstatp (Bool -> Bool -> CInt waitOptions Bool block Bool stopped ))caseCPid pid ofCPid 0->Maybe (CPid, ProcessStatus) -> IO (Maybe (CPid, ProcessStatus)) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnMaybe (CPid, ProcessStatus) forall a. Maybe a NothingCPid _->doProcessStatus ps <-Ptr CInt -> IO ProcessStatus readWaitStatus Ptr CInt wstatp Maybe (CPid, ProcessStatus) -> IO (Maybe (CPid, ProcessStatus)) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return((CPid, ProcessStatus) -> Maybe (CPid, ProcessStatus) forall a. a -> Maybe a Just(CPid pid ,ProcessStatus ps )){-# LINE 568 "System/Posix/Process/Common.hsc" #-}{-# LINE 577 "System/Posix/Process/Common.hsc" #-}-- | @'getAnyProcessStatus' blk stopped@ calls @waitpid@, returning-- @'Just' (pid, tc)@, the 'ProcessID' and 'ProcessStatus' for any-- child process if a child process has exited, or 'Nothing' if-- there are child processes but none have exited. If there are no-- child processes, then 'getAnyProcessStatus' raises an-- 'isDoesNotExistError' exception.---- If @blk@ is 'False', then @WNOHANG@ is set in the options for-- @waitpid@, otherwise not. If @stopped@ is 'True', then-- @WUNTRACED@ is set in the options for @waitpid@, otherwise not.getAnyProcessStatus ::Bool->Bool->IO(Maybe(ProcessID,ProcessStatus ))getAnyProcessStatus :: Bool -> Bool -> IO (Maybe (CPid, ProcessStatus)) getAnyProcessStatus Bool block Bool stopped =Bool -> Bool -> CPid -> IO (Maybe (CPid, ProcessStatus)) getGroupProcessStatus Bool block Bool stopped CPid 1{-# LINE 592 "System/Posix/Process/Common.hsc" #-}{-# LINE 594 "System/Posix/Process/Common.hsc" #-}waitOptions ::Bool->Bool->CInt-- block stoppedwaitOptions :: Bool -> Bool -> CInt waitOptions Bool FalseBool False=(CInt 1){-# LINE 598 "System/Posix/Process/Common.hsc" #-}waitOptionsFalseTrue=(3){-# LINE 599 "System/Posix/Process/Common.hsc" #-}waitOptionsTrueFalse=0waitOptions Bool TrueBool True=(CInt 2){-# LINE 601 "System/Posix/Process/Common.hsc" #-}-- Turn a (ptr to a) wait status into a ProcessStatusreadWaitStatus ::PtrCInt->IOProcessStatus readWaitStatus :: Ptr CInt -> IO ProcessStatus readWaitStatus Ptr CInt wstatp =doCInt wstat <-Ptr CInt -> IO CInt forall a. Storable a => Ptr a -> IO a peekPtr CInt wstatp CInt -> IO ProcessStatus decipherWaitStatus CInt wstat {-# LINE 610 "System/Posix/Process/Common.hsc" #-}-- ------------------------------------------------------------------------------- Exiting-- | @'exitImmediately' status@ calls @_exit@ to terminate the process-- with the indicated exit @status@.-- The operation never returns. Since it does not use the Haskell exception-- system and it cannot be caught.---- Note: Prior to @unix-2.8.0.0@ the type-signature of 'exitImmediately' was-- @ExitCode -> IO ()@.---- @since 2.8.0.0exitImmediately ::ExitCode->IOa exitImmediately :: forall a. ExitCode -> IO a exitImmediately ExitCode status =do() _<-CInt -> IO () c_exit (ExitCode -> CInt forall {a}. Num a => ExitCode -> a exitcode2Int ExitCode status )-- The above will exit the program, but need the following to satisfy-- the type signature.ExitCode -> IO a forall a. ExitCode -> IO a exitImmediately ExitCode status whereexitcode2Int :: ExitCode -> a exitcode2Int ExitCode ExitSuccess=a 0exitcode2Int (ExitFailureInt n )=Int -> a forall a b. (Integral a, Num b) => a -> b fromIntegralInt n foreignimportccallunsafe"exit"c_exit ::CInt->IO(){-# LINE 649 "System/Posix/Process/Common.hsc" #-}-- ------------------------------------------------------------------------------- Deprecated or subject to change{-# DEPRECATEDcreateProcessGroup"This function is scheduled to be replaced by something different in the future, we therefore recommend that you do not use this version and use 'createProcessGroupFor' instead."#-}-- deprecated in 7.2-- | @'createProcessGroup' pid@ calls @setpgid@ to make-- process @pid@ a new process group leader.-- This function is currently deprecated,-- and might be changed to making the current-- process a new process group leader in future versions.createProcessGroup ::ProcessID->IOProcessGroupIDcreateProcessGroup :: CPid -> IO CPid createProcessGroup CPid pid =doString -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "createProcessGroup"(CPid -> CPid -> IO CInt c_setpgid CPid pid CPid 0)CPid -> IO CPid forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnCPid pid {-# DEPRECATEDsetProcessGroupID"This function is scheduled to be replaced by something different in the future, we therefore recommend that you do not use this version and use 'setProcessGroupIDOf' instead."#-}-- deprecated in 7.2-- | @'setProcessGroupID' pid pgid@ calls @setpgid@ to set the-- 'ProcessGroupID' for process @pid@ to @pgid@.-- This function is currently deprecated,-- and might be changed to setting the 'ProcessGroupID'-- for the current process in future versions.setProcessGroupID ::ProcessID->ProcessGroupID->IO()setProcessGroupID :: CPid -> CPid -> IO () setProcessGroupID CPid pid CPid pgid =String -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1_String "setProcessGroupID"(CPid -> CPid -> IO CInt c_setpgid CPid pid CPid pgid )-- -----------------------------------------------------------------------------{-# LINE 677 "System/Posix/Process/Common.hsc" #-}