Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | stable |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
The standard IO library.
Synopsis
- data IO a
- fixIO :: (a -> IO a) -> IO a
- type FilePath = String
- data Handle
- stdin :: Handle
- stdout :: Handle
- stderr :: Handle
- withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
- openFile :: FilePath -> IOMode -> IO Handle
- data IOMode
- hClose :: Handle -> IO ()
- readFile :: FilePath -> IO String
- readFile' :: FilePath -> IO String
- writeFile :: FilePath -> String -> IO ()
- appendFile :: FilePath -> String -> IO ()
- hFileSize :: Handle -> IO Integer
- hSetFileSize :: Handle -> Integer -> IO ()
- hIsEOF :: Handle -> IO Bool
- isEOF :: IO Bool
- data BufferMode
- hSetBuffering :: Handle -> BufferMode -> IO ()
- hGetBuffering :: Handle -> IO BufferMode
- hFlush :: Handle -> IO ()
- hGetPosn :: Handle -> IO HandlePosn
- hSetPosn :: HandlePosn -> IO ()
- data HandlePosn
- hSeek :: Handle -> SeekMode -> Integer -> IO ()
- data SeekMode
- hTell :: Handle -> IO Integer
- hIsOpen :: Handle -> IO Bool
- hIsClosed :: Handle -> IO Bool
- hIsReadable :: Handle -> IO Bool
- hIsWritable :: Handle -> IO Bool
- hIsSeekable :: Handle -> IO Bool
- hIsTerminalDevice :: Handle -> IO Bool
- hSetEcho :: Handle -> Bool -> IO ()
- hGetEcho :: Handle -> IO Bool
- hShow :: Handle -> IO String
- hWaitForInput :: Handle -> Int -> IO Bool
- hReady :: Handle -> IO Bool
- hGetChar :: Handle -> IO Char
- hGetLine :: Handle -> IO String
- hLookAhead :: Handle -> IO Char
- hGetContents :: Handle -> IO String
- hGetContents' :: Handle -> IO String
- hPutChar :: Handle -> Char -> IO ()
- hPutStr :: Handle -> String -> IO ()
- hPutStrLn :: Handle -> String -> IO ()
- hPrint :: Show a => Handle -> a -> IO ()
- interact :: (String -> String) -> IO ()
- putChar :: Char -> IO ()
- putStr :: String -> IO ()
- putStrLn :: String -> IO ()
- print :: Show a => a -> IO ()
- getChar :: IO Char
- getLine :: IO String
- getContents :: IO String
- getContents' :: IO String
- readIO :: Read a => String -> IO a
- readLn :: Read a => IO a
- withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
- openBinaryFile :: FilePath -> IOMode -> IO Handle
- hSetBinaryMode :: Handle -> Bool -> IO ()
- hPutBuf :: Handle -> Ptr a -> Int -> IO ()
- hGetBuf :: Handle -> Ptr a -> Int -> IO Int
- hGetBufSome :: Handle -> Ptr a -> Int -> IO Int
- hPutBufNonBlocking :: Handle -> Ptr a -> Int -> IO Int
- hGetBufNonBlocking :: Handle -> Ptr a -> Int -> IO Int
- openTempFile :: FilePath -> String -> IO (FilePath, Handle)
- openBinaryTempFile :: FilePath -> String -> IO (FilePath, Handle)
- openTempFileWithDefaultPermissions :: FilePath -> String -> IO (FilePath, Handle)
- openBinaryTempFileWithDefaultPermissions :: FilePath -> String -> IO (FilePath, Handle)
- hSetEncoding :: Handle -> TextEncoding -> IO ()
- hGetEncoding :: Handle -> IO (Maybe TextEncoding)
- data TextEncoding
- latin1 :: TextEncoding
- utf8 :: TextEncoding
- utf8_bom :: TextEncoding
- utf16 :: TextEncoding
- utf16le :: TextEncoding
- utf16be :: TextEncoding
- utf32 :: TextEncoding
- utf32le :: TextEncoding
- utf32be :: TextEncoding
- localeEncoding :: TextEncoding
- char8 :: TextEncoding
- mkTextEncoding :: String -> IO TextEncoding
- hSetNewlineMode :: Handle -> NewlineMode -> IO ()
- data Newline
- nativeNewline :: Newline
- data NewlineMode = NewlineMode {}
- noNewlineTranslation :: NewlineMode
- universalNewlineMode :: NewlineMode
- nativeNewlineMode :: NewlineMode
The IO monad
A value of type
is a computation which, when performed,
does some I/O before returning a value of type IO
aa
.
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
fixIO :: (a -> IO a) -> IO a Source #
The implementation of mfix
for IO
.
This operation may fail with:
FixIOException
if the function passed tofixIO
inspects its argument.
Examples
the IO-action is only executed once. The recursion is only on the values.
>>>
take 3 <$> fixIO (\x -> putStr ":D" >> (:x) <$> readLn @Int)
:D 2 [2,2,2]
If we are strict in the value, just as with fix
, we do not get termination:
>>>
fixIO (\x -> putStr x >> pure ('x' : x))
* hangs forever *
We can tie the knot of a structure within IO
using fixIO
:
data Node = MkNode Int (IORef Node) foo :: IO () foo = do p <- fixIO (p -> newIORef (MkNode 0 p)) q <- output p r <- output q _ <- output r pure () output :: IORef Node -> IO (IORef Node) output ref = do MkNode x p <- readIORef ref print x pure p
>>>
foo
0 0 0
Files and handles
type FilePath = String Source #
File and directory names are values of type 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.
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.
GHC note: a Handle
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
to close Handle
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 files
Opening files
:: FilePath | The path to the file that should be opened |
-> IOMode | The mode in which the file should be opened |
-> (Handle -> IO r) | The action to run with the obtained handle |
-> IO r |
The computation
opens the file and runs withFile
path mode actionaction
with the obtained handle before closing the file.
Even when an exception is raised within the action
, the file will still be closed.
This is why
is preferable towithFile
path mode act
openFile
path mode >>= (\hdl -> act hdl >>=hClose
hdl)
See also: bracket
:: FilePath | The path to the file that should be opened |
-> IOMode | The mode in which the file should be opened |
-> IO Handle |
The computation
returns a file handle that can be
used to interact with the file.openFile
path mode
The handle is open in text mode with localeEncoding
.
You can change the encoding with hSetEncoding
.
See openFile
Instances
Enum IOMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.IOMode succ :: IOMode -> IOMode Source # pred :: IOMode -> IOMode Source # toEnum :: Int -> IOMode Source # fromEnum :: IOMode -> Int Source # enumFrom :: IOMode -> [IOMode] Source # enumFromThen :: IOMode -> IOMode -> [IOMode] Source # enumFromTo :: IOMode -> IOMode -> [IOMode] Source # enumFromThenTo :: IOMode -> IOMode -> IOMode -> [IOMode] Source # | |
Ix IOMode Source # | Since: base-4.2.0.0 |
Read IOMode Source # | Since: base-4.2.0.0 |
Show IOMode Source # | Since: base-4.2.0.0 |
Eq IOMode Source # | Since: base-4.2.0.0 |
Ord IOMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.IOMode |
Closing files
hClose :: 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.
hClose
is an interruptible operation in the sense described in
Control.Exception. If hClose
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.
readFile :: FilePath -> IO String Source #
The readFile
function reads a file and
returns the contents of the file as a string.
The file is read lazily, on demand, as with getContents
.
This operation may fail with the same errors as hGetContents
and openFile
.
Examples
>>>
readFile "~/hello_world"
"Greetings!"
>>>
take 5 <$> readFile "/dev/zero"
"\NUL\NUL\NUL\NUL\NUL"
readFile' :: FilePath -> IO String Source #
The readFile'
function reads a file and
returns the contents of the file as a string.
This is identical to readFile
, but the file is fully read before being returned,
as with getContents'
.
Since: base-4.15.0.0
writeFile :: FilePath -> String -> IO () Source #
The computation
function writes the string writeFile
file strstr
,
to the file file
.
This operation may fail with the same errors as hPutStr
and withFile
.
Examples
>>>
writeFile "hello" "world" >> readFile "hello"
"world"
>>>
writeFile "~/" "D:"
*** Exception: ~/: withFile: inappropriate type (Is a directory)
appendFile :: FilePath -> String -> IO () Source #
The computation
function appends the string appendFile
file strstr
,
to the file file
.
Note that writeFile
and appendFile
write a literal string
to a file. To write a value of any printable type, as with print
,
use the show
function to convert the value to a string first.
This operation may fail with the same errors as hPutStr
and withFile
.
Examples
The following example could be more efficently written by acquiring a handle
instead with openFile
and using the computations capable of writing to handles
such as hPutStr
.
>>>
let fn = "hello_world"
>>>
in writeFile fn "hello" >> appendFile fn " world!" >> (readFile fn >>= putStrLn)
"hello world!"
>>>
let fn = "foo"; output = readFile' fn >>= putStrLn
>>>
in output >> appendFile fn (show [1,2,3]) >> output
this is what's in the file this is what's in the file[1,2,3]
Operations on handles
Determining and changing the size of a file
hFileSize :: Handle -> IO Integer Source #
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 () Source #
hSetFileSize
hdl
size
truncates the physical file with handle hdl
to size
bytes.
Detecting the end of input
hIsEOF :: 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 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:
- 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.
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 |
Instances
Read BufferMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Handle.Types | |
Show BufferMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Handle.Types | |
Eq BufferMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Handle.Types (==) :: BufferMode -> BufferMode -> Bool Source # (/=) :: BufferMode -> BufferMode -> Bool Source # | |
Ord BufferMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Handle.Types compare :: BufferMode -> BufferMode -> Ordering Source # (<) :: BufferMode -> BufferMode -> Bool Source # (<=) :: BufferMode -> BufferMode -> Bool Source # (>) :: BufferMode -> BufferMode -> Bool Source # (>=) :: BufferMode -> BufferMode -> Bool Source # max :: BufferMode -> BufferMode -> BufferMode Source # min :: BufferMode -> BufferMode -> BufferMode Source # |
hSetBuffering :: Handle -> BufferMode -> IO () Source #
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 forhFlush
; - if
hdl
is not writable, the contents of the buffer are 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 Source #
Computation hGetBuffering
hdl
returns the current buffering mode
for hdl
.
hFlush :: 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.
Repositioning handles
hGetPosn :: Handle -> IO HandlePosn Source #
Computation hGetPosn
hdl
returns the current I/O position of
hdl
as a value of the abstract type HandlePosn
.
hSetPosn :: HandlePosn -> IO () Source #
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 Source #
Instances
Show HandlePosn Source # | Since: base-4.1.0.0 |
Defined in GHC.Internal.IO.Handle | |
Eq HandlePosn Source # | Since: base-4.1.0.0 |
Defined in GHC.Internal.IO.Handle (==) :: HandlePosn -> HandlePosn -> Bool Source # (/=) :: HandlePosn -> HandlePosn -> Bool Source # |
hSeek :: Handle -> SeekMode -> Integer -> IO () Source #
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.
A mode that determines the effect of hSeek
hdl mode i
.
AbsoluteSeek | the position of |
RelativeSeek | the position of |
SeekFromEnd | the position of |
Instances
Enum SeekMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Device succ :: SeekMode -> SeekMode Source # pred :: SeekMode -> SeekMode Source # toEnum :: Int -> SeekMode Source # fromEnum :: SeekMode -> Int Source # enumFrom :: SeekMode -> [SeekMode] Source # enumFromThen :: SeekMode -> SeekMode -> [SeekMode] Source # enumFromTo :: SeekMode -> SeekMode -> [SeekMode] Source # enumFromThenTo :: SeekMode -> SeekMode -> SeekMode -> [SeekMode] Source # | |
Ix SeekMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Device | |
Read SeekMode Source # | Since: base-4.2.0.0 |
Show SeekMode Source # | Since: base-4.2.0.0 |
Eq SeekMode Source # | Since: base-4.2.0.0 |
Ord SeekMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Device |
hTell :: Handle -> IO Integer Source #
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.
Handle properties
hIsOpen :: Handle -> IO Bool Source #
returns whether the handle is open.
If the hIsOpen
hdlhaType
of hdl
is ClosedHandle
or SemiClosedHandle
this returns False
and True
otherwise.
hIsClosed :: Handle -> IO Bool Source #
returns whether the handle is closed.
If the hIsOpen
hdlhaType
of hdl
is ClosedHandle
this returns True
and False
otherwise.
hIsReadable :: Handle -> IO Bool Source #
returns whether it is possible to read from the handle.hIsReadable
hdl
hIsWritable :: Handle -> IO Bool Source #
returns whether it is possible to write to the handle.hIsWritable
hdl
hIsSeekable :: Handle -> IO Bool Source #
returns whether it is possible to hIsSeekable
hdlhSeek
with the given handle.
Terminal operations (not portable: GHC only)
hIsTerminalDevice :: Handle -> IO Bool Source #
Is the handle connected to a terminal?
On Windows the result of hIsTerminalDevide
might be misleading,
because non-native terminals, such as MinTTY used in MSYS and Cygwin environments,
are implemented via redirection.
Use System.Win32.Types.withHandleToHANDLE System.Win32.MinTTY.isMinTTYHandle
to recognise it. Also consider ansi-terminal
package for crossplatform terminal
support.
hSetEcho :: Handle -> Bool -> IO () Source #
Set the echoing status of a handle connected to a terminal.
Showing handle state (not portable: GHC only)
Text input and output
Text input
hWaitForInput :: Handle -> Int -> IO Bool Source #
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 Source #
Computation hReady
hdl
indicates whether at least one item is
available for input from handle hdl
.
This operation may fail with:
isEOFError
if the end of file has been reached.
hGetChar :: 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:
isEOFError
if the end of file has been reached.
hGetLine :: Handle -> IO String Source #
Computation hGetLine
hdl
reads a line from the file or
channel managed by hdl
.
hGetLine
does not return the newline as part of the result.
A line is separated by the newline
set with hSetNewlineMode
or nativeNewline
by default.
The read newline character(s) are not returned as part of the result.
If hGetLine
encounters end-of-file at any point while reading
in the middle of a line, it is treated as a line terminator and the (partial)
line is returned.
This operation may fail with:
isEOFError
if the end of file is encountered when reading the first character of the line.
Examples
>>>
withFile "/home/user/foo" ReadMode hGetLine >>= putStrLn
this is the first line of the file :O
>>>
withFile "/home/user/bar" ReadMode (replicateM 3 . hGetLine)
["this is the first line","this is the second line","this is the third line"]
hLookAhead :: Handle -> IO Char Source #
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 Source #
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:
isEOFError
if the end of file has been reached.
hGetContents' :: Handle -> IO String Source #
The hGetContents'
operation reads all input on the given handle
before returning it as a String
and closing the handle.
This is a strict version of hGetContents
Since: base-4.15.0.0
Text output
hPutChar :: 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:
isFullError
if the device is full.isPermissionError
if another system resource limit would be exceeded.
hPutStr :: Handle -> String -> IO () Source #
Computation hPutStr
hdl s
writes the string
s
to the file or channel managed by hdl
.
Note that hPutStr
is not concurrency safe unless the BufferMode
of
hdl
is set to LineBuffering
or BlockBuffering
:
>>>
let f = forkIO . hPutStr stdout
>>>
in do hSetBuffering stdout NoBuffering; f "This is a longer string"; f ":D"; f "Hello Haskell"; pure ()
This: HDiesl lao lHoansgkeerl lstring
>>>
let f = forkIO . hPutStr stdout
>>>
in do hSetBuffering stdout LineBuffering; f "This is a longer string"; f ":D"; f "Hello Haskell"; pure ()
This is a longer string:DHello Haskell
This operation may fail with:
isFullError
if the device is full.isPermissionError
if another system resource limit would be exceeded.
hPrint :: Show a => Handle -> a -> IO () Source #
Computation hPrint
hdl t
writes the string representation of t
given by the show
function to the file or channel managed by hdl
and appends a newline.
This operation may fail with the same errors as hPutStrLn
Examples
>>>
hPrint stdout [1,2,3]
[1,2,3]
>>>
hPrint stdin [4,5,6]
*** Exception: <stdin>: hPutStr: illegal operation (handle is not open for writing)
Special cases for standard input and output
These functions are also exported by the Prelude.
interact :: (String -> String) -> IO () Source #
takes the entire input from interact
fstdin
and applies f
to it.
The resulting string is written to the stdout
device.
Note that this operation is lazy, which allows to produce output even before all input has been consumed.
This operation may fail with the same errors as getContents
and putStr
.
Examples
>>>
interact (\str -> str ++ str)
> hi :) hi :) > ^D hi :)
>>>
interact (const ":D")
:D
>>>
interact (show . words)
> hello world! > I hope you have a great day > ^D ["hello","world!","I","hope","you","have","a","great","day"]
putStr :: String -> IO () Source #
Write a string to the standard output device
putStr
is implemented as
.hPutStr
stdout
This operation may fail with the same errors, and has the same issues with concurrency, as hPutStr
!
Examples
Note that the following do not put a newline.
>>>
putStr "Hello, World!"
Hello, World!
>>>
putStr "\0052\0042\0050"
4*2
print :: Show a => a -> IO () Source #
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.
print
is implemented as putStrLn
.
show
This operation may fail with the same errors, and has the same issues with concurrency, as hPutStr
!
Examples
>>>
print [1, 2, 3]
[1,2,3]
Be careful when using print
for outputting strings,
as this will invoke show
and cause strings to be printed
with quotation marks and non-ascii symbols escaped.
>>>
print "λ :D"
"\995 :D"
A program to print the first 8 integers and their powers of 2 could be written as:
>>>
print [(n, 2^n) | n <- [0..8]]
[(0,1),(1,2),(2,4),(3,8),(4,16),(5,32),(6,64),(7,128),(8,256)]
getContents :: IO String Source #
The getContents
operation returns all user input as a single string,
which is read lazily as it is needed.
getContents
is implemented as
.hGetContents
stdin
This operation may fail with the same errors as hGetContents
.
Examples
>>>
getContents >>= putStr
> aaabbbccc :D aaabbbccc :D > I hope you have a great day I hope you have a great day > ^D
>>>
getContents >>= print . length
> abc > <3 > def ^D 11
getContents' :: IO String Source #
The getContents'
operation returns all user input as a single string,
which is fully read before being returned
getContents'
is implemented as
.hGetContents'
stdin
This operation may fail with the same errors as hGetContents'
.
Examples
>>>
getContents' >>= putStr
> aaabbbccc :D > I hope you have a great day aaabbbccc :D I hope you have a great day
>>>
getContents' >>= print . length
> abc > <3 > def ^D 11
Since: base-4.15.0.0
readIO :: Read a => String -> IO a Source #
The readIO
function is similar to read
except that it signals
parse failure to the IO
monad instead of terminating the program.
This operation may fail with:
isUserError
if there is no unambiguous parse.
Examples
>>>
fmap (+ 1) (readIO "1")
2
>>>
readIO "not quite ()" :: IO ()
*** Exception: user error (Prelude.readIO: no parse)
Binary input and output
withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r Source #
The computation
opens the binary file
and runs withBinaryFile
path mode actionaction
with the obtained handle before closing the binary file.
This is different from withFile
as in that it does not use any file encoding.
Even when an exception is raised within the action
, the file will still be closed.
This is why
is preferable towithBinaryFile
path mode act
openBinaryFile
path mode >>= (\hdl -> act hdl >>=hClose
hdl)
See also: bracket
:: FilePath | The path to the binary file that should be opened |
-> IOMode | The mode in which the binary file should be opened |
-> IO Handle |
The computation
returns a file handle that can be
used to interact with the binary file.openBinaryFile
path mode
This is different from openFile
as in that it does not use any file encoding.
hSetBinaryMode :: Handle -> Bool -> IO () Source #
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 () Source #
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 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 :: 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.
hGetBufNonBlocking :: 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 does not work correctly; it
behaves identically to hGetBuf
.
Temporary files
:: 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. On Windows, the template prefix may be truncated to 3 chars, e.g. "foobar.ext" will be "fooXXX.ext". |
-> 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
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 :: FilePath -> String -> IO (FilePath, Handle) Source #
Like openTempFile
, but opens the file in binary mode. See openBinaryFile
for more comments.
openTempFileWithDefaultPermissions :: FilePath -> String -> IO (FilePath, Handle) Source #
Like openTempFile
, but uses the default file permissions
openBinaryTempFileWithDefaultPermissions :: FilePath -> String -> IO (FilePath, Handle) Source #
Like openBinaryTempFile
, but uses the default file permissions
Unicode encoding/decoding
A text-mode Handle
has an associated TextEncoding
, which
is used to decode bytes into Unicode characters when reading,
and encode Unicode characters into bytes when writing.
The default TextEncoding
is the same as the default encoding
on your system, which is also available as localeEncoding
.
(GHC note: on Windows, we currently do not support double-byte
encodings; if the console's code page is unsupported, then
localeEncoding
will be latin1
.)
Encoding and decoding errors are always detected and reported,
except during lazy I/O (hGetContents
, getContents
, and
readFile
), where a decoding error merely results in
termination of the character stream, as with other I/O errors.
hSetEncoding :: Handle -> TextEncoding -> IO () Source #
The action 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 :: 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.
Unicode encodings
data TextEncoding Source #
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
Show TextEncoding Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.IO.Encoding.Types |
utf8 :: TextEncoding Source #
The UTF-8 Unicode encoding
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
,
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 Source #
The UTF-16 Unicode encoding (a byte-order-mark should be used to indicate endianness).
utf16le :: TextEncoding Source #
The UTF-16 Unicode encoding (little-endian)
utf16be :: TextEncoding Source #
The UTF-16 Unicode encoding (big-endian)
utf32 :: TextEncoding Source #
The UTF-32 Unicode encoding (a byte-order-mark should be used to indicate endianness).
utf32le :: TextEncoding Source #
The UTF-32 Unicode encoding (little-endian)
utf32be :: TextEncoding Source #
The UTF-32 Unicode encoding (big-endian)
localeEncoding :: TextEncoding Source #
The 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 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
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 criterion, 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"
.
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
has an associated NewlineMode
that
specifies how to translate newline characters. The
NewlineMode
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
for a Handle
is
nativeNewlineMode
, which does no translation on Unix systems,
but translates '\r\n'
to '\n'
and back on Windows.
Binary-mode Handle
s do no newline translation at all.
hSetNewlineMode :: Handle -> NewlineMode -> IO () Source #
Set the NewlineMode
on the specified Handle
. All buffered
data is flushed first.
The representation of a newline in the external file or stream.
Instances
Read Newline Source # | Since: base-4.3.0.0 |
Show Newline Source # | Since: base-4.3.0.0 |
Eq Newline Source # | Since: base-4.2.0.0 |
Ord Newline Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.IO.Handle.Types |
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.
Instances
Read NewlineMode Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.IO.Handle.Types | |
Show NewlineMode Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.IO.Handle.Types | |
Eq NewlineMode Source # | Since: base-4.2.0.0 |
Defined in GHC.Internal.IO.Handle.Types (==) :: NewlineMode -> NewlineMode -> Bool Source # (/=) :: NewlineMode -> NewlineMode -> Bool Source # | |
Ord NewlineMode Source # | Since: base-4.3.0.0 |
Defined in GHC.Internal.IO.Handle.Types compare :: NewlineMode -> NewlineMode -> Ordering Source # (<) :: NewlineMode -> NewlineMode -> Bool Source # (<=) :: NewlineMode -> NewlineMode -> Bool Source # (>) :: NewlineMode -> NewlineMode -> Bool Source # (>=) :: NewlineMode -> NewlineMode -> Bool Source # max :: NewlineMode -> NewlineMode -> NewlineMode Source # min :: NewlineMode -> NewlineMode -> NewlineMode Source # |
noNewlineTranslation :: NewlineMode Source #
Do no newline translation at all.
noNewlineTranslation = NewlineMode { inputNL = LF, outputNL = LF }
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 }