explicit-iomodes-0.1.2: File handles with explicit IOModes

MaintainerBas van Dijk <v.dijk.bas@gmail.com>

System.IO.ExplicitIOModes

Contents

Description

This module exports a Handle to a file which is parameterized with the IOMode the handle is in. All operations on handles explicitly specify the needed IOMode. This way it is impossible to read from a write-only handle or write to a read-only handle for example.

This modules re-exports everything from System.IO so you can just replace: import System.IO with: import System.IO.ExplicitIOModes, change some type signatures and expect everything to type-check.

There's one exception to this last statement: If you are using the standard handles stdin, stdout or stderr in a mode which isn't their default mode (R for stdin and W for stdout and stderr) you have to cast these handles to the expected IOMode.

Synopsis

The IO monad

data IO a

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

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

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

Instances

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

Files and handles

type FilePath = String

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.

data Handle ioMode Source

A handle to a file with an explicit IOMode.

Wraps: System.IO.Handle.

Instances

Typeable1 Handle 
Eq (Handle ioMode) 
Show (Handle ioMode) 

regularHandle :: Handle ioMode -> HandleSource

Retrieves the regular System.IO.Handle.

IO Modes

Types that represent the IOMode a Handle can be in.

data R Source

Read only.

Instances

CheckMode R 
ReadModes R 

data W Source

Write only.

Instances

CheckMode W 
WriteModes W 

data A Source

Append.

Instances

CheckMode A 
WriteModes A 

data RW Source

Read and write.

Instances

CheckMode RW 
WriteModes RW 
ReadModes RW 

Standard handles

These standard handles have concrete IOModes by default which work for the majority of cases. In the rare occasion that you know these handles have different IOModes you can cast them.

stdin :: Handle RSource

Wraps: System.IO.stdin.

stdout :: Handle WSource

Wraps: System.IO.stdout.

stderr :: Handle WSource

Wraps: System.IO.stderr.

cast :: forall anyIOMode castedIOMode. CheckMode castedIOMode => Handle anyIOMode -> IO (Maybe (Handle castedIOMode))Source

Cast the IOMode of a handle if the handle supports it.

Opening and closing files

Opening files

withFile :: FilePath -> IOMode ioMode -> (Handle ioMode -> IO α) -> IO αSource

Wraps: System.IO.withFile.

openFile :: FilePath -> IOMode ioMode -> IO (Handle ioMode)Source

Wraps: System.IO.openFile.

data IOMode ioMode whereSource

The IOMode GADT which for each constructor specifies the associated IOMode type.

Also see: System.IO.IOMode.

Instances

Eq (IOMode ioMode) 
Ord (IOMode ioMode) 
Show (IOMode ioMode) 

Closing files

hClose :: Handle ioMode -> IO ()Source

Wraps: System.IO.hClose.

Special cases

readFile :: FilePath -> IO String

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.

writeFile :: FilePath -> String -> IO ()

The computation writeFile file str function writes the string str, to the file file.

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

The computation appendFile file str function appends the string str, 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.

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

Operations on handles

Determining and changing the size of a file

hFileSize :: Handle ioMode -> IO IntegerSource

Wraps: System.IO.hFileSize.

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

Wraps: System.IO.hSetFileSize.

Detecting the end of input

hIsEOF :: ReadModes ioMode => Handle ioMode -> IO BoolSource

Wraps: System.IO.hIsEOF.

isEOF :: IO Bool

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

Buffering operations

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 System.IO.hFlush is issued, or the handle is closed.
  • block-buffering: the entire buffer is written out whenever it overflows, a System.IO.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 System.IO.hLookAhead operation implies that even a no-buffered handle may require a one-character buffer.

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

Constructors

NoBuffering

buffering is disabled if possible.

LineBuffering

line-buffering should be enabled if possible.

BlockBuffering (Maybe Int)

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

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

Wraps: System.IO.hSetBuffering.

hGetBuffering :: Handle ioMode -> IO BufferModeSource

Wraps: System.IO.hGetBuffering.

hFlush :: Handle ioMode -> IO ()Source

Wraps: System.IO.hFlush.

Repositioning handles

hGetPosn :: Handle ioMode -> IO HandlePosnSource

Wraps: System.IO.hGetPosn.

hSetPosn :: HandlePosn -> IO ()

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

This operation may fail with:

  • isPermissionError if a system resource limit would be exceeded.

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

