safer-file-handles-0.3.0.1: Type-safe file handlingSource codeContentsIndex
System.IO.SaferFileHandles
MaintainerBas van Dijk <v.dijk.bas@gmail.com>
Contents
Files with explicit IO modes as scarce resources
IO Modes
Opening files in a region
Standard handles
Operations on regional file 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
Unicode encoding/decoding
Unicode encodings
Newline conversion
Description

This module provides the type File which represents an actual file. A file is a scarce resource, that is, in certain IOModes it can only be used by one user at a time. Because of the scarcity, a file needs to be opened to grant temporary sole access to the file. When the file is no longer needed it should be closed a.s.a.p to grant others access to the file.

The contributions of this module are as follows:

  • First of all this module provides an instance for Resource for File which allows it to be used with the regions package. The regions package provides the region monad transformer RegionT. Scarce resources, like files for example, can be opened in a region. When the region terminates, all opened resources will be automatically closed. The main advantage of regions is that the handles to the opened resources can not be returned from the region which ensures no I/O with closed resources is possible. The primary technique used in regions is called "Lightweight monadic regions" which was invented by Oleg Kiselyov and Chung-chieh Shan. See: http://okmij.org/ftp/Haskell/regions.html#light-weight
  • Secondly this module provides all the file operations of System.IO lifted to the region monad.
  • The final contribution of this module is that file handles are parameterised with the IOMode in which the file was opened. This can be either R, W, A or RW. All operations on files explicitly specify the needed IOMode using the ReadModes and WriteModes type classes. This way it is impossible to read from a write-only handle or write to a read-only handle for example.

See the safer-file-handles-examples package for examples how to use this package:

darcs get http://code.haskell.org/~basvandijk/code/safer-file-handles-examples

Note that this package is early work and still very experimental. Take note of the following warnings:

  • WARNING: You are able to lift an arbitrary IO action into a region. This action may throw an IOError which may contain a low-level handle to a file. This handle can be retrieved from the IOError using ioeGetHandle from System.IO.Error. So when an IOError is thrown you will be able to manually close the respected file! This will defeat the safety-guarantees that this package promises to provide. TODO: Think about how to solve this... The solution that Oleg provides in his paper is to filter out the low-level handle in an IOError when it's thrown. I can't easily do this because I have to modify the catch method of the MonadCatchIO instance for RegionT in the regions package. It feels like an ugly hack to solve this safer-file-handles specific problem in the independent general regions package.
  • WARNING: Currenly the handling of the standard files (stdin, stdout and stderr) is not to my liking. See the documentation for details.
  • NOTE: This module also provides functions from System.IO which don't directly work with file handles like putStrLn or getLine for example. These functions implicitly use the standard handles. I actually provide more general versions of these that work in any MonadIO. It could be argued that these functions don't belong in this module because they don't have anything to do with regions and explicit IOModes. However I provide them as a convenience. But be warned that in the future these lifted functions may move to their own package!
