The Revenge of Finalizers

George Russell ger at tzi.de
Fri Oct 11 12:48:34 EDT 2002


Malcolm Wallace wrote
[snip]
> I don't think MVars make any sense without concurrency, so I don't see
> the point of implementing the one without the other.  I'm willing to
> be persuaded otherwise.  (It would be nice to have some concurrency
> in nhc98, of course, but I don't foresee that happening soon.)
> 
> > I apologise to Malcolm, but in any case I doubt if implementing
> > MVars in a world with only one thread would cost him a great deal of
> > effort.
> 
> Well it would be simple enough provided you didn't mind your
> computation halting with deadlock rather unpredictably.  :-)
[snip]
OK, the point is to make programs more portable from NHC to other systems.
(Perhaps you would rather lock them in? 8-)  If I write, say, Alastair
Reid's newObject and killObject in NHC using IORefs, then this will work
fine in NHC, but may mysteriously go wrong when someone ports them to GHC
and calls newObject and killObject simultaneously.

I'm not sure we should be discussing this here; really we should have a 
separate Haskell Mutable State standard.  However let's try anyway.

Clearly it would be trivial to implement MVars in NHC to fit such a goal,
something like

newtype MVar a = MVar (IORef (Maybe a))

takeMVar (MVar ioRef) =
   do
      aOpt <- readIORef ioRef
      case aOpt of
         Nothing -> error "Computer deadlocked.  Please buy a new one."
         Just a -> 
            do
               writeIORef ioRef Nothing
               return a

(newMVar and putMVar I'll leave as exercises for the reader.)

I admit though that Alastair is right in this: while NHC + MVars and NHC 
+ Haskell finalizers may be doable, NHC + Haskell finalizers + MVars may 
not be, because then you have the problem of blocking.  If the main program 
and the finalizer both do

   x <- takeMVar mVar
   putMVar mVar (update x)

then the program will unnecessarily deadlock if the finalizer is called inbetween the
take and the put.  

Malcolm, is it feasible to implement a workaround to this?

However even if Haskell finalizers + MVars are impossible in NHC, I don't think
Haskell finalizers + mutable state have to be.  For example another mutable variable
we could have would be a PVar which is always full and has functions

newPVar :: a -> IO (PVar a)
updatePVar :: PVar a -> (a -> a) -> IO a

updatePVar represents an atomic update; the function is applied to the value in the PVar 
and the old value is returned.  For GHC and Hugs you could implement PVars using MVars.   
NHC could implement them as follows:

newtype PVar = PVar (IORef a)

updatePVar (PVar ioRef) updateFn =
   do
      [stop any new finalizers running]
      a <- readIORef ioRef
      writeIORef (updateFn a)
      [reenable finalizers]
      return a

Then we have mutable state (enough to implement Alastair's killObject/newObject safely)
in a way that I think NHC wouldn't find it too hard to implement.
Of course you need a global flag which disables removing things from the finalizer queue,
and the reenable-finalizers primitive could also check to see if any finalizers had arisen
in the meantime.  Also we are implicitly assuming that the execution of finalizers is
properly nested, but that doesn't seem to hard a condition to ensure (in the context of NHC).
Malcolm, does all this make sense to you, or am I talking total rubbish?

I don't claim these PVars are perfect; there are things I can do with MVars which I don't
know how to do with PVars.  But I do claim that they provide sufficient mutable state to
be useful in finalizers, without being hard for anyone (GHC, Hugs or NHC) to implement
with finalizers.  

A "Mutable Variables Standard" could then define IORefs and PVars.  Then with Haskell98 + FFI +
Mutable Variables you would be able to write portable code that does mutable things in finalizers,
and we would all be happy.



More information about the FFI mailing list