Chapter 6. The posix category: POSIX support

6.1. The Posix library

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 -syslib posix on your command-line.

6.1.1. Posix data types

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 -- instances of : Eq Ord Num Real Integral Ix Enum Show

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
A DirStream is a primitive of type DIR *.

data FileStatus
A FileStatus is a primitive of type struct stat.

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
TerminalAttributes is a primitive of type struct termios.

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.

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)

6.1.2. Posix Process Primitives

forkProcess :: IO (Maybe ProcessID)

forkProcess calls fork, returning Just pid to the parent, where pid is the ProcessID of the child, and returning Nothing to the child.

executeFile :: FilePath                   -- Command
            -> Bool                       -- Search PATH?
            -> [String]                   -- Arguments
            -> Maybe [(String, String)]   -- Environment
            -> IO ()

executeFile cmd args env calls one of the execv* family, depending on whether or not the current PATH is to be searched for the command, and whether or not an environment is provided to supersede the process's current environment. The basename (leading directory names suppressed) of the command is passed to execv* as arg[0]; the argument list passed to executeFile therefore begins with arg[1].

Search PATH?    Supersede environ?      Call
~~~~~~~~~~~~    ~~~~~~~~~~~~~~~~~~      ~~~~~~~
False           False                   execv
False           True                    execve
True            False                   execvp
True            True                    execvpe*

Note that execvpe is not provided by the POSIX standard, and must be written by hand. Care must be taken to ensure that the search path is extracted from the original environment, and not from the environment to be passed on to the new image.