Synopsis
data File ioMode where
File :: Binary -> FilePath -> IOMode ioMode -> File ioMode
TempFile :: Binary -> FilePath -> Template -> DefaultPermissions -> File RW
Std :: Standard ioMode -> File ioMode
type Binary = Bool
data Standard ioMode where
In :: Standard R
Out :: Standard W
Err :: Standard W
type FilePath = String
data R
data W
data A
data RW
class ReadModes ioMode
class WriteModes ioMode
module Control.Monad.Trans.Region
type RegionalFileHandle ioMode r = RegionalHandle (File ioMode) r
openFile :: MonadCatchIO pr => FilePath -> IOMode ioMode -> RegionT s pr (RegionalFileHandle ioMode (RegionT s pr))
withFile :: MonadCatchIO pr => FilePath -> IOMode ioMode -> (forall s. RegionalFileHandle ioMode (RegionT s pr) -> RegionT s pr α) -> pr α
data IOMode ioMode where
ReadMode :: IOMode R
WriteMode :: IOMode W
AppendMode :: IOMode A
ReadWriteMode :: IOMode RW
stdin :: MonadCatchIO pr => RegionT s pr (RegionalFileHandle R (RegionT s pr))
stdout :: MonadCatchIO pr => RegionT s pr (RegionalFileHandle W (RegionT s pr))
stderr :: MonadCatchIO pr => RegionT s pr (RegionalFileHandle W (RegionT s pr))
hFileSize :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr Integer
hSetFileSize :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> Integer -> cr ()
hIsEOF :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> cr Bool
isEOF :: MonadIO m => m Bool
data BufferMode
= NoBuffering
| LineBuffering
| BlockBuffering (Maybe Int)
hSetBuffering :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> BufferMode -> cr ()
hGetBuffering :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr BufferMode
hFlush :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr ()
hGetPosn :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr HandlePosn
hSetPosn :: MonadIO m => HandlePosn -> m ()
data HandlePosn
hSeek :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> SeekMode -> Integer -> cr ()
data SeekMode
= AbsoluteSeek
| RelativeSeek
| SeekFromEnd
hTell :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr Integer
hIsOpen :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr Bool
hIsClosed :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr Bool
hIsReadable :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr Bool
hIsWritable :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr Bool
hIsSeekable :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr Bool
hIsTerminalDevice :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr Bool
hSetEcho :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> Bool -> cr ()
hGetEcho :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr Bool
hShow :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr String
hWaitForInput :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> Int -> cr Bool
hReady :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> cr Bool
hGetChar :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> cr Char
hGetLine :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> cr String
hLookAhead :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> cr Char
hGetContents :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> cr String
hPutChar :: (ParentOf pr cr, MonadIO cr, WriteModes ioMode) => RegionalFileHandle ioMode pr -> Char -> cr ()
hPutStr :: (ParentOf pr cr, MonadIO cr, WriteModes ioMode) => RegionalFileHandle ioMode pr -> String -> cr ()
hPutStrLn :: (ParentOf pr cr, MonadIO cr, WriteModes ioMode) => RegionalFileHandle ioMode pr -> String -> cr ()
hPrint :: (ParentOf pr cr, MonadIO cr, WriteModes ioMode, Show α) => RegionalFileHandle ioMode pr -> α -> cr ()
interact :: MonadIO m => (String -> String) -> m ()
putChar :: MonadIO m => Char -> m ()
putStr :: MonadIO m => String -> m ()
putStrLn :: MonadIO m => String -> m ()
print :: (MonadIO m, Show α) => α -> m ()
getChar :: MonadIO m => m Char
getLine :: MonadIO m => m String
getContents :: MonadIO m => m String
readIO :: (MonadIO m, Read α) => String -> m α
readLn :: (MonadIO m, Read α) => m α
withBinaryFile :: MonadCatchIO pr => FilePath -> IOMode ioMode -> (forall s. RegionalFileHandle ioMode (RegionT s pr) -> RegionT s pr α) -> pr α
openBinaryFile :: MonadCatchIO pr => FilePath -> IOMode ioMode -> RegionT s pr (RegionalFileHandle ioMode (RegionT s pr))
hSetBinaryMode :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> Bool -> cr ()
hPutBuf :: (ParentOf pr cr, MonadIO cr, WriteModes ioMode) => RegionalFileHandle ioMode pr -> Ptr α -> Int -> cr ()
hGetBuf :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> Ptr α -> Int -> cr Int
hPutBufNonBlocking :: (ParentOf pr cr, MonadIO cr, WriteModes ioMode) => RegionalFileHandle ioMode pr -> Ptr α -> Int -> cr Int
hGetBufNonBlocking :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> Ptr α -> Int -> cr Int
type DefaultPermissions = Bool
type Template = String
openTempFile :: MonadCatchIO pr => FilePath -> Template -> RegionT s pr (FilePath, RegionalFileHandle RW (RegionT s pr))
openBinaryTempFile :: MonadCatchIO pr => FilePath -> Template -> RegionT s pr (FilePath, RegionalFileHandle RW (RegionT s pr))
openTempFileWithDefaultPermissions :: MonadCatchIO pr => FilePath -> Template -> RegionT s pr (FilePath, RegionalFileHandle RW (RegionT s pr))
openBinaryTempFileWithDefaultPermissions :: MonadCatchIO pr => FilePath -> Template -> RegionT s pr (FilePath, RegionalFileHandle RW (RegionT s pr))
hSetEncoding :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> TextEncoding -> cr ()
hGetEncoding :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr (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
mkTextEncoding :: MonadIO m => String -> m TextEncoding
hSetNewlineMode :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> NewlineMode -> cr ()
data Newline
= LF
| CRLF
nativeNewline :: Newline
data NewlineMode = NewlineMode {
inputNL :: Newline
outputNL :: Newline
}
noNewlineTranslation :: NewlineMode
universalNewlineMode :: NewlineMode
nativeNewlineMode :: NewlineMode
Files with explicit IO modes as scarce resources
data File ioMode whereSource

A file scarce resource parameterized by the IOMode in which you want to open the file.

Note that this module provides an instance for Resource for File ioMode. This allows you to open files in a region which are automatically closed when the region terminates but it disallows you to return handles to these closed files from the region so preventing I/O with closed files.

Constructors
File :: Binary -> FilePath -> IOMode ioMode -> File ioMode
TempFile :: Binary -> FilePath -> Template -> DefaultPermissions -> File RW
Std :: Standard ioMode -> File ioMode
show/hide Instances
Resource (File ioMode)
type Binary = BoolSource
Should the file be opened in binary mode?
data Standard ioMode whereSource
The standard files parameterized by concrete IOModes which work for the majority of cases.
Constructors
In :: Standard R
Out :: Standard W
Err :: Standard W
type FilePath = StringSource
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.
IO Modes
Types that represent the IOMode an opened file can be in.
data R Source
Read only.
show/hide Instances
data W Source
Write only.
show/hide Instances
data A Source
Write only by appending.
show/hide Instances
data RW Source
Both read and write.
show/hide Instances
class ReadModes ioMode Source
Class of readable IO mode types.
show/hide Instances
class WriteModes ioMode Source
Class of writable IO mode types.
show/hide Instances
Opening files in a region

Note that this module re-exports the Control.Monad.Trans.Region module from the regions package which allows you to:

module Control.Monad.Trans.Region
type RegionalFileHandle ioMode r = RegionalHandle (File ioMode) rSource
A handy type synonym for a regional handle to an opened file parameterized by the IOMode in which you opened the file and the region in which it was created.
openFile :: MonadCatchIO pr => FilePath -> IOMode ioMode -> RegionT s pr (RegionalFileHandle ioMode (RegionT s pr))Source

Convenience function for opening a file which yields a regional handle to it. This provides a safer replacement for System.IO.openFile.

Note that: openFile filePath ioMode = open $ File False filePath ioMode.

Note that the returned regional file handle is parameterized by the region in which it was created. This ensures that handles can never escape their region. And it also allows operations on handles to be executed in a child region of the region in which the handle was created.

Note that if you do wish to return a handle from the region in which it was created you have to duplicate the handle by applying dup to it.

withFile :: MonadCatchIO pr => FilePath -> IOMode ioMode -> (forall s. RegionalFileHandle ioMode (RegionT s pr) -> RegionT s pr α) -> pr αSource

Convenience function which opens a file, applies the given continuation function to the resulting regional file handle and runs the resulting region. This provides a safer safer replacement for System.IO.withFile.

Note that: withFile filePath ioMode = with $ File False filePath ioMode.

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)
Standard handles