Wraps: System.IO.hSeek.

data SeekMode

A mode that determines the effect of hSeek hdl mode i, as follows:

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 ioMode -> IO IntegerSource

Wraps: System.IO.hTell.

Handle properties

hIsOpen :: Handle ioMode -> IO BoolSource

Wraps: System.IO.hIsOpen.

hIsClosed :: Handle ioMode -> IO BoolSource

Wraps: System.IO.hIsClosed.

hIsReadable :: Handle ioMode -> IO BoolSource

Wraps: System.IO.hIsReadable.

hIsWritable :: Handle ioMode -> IO BoolSource

Wraps: System.IO.hIsWritable.

hIsSeekable :: Handle ioMode -> IO BoolSource

Wraps: System.IO.hIsSeekable.

Terminal operations (not portable: GHC/Hugs only)

hIsTerminalDevice :: Handle ioMode -> IO BoolSource

Wraps: System.IO.hIsTerminalDevice.

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

Wraps: System.IO.hSetEcho.

hGetEcho :: Handle ioMode -> IO BoolSource

Wraps: System.IO.hGetEcho.

Showing handle state (not portable: GHC only)

hShow :: Handle ioMode -> IO StringSource

Wraps: System.IO.hShow.

Text input and output

Text input

Note that the following text input operations are polymorphic in the IOMode of the given handle. However the IOModes are restricted to ReadModes only which can be either R or RW.

hWaitForInput :: ReadModes ioMode => Handle ioMode -> Int -> IO BoolSource

Wraps: System.IO.hWaitForInput.

hReady :: ReadModes ioMode => Handle ioMode -> IO BoolSource

Wraps: System.IO.hReady.

hGetChar :: ReadModes ioMode => Handle ioMode -> IO CharSource

Wraps: System.IO.hGetChar.

hGetLine :: ReadModes ioMode => Handle ioMode -> IO StringSource

Wraps: System.IO.hGetLine.

hLookAhead :: ReadModes ioMode => Handle ioMode -> IO CharSource

Wraps: System.IO.hLookAhead.

hGetContents :: ReadModes ioMode => Handle ioMode -> IO StringSource

Wraps: System.IO.hGetContents.

Text ouput

Note that the following text output operations are polymorphic in the IOMode of the given handle. However the IOModes are restricted to WriteModes only which can be either W, A or RW.

hPutChar :: WriteModes ioMode => Handle ioMode -> Char -> IO ()Source

Wraps: System.IO.hPutChar.

hPutStr :: WriteModes ioMode => Handle ioMode -> String -> IO ()Source

Wraps: System.IO.hPutStr.

hPutStrLn :: WriteModes ioMode => Handle ioMode -> String -> IO ()Source

Wraps: System.IO.hPutStrLn.

hPrint :: (WriteModes ioMode, Show a) => Handle ioMode -> a -> IO ()Source

Wraps: System.IO.hPrint.

Special cases for standard input and output

These functions are also exported by the "Prelude".

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

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

putChar :: Char -> IO ()

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

putStr :: String -> IO ()

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

putStrLn :: String -> IO ()

The same as putStr, but adds a newline character.

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

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

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

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

getChar :: IO Char

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

getLine :: IO String

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

getContents :: IO String

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

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

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

readLn :: Read a => IO a

The readLn function combines getLine and readIO.

Binary input and output

withBinaryFile :: FilePath -> IOMode ioMode -> (Handle ioMode -> IO r) -> IO rSource

Wraps: System.IO.withBinaryFile.

openBinaryFile :: FilePath -> IOMode ioMode -> IO (Handle ioMode)Source

Wraps: System.IO.openBinaryFile.

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

Wraps: System.IO.hSetBinaryMode.

hPutBuf :: WriteModes ioMode => Handle ioMode -> Ptr α -> Int -> IO ()Source

Wraps: System.IO.hPutBuf.

hGetBuf :: ReadModes ioMode => Handle ioMode -> Ptr α -> Int -> IO IntSource

Wraps: System.IO.hGetBuf.

hPutBufNonBlocking :: WriteModes ioMode => Handle ioMode -> Ptr α -> Int -> IO IntSource

Wraps: System.IO.hPutBufNonBlocking.

hGetBufNonBlocking :: ReadModes ioMode => Handle ioMode -> Ptr α -> Int -> IO IntSource

Wraps: System.IO.hGetBufNonBlocking.

Temporary files