sdp-io-0.2: SDP IO extension
Copyright(c) Andrey Mulik 2020
LicenseBSD-style
Maintainerwork.a.mulik@gmail.com
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.IO.Handle

Description

System.IO.Handle is safe import of System.IO.

Synopsis

Handles

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

Instances details
Eq Handle

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Methods

(==) :: Handle -> Handle -> Bool #

(/=) :: Handle -> Handle -> Bool #

Show Handle

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

hClose :: MonadIO io => Handle -> io () Source #

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.

Standard handles

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.

IO mode

data IOMode #

Instances

Instances details
Enum IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Eq IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Methods

(==) :: IOMode -> IOMode -> Bool #

(/=) :: IOMode -> IOMode -> Bool #

Ord IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Read IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Show IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Ix IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

File size

hGetFileSize :: MonadIO io => Handle -> io Integer Source #

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

hSetFileSize :: MonadIO io => Handle -> Integer -> io () Source #

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

Detecting the end of input

isEOF :: MonadIO io => io Bool Source #

Computation isEOF is equal to hIsEOF stdin

hIsEOF :: MonadIO io => Handle -> io Bool Source #

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.

Buffering

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.

Instances

Instances details
Eq BufferMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Ord BufferMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Read BufferMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show BufferMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

hFlush :: MonadIO io => Handle -> io () Source #

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.

hSetBuffering :: MonadIO io => Handle -> BufferMode -> io () Source #

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 :: MonadIO io => Handle -> io BufferMode Source #

hGetBuffering hdl returns the current buffering mode for hdl.

Repositioning

data HandlePosn #

Instances

Instances details
Eq HandlePosn

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle

Show HandlePosn

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle

hGetPosn :: MonadIO io => Handle -> io HandlePosn Source #

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

hSetPosn :: MonadIO io => HandlePosn -> io () Source #

If a call to hGetPosn hdl returns a position p, then 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:

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.

Instances

Instances details
Enum SeekMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

Eq SeekMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

Ord SeekMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

Read SeekMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

Show SeekMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

Ix SeekMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

hSeek :: MonadIO io => Handle -> SeekMode -> Integer -> io () Source #

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 isn't 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 isn't 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:

hTell :: MonadIO io => Handle -> io Integer Source #

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:

Properties

hIsOpen :: MonadIO io => Handle -> io Bool Source #

Same as hIsOpen.

hIsClosed :: MonadIO io => Handle -> io Bool Source #

Same as hIsClosed.

Terminal operations (not portable: GHC only)

hIsTerminalDevice :: MonadIO io => Handle -> io Bool Source #

Is the handle connected to a terminal?

hSetEcho :: MonadIO io => Handle -> Bool -> io () Source #

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

hGetEcho :: MonadIO io => Handle -> io Bool Source #

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

Text IO

hWaitForInput :: MonadIO io => Handle -> Int -> io Bool Source #

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 :: MonadIO io => Handle -> io Bool Source #

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

This operation may fail with:

hLookAhead :: MonadIO io => Handle -> io Char Source #

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:

hGetChar :: MonadIO io => Handle -> io Char Source #

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

This operation may fail with:

hPutChar :: MonadIO io => Handle -> Char -> io () Source #

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:

getChar :: MonadIO io => io Char Source #

Read a character from the standard input device, hGetChar stdin.

putChar :: MonadIO io => Char -> io () Source #

Write a character to the standard output device hPutChar stdout.

Binary IO

hSetBinaryMode :: MonadIO io => Handle -> Bool -> io () Source #

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

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

withBinaryFile :: MonadIO io => FilePath -> IOMode -> (Handle -> IO r) -> io r Source #

withBinaryFile name mode act opens a file using openBinaryFile and passes the resulting handle to the computation act. The handle will be closed on exit from withBinaryFile, whether by normal termination or by raising an exception.

openBinaryFile :: MonadIO io => FilePath -> IOMode -> io Handle Source #

Like openFile, but open the file in binary mode. On Windows, reading a file in text mode (which is the default) will translate CRLF to LF, and writing will translate LF to CRLF. This is usually what you want with text files. With binary files this is undesirable; also, as usual under MS OSes, text mode treats control-Z as EOF. Binary mode turns off all special treatment of end-of-line and end-of-file characters.

hGetBuf :: MonadIO io => Handle -> Ptr a -> Int -> io Int Source #

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.