WARNING: I'm not satisfied with my current implementation of the standard handles (stdin, stdout and stderr)! Currently the standard handles are regional computations that return the regional file handles to the respected standard handles. There are 4 problems with this approach:

  • When the region terminates in which you call one of the standard handles the respected handle will be closed. I think this is not the expected behaviour. I would expect the standard handles to always remain open.
  • In System.IO the standard handles are pure values. My standard handles are monadic computations which makes them harder to work with.
  • There is no way to explicitly close a standard handle. Indeed, the whole purpose of lightweight monadic regions is to automatically close handles. However, when writing a Unix daemon for example, you need to be able to explicitly close the standard handles.
  • When reading 'man stdin' I'm confused if the standard handles are always open on program startup:

quote 'man stdin':

"...Under normal circumstances every Unix program has three streams opened for it when it starts up, one for input, one for output, and one for printing diagnostic or error messages..."

"...The stdin, stdout, and stderr macros conform to C89 and this standard also stipulates that these three streams shall be open at program startup...."

So now I'm confused... are these standard file handles always open on program startup or are there abnormal situations when they are closed?

Maybe I just have to believe the documentation in System.IO which specifies that they are always initially open.

If the standard handles are closed on startup using a handle returned from one of the standard handles will result in an exception! This would be a violation of my safety guarantees which is unacceptable.

