{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE Trustworthy #-}
module System.Posix.Process.Internals (
pPrPr_disableITimers, c_execvpe,
decipherWaitStatus, ProcessStatus(..) ) where
import Foreign
import Foreign.C
import System.Exit
import System.IO.Error
import GHC.Conc (Signal)
data ProcessStatus
= Exited ExitCode
| Terminated Signal Bool
| Stopped Signal
deriving (ProcessStatus -> ProcessStatus -> Bool
(ProcessStatus -> ProcessStatus -> Bool)
-> (ProcessStatus -> ProcessStatus -> Bool) -> Eq ProcessStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProcessStatus -> ProcessStatus -> Bool
$c/= :: ProcessStatus -> ProcessStatus -> Bool
== :: ProcessStatus -> ProcessStatus -> Bool
$c== :: ProcessStatus -> ProcessStatus -> Bool
External instance of the constraint type Eq Bool
External instance of the constraint type Eq ExitCode
External instance of the constraint type Eq CInt
Eq, Eq ProcessStatus
Eq ProcessStatus
-> (ProcessStatus -> ProcessStatus -> Ordering)
-> (ProcessStatus -> ProcessStatus -> Bool)
-> (ProcessStatus -> ProcessStatus -> Bool)
-> (ProcessStatus -> ProcessStatus -> Bool)
-> (ProcessStatus -> ProcessStatus -> Bool)
-> (ProcessStatus -> ProcessStatus -> ProcessStatus)
-> (ProcessStatus -> ProcessStatus -> ProcessStatus)
-> Ord ProcessStatus
ProcessStatus -> ProcessStatus -> Bool
ProcessStatus -> ProcessStatus -> Ordering
ProcessStatus -> ProcessStatus -> ProcessStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ProcessStatus -> ProcessStatus -> ProcessStatus
$cmin :: ProcessStatus -> ProcessStatus -> ProcessStatus
max :: ProcessStatus -> ProcessStatus -> ProcessStatus
$cmax :: ProcessStatus -> ProcessStatus -> ProcessStatus
>= :: ProcessStatus -> ProcessStatus -> Bool
$c>= :: ProcessStatus -> ProcessStatus -> Bool
> :: ProcessStatus -> ProcessStatus -> Bool
$c> :: ProcessStatus -> ProcessStatus -> Bool
<= :: ProcessStatus -> ProcessStatus -> Bool
$c<= :: ProcessStatus -> ProcessStatus -> Bool
< :: ProcessStatus -> ProcessStatus -> Bool
$c< :: ProcessStatus -> ProcessStatus -> Bool
compare :: ProcessStatus -> ProcessStatus -> Ordering
$ccompare :: ProcessStatus -> ProcessStatus -> Ordering
External instance of the constraint type Ord CInt
External instance of the constraint type Ord Bool
External instance of the constraint type Ord CInt
External instance of the constraint type Ord CInt
External instance of the constraint type Ord ExitCode
Instance of class: Eq of the constraint type Eq ProcessStatus
Instance of class: Ord of the constraint type Ord ProcessStatus
Instance of class: Eq of the constraint type Eq ProcessStatus
Ord, Int -> ProcessStatus -> ShowS
[ProcessStatus] -> ShowS
ProcessStatus -> String
(Int -> ProcessStatus -> ShowS)
-> (ProcessStatus -> String)
-> ([ProcessStatus] -> ShowS)
-> Show ProcessStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProcessStatus] -> ShowS
$cshowList :: [ProcessStatus] -> ShowS
show :: ProcessStatus -> String
$cshow :: ProcessStatus -> String
showsPrec :: Int -> ProcessStatus -> ShowS
$cshowsPrec :: Int -> ProcessStatus -> ShowS
External instance of the constraint type Show Bool
External instance of the constraint type Show CInt
External instance of the constraint type Show CInt
External instance of the constraint type Show ExitCode
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
Show)
foreign import capi unsafe "Rts.h stopTimer"
pPrPr_disableITimers :: IO ()
foreign import ccall unsafe "__hsunix_execvpe"
c_execvpe :: CString -> Ptr CString -> Ptr CString -> IO CInt
decipherWaitStatus :: CInt -> IO ProcessStatus
decipherWaitStatus :: CInt -> IO ProcessStatus
decipherWaitStatus CInt
wstat =
if CInt -> CInt
c_WIFEXITED CInt
wstat CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq CInt
/= CInt
0
then do
let exitstatus :: CInt
exitstatus = CInt -> CInt
c_WEXITSTATUS CInt
wstat
if CInt
exitstatus CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq CInt
== CInt
0
then ProcessStatus -> IO ProcessStatus
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (ExitCode -> ProcessStatus
Exited ExitCode
ExitSuccess)
else ProcessStatus -> IO ProcessStatus
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (ExitCode -> ProcessStatus
Exited (Int -> ExitCode
ExitFailure (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Int
External instance of the constraint type Integral CInt
fromIntegral CInt
exitstatus)))
else do
if CInt -> CInt
c_WIFSIGNALED CInt
wstat CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq CInt
/= CInt
0
then do
let termsig :: CInt
termsig = CInt -> CInt
c_WTERMSIG CInt
wstat
let coredumped :: Bool
coredumped = CInt -> CInt
c_WCOREDUMP CInt
wstat CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq CInt
/= CInt
0
ProcessStatus -> IO ProcessStatus
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (CInt -> Bool -> ProcessStatus
Terminated CInt
termsig Bool
coredumped)
else do
if CInt -> CInt
c_WIFSTOPPED CInt
wstat CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq CInt
/= CInt
0
then do
let stopsig :: CInt
stopsig = CInt -> CInt
c_WSTOPSIG CInt
wstat
ProcessStatus -> IO ProcessStatus
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad IO
return (CInt -> ProcessStatus
Stopped CInt
stopsig)
else do
IOError -> IO ProcessStatus
forall a. IOError -> IO a
ioError (IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError
mkIOError IOErrorType
illegalOperationErrorType
String
"waitStatus" Maybe Handle
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing)
foreign import capi unsafe "HsUnix.h WIFEXITED"
c_WIFEXITED :: CInt -> CInt
foreign import capi unsafe "HsUnix.h WEXITSTATUS"
c_WEXITSTATUS :: CInt -> CInt
foreign import capi unsafe "HsUnix.h WIFSIGNALED"
c_WIFSIGNALED :: CInt -> CInt
foreign import capi unsafe "HsUnix.h WTERMSIG"
c_WTERMSIG :: CInt -> CInt
foreign import capi unsafe "HsUnix.h WIFSTOPPED"
c_WIFSTOPPED :: CInt -> CInt
foreign import capi unsafe "HsUnix.h WSTOPSIG"
c_WSTOPSIG :: CInt -> CInt
foreign import capi unsafe "HsUnix.h WCOREDUMP"
c_WCOREDUMP :: CInt -> CInt