unix-2.4.0.1: POSIX functionalitySource codeContentsIndex
System.Posix.Signals
Portabilitynon-portable (requires POSIX)
Stabilityprovisional
Maintainerlibraries@haskell.org
Contents
The Signal type
Specific signals
Sending signals
Handling signals
Signal sets
The process signal mask
The alarm timer
Waiting for signals
The NOCLDSTOP flag
Description
POSIX signal support
Synopsis
type Signal = CInt
nullSignal :: Signal
internalAbort :: Signal
sigABRT :: CInt
realTimeAlarm :: Signal
sigALRM :: CInt
busError :: Signal
sigBUS :: CInt
processStatusChanged :: Signal
sigCHLD :: CInt
continueProcess :: Signal
sigCONT :: CInt
floatingPointException :: Signal
sigFPE :: CInt
lostConnection :: Signal
sigHUP :: CInt
illegalInstruction :: Signal
sigILL :: CInt
keyboardSignal :: Signal
sigINT :: CInt
killProcess :: Signal
sigKILL :: CInt
openEndedPipe :: Signal
sigPIPE :: CInt
keyboardTermination :: Signal
sigQUIT :: CInt
segmentationViolation :: Signal
sigSEGV :: CInt
softwareStop :: Signal
sigSTOP :: CInt
softwareTermination :: Signal
sigTERM :: CInt
keyboardStop :: Signal
sigTSTP :: CInt
backgroundRead :: Signal
sigTTIN :: CInt
backgroundWrite :: Signal
sigTTOU :: CInt
userDefinedSignal1 :: Signal
sigUSR1 :: CInt
userDefinedSignal2 :: Signal
sigUSR2 :: CInt
pollableEvent :: Signal
sigPOLL :: CInt
profilingTimerExpired :: Signal
sigPROF :: CInt
badSystemCall :: Signal
sigSYS :: CInt
breakpointTrap :: Signal
sigTRAP :: CInt
urgentDataAvailable :: Signal
sigURG :: CInt
virtualTimerExpired :: Signal
sigVTALRM :: CInt
cpuTimeLimitExceeded :: Signal
sigXCPU :: CInt
fileSizeLimitExceeded :: Signal
sigXFSZ :: CInt
raiseSignal :: Signal -> IO ()
signalProcess :: Signal -> ProcessID -> IO ()
signalProcessGroup :: Signal -> ProcessGroupID -> IO ()
data Handler
= Default
| Ignore
| Catch (IO ())
| CatchOnce (IO ())
installHandler :: Signal -> Handler -> Maybe SignalSet -> IO Handler
data SignalSet
emptySignalSet :: SignalSet
fullSignalSet :: SignalSet
addSignal :: Signal -> SignalSet -> SignalSet
deleteSignal :: Signal -> SignalSet -> SignalSet
inSignalSet :: Signal -> SignalSet -> Bool
getSignalMask :: IO SignalSet
setSignalMask :: SignalSet -> IO ()
blockSignals :: SignalSet -> IO ()
unblockSignals :: SignalSet -> IO ()
scheduleAlarm :: Int -> IO Int
getPendingSignals :: IO SignalSet
awaitSignal :: Maybe SignalSet -> IO ()
setStoppedChildFlag :: Bool -> IO Bool
queryStoppedChildFlag :: IO Bool
The Signal type
type Signal = CIntSource
Specific signals
nullSignal :: SignalSource
internalAbort :: SignalSource
sigABRT :: CIntSource
realTimeAlarm :: SignalSource
sigALRM :: CIntSource
busError :: SignalSource
sigBUS :: CIntSource
processStatusChanged :: SignalSource
sigCHLD :: CIntSource
continueProcess :: SignalSource
sigCONT :: CIntSource
floatingPointException :: SignalSource
sigFPE :: CIntSource
lostConnection :: SignalSource
sigHUP :: CIntSource
illegalInstruction :: SignalSource
sigILL :: CIntSource
keyboardSignal :: SignalSource
sigINT :: CIntSource
killProcess :: SignalSource
sigKILL :: CIntSource
openEndedPipe :: SignalSource
sigPIPE :: CIntSource
keyboardTermination :: SignalSource
sigQUIT :: CIntSource
segmentationViolation :: SignalSource
sigSEGV :: CIntSource
softwareStop :: SignalSource
sigSTOP :: CIntSource
softwareTermination :: SignalSource
sigTERM :: CIntSource
keyboardStop :: SignalSource
sigTSTP :: CIntSource
backgroundRead :: SignalSource
sigTTIN :: CIntSource
backgroundWrite :: SignalSource
sigTTOU :: CIntSource
userDefinedSignal1 :: SignalSource
sigUSR1 :: CIntSource
userDefinedSignal2 :: SignalSource
sigUSR2 :: CIntSource
pollableEvent :: SignalSource
sigPOLL :: CIntSource
profilingTimerExpired :: SignalSource
sigPROF :: CIntSource
badSystemCall :: SignalSource
sigSYS :: CIntSource
breakpointTrap :: SignalSource
sigTRAP :: CIntSource
urgentDataAvailable :: SignalSource
sigURG :: CIntSource
virtualTimerExpired :: SignalSource
sigVTALRM :: CIntSource
cpuTimeLimitExceeded :: SignalSource
sigXCPU :: CIntSource
fileSizeLimitExceeded :: SignalSource
sigXFSZ :: CIntSource
Sending signals
raiseSignal :: Signal -> IO ()Source
raiseSignal int calls kill to signal the current process with interrupt signal int.
signalProcess :: Signal -> ProcessID -> IO ()Source
signalProcess int pid calls kill to signal process pid with interrupt signal int.
signalProcessGroup :: Signal -> ProcessGroupID -> IO ()Source
signalProcessGroup int pgid calls kill to signal all processes in group pgid with interrupt signal int.
Handling signals
data Handler Source
The actions to perform when a signal is received.
Constructors
Default
Ignore
Catch (IO ())
CatchOnce (IO ())
show/hide Instances
installHandlerSource
:: Signal
-> Handler
-> Maybe SignalSetother signals to block
-> IO Handlerold handler
installHandler int handler iset calls sigaction to install an interrupt handler for signal int. If handler is Default, SIG_DFL is installed; if handler is Ignore, SIG_IGN is installed; if handler is Catch action, a handler is installed which will invoke action in a new thread when (or shortly after) the signal is received. If iset is Just s, then the sa_mask of the sigaction structure is set to s; otherwise it is cleared. The previously installed signal handler for int is returned
Signal sets
data SignalSet Source
emptySignalSet :: SignalSetSource
fullSignalSet :: SignalSetSource
addSignal :: Signal -> SignalSet -> SignalSetSource
deleteSignal :: Signal -> SignalSet -> SignalSetSource
inSignalSet :: Signal -> SignalSet -> BoolSource
The process signal mask
getSignalMask :: IO SignalSetSource
getSignalMask calls sigprocmask to determine the set of interrupts which are currently being blocked.
setSignalMask :: SignalSet -> IO ()Source
setSignalMask mask calls sigprocmask with SIG_SETMASK to block all interrupts in mask.
blockSignals :: SignalSet -> IO ()Source
blockSignals mask calls sigprocmask with SIG_BLOCK to add all interrupts in mask to the set of blocked interrupts.
unblockSignals :: SignalSet -> IO ()Source
unblockSignals mask calls sigprocmask with SIG_UNBLOCK to remove all interrupts in mask from the set of blocked interrupts.
The alarm timer
scheduleAlarm :: Int -> IO IntSource
scheduleAlarm i calls alarm to schedule a real time alarm at least i seconds in the future.
Waiting for signals
getPendingSignals :: IO SignalSetSource
getPendingSignals calls sigpending to obtain the set of interrupts which have been received but are currently blocked.
awaitSignal :: Maybe SignalSet -> IO ()Source
awaitSignal iset suspends execution until an interrupt is received. If iset is Just s, awaitSignal calls sigsuspend, installing s as the new signal mask before suspending execution; otherwise, it calls pause. awaitSignal returns on receipt of a signal. If you have installed any signal handlers with installHandler, it may be wise to call yield directly after awaitSignal to ensure that the signal handler runs as promptly as possible.
The NOCLDSTOP flag
setStoppedChildFlag :: Bool -> IO BoolSource
Tells the system whether or not to set the SA_NOCLDSTOP flag when installing new signal handlers.
queryStoppedChildFlag :: IO BoolSource
Queries the current state of the stopped child flag.
Produced by Haddock version 2.6.1