Does anyone have a solution?

stdin :: MonadCatchIO pr => RegionT s pr (RegionalFileHandle R (RegionT s pr))Source

Convenience function for returning a regional handle to standard input. This provides a safer replacement for System.IO.stdin.

Note that: stdin = open $ Std In.

stdout :: MonadCatchIO pr => RegionT s pr (RegionalFileHandle W (RegionT s pr))Source

Convenience function for returning a regional handle to standard output. This provides a safer replacement for System.IO.stdout.

Note that: stdin = open $ Std Out.

stderr :: MonadCatchIO pr => RegionT s pr (RegionalFileHandle W (RegionT s pr))Source

Convenience function for returning a regional handle to standard error. This provides a safer replacement for System.IO.stderr.

Note that: stdin = open $ Std Err.

TODO:

The 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 should be able to cast them to the expected IOMode.

The explicit-iomodes package defines this cast function. I should also define it here:

cast :: forall anyIOMode castedIOMode
     . (pr `ParentOf` cr, LiftIO cr, CheckMode castedIOMode)
     => RegionalFileHandle anyIOMode pr
     -> cr (Maybe (RegionalFileHandle castedIOMode pr))

However I'm not sure yet how to implement it...

Operations on regional file handles
Determining and changing the size of a file
hFileSize :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr IntegerSource
Wraps System.IO.hFileSize.
hSetFileSize :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> Integer -> cr ()Source
Wraps System.IO.hSetFileSize.
Detecting the end of input
hIsEOF :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> cr BoolSource
Wraps System.IO.hIsEOF.
isEOF :: MonadIO m => m BoolSource
Wraps System.IO.isEOF.
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 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
NoBufferingbuffering is disabled if possible.
LineBufferingline-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.
show/hide Instances
hSetBuffering :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> BufferMode -> cr ()Source
Wraps System.IO.hSetBuffering.
hGetBuffering :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr BufferModeSource
Wraps System.IO.hGetBuffering.
hFlush :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr ()Source
Wraps System.IO.hFlush.
Repositioning handles
hGetPosn :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr HandlePosnSource
Wraps System.IO.hGetPosn.
hSetPosn :: MonadIO m => HandlePosn -> m ()Source
Wraps System.IO.hSetPosn.
data HandlePosn Source
show/hide Instances
hSeek :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> SeekMode -> Integer -> cr ()Source
Wraps System.IO.hSeek.
data SeekMode Source
A mode that determines the effect of hSeek hdl mode i, as follows:
Constructors
AbsoluteSeekthe position of hdl is set to i.
RelativeSeekthe position of hdl is set to offset i from the current position.
SeekFromEndthe position of hdl is set to offset i from the end of the file.
show/hide Instances
hTell :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr IntegerSource
Wraps System.IO.hTell.
Handle properties
hIsOpen :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr BoolSource
Wraps System.IO.hIsOpen.
hIsClosed :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr BoolSource
Wraps System.IO.hIsClosed.
hIsReadable :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr BoolSource
Wraps System.IO.hIsReadable.
hIsWritable :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr BoolSource
Wraps System.IO.hIsWritable.
hIsSeekable :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr BoolSource
Wraps System.IO.hIsSeekable.
Terminal operations (not portable: GHC/Hugs only)
hIsTerminalDevice :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr BoolSource
Wraps System.IO.hIsTerminalDevice.
hSetEcho :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> Bool -> cr ()Source
Wraps System.IO.hSetEcho.
hGetEcho :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr BoolSource
Wraps System.IO.hGetEcho.
Showing handle state (not portable: GHC only)
hShow :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr 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 :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> Int -> cr BoolSource
Wraps System.IO.hWaitForInput.
hReady :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> cr BoolSource
Wraps System.IO.hReady.
hGetChar :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> cr CharSource
Wraps System.IO.hGetChar.
hGetLine :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> cr StringSource
Wraps System.IO.hGetLine.
hLookAhead :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> cr CharSource
Wraps System.IO.hLookAhead.
hGetContents :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> cr 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 :: (ParentOf pr cr, MonadIO cr, WriteModes ioMode) => RegionalFileHandle ioMode pr -> Char -> cr ()Source
Wraps System.IO.hPutChar.
hPutStr :: (ParentOf pr cr, MonadIO cr, WriteModes ioMode) => RegionalFileHandle ioMode pr -> String -> cr ()Source
Wraps System.IO.hPutStr.
hPutStrLn :: (ParentOf pr cr, MonadIO cr, WriteModes ioMode) => RegionalFileHandle ioMode pr -> String -> cr ()Source
Wraps System.IO.hPutStrLn.
hPrint :: (ParentOf pr cr, MonadIO cr, WriteModes ioMode, Show α) => RegionalFileHandle ioMode pr -> α -> cr ()Source
Wraps System.IO.hPrint.
Special cases for standard input and output
interact :: MonadIO m => (String -> String) -> m ()Source
Generalizes System.IO.interact to any MonadIO.
putChar :: MonadIO m => Char -> m ()Source
Generalizes System.IO.putChar to any MonadIO.
putStr :: MonadIO m => String -> m ()Source
Generalizes System.IO.putStr to any MonadIO.
putStrLn :: MonadIO m => String -> m ()Source
Generalizes System.IO.putStrLn to any MonadIO.
print :: (MonadIO m, Show α) => α -> m ()Source
Generalizes System.IO.print to any MonadIO.
getChar :: MonadIO m => m CharSource
Generalizes System.IO.getChar to any MonadIO.
getLine :: MonadIO m => m StringSource
Generalizes System.IO.getLine to any MonadIO.
getContents :: MonadIO m => m StringSource
Generalizes System.IO.getContents to any MonadIO.
readIO :: (MonadIO m, Read α) => String -> m αSource
Generalizes System.IO.readIO to any MonadIO.
readLn :: (MonadIO m, Read α) => m αSource
Generalizes System.IO.readLn to any MonadIO.
Binary input and output
withBinaryFile :: MonadCatchIO pr => FilePath -> IOMode ioMode -> (forall s. RegionalFileHandle ioMode (RegionT s pr) -> RegionT s pr α) -> pr αSource

