strict-io-0.2.2: A library wrapping standard IO modules to provide strict IO.

Copyright(c) Nicolas Pouillard 2009
LicenseBSD3
MaintainerNicolas Pouillard <nicolas.pouillard@gmail.com>
Stabilityprovisional
Safe HaskellNone
LanguageHaskell98

System.IO.Strict

Contents

Description

This module wraps the functions of the System.IO module at a different type namely SIO.

The purpose of this module is to export only strict IO functions, by strict we mean strict in the result. The arguments of these functions may only by partially forced, but when the function returns, the arguments can no longer be forced by the function. When the type of the value to be forced is polymorphic, a NFData constraint is added since we (internally) use rnf to force the value. Then we rely on the behavior of NFData instances to provide the fact that any lazy argument passed to a SIO function will not leak-out after the call.

These functions do not necessarily use their arguments completely but they do not hold or return any value that could depend on these arguments. If the original functions from System.IO module were already strict, then this module just provides them at another type. Some functions from the original module are famously lazy like the getContents like functions: in this module their results are deeply forced.

In Haskell, monad operations (return and >>=) have to be lazy. Therefore the SIO monad is not completely strict (i.e. pure values can still be lazy). So in this module we expose the return' function that forces the given value before putting it into the monad.

Since this module uses the same names as System.IO, it is designed to be imported qualified.

   import System.IO.Strict (SIO)
   import qualified System.IO.Strict as SIO

Synopsis

Types

data SIO a Source #

Instances

Monad SIO Source # 

Methods

(>>=) :: SIO a -> (a -> SIO b) -> SIO b #

(>>) :: SIO a -> SIO b -> SIO b #

return :: a -> SIO a #

fail :: String -> SIO a #

Functor SIO Source # 

Methods

fmap :: (a -> b) -> SIO a -> SIO b #

(<$) :: a -> SIO b -> SIO a #

MonadFix SIO Source # 

Methods

mfix :: (a -> SIO a) -> SIO a #

Applicative SIO Source # 

Methods

pure :: a -> SIO a #

(<*>) :: SIO (a -> b) -> SIO a -> SIO b #

(*>) :: SIO a -> SIO b -> SIO b #

(<*) :: SIO a -> SIO b -> SIO a #

run :: NFData sa => SIO sa -> IO sa Source #

run allows to return to the wider world of IOs.

return' :: (Monad m, NFData sa) => sa -> m sa Source #

A stricter version of return, that works for every monad.

Functions stricter than there System.IO counterparts

getContents :: SIO String Source #

Note that getContents is stricter than its counterpart in System.IO.

hGetContents :: Handle -> SIO String Source #

Note that hGetContents is stricter than its counterpart in System.IO.

readFile :: FilePath -> SIO String Source #

Note that readFile is stricter than its counterpart in System.IO.

read :: (NFData sa, Read sa) => String -> SIO sa Source #

Note that read is stricter than its counterpart in System.IO.

readLn :: (NFData sa, Read sa) => SIO sa Source #

Note that readLn is stricter than its counterpart in System.IO.

fix :: NFData sa => (sa -> SIO sa) -> SIO sa Source #

Note that fix is stricter than its counterpart in System.IO.

withBinaryFile :: NFData sr => FilePath -> IOMode -> (Handle -> SIO sr) -> SIO sr Source #

Note that withBinaryFile is stricter than its counterpart in System.IO.

withFile :: NFData sr => FilePath -> IOMode -> (Handle -> SIO sr) -> SIO sr Source #

Note that withFile is stricter than its counterpart in System.IO.

Functions as strict as there System.IO counterparts

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

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

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