[Haskell-cafe] Safe top-level IORefs

Roberto Zunino zunino at di.unipi.it
Sun Mar 4 17:08:39 EST 2007


Neil Mitchell wrote:
> Hi
> 
> On 3/4/07, Roberto Zunino <zunino at di.unipi.it> wrote:
>> 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.
> 
> That looks cool, does it work on Hugs?

I've tested it right now.

Yes, it works with -98, but you have to provide a (correct!) instance of
Typeable X on your own.

Declaring a ref becomes a bit more cumbersome:

data X  -- the actual name of the IORef
instance Typeable X where typeOf _ = mkTyConApp (mkTyCon "Main.X") []
instance IORefDefault X Int where ioRefDefault _ = 42  -- initial value
x = ioRef (undefined :: X) -- a convenient name for the IORef

It would be better to use drift to write the instance for you, since
getting that wrong breaks Typeable, and ioRef roo.

Finally, IORefs.ioRef must be changed to use asTypeOf.

Zun.

================================================================
-- Hugs & GHC version
ioRef :: 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 `asTypeOf` x)
                 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



More information about the Haskell-Cafe mailing list