{-# LINE 1 "libraries/unix/System/Posix/Process/Common.hsc" #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE InterruptibleFFI, RankNTypes #-}
{-# LANGUAGE Trustworthy #-}
module System.Posix.Process.Common (
    
    
    forkProcess,
    forkProcessWithUnmask,
    
    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.C.Error
import Foreign.C.Types
import Foreign.Marshal.Alloc ( alloca, allocaBytes )
import Foreign.Ptr ( Ptr )
import Foreign.StablePtr ( StablePtr, newStablePtr, freeStablePtr )
import Foreign.Storable ( Storable(..) )
import System.Exit
import System.Posix.Process.Internals
import System.Posix.Types
import Control.Monad
import Control.Exception.Base ( bracket, getMaskingState, MaskingState(..) ) 
import GHC.TopHandler   ( runIO )
import GHC.IO ( unsafeUnmask, uninterruptibleMask_ )
getProcessID :: IO ProcessID
getProcessID = c_getpid
foreign import ccall unsafe "getpid"
   c_getpid :: IO CPid
getParentProcessID :: IO ProcessID
getParentProcessID = c_getppid
foreign import ccall unsafe "getppid"
  c_getppid :: IO CPid
getProcessGroupID :: IO ProcessGroupID
getProcessGroupID = c_getpgrp
foreign import ccall unsafe "getpgrp"
  c_getpgrp :: IO CPid
getProcessGroupIDOf :: ProcessID -> IO ProcessGroupID
getProcessGroupIDOf pid =
  throwErrnoIfMinus1 "getProcessGroupIDOf" (c_getpgid pid)
foreign import ccall unsafe "getpgid"
  c_getpgid :: CPid -> IO CPid
createProcessGroupFor :: ProcessID -> IO ProcessGroupID
createProcessGroupFor pid = do
  throwErrnoIfMinus1_ "createProcessGroupFor" (c_setpgid pid 0)
  return pid
joinProcessGroup :: ProcessGroupID -> IO ()
joinProcessGroup pgid =
  throwErrnoIfMinus1_ "joinProcessGroup" (c_setpgid 0 pgid)
setProcessGroupIDOf :: ProcessID -> ProcessGroupID -> IO ()
setProcessGroupIDOf pid pgid =
  throwErrnoIfMinus1_ "setProcessGroupIDOf" (c_setpgid pid pgid)
foreign import ccall unsafe "setpgid"
  c_setpgid :: CPid -> CPid -> IO CInt
createSession :: IO ProcessGroupID
createSession = throwErrnoIfMinus1 "createSession" c_setsid
foreign import ccall unsafe "setsid"
  c_setsid :: IO CPid
data ProcessTimes
  = ProcessTimes { elapsedTime     :: ClockTick
                 , userTime        :: ClockTick
                 , systemTime      :: ClockTick
                 , childUserTime   :: ClockTick
                 , childSystemTime :: ClockTick
                 }
getProcessTimes :: IO ProcessTimes
getProcessTimes = do
   allocaBytes (32) $ \p_tms -> do
{-# LINE 194 "libraries/unix/System/Posix/Process/Common.hsc" #-}
     elapsed <- throwErrnoIfMinus1 "getProcessTimes" (c_times p_tms)
     ut  <- ((\hsc_ptr -> peekByteOff hsc_ptr 0))  p_tms
{-# LINE 196 "libraries/unix/System/Posix/Process/Common.hsc" #-}
     st  <- ((\hsc_ptr -> peekByteOff hsc_ptr 8))  p_tms
{-# LINE 197 "libraries/unix/System/Posix/Process/Common.hsc" #-}
     cut <- ((\hsc_ptr -> peekByteOff hsc_ptr 16)) p_tms
{-# LINE 198 "libraries/unix/System/Posix/Process/Common.hsc" #-}
     cst <- ((\hsc_ptr -> peekByteOff hsc_ptr 24)) p_tms
{-# LINE 199 "libraries/unix/System/Posix/Process/Common.hsc" #-}
     return (ProcessTimes{ elapsedTime     = elapsed,
                           userTime        = ut,
                           systemTime      = st,
                           childUserTime   = cut,
                           childSystemTime = cst
                          })
data {-# CTYPE "struct tms" #-} CTms
foreign import capi unsafe "HsUnix.h times"
  c_times :: Ptr CTms -> IO CClock
nice :: Int -> IO ()
nice prio = do
  resetErrno
  res <- c_nice (fromIntegral prio)
  when (res == -1) $ do
    err <- getErrno
    when (err /= eOK) (throwErrno "nice")
foreign import ccall unsafe "nice"
  c_nice :: CInt -> IO CInt
getProcessPriority      :: ProcessID      -> IO Int
getProcessGroupPriority :: ProcessGroupID -> IO Int
getUserPriority         :: UserID         -> IO Int
getProcessPriority pid = do
  r <- throwErrnoIfMinus1 "getProcessPriority" $
         c_getpriority (0) (fromIntegral pid)
{-# LINE 232 "libraries/unix/System/Posix/Process/Common.hsc" #-}
  return (fromIntegral r)
getProcessGroupPriority pid = do
  r <- throwErrnoIfMinus1 "getProcessPriority" $
         c_getpriority (1) (fromIntegral pid)
{-# LINE 237 "libraries/unix/System/Posix/Process/Common.hsc" #-}
  return (fromIntegral r)
getUserPriority uid = do
  r <- throwErrnoIfMinus1 "getUserPriority" $
         c_getpriority (2) (fromIntegral uid)
{-# LINE 242 "libraries/unix/System/Posix/Process/Common.hsc" #-}
  return (fromIntegral r)
foreign import ccall unsafe "getpriority"
  c_getpriority :: CInt -> CInt -> IO CInt
setProcessPriority      :: ProcessID      -> Int -> IO ()
setProcessGroupPriority :: ProcessGroupID -> Int -> IO ()
setUserPriority         :: UserID         -> Int -> IO ()
setProcessPriority pid val =
  throwErrnoIfMinus1_ "setProcessPriority" $
    c_setpriority (0) (fromIntegral pid) (fromIntegral val)
{-# LINE 254 "libraries/unix/System/Posix/Process/Common.hsc" #-}
setProcessGroupPriority pid val =
  throwErrnoIfMinus1_ "setProcessPriority" $
    c_setpriority (1) (fromIntegral pid) (fromIntegral val)
{-# LINE 258 "libraries/unix/System/Posix/Process/Common.hsc" #-}
setUserPriority uid val =
  throwErrnoIfMinus1_ "setUserPriority" $
    c_setpriority (2) (fromIntegral uid) (fromIntegral val)
{-# LINE 262 "libraries/unix/System/Posix/Process/Common.hsc" #-}
foreign import ccall unsafe "setpriority"
  c_setpriority :: CInt -> CInt -> CInt -> IO CInt
forkProcess :: IO () -> IO ProcessID
forkProcess action = do
  
  
  
  mstate <- getMaskingState
  let action' = case mstate of
          Unmasked              -> unsafeUnmask action
          MaskedInterruptible   -> action
          MaskedUninterruptible -> uninterruptibleMask_ action
  bracket
    (newStablePtr (runIO action'))
    freeStablePtr
    (\stable -> throwErrnoIfMinus1 "forkProcess" (forkProcessPrim stable))
foreign import ccall "forkProcess" forkProcessPrim :: StablePtr (IO ()) -> IO CPid
forkProcessWithUnmask :: ((forall a . IO a -> IO a) -> IO ()) -> IO ProcessID
forkProcessWithUnmask action = forkProcess (action unsafeUnmask)
getProcessStatus :: Bool -> Bool -> ProcessID -> IO (Maybe ProcessStatus)
getProcessStatus block stopped pid =
  alloca $ \wstatp -> do
    pid' <- throwErrnoIfMinus1Retry "getProcessStatus"
                (c_waitpid pid wstatp (waitOptions block stopped))
    case pid' of
      0  -> return Nothing
      _  -> do ps <- readWaitStatus wstatp
               return (Just ps)
foreign import ccall interruptible "waitpid"
  c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid
getGroupProcessStatus :: Bool
                      -> Bool
                      -> ProcessGroupID
                      -> IO (Maybe (ProcessID, ProcessStatus))
getGroupProcessStatus block stopped pgid =
  alloca $ \wstatp -> do
    pid <- throwErrnoIfMinus1Retry "getGroupProcessStatus"
                (c_waitpid (-pgid) wstatp (waitOptions block stopped))
    case pid of
      0  -> return Nothing
      _  -> do ps <- readWaitStatus wstatp
               return (Just (pid, ps))
getAnyProcessStatus :: Bool -> Bool -> IO (Maybe (ProcessID, ProcessStatus))
getAnyProcessStatus block stopped = getGroupProcessStatus block stopped 1
waitOptions :: Bool -> Bool -> CInt
waitOptions False False = (1)
{-# LINE 370 "libraries/unix/System/Posix/Process/Common.hsc" #-}
waitOptions False True  = (3)
{-# LINE 371 "libraries/unix/System/Posix/Process/Common.hsc" #-}
waitOptions True  False = 0
waitOptions True  True  = (2)
{-# LINE 373 "libraries/unix/System/Posix/Process/Common.hsc" #-}
readWaitStatus :: Ptr CInt -> IO ProcessStatus
readWaitStatus wstatp = do
  wstat <- peek wstatp
  decipherWaitStatus wstat
exitImmediately :: ExitCode -> IO ()
exitImmediately exitcode = c_exit (exitcode2Int exitcode)
  where
    exitcode2Int ExitSuccess = 0
    exitcode2Int (ExitFailure n) = fromIntegral n
foreign import ccall unsafe "exit"
  c_exit :: CInt -> IO ()
{-# DEPRECATED createProcessGroup "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." #-} 
createProcessGroup :: ProcessID -> IO ProcessGroupID
createProcessGroup pid = do
  throwErrnoIfMinus1_ "createProcessGroup" (c_setpgid pid 0)
  return pid
{-# DEPRECATED setProcessGroupID "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." #-} 
setProcessGroupID :: ProcessID -> ProcessGroupID -> IO ()
setProcessGroupID pid pgid =
  throwErrnoIfMinus1_ "setProcessGroupID" (c_setpgid pid pgid)