The Death of Finalizers

Dean Herington heringto at cs.unc.edu
Tue Oct 22 13:10:07 EDT 2002


George Russell wrote:

> Simon Peyton-Jones wrote:
> >
> > | In the meantime, I'm glad we have got a new function
> > |    atomicModifyIORef
> > | which I for one will use, when it gets into GHC's regular release.
> >
> > Just before this gets out of the door... any chance of calling it
> >
> >         modifyIORef
> >
> > and documenting that it's atomic
>
> My vote goes for
>
> modifyIORef :: IORef a -> (a -> (a,b)) -> IO b
> modifyIORef_ :: IORef a -> (a -> a) -> IO a
>
> modifyIORef_ ioRef fn = modifyIORef ioRef (\ a0 -> let a1 = fn a0 in (a1,a1))
>
> The names are similar to those of GHC's modifyMVar and modifyMVar_.
> I think there's some sense in providing modifyIORef_ as well as
> modifyIORef, as I think for some implementations it will be even faster,
> since it's unnecessary to create thunks for (fst (fn a0)) and
> (snd (fn a0)).  But you lot know a lot more about writing Haskell
> compilers than I do . . .
>
> Thus you can implement a counter returning integers 1,2,3,...
> via
>
>    newCounter :: IO (IO Integer)
>    newCounter = do
>       ioRef <- newIORef 0
>       return (modifyIORef_ ioRef (+1))
>
> I don't think it's necessary for the name to include "atomic".
> We are unlikely ever to want a non-atomic version of atomicModifyIORef,
> especially as such a thing would be quite dangerous, and you can roll
> your own from readIORef and writeIORef.

I like the idea of consistency (in naming, signatures, and semantics) between the
sets of functions manipulating IORefs and MVars.  Here's the scheme I would
prefer for the "modify" subset of these functions.  Existing functions are
labeled "(e)", proposed functions "(p)".  "(*)" indicates an existing function
with a different interface.

(e)   modifyMVar :: MVar a -> (a -> IO (a, b)) -> IO b
(e)   modifyMVar_ :: MVar a -> (a -> IO a) -> IO ()
(p)   atomicModifyMVar :: MVar a -> (a -> (a, b)) -> IO b
(p)   atomicModifyMVar_ :: MVar a -> (a -> a) -> IO ()

(*)   modifyIORef :: IORef a -> (a -> IO (a, b)) -> IO b
(p)   modifyIORef_ :: IORef a -> (a -> IO a) -> IO ()
(p)   atomicModifyIORef :: IORef a -> (a -> (a, b)) -> IO b
(p)   atomicModifyIORef_ :: IORef a -> (a -> a) -> IO ()

Notes:

* I prefer having the "*modify*_" functions return IO (), despite the fact that
it means the newCounter example George gives becomes more complicated.

* I strongly agree with Alastair that an atomic function should be so labeled.

* The nonatomic functions are all simply convenient combinations of other
functions.  As such, they could be dispensed with.  Even if they were dispensed
with, however, I would recommend against using their (without-"atomic") names for
the atomic functions, because I think the natural interfaces for the nonatomic
names are the ones given above.

* In fact, only atomicModifyMVar and atomicModifyIORef are primitive.

* The existence of modifyIORef with the "wrong" interface is an unfortunate
problem with this scheme.

 -- Dean




More information about the FFI mailing list