A convenience function which opens a file in binary mode, applies the given continuation function to the resulting regional file handle and runs the resulting region. This provides a safer replacement for System.IO.withBinaryFile.

Note that: withBinaryFile filePath ioMode = with $ File True filePath ioMode.

openBinaryFile :: MonadCatchIO pr => FilePath -> IOMode ioMode -> RegionT s pr (RegionalFileHandle ioMode (RegionT s pr))Source

Convenience function whichs opens a file in binary mode yielding a regional handle to it. This provides a safer replacement for System.IO.openBinaryFile.

Note that: openBinaryFile filePath ioMode = open $ File True filePath ioMode.

hSetBinaryMode :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> Bool -> cr ()Source
Wraps System.IO.hSetBinaryMode.
hPutBuf :: (ParentOf pr cr, MonadIO cr, WriteModes ioMode) => RegionalFileHandle ioMode pr -> Ptr α -> Int -> cr ()Source
Wraps System.IO.hPutBuf.
hGetBuf :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> Ptr α -> Int -> cr IntSource
Wraps System.IO.hGetBuf.
hPutBufNonBlocking :: (ParentOf pr cr, MonadIO cr, WriteModes ioMode) => RegionalFileHandle ioMode pr -> Ptr α -> Int -> cr IntSource
Wraps System.IO.hPutBufNonBlocking.
hGetBufNonBlocking :: (ParentOf pr cr, MonadIO cr, ReadModes ioMode) => RegionalFileHandle ioMode pr -> Ptr α -> Int -> cr IntSource
Wraps System.IO.hGetBufNonBlocking.
Temporary files
type DefaultPermissions = BoolSource
Should default permissions be used when opening a temporary file?
type Template = StringSource
The template of a temporary file path.
openTempFile :: MonadCatchIO pr => FilePath -> Template -> RegionT s pr (FilePath, RegionalFileHandle RW (RegionT s pr))Source
Open a temporary file yielding a regional handle to it paired with the generated file path. This provides a safer replacement for System.IO.openTempFile.
openBinaryTempFile :: MonadCatchIO pr => FilePath -> Template -> RegionT s pr (FilePath, RegionalFileHandle RW (RegionT s pr))Source
Open a temporary file in binary mode yielding a regional handle to it paired with the generated file path. This provides a safer replacement for System.IO.openBinaryTempFile.
openTempFileWithDefaultPermissions :: MonadCatchIO pr => FilePath -> Template -> RegionT s pr (FilePath, RegionalFileHandle RW (RegionT s pr))Source
Open a temporary file with default permissions yielding a regional handle to it paired with the generated file path. This provides a safer replacement for System.IO.openTempFileWithDefaultPermissions.
openBinaryTempFileWithDefaultPermissions :: MonadCatchIO pr => FilePath -> Template -> RegionT s pr (FilePath, RegionalFileHandle RW (RegionT s pr))Source
Open a temporary file in binary mode with default permissions yielding a regional handle to it paired with the generated file path. This provides a safer replacement for System.IO.openBinaryTempFileWithDefaultPermissions.
Unicode encoding/decoding
hSetEncoding :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> TextEncoding -> cr ()Source
Wraps System.IO.hSetEncoding.
hGetEncoding :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> cr (Maybe TextEncoding)Source
Wraps System.IO.hGetEncoding.
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.

