pathtype-0.5.5: Type-safe replacement for System.FilePath etc

Safe HaskellSafe
LanguageHaskell98

System.Path.IO

Contents

Description

This module provides type-safe access to IO operations.

It is designed to be imported instead of System.IO. (It is intended to provide versions of functions from that module which have equivalent functionality but are more typesafe). System.Path is a companion module providing a type-safe alternative to System.FilePath.

You will typically want to import as follows:

import Prelude hiding (FilePath)
import System.Path
import System.Path.Directory
import System.Path.IO

Ben Moseley - (c) 2009

Synopsis

Covers for System.IO functions

withFile :: AbsRelClass ar => FilePath ar -> IOMode -> (Handle -> IO r) -> IO r Source

withBinaryFile :: AbsRelClass ar => FilePath ar -> IOMode -> (Handle -> IO r) -> IO r Source

Re-exports

data IO a :: * -> *

A value of type IO a is a computation which, when performed, does some I/O before returning a value of type a.

There is really only one way to "perform" an I/O action: bind it to Main.main in your program. When your program is run, the I/O will be performed. It isn't possible to perform I/O from an arbitrary function, unless that function is itself in the IO monad and called at some point, directly or indirectly, from Main.main.

IO is a monad, so IO actions can be combined using either the do-notation or the >> and >>= operations from the Monad class.

Instances

Monad IO 
Functor IO 
Applicative IO 
(~) * a () => PrintfType (IO a) 
(~) * a () => HPrintfType (IO a) 

fixIO :: (a -> IO a) -> IO a

data Handle :: *

Haskell defines operations to read and write characters from and to files, represented by values of type Handle. Each value of this type is a handle: a record used by the Haskell run-time system to manage I/O with file system objects. A handle has at least the following properties:

  • whether it manages input or output or both;
  • whether it is open, closed or semi-closed;
  • whether the object is seekable;
  • whether buffering is disabled, or enabled on a line or block basis;
  • a buffer (whose length may be zero).

Most handles will also have a current I/O position indicating where the next input or output operation will occur. A handle is readable if it manages only input or both input and output; likewise, it is writable if it manages only output or both input and output. A handle is open when first allocated. Once it is closed it can no longer be used for either input or output, though an implementation cannot re-use its storage while references remain to it. Handles are in the Show and Eq classes. The string produced by showing a handle is system dependent; it should include enough information to identify the handle for debugging. A handle is equal according to == only to itself; no attempt is made to compare the internal state of different handles for equality.

Instances

stdin :: Handle

A handle managing input from the Haskell program's standard input channel.

stdout :: Handle

A handle managing output to the Haskell program's standard output channel.

stderr :: Handle

A handle managing output to the Haskell program's standard error channel.

hClose :: Handle -> IO ()

Computation hClose hdl makes handle hdl closed. Before the computation finishes, if hdl is writable its buffer is flushed as for hFlush. Performing hClose on a handle that has already been closed has no effect; doing so is not an error. All other operations on a closed handle will fail. If hClose fails for any reason, any further operations (apart from hClose) on the handle will still fail as if hdl had been successfully closed.

hFileSize :: Handle -> IO Integer

For a handle hdl which attached to a physical file, hFileSize hdl returns the size of that file in 8-bit bytes.

hSetFileSize :: Handle -> Integer -> IO ()

hSetFileSize hdl size truncates the physical file with handle hdl to size bytes.

hIsEOF :: Handle -> IO Bool

For a readable handle hdl, hIsEOF hdl returns True if no further input can be taken from hdl or for a physical file, if the current I/O position is equal to the length of the file. Otherwise, it returns False.

NOTE: hIsEOF may block, because it has to attempt to read from the stream to determine whether there is any more data to be read.

isEOF :: IO Bool

The computation isEOF is identical to hIsEOF, except that it works only on stdin.

data BufferMode :: *

Three kinds of buffering are supported: line-buffering, block-buffering or no-buffering. These modes have the following effects. For output, items are written out, or flushed, from the internal buffer according to the buffer mode:

  • line-buffering: the entire output buffer is flushed whenever a newline is output, the buffer overflows, a hFlush is issued, or the handle is closed.
  • block-buffering: the entire buffer is written out whenever it overflows, a hFlush is issued, or the handle is closed.
  • no-buffering: output is written immediately, and never stored in the buffer.

An implementation is free to flush the buffer more frequently, but not less frequently, than specified above. The output buffer is emptied as soon as it has been written out.

Similarly, input occurs according to the buffer mode for the handle:

  • line-buffering: when the buffer for the handle is not empty, the next item is obtained from the buffer; otherwise, when the buffer is empty, characters up to and including the next newline character are read into the buffer. No characters are available until the newline character is available or the buffer is full.
  • block-buffering: when the buffer for the handle becomes empty, the next block of data is read into the buffer.
  • no-buffering: the next input item is read and returned. The hLookAhead operation implies that even a no-buffered handle may require a one-character buffer.

The default buffering mode when a handle is opened is implementation-dependent and may depend on the file system object which is attached to that handle. For most implementations, physical files will normally be block-buffered and terminals will normally be line-buffered.