NOTE: In general, sharing open files between parent and child processes is potential bug farm, and should be avoided unless you really depend on this `feature' of POSIX' fork() semantics. Using Haskell, there's the extra complication that arguments to executeFile might come from files that are read lazily (using hGetContents, or some such.) If this is the case, then for your own sanity, please ensure that the arguments to executeFile have been fully evaluated before calling forkProcess (followed by executeFile.) Consider yourself warned :-)

A successful executeFile overlays the current process image with a new one, so it only returns on failure.

runProcess :: FilePath                    -- Command
           -> [String]                    -- Arguments
           -> Maybe [(String, String)]    -- Environment (Nothing -> Inherited)
           -> Maybe FilePath              -- Working directory (Nothing -> inherited)
           -> Maybe Handle                -- stdin  (Nothing -> inherited)
           -> Maybe Handle                -- stdout (Nothing -> inherited)
           -> Maybe Handle                -- stderr (Nothing -> inherited)
           -> IO ()

runProcess is our candidate for the high-level OS-independent primitive.

runProcess cmd args env wd inhdl outhdl errhdl runs cmd (searching the current PATH) with arguments args. If env is Just pairs, the command is executed with the environment specified by pairs of variables and values; otherwise, the command is executed with the current environment. If wd is Just dir, the command is executed with working directory dir; otherwise, the command is executed in the current working directory. If {in,out,errhdl} is Just handle, the command is executed with the Fd for std{in,out,err} attached to the specified handle; otherwise, the Fd for std{in,out,err} is left unchanged.

getProcessStatus :: Bool              -- Block?
                 -> Bool              -- Stopped processes?
                 -> ProcessID 
                 -> IO (Maybe ProcessStatus)

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.

getGroupProcessStatus :: Bool         -- Block?
                      -> Bool         -- Stopped processes?
                      -> ProcessGroupID 
                      -> IO (Maybe (ProcessID, ProcessStatus))

getGroupProcessStatus blk stopped pgid calls waitpid, returning Just (pid, tc), the ProcessID and ProcessStatus for any process in group pgid if one 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.

getAnyProcessStatus :: Bool           -- Block?
                    -> Bool           -- Stopped processes?
                    -> IO (Maybe (ProcessID, ProcessStatus))

getAnyProcessStatus blk stopped calls waitpid, returning Just (pid, tc), the ProcessID and ProcessStatus for any child process if one 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.

exitImmediately :: ExitCode -> IO ()

exitImmediately status calls _exit to terminate the process with the indicated exit status. The operation never returns.

getEnvironment :: IO [(String, String)]

getEnvironment parses the environment variable mapping provided by environ, returning (variable, value) pairs. The operation never fails.

setEnvironment :: [(String, String)] -> IO ()

setEnvironment replaces the process environment with the provided mapping of (variable, value) pairs.

getEnvVar :: String -> IO String

getEnvVar var returns the value associated with variable var in the current environment (identical functionality provided through standard Haskell library function System.getEnv).

The operation may fail with:

NoSuchThing

The variable has no mapping in the current environment.

setEnvVar :: String -> String -> IO ()

setEnvVar var val sets the value associated with variable var in the current environment to be val. Any previous mapping is superseded.

removeEnvVar :: String -> IO ()

removeEnvVar var removes any value associated with variable var in the current environment. Deleting a variable for which there is no mapping does not generate an error.

nullSignal :: Signal
nullSignal = 0

backgroundRead, sigTTIN        :: Signal
backgroundWrite, sigTTOU       :: Signal
continueProcess, sigCONT       :: Signal
floatingPointException, sigFPE :: Signal
illegalInstruction, sigILL     :: Signal
internalAbort, sigABRT         :: Signal
keyboardSignal, sigINT         :: Signal
keyboardStop, sigTSTP          :: Signal
keyboardTermination, sigQUIT   :: Signal
killProcess, sigKILL           :: Signal
lostConnection, sigHUP         :: Signal
openEndedPipe, sigPIPE         :: Signal
processStatusChanged, sigCHLD  :: Signal
realTimeAlarm, sigALRM         :: Signal
segmentationViolation, sigSEGV :: Signal
softwareStop, sigSTOP          :: Signal
softwareTermination, sigTERM   :: Signal
userDefinedSignal1, sigUSR1    :: Signal
userDefinedSignal2, sigUSR2    :: Signal

signalProcess :: Signal -> ProcessID -> IO ()

signalProcess int pid calls kill to signal process pid with interrupt signal int.

raiseSignal :: Signal -> IO ()

raiseSignal int calls kill to signal the current process with interrupt signal int.

signalProcessGroup :: Signal -> ProcessGroupID -> IO ()

signalProcessGroup int pgid calls kill to signal all processes in group pgid with interrupt signal int.

setStoppedChildFlag :: Bool -> IO Bool

setStoppedChildFlag bool sets a flag which controls whether or not the NOCLDSTOP option will be used the next time a signal handler is installed for SIGCHLD. If bool is True (the default), NOCLDSTOP will not be used; otherwise it will be. The operation never fails.

queryStoppedChildFlag :: IO Bool

queryStoppedChildFlag queries the flag which controls whether or not the NOCLDSTOP option will be used the next time a signal handler is installed for SIGCHLD. If NOCLDSTOP will be used, it returns False; otherwise (the default) it returns True. The operation never fails.

emptySignalSet :: SignalSet
fullSignalSet  :: SignalSet
addSignal      :: Signal -> SignalSet -> SignalSet
deleteSignal   :: Signal -> SignalSet -> SignalSet
inSignalSet    :: Signal -> SignalSet -> Bool

installHandler :: Signal
               -> Handler 
               -> Maybe SignalSet       -- other signals to block
               -> IO Handler            -- old 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. See Section 1.1 for details on how to communicate between threads.

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.

getSignalMask :: IO SignalSet

getSignalMask calls sigprocmask to determine the set of interrupts which are currently being blocked.

setSignalMask :: SignalSet -> IO SignalSet

setSignalMask mask calls sigprocmask with SIG_SETMASK to block all interrupts in mask. The previous set of blocked interrupts is returned.

blockSignals :: SignalSet -> IO SignalSet

setSignalMask mask calls sigprocmask with SIG_BLOCK to add all interrupts in mask to the set of blocked interrupts. The previous set of blocked interrupts is returned.

unBlockSignals :: SignalSet -> IO SignalSet

setSignalMask mask calls sigprocmask with SIG_UNBLOCK to remove all interrupts in mask from the set of blocked interrupts. The previous set of blocked interrupts is returned.

getPendingSignals :: IO SignalSet

getPendingSignals calls sigpending to obtain the set of interrupts which have been received but are currently blocked.

awaitSignal :: Maybe SignalSet -> IO ()

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.

scheduleAlarm :: Int -> IO Int

scheduleAlarm i calls alarm to schedule a real time alarm at least i seconds in the future.

sleep :: Int -> IO ()

sleep i calls sleep to suspend execution of the program until at least i seconds have elapsed or a signal is received.

6.1.3. Posix Process Environment

getProcessID :: IO ProcessID

getProcessID calls getpid to obtain the ProcessID for the current process.

getParentProcessID :: IO ProcessID

getProcessID calls getppid to obtain the ProcessID for the parent of the current process.

getRealUserID :: IO UserID

getRealUserID calls getuid to obtain the real UserID associated with the current process.

getEffectiveUserID :: IO UserID

getRealUserID calls geteuid to obtain the effective UserID associated with the current process.

setUserID :: UserID -> IO ()

setUserID uid calls setuid to set the real, effective, and saved set-user-id associated with the current process to uid.

getLoginName :: IO String

getLoginName calls getlogin to obtain the login name associated with the current process.

getRealGroupID :: IO GroupID

getRealGroupID calls getgid to obtain the real GroupID associated with the current process.

getEffectiveGroupID :: IO GroupID

getEffectiveGroupID calls getegid to obtain the effective GroupID associated with the current process.

setGroupID :: GroupID -> IO ()

setGroupID gid calls setgid to set the real, effective, and saved set-group-id associated with the current process to gid.

getGroups :: IO [GroupID]

getGroups calls getgroups to obtain the list of supplementary GroupIDs associated with the current process.

getEffectiveUserName :: IO String

getEffectiveUserName calls cuserid to obtain a name associated with the effective UserID of the process.

getProcessGroupID :: IO ProcessGroupID

getProcessGroupID calls getpgrp to obtain the ProcessGroupID for the current process.

createProcessGroup :: ProcessID -> IO ProcessGroupID

createProcessGroup pid calls setpgid to make process pid a new process group leader.

joinProcessGroup :: ProcessGroupID -> IO ProcessGroupID

joinProcessGroup pgid calls setpgid to set the ProcessGroupID of the current process to pgid.

setProcessGroupID :: ProcessID -> ProcessGroupID -> IO ()

setProcessGroupID pid pgid calls setpgid to set the ProcessGroupID for process pid to pgid.

createSession :: IO ProcessGroupID

createSession calls setsid to create a new session with the current process as session leader.

systemName :: SystemID -> String
nodeName :: SystemID -> String
release :: SystemID -> String
version :: SystemID -> String
machine :: SystemID -> String

getSystemID :: IO SystemID

getSystemID calls uname to obtain information about the current operating system.

> epochTime :: IO EpochTime

epochTime calls time to obtain the number of seconds that have elapsed since the epoch (Jan 01 00:00:00 GMT 1970).

elapsedTime     :: ProcessTimes -> ClockTick
userTime        :: ProcessTimes -> ClockTick
systemTime      :: ProcessTimes -> ClockTick
childUserTime   :: ProcessTimes -> ClockTick
childSystemTime :: ProcessTimes -> ClockTick

getProcessTimes :: IO ProcessTimes

getProcessTimes calls times to obtain time-accounting information for the current process and its children.

getControllingTerminalName :: IO FilePath

getControllingTerminalName calls ctermid to obtain a name associated with the controlling terminal for the process. If a controlling terminal exists, getControllingTerminalName returns the name of the controlling terminal.

The operation may fail with:

NoSuchThing

There is no controlling terminal, or its name cannot be determined.

SystemError

Various other causes.

getTerminalName :: Fd -> IO FilePath

getTerminalName fd calls ttyname to obtain a name associated with the terminal for Fd fd. If fd is associated with a terminal, getTerminalName returns the name of the terminal.

The operation may fail with:

InappropriateType

The channel is not associated with a terminal.

NoSuchThing

The channel is associated with a terminal, but it has no name.

SystemError

Various other causes.

queryTerminal :: Fd -> IO Bool

queryTerminal fd calls isatty to determine whether or not Fd fd is associated with a terminal.

getSysVar :: SysVar -> IO Limit

getSysVar var calls sysconf to obtain the dynamic value of the requested configurable system limit or option. For defined system limits, getSysVar returns the associated value. For defined system options, the result of getSysVar is undefined, but not failure.

The operation may fail with:

NoSuchThing

The requested system limit or option is undefined.

6.1.4. Posix operations on files and directories

openDirStream :: FilePath -> IO DirStream

openDirStream dir calls opendir to obtain a directory stream for dir.

readDirStream :: DirStream -> IO String

readDirStream dp calls readdir to obtain the next directory entry (struct dirent) for the open directory stream dp, and returns the d_name member of that structure.

The operation may fail with:

EOF

End of file has been reached.

SystemError

Various other causes.

rewindDirStream :: DirStream -> IO ()

rewindDirStream dp calls rewinddir to reposition the directory stream dp at the beginning of the directory.

closeDirStream :: DirStream -> IO ()

closeDirStream dp calls closedir to close the directory stream dp.

getWorkingDirectory :: IO FilePath

getWorkingDirectory calls getcwd to obtain the name of the current working directory.

changeWorkingDirectory :: FilePath -> IO ()

changeWorkingDirectory dir calls chdir to change the current working directory to dir.

nullFileMode       :: FileMode       -- ---------
ownerReadMode      :: FileMode       -- r--------
ownerWriteMode     :: FileMode       -- -w-------
ownerExecuteMode   :: FileMode       -- --x------
groupReadMode      :: FileMode       -- ---r-----
groupWriteMode     :: FileMode       -- ----w----
groupExecuteMode   :: FileMode       -- -----x---
otherReadMode      :: FileMode       -- ------r--
otherWriteMode     :: FileMode       -- -------w-
otherExecuteMode   :: FileMode       -- --------x
setUserIDMode      :: FileMode       -- --S------
setGroupIDMode     :: FileMode       -- -----S---
                               
stdFileMode        :: FileMode       -- rw-rw-rw-
                               
ownerModes         :: FileMode       -- rwx------
groupModes         :: FileMode       -- ---rwx---
otherModes         :: FileMode       -- ------rwx
accessModes        :: FileMode       -- rwxrwxrwx

unionFileModes     :: FileMode -> FileMode -> FileMode
intersectFileModes :: FileMode -> FileMode -> FileMode

stdInput  :: Fd
stdInput  = intToFd 0

stdOutput :: Fd
stdOutput = intToFd 1

stdError  :: Fd
stdError  = intToFd 2

data OpenFileFlags =
 OpenFileFlags {
    append    :: Bool,
    exclusive :: Bool,
    noctty    :: Bool,
    nonBlock  :: Bool,
    trunc     :: Bool
 }

openFd :: FilePath
       -> OpenMode
       -> Maybe FileMode  -- Just x => O_CREAT, Nothing => must exist
       -> OpenFileFlags
       -> IO Fd

openFd path acc mode (OpenFileFlags app excl noctty nonblock trunc) calls open to obtain a Fd for the file path with access mode acc. If mode is Just m, the O_CREAT flag is set and the file's permissions will be based on m if it does not already exist; otherwise, the O_CREAT flag is not set. The arguments app, excl, noctty, nonblock, and trunc control whether or not the flags O_APPEND, O_EXCL, O_NOCTTY, O_NONBLOCK, and O_TRUNC are set, respectively.

createFile :: FilePath -> FileMode -> IO Fd

createFile path mode calls creat to obtain a Fd for file path, which will be created with permissions based on mode if it does not already exist.

setFileCreationMask :: FileMode -> IO FileMode

setFileCreationMask mode calls umask to set the process's file creation mask to mode. The previous file creation mask is returned.

createLink :: FilePath -> FilePath -> IO ()

createLink old new calls link to create a new path, new, linked to an existing file, old.
createDirectory :: FilePath -> FileMode -> IO ()

createDirectory dir mode calls mkdir to create a new directory, dir, with permissions based on mode.

createNamedPipe :: FilePath -> FileMode -> IO ()

createNamedPipe fifo mode calls mkfifo to create a new named pipe, fifo, with permissions based on mode.

removeLink :: FilePath -> IO ()

removeLink path calls unlink to remove the link named path.

removeDirectory :: FilePath -> IO ()

removeDirectory dir calls rmdir to remove the directory named dir.

rename :: FilePath -> FilePath -> IO ()

rename old new calls rename to rename a file or directory from old to new.

fileMode          :: FileStatus -> FileMode
                   
fileID            :: FileStatus -> FileID
deviceID          :: FileStatus -> DeviceID
                   
linkCount         :: FileStatus -> LinkCount
                   
fileOwner         :: FileStatus -> UserID
fileGroup         :: FileStatus -> GroupID
fileSize          :: FileStatus -> FileOffset

accessTime        :: FileStatus -> EpochTime
modificationTime  :: FileStatus -> EpochTime
statusChangeTime  :: FileStatus -> EpochTime

isDirectory       :: FileStatus -> Bool
isCharacterDevice :: FileStatus -> Bool
isBlockDevice     :: FileStatus -> Bool
isRegularFile     :: FileStatus -> Bool
isNamedPipe       :: FileStatus -> Bool

getFileStatus     :: FilePath -> IO FileStatus

getFileStatus path calls stat to get the FileStatus information for the file path.

getFdStatus :: Fd -> IO FileStatus

getFdStatus fd calls fstat to get the FileStatus information for the file associated with Fd fd.

queryAccess :: FilePath -> Bool -> Bool -> Bool -> IO Bool

queryAccess path r w x calls access to test the access permissions for file path. The three arguments, r, w, and x control whether or not access is called with R_OK, W_OK, and X_OK respectively.

queryFile :: FilePath -> IO Bool

queryFile path calls access with F_OK to test for the existence for file path.

setFileMode :: FilePath -> FileMode -> IO ()

setFileMode path mode calls chmod to set the permission bits associated with file path to mode.

setOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO ()

setOwnerAndGroup path uid gid calls chown to set the UserID and GroupID associated with file path to uid and gid, respectively.

setFileTimes :: FilePath -> EpochTime -> EpochTime -> IO ()

setFileTimes path atime mtime calls utime to set the access and modification times associated with file path to atime and mtime, respectively.

touchFile :: FilePath -> IO ()

touchFile path calls utime to set the access and modification times associated with file path to the current time.

getPathVar :: PathVar -> FilePath -> IO Limit

getPathVar var path calls pathconf to obtain the dynamic value of the requested configurable file limit or option associated with file or directory path. For defined file limits, getPathVar returns the associated value. For defined file options, the result of getPathVar is undefined, but not failure. The operation may fail with:

NoSuchThing

The requested file limit or option is undefined.

SystemError

Various other causes.

getFdVar :: PathVar -> Fd -> IO Limit

getFdVar var fd calls fpathconf to obtain the dynamic value of the requested configurable file limit or option associated with the file or directory attached to the open channel fd. For defined file limits, getFdVar returns the associated value. For defined file options, the result of getFdVar is undefined, but not failure.

The operation may fail with:

NoSuchThing

The requested file limit or option is undefined.

SystemError

Various other causes.

6.1.5. Posix Input and Output Primitives

createPipe :: IO (Fd, Fd)

createPipe calls pipe to create a pipe and returns a pair of Fds, the first for reading and the second for writing.

dup :: Fd -> IO Fd

dup fd calls dup to duplicate Fd fd to another Fd.

dupTo :: Fd -> Fd -> IO ()

dupTo src dst calls dup2 to duplicate Fd src to Fd dst.

fdClose :: Fd -> IO ()

fdClose fd calls close to close Fd fd.

fdRead :: Fd -> ByteCount -> IO (String, ByteCount)

fdRead fd nbytes calls read to read at most nbytes bytes from Fd fd, and returns the result as a string paired with the number of bytes actually read.

The operation may fail with:

EOF

End of file has been reached.

SystemError

Various other causes.

fdWrite :: Fd -> String -> IO ByteCount

fdWrite fd s calls write to write the string s to Fd fd as a contiguous sequence of bytes. It returns the number of bytes successfully written.

queryFdOption :: FdOption -> Fd -> IO Bool

getFdOption opt fd calls fcntl to determine whether or not the flag associated with FdOption opt is set for Fd fd.

setFdOption :: Fd -> FdOption -> Bool -> IO ()

setFdOption fd opt val calls fcntl to set the flag associated with FdOption opt on Fd fd to val.

getLock :: Fd -> FileLock -> IO (Maybe (ProcessID, FileLock))

getLock fd lock calls fcntl to get the first FileLock for Fd fd which blocks the FileLock lock. If no such FileLock exists, getLock returns Nothing. Otherwise, it returns Just (pid, block), where block is the blocking FileLock and pid is the ProcessID of the process holding the blocking FileLock.

setLock :: Fd -> FileLock -> IO ()

setLock fd lock calls fcntl with F_SETLK to set or clear a lock segment for Fd fd as indicated by the FileLock lock. setLock does not block, but fails with SystemError if the request cannot be satisfied immediately.

waitToSetLock :: Fd -> FileLock -> IO ()

waitToSetLock fd lock calls fcntl with F_SETLKW to set or clear a lock segment for Fd fd as indicated by the FileLock lock. If the request cannot be satisfied immediately, waitToSetLock blocks until the request can be satisfied.

fdSeek :: Fd -> SeekMode -> FileOffset -> IO FileOffset

fdSeek fd whence offset calls lseek to position the Fd fd at the given offset from the starting location indicated by whence. It returns the resulting offset from the start of the file in bytes.

6.1.6. Posix, Device- and Class-Specific Functions

terminalMode    :: TerminalMode -> TerminalAttributes -> Bool
withMode        :: TerminalAttributes -> TerminalMode -> TerminalAttributes
withoutMode     :: TerminalAttributes -> TerminalMode -> TerminalAttributes

bitsPerByte     :: TerminalAttributes -> Int
withBits        :: TerminalAttributes -> Int -> TerminalAttributes

controlChar     :: TerminalAttributes -> ControlCharacter -> Maybe Char
withCC          :: TerminalAttributes
                -> (ControlCharacter, Char)
                -> TerminalAttributes 
withoutCC       :: TerminalAttributes 
                -> ControlCharacter 
                -> TerminalAttributes
                  
inputTime       :: TerminalAttributes -> Int
withTime        :: TerminalAttributes -> Int -> TerminalAttributes
                  
minInput        :: TerminalAttributes -> Int
withMinInput    :: TerminalAttributes -> Int -> TerminalAttributes
                  
inputSpeed      :: TerminalAttributes -> BaudRate
withInputSpeed  :: TerminalAttributes -> BaudRate -> TerminalAttributes
                  
outputSpeed     :: TerminalAttributes -> BaudRate
withOutputSpeed :: TerminalAttributes -> BaudRate -> TerminalAttributes

getTerminalAttributes :: Fd -> IO TerminalAttributes

getTerminalAttributes fd calls tcgetattr to obtain the TerminalAttributes associated with Fd fd.

setTerminalAttributes :: Fd
                      -> TerminalAttributes 
                      -> TerminalState
                      -> IO ()

setTerminalAttributes fd attr ts calls tcsetattr to change the TerminalAttributes associated with Fd fd to attr, when the terminal is in the state indicated by ts.

sendBreak :: Fd -> Int -> IO ()

sendBreak fd duration calls tcsendbreak to transmit a continuous stream of zero-valued bits on Fd fd for the specified implementation-dependent duration.

drainOutput :: Fd -> IO ()

drainOutput fd calls tcdrain to block until all output written to Fd fd has been transmitted.

discardData :: Fd -> QueueSelector -> IO ()

discardData fd queues calls tcflush to discard pending input and/or output for Fd fd, as indicated by the QueueSelector queues.

controlFlow :: Fd -> FlowAction -> IO ()

controlFlow fd action calls tcflow to control the flow of data on Fd fd, as indicated by action.

getTerminalProcessGroupID :: Fd -> IO ProcessGroupID

getTerminalProcessGroupID fd calls tcgetpgrp to obtain the ProcessGroupID of the foreground process group associated with the terminal attached to Fd fd.

setTerminalProcessGroupID :: Fd -> ProcessGroupID -> IO ()

setTerminalProcessGroupID fd pgid calls tcsetpgrp to set the ProcessGroupID of the foreground process group associated with the terminal attached to Fd fd to pgid.

6.1.7. Posix System Databases

groupName    :: GroupEntry -> String
groupID      :: GroupEntry -> GroupID
groupMembers :: GroupEntry -> [String]

getGroupEntryForID :: GroupID -> IO GroupEntry

getGroupEntryForID gid calls getgrgid to obtain the GroupEntry information associated with GroupID gid.

The operation may fail with:

NoSuchThing

There is no group entry for the GroupID.

getGroupEntryForName :: String -> IO GroupEntry

getGroupEntryForName name calls getgrnam to obtain the GroupEntry information associated with the group called name.

The operation may fail with:

NoSuchThing

There is no group entry for the name.

userName      :: UserEntry -> String
userID        :: UserEntry -> UserID
userGroupID   :: UserEntry -> GroupID
homeDirectory :: UserEntry -> String
userShell     :: UserEntry -> String

getUserEntryForID :: UserID -> IO UserEntry

getUserEntryForID gid calls getpwuid to obtain the UserEntry information associated with UserID uid. The operation may fail with:

NoSuchThing

There is no user entry for the UserID.

getUserEntryForName :: String -> IO UserEntry

getUserEntryForName name calls getpwnam to obtain the UserEntry information associated with the user login name.

The operation may fail with:

NoSuchThing

There is no user entry for the name.

6.1.8. POSIX Errors

getErrorCode :: IO ErrorCode

getErrorCode returns the current value of the external variable errno. It never fails.

setErrorCode :: ErrorCode -> IO ()

setErrorCode err sets the external variable errno to err. It never fails.

noError :: ErrorCode
noError = 0

argumentListTooLong, e2BIG              :: ErrorCode
badFd, eBADF                            :: ErrorCode
brokenPipe, ePIPE                       :: ErrorCode
directoryNotEmpty, eNOTEMPTY            :: ErrorCode
execFormatError, eNOEXEC                :: ErrorCode
fileAlreadyExists, eEXIST               :: ErrorCode
fileTooLarge, eFBIG                     :: ErrorCode
filenameTooLong, eNAMETOOLONG           :: ErrorCode
improperLink, eXDEV                     :: ErrorCode
inappropriateIOControlOperation, eNOTTY :: ErrorCode
inputOutputError, eIO                   :: ErrorCode
interruptedOperation, eINTR             :: ErrorCode
invalidArgument, eINVAL                 :: ErrorCode
invalidSeek, eSPIPE                     :: ErrorCode
isADirectory, eISDIR                    :: ErrorCode
noChildProcess, eCHILD                  :: ErrorCode
noLocksAvailable, eNOLCK                :: ErrorCode
noSpaceLeftOnDevice, eNOSPC             :: ErrorCode
noSuchOperationOnDevice, eNODEV         :: ErrorCode
noSuchDeviceOrAddress, eNXIO            :: ErrorCode
noSuchFileOrDirectory, eNOENT           :: ErrorCode
noSuchProcess, eSRCH                    :: ErrorCode
notADirectory, eNOTDIR                  :: ErrorCode
notEnoughMemory, eNOMEM                 :: ErrorCode
operationNotImplemented, eNOSYS         :: ErrorCode
operationNotPermitted, ePERM            :: ErrorCode
permissionDenied, eACCES                :: ErrorCode
readOnlyFileSystem, eROFS               :: ErrorCode
resourceBusy, eBUSY                     :: ErrorCode
resourceDeadlockAvoided, eDEADLK        :: ErrorCode
resourceTemporarilyUnavailable, eAGAIN  :: ErrorCode
tooManyLinks, eMLINK                    :: ErrorCode
tooManyOpenFiles, eMFILE                :: ErrorCode
tooManyOpenFilesInSystem, eNFILE        :: ErrorCode