The Posix interface gives you access to the set of OS services standardised by POSIX 1003.1b (or the IEEE Portable Operating System Interface for Computing Environments - IEEE Std. 1003.1). The interface is accessed by import Posix and adding -package posix on your command-line.
data ByteCount -- instances of : Eq Ord Num Real Integral Ix Enum Show |
A ByteCount is a primitive of type unsigned. At a minimum, an conforming implementation must support values in the range [0, UINT_MAX].
data ClockTick -- instances of : Eq Ord Num Real Integral Ix Enum Show |
A ClockTick is a primitive of type clock_t, which is used to measure intervals of time in fractions of a second. The resolution is determined by getSysVar ClockTick.
data DeviceID -- instances of : Eq Ord Num Real Integral Ix Enum Show |
A DeviceID is a primitive of type dev_t. It must be an arithmetic type.
data EpochTime -- instances of : Eq Ord Num Real Integral Ix Enum Show |
A EpochTime is a primitive of type time_t, which is used to measure seconds since the Epoch. At a minimum, the implementation must support values in the range [0, INT_MAX].
data FileID -- instances of : Eq Ord Num Real Integral Ix Enum Show |
A FileID is a primitive of type ino_t. It must be an arithmetic type.
data FileMode -- instance of : Eq |
A FileMode is a primitive of type mode_t. It must be an arithmetic type.
data FileOffset -- instances of : Eq Ord Num Real Integral Ix Enum Show |
A FileOffset is a primitive of type off_t. It must be an arithmetic type.
data GroupID -- instances of : Eq Ord Num Real Integral Ix Enum Show |
A GroupID is a primitive of type gid_t. It must be an arithmetic type.
data Limit -- instances of : Eq Ord Num Real Integral Ix Enum Show |
A Limit is a primitive of type long. At a minimum, the implementation must support values in the range [LONG_MIN, LONG_MAX].
data LinkCount -- instances of : Eq Ord Num Real Integral Ix Enum Show |
A LinkCount is a primitive of type nlink_t. It must be an arithmetic type.
data ProcessID -- instances of : Eq Ord Num Real Integral Ix Enum Show type ProcessGroupID = ProcessID |
A ProcessID is a primitive of type pid_t. It must be a signed arithmetic type.
data UserID -- instances of : Eq Ord Num Real Integral Ix Enum Show |
A UserID is a primitive of type uid_t. It must be an arithmetic type.
data DirStream |
data FileStatus |
data GroupEntry |
A GroupEntry is a primitive of type struct group.
data ProcessTimes |
ProcessTimes is a primitive structure containing a clock_t and a struct tms.
data SignalSet |
An SignalSet is a primitive of type sigset_t.
data SystemID |
A SystemID is a primitive of type struct utsname.
data TerminalAttributes |
data UserEntry |
A UserEntry is a primitive of type struct passwd.
data BaudRate = B0 | B50 | B75 | B110 | B134 | B150 | B200 | B300 | B600
| B1200 | B1800 | B2400 | B4800 | B9600 | B19200 | B38400
deriving (Eq, Show)
data Fd
intToFd :: Int -> Fd -- use with care.
fdToInt :: Fd -> Int -- ditto.
data FdOption = AppendOnWrite
| CloseOnExec
| NonBlockingRead
data ControlCharacter = EndOfFile
| EndOfLine
| Erase
| Interrupt
| Kill
| Quit
| Suspend
| Start
| Stop
type ErrorCode = Int
type FileLock = (LockRequest, SeekMode, FileOffset, FileOffset)
-- whence start length
data FlowAction = SuspendOutput | RestartOutput | TransmitStop | TransmitStart
data Handler = Default | Ignore | Catch (IO ())
data LockRequest = ReadLock | WriteLock | Unlock
deriving (Eq, Show)
data OpenMode = ReadOnly | WriteOnly | ReadWrite
data PathVar = LinkLimit
| InputLineLimit
| InputQueueLimit
| FileNameLimit
| PathNameLimit
| PipeBufferLimit
| SetOwnerAndGroupIsRestricted
| FileNamesAreNotTruncated
data QueueSelector = InputQueue | OutputQueue | BothQueues
type Signal = Int
data SysVar = ArgumentLimit
| ChildLimit
| ClockTick
| GroupLimit
| OpenFileLimit
| PosixVersion
| HasSavedIDs
| HasJobControl
data TerminalMode = InterruptOnBreak -- BRKINT
| MapCRtoLF -- ICRNL
| IgnoreBreak -- IGNBRK
| IgnoreCR -- IGNCR
| IgnoreParityErrors -- IGNPAR
| MapLFtoCR -- INLCR
| CheckParity -- INPCK
| StripHighBit -- ISTRIP
| StartStopInput -- IXOFF
| StartStopOutput -- IXON
| MarkParityErrors -- PARMRK
| ProcessOutput -- OPOST
| LocalMode -- CLOCAL
| ReadEnable -- CREAD
| TwoStopBits -- CSTOPB
| HangupOnClose -- HUPCL
| EnableParity -- PARENB
| OddParity -- PARODD
| EnableEcho -- ECHO
| EchoErase -- ECHOE
| EchoKill -- ECHOK
| EchoLF -- ECHONL
| ProcessInput -- ICANON
| ExtendedFunctions -- IEXTEN
| KeyboardInterrupts -- ISIG
| NoFlushOnInterrupt -- NOFLSH
| BackgroundWriteInterrupt -- TOSTOP
data TerminalState = Immediately | WhenDrained | WhenFlushed
data ProcessStatus = Exited ExitCode
| Terminated Signal
| Stopped Signal
deriving (Eq, Show) |