Constructors

NoBuffering

buffering is disabled if possible.

LineBuffering

line-buffering should be enabled if possible.

BlockBuffering (Maybe Int)

block-buffering should be enabled if possible. The size of the buffer is n items if the argument is Just n and is otherwise implementation-dependent.

hSetBuffering :: Handle -> BufferMode -> IO ()

Computation hSetBuffering hdl mode sets the mode of buffering for handle hdl on subsequent reads and writes.

If the buffer mode is changed from BlockBuffering or LineBuffering to NoBuffering, then

  • if hdl is writable, the buffer is flushed as for hFlush;
  • if hdl is not writable, the contents of the buffer is discarded.

This operation may fail with:

  • isPermissionError if the handle has already been used for reading or writing and the implementation does not allow the buffering mode to be changed.

hGetBuffering :: Handle -> IO BufferMode

Computation hGetBuffering hdl returns the current buffering mode for hdl.

hFlush :: Handle -> IO ()

The action hFlush hdl causes any items buffered for output in handle hdl to be sent immediately to the operating system.

This operation may fail with:

  • isFullError if the device is full;
  • isPermissionError if a system resource limit would be exceeded. It is unspecified whether the characters in the buffer are discarded or retained under these circumstances.

hGetPosn :: Handle -> IO HandlePosn

Computation hGetPosn hdl returns the current I/O position of hdl as a value of the abstract type HandlePosn.

hSetPosn :: HandlePosn -> IO ()

If a call to hGetPosn hdl returns a position p, then computation hSetPosn p sets the position of hdl to the position it held at the time of the call to hGetPosn.

This operation may fail with:

  • isPermissionError if a system resource limit would be exceeded.

data HandlePosn :: *

hSeek :: Handle -> SeekMode -> Integer -> IO ()

Computation hSeek hdl mode i sets the position of handle hdl depending on mode. The offset i is given in terms of 8-bit bytes.

If hdl is block- or line-buffered, then seeking to a position which is not in the current buffer will first cause any items in the output buffer to be written to the device, and then cause the input buffer to be discarded. Some handles may not be seekable (see hIsSeekable), or only support a subset of the possible positioning operations (for instance, it may only be possible to seek to the end of a tape, or to a positive offset from the beginning or current position). It is not possible to set a negative I/O position, or for a physical file, an I/O position beyond the current end-of-file.

This operation may fail with:

  • isIllegalOperationError if the Handle is not seekable, or does not support the requested seek mode.
  • isPermissionError if a system resource limit would be exceeded.

data SeekMode :: *

A mode that determines the effect of hSeek hdl mode i.

Constructors

AbsoluteSeek

the position of hdl is set to i.

RelativeSeek

the position of hdl is set to offset i from the current position.

SeekFromEnd

the position of hdl is set to offset i from the end of the file.

hTell :: Handle -> IO Integer

Computation hTell hdl returns the current position of the handle hdl, as the number of bytes from the beginning of the file. The value returned may be subsequently passed to hSeek to reposition the handle to the current position.

This operation may fail with:

  • isIllegalOperationError if the Handle is not seekable.

hIsTerminalDevice :: Handle -> IO Bool

Is the handle connected to a terminal?

hSetEcho :: Handle -> Bool -> IO ()

Set the echoing status of a handle connected to a terminal.

hGetEcho :: Handle -> IO Bool

Get the echoing status of a handle connected to a terminal.

hShow :: Handle -> IO String

hShow is in the IO monad, and gives more comprehensive output than the (pure) instance of Show for Handle.

hWaitForInput :: Handle -> Int -> IO Bool

Computation hWaitForInput hdl t waits until input is available on handle hdl. It returns True as soon as input is available on hdl, or False if no input is available within t milliseconds. Note that hWaitForInput waits until one or more full characters are available, which means that it needs to do decoding, and hence may fail with a decoding error.

If t is less than zero, then hWaitForInput waits indefinitely.

This operation may fail with:

  • isEOFError if the end of file has been reached.
  • a decoding error, if the input begins with an invalid byte sequence in this Handle's encoding.

NOTE for GHC users: unless you use the -threaded flag, hWaitForInput hdl t where t >= 0 will block all other Haskell threads for the duration of the call. It behaves like a safe foreign call in this respect.

hReady :: Handle -> IO Bool

Computation hReady hdl indicates whether at least one item is available for input from handle hdl.

This operation may fail with:

hGetChar :: Handle -> IO Char

Computation hGetChar hdl reads a character from the file or channel managed by hdl, blocking until a character is available.

This operation may fail with:

hGetLine :: Handle -> IO String

Computation hGetLine hdl reads a line from the file or channel managed by hdl.

This operation may fail with:

  • isEOFError if the end of file is encountered when reading the first character of the line.

If hGetLine encounters end-of-file at any other point while reading in a line, it is treated as a line terminator and the (partial) line is returned.

hLookAhead :: Handle -> IO Char

Computation hLookAhead returns the next character from the handle without removing it from the input buffer, blocking until a character is available.

