Adding a finalizer to a TVar

Merijn Verstraaten merijn at inconsistent.nl
Mon Dec 23 00:44:43 UTC 2013


+1 on adding to stm, I need this too.

Cheers,
Merijn

On Dec 22, 2013, at 21:10 , John Lato wrote:
> On Dec 22, 2013 4:56 AM, "Sebastiaan Visser" <haskell at fvisser.nl> wrote:
> >
> > Hi,
> >
> > Both MVar and IORef have specialized functions to attach a finalizer to there inner identifiable (stable) reference cell. I happen to need something similar for TVars, but that one doesn't seem to exist.
> >
> > The documentation of System.Mem.Weak tells me:
> >
> >  "Finalizers can be used reliably for types that are created explicitly and have identity, such as IORef and MVar. However, to place a finalizer on one of these types, you should use the specific operation provided for that type, e.g. mkWeakIORef and addMVarFinalizer respectively (the non-uniformity is accidental). These operations attach the finalizer to the primitive object inside the box (e.g. MutVar# in the case of IORef), because attaching the finalizer to the box itself fails when the outer box is optimised away by the compiler."
> >
> > Does it make sense to add a similar function to the STM package?
> >
> > What I do now is hack around it by adding an IORef next to my TVar which I attach the finalizer to. Because my outer datatype is opaque I expect both variables to go out of scope and get garbage collected simultaneously. As you might expect, this isn't a very satisfiable solution.
> >
> > Thanks,
> > Sebastiaan
> >
> 
> 
> I needed something similar a while ago, and wrote this (I think it's correct, haven't had any problems at  any rate):
> 
> > {-# LANGUAGE MagicHash #-}
> > {-# LANGUAGE UnboxedTuples #-}
> > 
> > {-# OPTIONS_GHC -Wall #-}
> > module Weak.TVar (
> >   mkWeakTVar
> > , mkWeakTVarKey
> > ) where
> > 
> > import GHC.Conc.Sync (TVar (..))
> > import GHC.Weak
> > import GHC.Base
> > 
> > mkWeakTVar :: TVar a -> Maybe (IO ()) -> IO (Weak (TVar a))
> > mkWeakTVar t f = mkWeakTVarKey t t f
> >
> > -- | Create a Weak reference keyed off a TVar.
> > mkWeakTVarKey :: TVar b -> a -> Maybe (IO ()) -> IO (Weak a)
> > mkWeakTVarKey (TVar r#) v (Just f) = IO $ \s ->
> >       case mkWeak# r# v f s of (# s1, w #) -> (# s1, Weak w #)
> > mkWeakTVarKey (TVar r#) v Nothing = IO $ \s ->
> >       case mkWeakNoFinalizer# r# v s of (# s1, w #) -> (# s1, Weak w #)
> Perhaps something similar would work for you until such a function is added?
> (FWIW I support adding this function to the stm package)
> John L.
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20131223/0baa18d1/attachment-0001.html>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 801 bytes
Desc: Message signed with OpenPGP using GPGMail
URL: <http://www.haskell.org/pipermail/libraries/attachments/20131223/0baa18d1/attachment-0001.sig>


More information about the Libraries mailing list