This library provides the following extensions to the IO monad:
fixIO
, unsafePerformIO
and unsafeInterleaveIO
described in [ImperativeFP]
performGC
triggers an immediate garbage collection
trace
prints the string in its first argument, and then
returns the second argument as its result. The trace
function is not
referentially transparent, and should only be used for debugging, or for
monitoring execution.
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
module IOExts where
fixIO :: (a -> IO a) -> IO a
unsafePerformIO :: IO a -> a
unsafeInterleaveIO :: IO a -> IO a
data IORef a -- mutable variables containing values of type a
newIORef :: a -> IO (IORef a)
readIORef :: IORef a -> IO a
writeIORef :: IORef a -> a -> IO ()
instance Eq (IORef a)
data IOArray ix elt -- mutable arrays indexed by values of type ix
-- containing values of type a.
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)
instance Eq (IOArray ix elt)
performGC :: IO ()
trace :: String -> a -> a
unsafePtrEq :: a -> a -> Bool