This operation may fail with:

  • isEOFError if the end of file has been reached.

hGetContents :: Handle -> IO String

Computation hGetContents hdl returns the list of characters corresponding to the unread portion of the channel or file managed by hdl, which is put into an intermediate state, semi-closed. In this state, hdl is effectively closed, but items are read from hdl on demand and accumulated in a special list returned by hGetContents hdl.

Any operation that fails because a handle is closed, also fails if a handle is semi-closed. The only exception is hClose. A semi-closed handle becomes closed:

  • if hClose is applied to it;
  • if an I/O error occurs when reading an item from the handle;
  • or once the entire contents of the handle has been read.

Once a semi-closed handle becomes closed, the contents of the associated list becomes fixed. The contents of this final list is only partially specified: it will contain at least all the items of the stream that were evaluated prior to the handle becoming closed.

Any I/O errors encountered while a handle is semi-closed are simply discarded.

This operation may fail with:

hPutChar :: Handle -> Char -> IO ()

Computation hPutChar hdl ch writes the character ch to the file or channel managed by hdl. Characters may be buffered if buffering is enabled for hdl.

This operation may fail with:

hPutStr :: Handle -> String -> IO ()

Computation hPutStr hdl s writes the string s to the file or channel managed by hdl.

This operation may fail with:

hPutStrLn :: Handle -> String -> IO ()

The same as hPutStr, but adds a newline character.

hPrint :: Show a => Handle -> a -> IO ()

Computation hPrint hdl t writes the string representation of t given by the shows function to the file or channel managed by hdl and appends a newline.

This operation may fail with:

interact :: (String -> String) -> IO ()

The interact function takes a function of type String->String as its argument. The entire input from the standard input device is passed to this function as its argument, and the resulting string is output on the standard output device.

putChar :: Char -> IO ()

Write a character to the standard output device (same as hPutChar stdout).

putStr :: String -> IO ()

Write a string to the standard output device (same as hPutStr stdout).

putStrLn :: String -> IO ()

The same as putStr, but adds a newline character.

print :: Show a => a -> IO ()

The print function outputs a value of any printable type to the standard output device. Printable types are those that are instances of class Show; print converts values to strings for output using the show operation and adds a newline.

For example, a program to print the first 20 integers and their powers of 2 could be written as:

main = print ([(n, 2^n) | n <- [0..19]])

getChar :: IO Char

Read a character from the standard input device (same as hGetChar stdin).

getLine :: IO String

Read a line from the standard input device (same as hGetLine stdin).

getContents :: IO String

The getContents operation returns all user input as a single string, which is read lazily as it is needed (same as hGetContents stdin).

readIO :: Read a => String -> IO a

The readIO function is similar to read except that it signals parse failure to the IO monad instead of terminating the program.

readLn :: Read a => IO a

The readLn function combines getLine and readIO.

hSetBinaryMode :: Handle -> Bool -> IO ()

Select binary mode (True) or text mode (False) on a open handle. (See also openBinaryFile.)

This has the same effect as calling hSetEncoding with char8, together with hSetNewlineMode with noNewlineTranslation.

hPutBuf :: Handle -> Ptr a -> Int -> IO ()

hPutBuf hdl buf count writes count 8-bit bytes from the buffer buf to the handle hdl. It returns ().

hPutBuf ignores any text encoding that applies to the Handle, writing the bytes directly to the underlying file or device.

hPutBuf ignores the prevailing TextEncoding and NewlineMode on the Handle, and writes bytes directly.

This operation may fail with:

  • ResourceVanished if the handle is a pipe or socket, and the reading end is closed. (If this is a POSIX system, and the program has not asked to ignore SIGPIPE, then a SIGPIPE may be delivered instead, whose default action is to terminate the program).

hGetBuf :: Handle -> Ptr a -> Int -> IO Int

hGetBuf hdl buf count reads data from the handle hdl into the buffer buf until either EOF is reached or count 8-bit bytes have been read. It returns the number of bytes actually read. This may be zero if EOF was reached before any data was read (or if count is zero).

hGetBuf never raises an EOF exception, instead it returns a value smaller than count.

If the handle is a pipe or socket, and the writing end is closed, hGetBuf will behave as if EOF was reached.

hGetBuf ignores the prevailing TextEncoding and NewlineMode on the Handle, and reads bytes directly.

hGetBufNonBlocking :: Handle -> Ptr a -> Int -> IO Int

hGetBufNonBlocking hdl buf count reads data from the handle hdl into the buffer buf until either EOF is reached, or count 8-bit bytes have been read, or there is no more data available to read immediately.

hGetBufNonBlocking is identical to hGetBuf, except that it will never block waiting for data to become available, instead it returns only whatever data is available. To wait for data to arrive before calling hGetBufNonBlocking, use hWaitForInput.

If the handle is a pipe or socket, and the writing end is closed, hGetBufNonBlocking will behave as if EOF was reached.

hGetBufNonBlocking ignores the prevailing TextEncoding and NewlineMode on the Handle, and reads bytes directly.

NOTE: on Windows, this function does not work correctly; it behaves identically to hGetBuf.