System.IO (original) (raw)

The IO monad

data IO a Source #

A value of type `[IO](System-IO.html#t:IO "System.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 toMain.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](System-IO.html#t:IO "System.IO") monad and called at some point, directly or indirectly, from Main.main.

[IO](System-IO.html#t:IO "System.IO") is a monad, so [IO](System-IO.html#t:IO "System.IO") actions can be combined using either the do-notation or the [>>](Prelude.html#v:-62--62- "Prelude") and [>>=](Prelude.html#v:-62--62--61- "Prelude") operations from the [Monad](Prelude.html#v:Monad "Prelude")class.

Files and handles

type FilePath = String Source #

File and directory names are values of type [String](Data-String.html#t:String "Data.String"), whose precise meaning is operating system dependent. Files can be opened, yielding a handle which can then be used to operate on the contents of that file.

data Handle Source #

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:

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](Text-Show.html#t:Show "Text.Show") and [Eq](Data-Eq.html#t:Eq "Data.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 [==](Data-Eq.html#v:-61--61- "Data.Eq") only to itself; no attempt is made to compare the internal state of different handles for equality.

Instances

Instances details

GHC note: a [Handle](System-IO.html#t:Handle "System.IO") will be automatically closed when the garbage collector detects that it has become unreferenced by the program. However, relying on this behaviour is not generally recommended: the garbage collector is unpredictable. If possible, use an explicit [hClose](System-IO.html#v:hClose "System.IO") to close [Handle](System-IO.html#t:Handle "System.IO")s when they are no longer required. GHC does not currently attempt to free up file descriptors when they have run out, it is your responsibility to ensure that this doesn't happen.

Standard handles

Three handles are allocated during program initialisation, and are initially open.

Opening and closing filesOpening filesClosing files

hClose :: Handle -> IO () Source #

Computation [hClose](System-IO.html#v:hClose "System.IO") hdl makes handle hdl closed. Before the computation finishes, if hdl is writable its buffer is flushed as for [hFlush](System-IO.html#v:hFlush "System.IO"). Performing [hClose](System-IO.html#v:hClose "System.IO") 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](System-IO.html#v:hClose "System.IO") fails for any reason, any further operations (apart from[hClose](System-IO.html#v:hClose "System.IO")) on the handle will still fail as if hdl had been successfully closed.

[hClose](System-IO.html#v:hClose "System.IO") is an interruptible operation in the sense described inControl.Exception. If [hClose](System-IO.html#v:hClose "System.IO") is interrupted by an asynchronous exception in the process of flushing its buffers, then the I/O device (e.g., file) will be closed anyway.

Special cases

These functions are also exported by the Prelude.

appendFile :: FilePath -> String -> IO () Source #

The computation [appendFile](System-IO.html#v:appendFile "System.IO") file str function appends the string str, to the file file.

Note that [writeFile](System-IO.html#v:writeFile "System.IO") and [appendFile](System-IO.html#v:appendFile "System.IO") write a literal string to a file. To write a value of any printable type, as with [print](System-IO.html#v:print "System.IO"), use the [show](Text-Show.html#v:show "Text.Show") function to convert the value to a string first.

main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]])

File locking

Implementations should enforce as far as possible, at least locally to the Haskell process, multiple-reader single-writer locking on files. That is, there may either be many handles on the same file which manage input, or just one handle on the file which manages output. If any open or semi-closed handle is managing a file for output, no new handle can be allocated for that file. If any open or semi-closed handle is managing a file for input, new handles can only be allocated if they do not manage output. Whether two files are the same is implementation-dependent, but they should normally be the same if they have the same absolute path name and neither has been renamed, for example.

Warning: the [readFile](System-IO.html#v:readFile "System.IO") operation holds a semi-closed handle on the file until the entire contents of the file have been consumed. It follows that an attempt to write to a file (using [writeFile](System-IO.html#v:writeFile "System.IO"), for example) that was earlier opened by [readFile](System-IO.html#v:readFile "System.IO") will usually result in failure with [isAlreadyInUseError](System-IO-Error.html#v:isAlreadyInUseError "System.IO.Error").

Operations on handlesDetermining and changing the size of a fileDetecting the end of input

hIsEOF :: Handle -> IO Bool Source #

For a readable handle hdl, [hIsEOF](System-IO.html#v:hIsEOF "System.IO") hdl returns[True](Data-Bool.html#v:True "Data.Bool") 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](Data-Bool.html#v:False "Data.Bool").

NOTE: [hIsEOF](System-IO.html#v:hIsEOF "System.IO") may block, because it has to attempt to read from the stream to determine whether there is any more data to be read.

Buffering operations

data BufferMode Source #

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:

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:

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.

hFlush :: Handle -> IO () Source #

The action [hFlush](System-IO.html#v:hFlush "System.IO") hdl causes any items buffered for output in handle hdl to be sent immediately to the operating system.

This operation may fail with:

Repositioning handles

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

Computation [hSeek](System-IO.html#v:hSeek "System.IO") hdl mode i sets the position of handlehdl 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](System-IO.html#v:hIsSeekable "System.IO")), 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:

data SeekMode Source #

A mode that determines the effect of [hSeek](System-IO.html#v:hSeek "System.IO") 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 Source #

Computation [hTell](System-IO.html#v:hTell "System.IO") 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](System-IO.html#v:hSeek "System.IO") to reposition the handle to the current position.

This operation may fail with:

Handle propertiesTerminal operations (not portable: GHC only)Showing handle state (not portable: GHC only)Text input and outputText input

hWaitForInput :: Handle -> Int -> IO Bool Source #

Computation [hWaitForInput](System-IO.html#v:hWaitForInput "System.IO") hdl t waits until input is available on handle hdl. It returns [True](Data-Bool.html#v:True "Data.Bool") as soon as input is available on hdl, or [False](Data-Bool.html#v:False "Data.Bool") if no input is available within t milliseconds. Note that[hWaitForInput](System-IO.html#v:hWaitForInput "System.IO") 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:

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 asafe foreign call in this respect.

hReady :: Handle -> IO Bool Source #

Computation [hReady](System-IO.html#v:hReady "System.IO") hdl indicates whether at least one item is available for input from handle hdl.

This operation may fail with:

hGetChar :: Handle -> IO Char Source #

Computation [hGetChar](System-IO.html#v:hGetChar "System.IO") 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 Source #

Computation [hGetLine](System-IO.html#v:hGetLine "System.IO") hdl reads a line from the file or channel managed by hdl.

This operation may fail with:

If [hGetLine](System-IO.html#v:hGetLine "System.IO") 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 Source #

Computation [hLookAhead](System-IO.html#v:hLookAhead "System.IO") 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:

hGetContents :: Handle -> IO String Source #

Computation [hGetContents](System-IO.html#v:hGetContents "System.IO") 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](System-IO.html#v:hGetContents "System.IO") hdl.

Any operation that fails because a handle is closed, also fails if a handle is semi-closed. The only exception is[hClose](System-IO.html#v:hClose "System.IO"). A semi-closed handle becomes closed:

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:

Text output

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

Computation [hPutChar](System-IO.html#v:hPutChar "System.IO") 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:

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

Computation [hPrint](System-IO.html#v:hPrint "System.IO") hdl t writes the string representation of t given by the [shows](Text-Show.html#v:shows "Text.Show") function to the file or channel managed by hdl and appends a newline.

This operation may fail with:

Special cases for standard input and output

These functions are also exported by the Prelude.

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

The [interact](System-IO.html#v:interact "System.IO") 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.

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

The [print](System-IO.html#v:print "System.IO") function outputs a value of any printable type to the standard output device. Printable types are those that are instances of class [Show](Text-Show.html#t:Show "Text.Show"); [print](System-IO.html#v:print "System.IO") converts values to strings for output using the [show](Text-Show.html#v:show "Text.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]])

Binary input and output

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

[hPutBuf](System-IO.html#v:hPutBuf "System.IO") hdl buf count writes count 8-bit bytes from the buffer buf to the handle hdl. It returns ().

[hPutBuf](System-IO.html#v:hPutBuf "System.IO") ignores any text encoding that applies to the [Handle](System-IO.html#t:Handle "System.IO"), writing the bytes directly to the underlying file or device.

[hPutBuf](System-IO.html#v:hPutBuf "System.IO") ignores the prevailing [TextEncoding](System-IO.html#v:TextEncoding "System.IO") and[NewlineMode](System-IO.html#t:NewlineMode "System.IO") on the [Handle](System-IO.html#t:Handle "System.IO"), and writes bytes directly.

This operation may fail with:

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

[hGetBuf](System-IO.html#v:hGetBuf "System.IO") hdl buf count reads data from the handle hdl into the buffer buf until either EOF is reached orcount 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](System-IO.html#v:hGetBuf "System.IO") 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](System-IO.html#v:hGetBuf "System.IO") will behave as if EOF was reached.

[hGetBuf](System-IO.html#v:hGetBuf "System.IO") ignores the prevailing [TextEncoding](System-IO.html#v:TextEncoding "System.IO") and [NewlineMode](System-IO.html#t:NewlineMode "System.IO") on the [Handle](System-IO.html#t:Handle "System.IO"), and reads bytes directly.

hGetBufSome :: Handle -> Ptr a -> Int -> IO Int Source #

[hGetBufSome](System-IO.html#v:hGetBufSome "System.IO") hdl buf count reads data from the handle hdl into the buffer buf. If there is any data available to read, then [hGetBufSome](System-IO.html#v:hGetBufSome "System.IO") 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](System-IO.html#v:hGetBufSome "System.IO") 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](System-IO.html#v:hGetBufSome "System.IO") will behave as if EOF was reached.

[hGetBufSome](System-IO.html#v:hGetBufSome "System.IO") ignores the prevailing [TextEncoding](System-IO.html#v:TextEncoding "System.IO") and[NewlineMode](System-IO.html#t:NewlineMode "System.IO") on the [Handle](System-IO.html#t:Handle "System.IO"), and reads bytes directly.

Temporary files

openTempFile Source #

Arguments

:: FilePath Directory in which to create the file
-> String File name template. If the template is "foo.ext" then the created file will be "fooXXX.ext" where XXX is some random number. Note that this should not contain any path separator characters.
-> IO (FilePath, Handle)

The function creates a temporary file in ReadWrite mode. 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 andO_EXCL flags are used to prevent this attack, but note thatO_EXCL is sometimes not supported on NFS filesystems, so if you rely on this behaviour it is best to use local filesystems only.

Unicode encoding/decoding

A text-mode [Handle](System-IO.html#t:Handle "System.IO") has an associated [TextEncoding](System-IO.html#t:TextEncoding "System.IO"), which is used to decode bytes into Unicode characters when reading, and encode Unicode characters into bytes when writing.

The default [TextEncoding](System-IO.html#t:TextEncoding "System.IO") is the same as the default encoding on your system, which is also available as [localeEncoding](System-IO.html#v:localeEncoding "System.IO"). (GHC note: on Windows, we currently do not support double-byte encodings; if the console's code page is unsupported, then[localeEncoding](System-IO.html#v:localeEncoding "System.IO") will be [latin1](System-IO.html#v:latin1 "System.IO").)

Encoding and decoding errors are always detected and reported, except during lazy I/O ([hGetContents](System-IO.html#v:hGetContents "System.IO"), [getContents](System-IO.html#v:getContents "System.IO"), and[readFile](System-IO.html#v:readFile "System.IO")), where a decoding error merely results in termination of the character stream, as with other I/O errors.

Unicode encodings

data TextEncoding Source #

A [TextEncoding](System-IO.html#t:TextEncoding "System.IO") 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](System-IO.html#t:TextEncoding "System.IO") for UTF-8 is [utf8](System-IO.html#v:utf8 "System.IO").

Instances

Instances details

latin1 :: TextEncoding Source #

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](System-IO.html#v:Handle "System.IO") using the [latin1](System-IO.html#v:latin1 "System.IO") encoding will result in an error.

utf8_bom :: TextEncoding Source #

The UTF-8 Unicode encoding, with a byte-order-mark (BOM; the byte sequence 0xEF 0xBB 0xBF). This encoding behaves like [utf8](System-IO.html#v:utf8 "System.IO"), 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.

char8 :: TextEncoding Source #

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

mkTextEncoding :: String -> IO TextEncoding Source #

Look up the named Unicode encoding. May fail with

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

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

In theory, this mechanism allows arbitrary data to be roundtripped via a [String](Data-String.html#t:String "Data.String") with no loss of data. In practice, there are two limitations to be aware of:

  1. 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.
  2. 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 prefixCP; for example, "CP1250".

Newline conversion

In Haskell, a newline is always represented by the character'\n'. However, in files and external character streams, a newline may be represented by another character sequence, such as '\r\n'.

A text-mode [Handle](System-IO.html#t:Handle "System.IO") has an associated [NewlineMode](System-IO.html#t:NewlineMode "System.IO") that specifies how to translate newline characters. The[NewlineMode](System-IO.html#t:NewlineMode "System.IO") specifies the input and output translation separately, so that for instance you can translate '\r\n' to '\n' on input, but leave newlines as '\n' on output.

The default [NewlineMode](System-IO.html#t:NewlineMode "System.IO") for a [Handle](System-IO.html#t:Handle "System.IO") is[nativeNewlineMode](System-IO.html#v:nativeNewlineMode "System.IO"), which does no translation on Unix systems, but translates '\r\n' to '\n' and back on Windows.

Binary-mode [Handle](System-IO.html#t:Handle "System.IO")s do no newline translation at all.

data Newline Source #

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

data NewlineMode Source #

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.

universalNewlineMode :: NewlineMode Source #

Map '\r\n' into '\n' on input, and '\n' to the native newline representation 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 Source #

Use the native newline representation on both input and output

nativeNewlineMode = NewlineMode { inputNL = nativeNewline outputNL = nativeNewline }