latin1 :: TextEncodingSource
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 :: TextEncodingSource
The UTF-8 Unicode encoding
utf8_bom :: TextEncodingSource

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 :: TextEncodingSource
The UTF-16 Unicode encoding (a byte-order-mark should be used to indicate endianness).
utf16le :: TextEncodingSource
The UTF-16 Unicode encoding (litte-endian)
utf16be :: TextEncodingSource
The UTF-16 Unicode encoding (big-endian)
utf32 :: TextEncodingSource
The UTF-32 Unicode encoding (a byte-order-mark should be used to indicate endianness).
utf32le :: TextEncodingSource
The UTF-32 Unicode encoding (litte-endian)
utf32be :: TextEncodingSource
The UTF-32 Unicode encoding (big-endian)
localeEncoding :: TextEncodingSource
The Unicode encoding of the current locale
mkTextEncoding :: MonadIO m => String -> m TextEncodingSource
Generalizes System.IO.mkTextEncoding to any MonadIO.
Newline conversion
hSetNewlineMode :: (ParentOf pr cr, MonadIO cr) => RegionalFileHandle ioMode pr -> NewlineMode -> cr ()Source
Wraps System.IO.hSetNewlineMode.
data Newline Source
The representation of a newline in the external file or stream.
Constructors
LF'\n'
CRLF'\r\n'
show/hide Instances
nativeNewline :: NewlineSource
The native newline representation for the current platform: LF on Unix systems, CRLF on Windows.
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.
Constructors
NewlineMode
inputNL :: Newlinethe representation of newlines on input
outputNL :: Newlinethe representation of newlines on output
show/hide Instances
noNewlineTranslation :: NewlineModeSource

Do no newline translation at all.

noNewlineTranslation = NewlineMode { inputNL = LF, outputNL = LF }
universalNewlineMode :: NewlineModeSource

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 :: NewlineModeSource

Use the native newline representation on both input and output

nativeNewlineMode = NewlineMode { inputNL = nativeNewline outputNL = nativeNewline }
Produced by Haddock version 2.6.0