hGetBufSome :: MonadIO io => Handle -> Ptr a -> Int -> io Int Source #

hGetBufSome hdl buf count reads data from the handle hdl into the buffer buf. If there is any data available to read, then hGetBufSome returns it immediately; it only blocks if there is no data to be 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).

hGetBufSome 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, hGetBufSome will behave as if EOF was reached.

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

hPutBuf :: MonadIO io => Handle -> Ptr a -> Int -> io () Source #

hPutBuf hdl buf count writes count 8-bit bytes from the buffer buf to the handle hdl.

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

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).

hPutBufNonBlocking :: MonadIO io => Handle -> Ptr a -> Int -> io Int Source #

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 doesn't work correctly; it behaves identically to hGetBuf.

hGetBufNonBlocking :: MonadIO io => Handle -> Ptr a -> Int -> io Int Source #

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 doesn't work correctly; it behaves identically to hGetBuf.

Temporary files

openTempFile :: MonadIO io => FilePath -> String -> io (FilePath, Handle) Source #

The function creates a temporary file in ReadWriteMode. The created file isn't deleted automatically, so you need to delete it manually.

The file is created with permissions such that only the current user can read/write it.

With some exceptions (see below), the file will be created securely in the sense that an attacker should not be able to cause openTempFile to overwrite another file on the filesystem using your credentials, by putting symbolic links (on Unix) in the place where the temporary file is to be created. On Unix the O_CREAT and O_EXCL flags are used to prevent this attack, but note that O_EXCL is sometimes not supported on NFS filesystems, so if you rely on this behaviour it is best to use local filesystems only.

openBinaryTempFile :: MonadIO io => FilePath -> String -> io (FilePath, Handle) Source #

Like openTempFile, but opens the file in binary mode.

openTempFileWith' :: MonadIO io => FilePath -> String -> io (FilePath, Handle) Source #

Like openTempFile, but uses the default file permissions.

openBinaryTempFile' :: MonadIO io => FilePath -> String -> io (FilePath, Handle) Source #

Like openBinaryTempFile, but uses the default file permissions.

Encoding

hSetEncoding :: MonadIO io => Handle -> TextEncoding -> io () Source #

hSetEncoding hdl encoding changes the text encoding for the handle hdl to encoding. The default encoding when a Handle is created is localeEncoding, namely the default encoding for the current locale.

To create a Handle with no encoding at all, use openBinaryFile. To stop further encoding or decoding on an existing Handle, use hSetBinaryMode.

hSetEncoding may need to flush buffered data in order to change the encoding

hGetEncoding :: MonadIO io => Handle -> io (Maybe TextEncoding) Source #

Return the current TextEncoding for the specified Handle, or Nothing if the Handle is in binary mode.

Note that the TextEncoding remembers nothing about the state of the encoder/decoder in use on this Handle. For example, if the encoding in use is UTF-16, then using hGetEncoding and hSetEncoding to save and restore the encoding may result in an extra byte-order-mark being written to the file.

encoding :: MonadIO io => Field io Handle (Maybe TextEncoding) Source #

Encoding Field, set hdl [encoding := Nothing] = hSetBinaryMode hdl True

data TextEncoding #

A TextEncoding is a specification of a conversion scheme between sequences of bytes and sequences of Unicode characters.

For example, UTF-8 is an encoding of Unicode characters into a sequence of bytes. The TextEncoding for UTF-8 is utf8.

Instances

Instances details
Show TextEncoding

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Encoding.Types

mkTextEncoding :: MonadIO io => String -> io TextEncoding Source #

Look up the named Unicode encoding. May fail with

  • isDoesNotExistError if the encoding is unknown

The set of known encodings is system-dependent, but includes at least:

  • UTF-8
  • UTF-16, UTF-16BE, UTF-16LE
  • UTF-32, UTF-32BE, UTF-32LE

There is additional notation (borrowed from GNU iconv) for specifying how illegal characters are handled:

  • a suffix of /IGNORE, e.g. UTF-8/IGNORE, will cause all illegal sequences on input to be ignored, and on output will drop all code points that have no representation in the target encoding.
  • a suffix of //TRANSLIT will choose a replacement character for illegal sequences or code points.
  • a suffix of //ROUNDTRIP will use a PEP383-style escape mechanism to represent any invalid bytes in the input as Unicode codepoints (specifically, as lone surrogates, which are normally invalid in UTF-32). Upon output, these special codepoints are detected and turned back into the corresponding original byte.

