explicit-iomodes-0.1: File handles with explicit IOModesSource codeContentsIndex
System.IO.ExplicitIOModes
MaintainerBas van Dijk <v.dijk.bas@gmail.com>
Contents
The IO monad
Files and handles
IO Modes
Standard handles
Opening and closing files
Opening files
Closing files
Special cases
Operations on handles
Determining and changing the size of a file
Detecting the end of input
Buffering operations
Repositioning handles
Handle properties
Terminal operations (not portable: GHC/Hugs only)
Showing handle state (not portable: GHC only)
Text input and output
Text input
Text ouput
Special cases for standard input and output
Binary input and output
Temporary files
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
IO (IO)
fixIO
FilePath
data Handle ioMode
data R
data W
data A
data RW
stdin :: Handle R
stdout :: Handle W
stderr :: Handle W
cast :: forall anyIOMode castedIOMode. CheckMode castedIOMode => Handle anyIOMode -> IO (Maybe (Handle castedIOMode))
withFile :: FilePath -> IOMode ioMode -> (Handle ioMode -> IO r) -> IO r
openFile :: FilePath -> IOMode ioMode -> IO (Handle ioMode)
data IOMode ioMode where
ReadMode :: IOMode R
WriteMode :: IOMode W
AppendMode :: IOMode A
ReadWriteMode :: IOMode RW
hClose :: Handle ioMode -> IO ()
readFile
writeFile
appendFile
hFileSize :: Handle ioMode -> IO Integer
hSetFileSize :: Handle ioMode -> Integer -> IO ()
hIsEOF :: ReadModes ioMode => Handle ioMode -> IO Bool
BufferMode (NoBuffering, LineBuffering, BlockBuffering)
hSetBuffering :: Handle ioMode -> BufferMode -> IO ()
hGetBuffering :: Handle ioMode -> IO BufferMode
hFlush :: Handle ioMode -> IO ()
hGetPosn :: Handle ioMode -> IO HandlePosn
hSetPosn
HandlePosn (HandlePosn)
hSeek :: Handle ioMode -> SeekMode -> Integer -> IO ()
SeekMode (AbsoluteSeek, RelativeSeek, SeekFromEnd)
hTell :: Handle ioMode -> IO Integer
hIsOpen :: Handle ioMode -> IO Bool
hIsClosed :: Handle ioMode -> IO Bool
hIsReadable :: Handle ioMode -> IO Bool
hIsWritable :: Handle ioMode -> IO Bool
hIsSeekable :: Handle ioMode -> IO Bool
hIsTerminalDevice :: Handle ioMode -> IO Bool
hSetEcho :: Handle ioMode -> Bool -> IO ()
hGetEcho :: Handle ioMode -> IO Bool
hShow :: Handle ioMode -> IO String
hWaitForInput :: ReadModes ioMode => Handle ioMode -> Int -> IO Bool
hReady :: ReadModes ioMode => Handle ioMode -> IO Bool
hGetChar :: ReadModes ioMode => Handle ioMode -> IO Char
hGetLine :: ReadModes ioMode => Handle ioMode -> IO String
hLookAhead :: ReadModes ioMode => Handle ioMode -> IO Char
hGetContents :: ReadModes ioMode => Handle ioMode -> IO String
hPutChar :: WriteModes ioMode => Handle ioMode -> Char -> IO ()
hPutStr :: WriteModes ioMode => Handle ioMode -> String -> IO ()
hPutStrLn :: WriteModes ioMode => Handle ioMode -> String -> IO ()
hPrint :: (WriteModes ioMode, Show a) => Handle ioMode -> a -> IO ()
interact
putChar
putStr
putStrLn
print
getChar
getLine
getContents
readIO
readLn
withBinaryFile :: FilePath -> IOMode ioMode -> (Handle ioMode -> IO r) -> IO r
openBinaryFile :: FilePath -> IOMode ioMode -> IO (Handle ioMode)
hSetBinaryMode :: Handle ioMode -> Bool -> IO ()
hPutBuf :: WriteModes ioMode => Handle ioMode -> Ptr a -> Int -> IO ()
hGetBuf :: ReadModes ioMode => Handle ioMode -> Ptr a -> Int -> IO Int
hPutBufNonBlocking :: WriteModes ioMode => Handle ioMode -> Ptr a -> Int -> IO Int
hGetBufNonBlocking :: ReadModes ioMode => Handle ioMode -> Ptr a -> Int -> IO Int
openTempFile :: FilePath -> String -> IO (FilePath, Handle RW)
openBinaryTempFile :: FilePath -> String -> IO (FilePath, Handle RW)
The IO monad
IO (IO)
fixIO
Files and handles
FilePath
data Handle ioMode Source

A handle to a file with an explicit IOMode.

Wraps: System.IO.Handle.

show/hide Instances
IO Modes
Types that represent the IOMode a Handle can be in.
data R Source
Read only.
show/hide Instances
CheckMode R
ReadModes R
data W Source
Write only.
show/hide Instances
CheckMode W
WriteModes W
data A Source
Append.
show/hide Instances
CheckMode A
WriteModes A
data RW Source
Read and write.
show/hide 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 r) -> IO rSource
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.

Constructors
ReadMode :: IOMode R
WriteMode :: IOMode W
AppendMode :: IOMode A
ReadWriteMode :: IOMode RW
show/hide Instances
Eq (IOMode ioMode)
Ord (IOMode ioMode)
Show (IOMode ioMode)
Closing files
hClose :: Handle ioMode -> IO ()Source
Wraps: System.IO.hClose.
Special cases
readFile
writeFile
appendFile
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.
Buffering operations
BufferMode (NoBuffering, LineBuffering, BlockBuffering)
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 (HandlePosn)
hSeek :: Handle ioMode -> SeekMode -> Integer -> IO ()Source
Wraps: System.IO.hSeek.
SeekMode (AbsoluteSeek, RelativeSeek, SeekFromEnd)
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
putChar
putStr
putStrLn
print
getChar
getLine
getContents
readIO
readLn
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 a -> Int -> IO ()Source
Wraps: System.IO.hPutBuf.
hGetBuf :: ReadModes ioMode => Handle ioMode -> Ptr a -> Int -> IO IntSource
Wraps: System.IO.hGetBuf.
hPutBufNonBlocking :: WriteModes ioMode => Handle ioMode -> Ptr a -> Int -> IO IntSource
Wraps: System.IO.hPutBufNonBlocking.
hGetBufNonBlocking :: ReadModes ioMode => Handle ioMode -> Ptr a -> Int -> IO IntSource
Wraps: System.IO.hGetBufNonBlocking.
Temporary files
openTempFile :: FilePath -> String -> IO (FilePath, Handle RW)Source
Wraps: System.IO.openTempFile.
openBinaryTempFile :: FilePath -> String -> IO (FilePath, Handle RW)Source
Wraps: System.IO.openBinaryTempFile.
Produced by Haddock version 2.4.2