[Haskell-cafe] Safe top-level IORefs

Roberto Zunino zunino at di.unipi.it
Sun Mar 4 16:28:32 EST 2007


I'm posting the code of a module, IORefs, allowing top-level IORefs to
be safely declared and used. Usafety reports are welcome. Tested in GHC 6.6.

** Features:

1) IORef a provided for any Typeable a
2) An unbounded number of IORef's can be declared
3) An IORef declaration is 3 lines long (+ optional type signature)
4) Each IORef has its own starting value
5) Referential transparency:
   no NOINLINE, no unsafePerformIO is needed in the user module
6) Negligible overhead: O(1) in the usual usage pattern
   (neglecting a O(log n) setup phase)

** Usage:

import Data.Typeable
import Data.IORef
import IORefs

data X deriving Typeable  -- the actual name of the IORef
instance IORefDefault X Int where ioRefDefault _ = 42 -- type+default
x = ioRef (undefined :: X) -- a convenient name for the IORef

x :: IORef Int -- optional signature

-- Still the same IORef as x !
y :: IORef Int
y = ioRef (undefined :: X)

main = do
       let printX = readIORef x >>= print
       printX -- 42
       writeIORef x 3
       printX -- 3
       modifyIORef x succ
       printX -- 4
       modifyIORef y succ  -- y is equal to x, so...
       printX -- 5
       -- ... the above is actually equivalent to
       modifyIORef (ioRef (undefined :: X) :: IORef Int) succ
       printX -- 6

Passing a non _|_ value to ioRef does not break the abstraction: ioRef
ignores this value. Similarly, ioRef always calls ioRefDefault with _|_,
so writing (ioRef (X1 :: X)) and (ioRef (X2 :: X)) will not cause the
initial value to be ill-defined, i.e. depending on which expression is
evaluated first.

On performance: ioRef takes O(log n) to return, where n is the number of
refs previous created by ioRef. In the common usage pattern, ioRef is
used only in a top-level definition. If no inlining happens, we pay only
a startup cost: then all IORefs are available in O(1). If inlining
happens, or if we use ioRef as in the last lines of main above, we pay
the log(n) price. Note that inlining only affects the performance, and
not the semantics.

Assumptions/known glitches:

1) We rely on cast from Typeable
2) GHCi is known not to reinitialize the refs on reload.
3) No multithreading support for now.
4) The IORefs module uses a memoization technique, relying on a
"classic" top-level IORef declared through NOINLINE + unsafePerformIO.

Regards,
Zun.

===========================================================================
{-# OPTIONS_GHC -Wall -fglasgow-exts #-}
module IORefs (ioRef, IORefDefault, ioRefDefault) where

import qualified Data.Map as M
import System.IO.Unsafe
import Data.IORef
import Data.Typeable

class (Typeable a, Typeable b) => IORefDefault a b | a -> b where
    ioRefDefault :: a -> b

data Ref = forall a . Typeable a => Ref (IORef a)
type RefMap = M.Map TypeRep Ref

{-# NOINLINE refs #-} -- This is crucial
refs :: IORef RefMap
refs = unsafePerformIO $ newIORef M.empty

-- This is like a memoized function, so inlining this should be safe.
-- (Needs locking for multithread, though.)
ioRef :: forall a b . IORefDefault a b => a -> IORef b
ioRef x = unsafePerformIO $
   do
   rs <- readIORef refs
   case typeOf x `M.lookup` rs of
      Nothing -> do
                 ref <- newIORef $ ioRefDefault (undefined :: a)
                 writeIORef refs $ M.insert (typeOf x) (Ref ref) rs
                 return ref
      Just (Ref aRef) -> case cast aRef of
                         Nothing  -> error $ "ioRef: impossible!"
                         Just ref -> return ref

-- Should be in Data.Typeable
instance Ord TypeRep where compare x y = compare (show x) (show y)




More information about the Haskell-Cafe mailing list