In theory, this mechanism allows arbitrary data to be roundtripped via a String with no loss of data. In practice, there are two limitations to be aware of:

  • This only stands a chance of working for an encoding which is an ASCII superset, as for security reasons we refuse to escape any bytes smaller than 128. Many encodings of interest are ASCII supersets (in particular, you can assume that the locale encoding is an ASCII superset) but many (such as UTF-16) are not.
  • If the underlying encoding is not itself roundtrippable, this mechanism can fail. Roundtrippable encodings are those which have an injective mapping into Unicode. Almost all encodings meet this criteria, but some do not. Notably, Shift-JIS (CP932) and Big5 contain several different encodings of the same Unicode codepoint.

On Windows, you can access supported code pages with the prefix CP; for example, CP1250.

localeEncoding :: TextEncoding #

The Unicode encoding of the current locale

This is the initial locale encoding: if it has been subsequently changed by setLocaleEncoding this value will not reflect that change.

char8 :: TextEncoding #

An encoding in which Unicode code points are translated to bytes by taking the code point modulo 256. When decoding, bytes are translated directly into the equivalent code point.

This encoding never fails in either direction. However, encoding discards information, so encode followed by decode is not the identity.

Since: base-4.4.0.0

latin1 :: TextEncoding #

The Latin1 (ISO8859-1) encoding. This encoding maps bytes directly to the first 256 Unicode code points, and is thus not a complete Unicode encoding. An attempt to write a character greater than '\255' to a Handle using the latin1 encoding will result in an error.

utf8 :: TextEncoding #

The UTF-8 Unicode encoding

utf8_bom :: TextEncoding #

The UTF-8 Unicode encoding, with a byte-order-mark (BOM; the byte sequence 0xEF 0xBB 0xBF). This encoding behaves like utf8, except that on input, the BOM sequence is ignored at the beginning of the stream, and on output, the BOM sequence is prepended.

The byte-order-mark is strictly unnecessary in UTF-8, but is sometimes used to identify the encoding of a file.

utf16 :: TextEncoding #

The UTF-16 Unicode encoding (a byte-order-mark should be used to indicate endianness).

utf16le :: TextEncoding #

The UTF-16 Unicode encoding (litte-endian)

utf16be :: TextEncoding #

The UTF-16 Unicode encoding (big-endian)

utf32 :: TextEncoding #

The UTF-32 Unicode encoding (a byte-order-mark should be used to indicate endianness).

utf32le :: TextEncoding #

The UTF-32 Unicode encoding (litte-endian)

utf32be :: TextEncoding #

The UTF-32 Unicode encoding (big-endian)

Newline conversion

data Newline #

The representation of a newline in the external file or stream.

Constructors

LF
'\n'
CRLF
'\r\n'

Instances

Instances details
Eq Newline

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Methods

(==) :: Newline -> Newline -> Bool #

(/=) :: Newline -> Newline -> Bool #

Ord Newline

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Read Newline

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show Newline

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

data NewlineMode #

Specifies the translation, if any, of newline characters between internal Strings and the external file or stream. Haskell Strings are assumed to represent newlines with the '\n' character; the newline mode specifies how to translate '\n' on output, and what to translate into '\n' on input.

Constructors

NewlineMode 

Fields

Instances

Instances details
Eq NewlineMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Ord NewlineMode

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Read NewlineMode

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show NewlineMode

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

nativeNewline :: Newline #

The native newline representation for the current platform: LF on Unix systems, CRLF on Windows.

hSetNewlineMode :: MonadIO io => Handle -> NewlineMode -> io () Source #

Set the NewlineMode on the specified Handle. All buffered data is flushed first.

noNewlineTranslation :: NewlineMode #

Do no newline translation at all.

noNewlineTranslation  = NewlineMode { inputNL  = LF, outputNL = LF }

universalNewlineMode :: NewlineMode #

Map '\r\n' into '\n' on input, and '\n' to the native newline represetnation on output. This mode can be used on any platform, and works with text files using any newline convention. The downside is that readFile >>= writeFile might yield a different file.

universalNewlineMode  = NewlineMode { inputNL  = CRLF,
                                      outputNL = nativeNewline }

nativeNewlineMode :: NewlineMode #

Use the native newline representation on both input and output

nativeNewlineMode  = NewlineMode { inputNL  = nativeNewline
                                   outputNL = nativeNewline }