X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FWeak.lhs;h=67046f88f3d0a2507b9fba19a5fe20ee8da30d7b;hb=41e8fba828acbae1751628af50849f5352b27873;hp=95dd3a543bca0d248fb10133c109f3c7e1f38841;hpb=d9e5fa673b75cdffbcd0e85cdcc98d706acbb29a;p=ghc-base.git diff --git a/GHC/Weak.lhs b/GHC/Weak.lhs index 95dd3a5..67046f8 100644 --- a/GHC/Weak.lhs +++ b/GHC/Weak.lhs @@ -1,40 +1,114 @@ -% ------------------------------------------------------------------------------ -% $Id: Weak.lhs,v 1.2 2001/07/03 14:13:32 simonmar Exp $ -% -% (c) The University of Glasgow, 1998-2000 -% - -\section[GHC.Weak]{Module @GHC.Weak@} - \begin{code} -{-# OPTIONS -fno-implicit-prelude #-} +{-# LANGUAGE CPP + , NoImplicitPrelude + , BangPatterns + , MagicHash + , UnboxedTuples + #-} +{-# OPTIONS_HADDOCK hide #-} + +----------------------------------------------------------------------------- +-- | +-- Module : GHC.Weak +-- Copyright : (c) The University of Glasgow, 1998-2002 +-- License : see libraries/base/LICENSE +-- +-- Maintainer : cvs-ghc@haskell.org +-- Stability : internal +-- Portability : non-portable (GHC Extensions) +-- +-- Weak pointers. +-- +----------------------------------------------------------------------------- +-- #hide module GHC.Weak where -import GHC.Prim import GHC.Base import Data.Maybe -import GHC.IOBase ( IO(..), unIO ) +import Data.Typeable + +{-| +A weak pointer object with a key and a value. The value has type @v@. + +A weak pointer expresses a relationship between two objects, the +/key/ and the /value/: if the key is considered to be alive by the +garbage collector, then the value is also alive. A reference from +the value to the key does /not/ keep the key alive. + +A weak pointer may also have a finalizer of type @IO ()@; if it does, +then the finalizer will be run at most once, at a time after the key +has become unreachable by the program (\"dead\"). The storage manager +attempts to run the finalizer(s) for an object soon after the object +dies, but promptness is not guaranteed. + +It is not guaranteed that a finalizer will eventually run, and no +attempt is made to run outstanding finalizers when the program exits. +Therefore finalizers should not be relied on to clean up resources - +other methods (eg. exception handlers) should be employed, possibly in +addition to finalisers. +References from the finalizer to the key are treated in the same way +as references from the value to the key: they do not keep the key +alive. A finalizer may therefore ressurrect the key, perhaps by +storing it in the same data structure. + +The finalizer, and the relationship between the key and the value, +exist regardless of whether the program keeps a reference to the +'Weak' object or not. + +There may be multiple weak pointers with the same key. In this +case, the finalizers for each of these weak pointers will all be +run in some arbitrary order, or perhaps concurrently, when the key +dies. If the programmer specifies a finalizer that assumes it has +the only reference to an object (for example, a file that it wishes +to close), then the programmer must ensure that there is only one +such finalizer. + +If there are no other threads to run, the runtime system will check +for runnable finalizers before declaring the system to be deadlocked. +-} data Weak v = Weak (Weak# v) -mkWeak :: k -- key - -> v -- value - -> Maybe (IO ()) -- finalizer - -> IO (Weak v) -- weak pointer +#include "Typeable.h" +INSTANCE_TYPEABLE1(Weak,weakTc,"Weak") + +-- | Establishes a weak pointer to @k@, with value @v@ and a finalizer. +-- +-- This is the most general interface for building a weak pointer. +-- +mkWeak :: k -- ^ key + -> v -- ^ value + -> Maybe (IO ()) -- ^ finalizer + -> IO (Weak v) -- ^ returns: a weak pointer object mkWeak key val (Just finalizer) = IO $ \s -> case mkWeak# key val finalizer s of { (# s1, w #) -> (# s1, Weak w #) } mkWeak key val Nothing = IO $ \s -> case mkWeak# key val (unsafeCoerce# 0#) s of { (# s1, w #) -> (# s1, Weak w #) } -mkWeakPtr :: k -> Maybe (IO ()) -> IO (Weak k) -mkWeakPtr key finalizer = mkWeak key key finalizer +{-| +Dereferences a weak pointer. If the key is still alive, then +@'Just' v@ is returned (where @v@ is the /value/ in the weak pointer), otherwise +'Nothing' is returned. + +The return value of 'deRefWeak' depends on when the garbage collector +runs, hence it is in the 'IO' monad. +-} +deRefWeak :: Weak v -> IO (Maybe v) +deRefWeak (Weak w) = IO $ \s -> + case deRefWeak# w s of + (# s1, flag, p #) -> case flag of + 0# -> (# s1, Nothing #) + _ -> (# s1, Just p #) -addFinalizer :: key -> IO () -> IO () -addFinalizer key finalizer = do - mkWeakPtr key (Just finalizer) -- throw it away - return () +-- | Causes a the finalizer associated with a weak pointer to be run +-- immediately. +finalize :: Weak v -> IO () +finalize (Weak w) = IO $ \s -> + case finalizeWeak# w s of + (# s1, 0#, _ #) -> (# s1, () #) -- already dead, or no finaliser + (# s1, _, f #) -> f s1 {- Instance Eq (Weak v) where @@ -52,13 +126,13 @@ Instance Eq (Weak v) where runFinalizerBatch :: Int -> Array# (IO ()) -> IO () runFinalizerBatch (I# n) arr = let go m = IO $ \s -> - case m of - 0# -> (# s, () #) - _ -> let m' = m -# 1# in - case indexArray# arr m' of { (# io #) -> - case unIO io s of { (# s, _ #) -> - unIO (go m') s - }} + case m of + 0# -> (# s, () #) + _ -> let !m' = m -# 1# in + case indexArray# arr m' of { (# io #) -> + case unIO io s of { (# s', _ #) -> + unIO (go m') s' + }} in go n