4.19. IOExts

This library is the home for miscellaneous IO-related extensions.

4.19.1. IO monad extensions

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

fixIO allows recursive IO operations to be defined. The first argument to fixIO should be a function that takes its own output as an argument (sometimes called "tying the knot").

unsafePerformIO :: IO a -> a

This is the "back door" into the IO monad, allowing IO computation to be performed at any time. For this to be safe, the IO computation should be free of side effects and independent of its environment.

If the I/O computation wrapped in unsafePerformIO performs side effects, then the relative order in which those side effects take place (relative to the main I/O trunk, or other calls to unsafePerformIO) is indeterminate.

However, it is less well known that unsafePerformIO is not type safe. For example:
test :: IORef [a]
test = unsafePerformIO $ newIORef []

main = do
        writeIORef test [42]
        bang <- readIORef test
        print (bang :: [Char])
This program will core dump. This problem with polymorphic references is well known in the ML community, and does not arise with normal monadic use of references. There is no easy way to make it impossible once you use unsafePerformIO. Indeed, it is possible to write coerce :: a -> b with the help of unsafePerformIO. So be careful!

unsafeInterleaveIO :: IO a -> IO a

unsafeInterleaveIO allows IO computation to be deferred lazily. When passed a value of type IO a, the IO will only be performed when the value of the a is demanded. This is used to implement lazy file reading, see IO.hGetContents.

4.19.2. Mutable Variables

data IORef      -- instance of: Eq
newIORef        :: a -> IO (IORef a)
readIORef       :: IORef a -> IO a
writeIORef      :: IORef a -> a -> IO ()
modifyIORef     :: IORef a -> (a -> a) -> IO ()
mkWeakIORef     :: IORef a -> IO () -> IO (Weak (IORef a))

-- deprecated, use modifyIORef
updateIORef     :: IORef a -> (a -> a) -> IO ()

4.19.3. Mutable Arrays

data IOArray          -- instance of: Eq
newIOArray            :: Ix ix => (ix,ix) -> elt -> IO (IOArray ix elt)
boundsIOArray       :: Ix ix => IOArray ix elt -> (ix, ix)
readIOArray         :: Ix ix => IOArray ix elt -> ix -> IO elt
writeIOArray        :: Ix ix => IOArray ix elt -> ix -> elt -> IO ()
freezeIOArray       :: Ix ix => IOArray ix elt -> IO (Array ix elt)
thawIOArray         :: Ix ix => Array ix elt -> IO (IOArray ix elt)
unsafeFreezeIOArray :: Ix ix => IOArray ix elt -> IO (Array ix elt)
unsafeThawIOArray   :: Ix ix => Array ix elt -> IO (IOArray ix elt)

Note: unsafeFreezeIOArray and unsafeThawIOArray are not provided by Hugs.

4.19.4. Extended file modes

  data IOModeEx 
   = BinaryMode IOMode
   | TextMode   IOMode
     deriving (Eq, Read, Show)

  openFileEx         :: FilePath -> IOModeEx -> IO Handle
  hSetBinaryMode     :: Handle -> Bool -> IO Bool

openFileEx extends the standard openFile action with support for opening binary files.

4.19.5. Bulk transfers

  hGetBuf       :: Handle -> Addr -> Int -> IO Int
  hGetBufFull   :: Handle -> Addr -> Int -> IO Int

  hPutBuf       :: Handle -> Addr -> Int -> IO Int
  hPutBufFull   :: Handle -> Addr -> Int -> IO ()

These functions read and write chunks of data to/from a handle. The versions without a Full suffix may return early if the request would have blocked; in this case they will return the number of characters actually transfered. The versions with a Full suffix will return only when either the full buffer has been transfered, or the end of file is reached (in the case of hGetBufFull.

If the end of file is reached when reading, then the operation will return a short read, and hIsEof will henceforthe return True for the handle. It isn't possible to tell whether the end of file is reached using hGetBuf alone, because a short read may indicate blocking.

  hGetBufBA     :: Handle -> MutableByteArray RealWorld a -> Int -> IO Int
  hGetBufBAFull :: Handle -> MutableByteArray RealWorld a -> Int -> IO Int

  hPutBufBA     :: Handle -> MutableByteArray RealWorld a -> Int -> IO ()
  hPutBufBAFull :: Handle -> MutableByteArray RealWorld a -> Int -> IO ()

These (GHC-only) functions mirror the previous set of functions, but operate on MutableByteArrays instead of Addrs. This may be more convenient and/or faster, depending on the circumstances.

4.19.6. Terminal control

  hIsTerminalDevice :: Handle -> IO Bool
  hSetEcho          :: Handle -> Bool -> IO ()
  hGetEcho          :: Handle -> IO Bool

4.19.7. Redirecting handles

  withHandleFor :: Handle -> Handle -> IO a -> IO a
  withStdout    :: Handle -> IO a -> IO a
  withStdin     :: Handle -> IO a -> IO a
  withStderr    :: Handle -> IO a -> IO a

4.19.8. Trace

trace :: String -> a -> a

When called, trace prints the string in its first argument to standard error, before returning the second argument as its result. The trace function is not referentially transparent, and should only be used for debugging, or for monitoring execution. Some implementations of trace may decorate the string that's output to indicate that you're tracing.

trace is implemented using unsafePerformIO.

4.19.9. Extra IOError Predicates

The IO module provides several predicates over the IOError type, such as isEOFError, isDoesNotExistError, and so on. Here we define an extended set of these predicates, taking into account more types of error:

  isHardwareFault	   :: IOError -> Bool
  isInappropriateType	   :: IOError -> Bool
  isInterrupted		   :: IOError -> Bool
  isInvalidArgument	   :: IOError -> Bool
  isOtherError		   :: IOError -> Bool
  isProtocolError	   :: IOError -> Bool
  isResourceVanished	   :: IOError -> Bool
  isSystemError		   :: IOError -> Bool
  isTimeExpired		   :: IOError -> Bool
  isUnsatisfiedConstraints :: IOError -> Bool
  isUnsupportedOperation   :: IOError -> Bool
  isComError               :: IOError -> Bool  -- Win32 only

4.19.10. Miscellany

  unsafePtrEq            :: a -> a -> Bool
  slurpFile              :: FilePath -> IO (Addr, Int)
  hConnectTo             :: Handle -> Handle -> IO ()
  performGC              :: IO ()
  freeHaskellFunctionPtr :: Addr -> IO ()

performGC triggers an immediate garbage collection

unsafePtrEq compares two values for pointer equality without evaluating them. The results are not referentially transparent and may vary significantly from one compiler to another or in the face of semantics-preserving program changes. However, pointer equality is useful in creating a number of referentially transparent constructs such as this simplified memoisation function:
> cache :: (a -> b) -> (a -> b)
> cache f = \x -> unsafePerformIO (check x)
>  where
>   ref = unsafePerformIO (newIORef (error "cache", error "cache"))
>   check x = readIORef ref >>= \ (x',a) ->
>          if x `unsafePtrEq` x' then
>            return a
>          else
>            let a = f x in
>            writeIORef ref (x, a) >>
>            return a