[project @ 2002-05-27 15:43:44 by simonmar]
[ghc-base.git] / GHC / Weak.lhs
1 \begin{code}
2 {-# OPTIONS -fno-implicit-prelude #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.Weak
6 -- Copyright   :  (c) The University of Glasgow, 1998-2002
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  cvs-ghc@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC Extensions)
12 --
13 -- Weak pointers.
14 --
15 -----------------------------------------------------------------------------
16
17 module GHC.Weak where
18
19 import GHC.Base
20 import Data.Maybe
21 import GHC.IOBase       ( IO(..), unIO )
22
23 {-|
24 A weak pointer object with a key and a value.  The value has type @v@.
25
26 A weak pointer expresses a relationship between two objects, the
27 /key/ and the /value/:  if the key is considered to be alive by the
28 garbage collector, then the value is also alive.  A reference from
29 the value to the key does /not/ keep the key alive.
30
31 A weak pointer may also have a finalizer of type @IO ()@; if it does,
32 then the finalizer will be run once, and once only, at a time after
33 the key has become unreachable by the program (\"dead\").  The storage
34 manager attempts to run the finalizer(s) for an object soon after the
35 object dies, but promptness is not guaranteed.  
36
37 References from the finalizer to the key are treated in the same way
38 as references from the value to the key: they do not keep the key
39 alive.  A finalizer may therefore ressurrect the key, perhaps by
40 storing it in the same data structure.
41
42 The finalizer, and the relationship between the key and the value,
43 exist regardless of whether the program keeps a reference to the
44 'Weak' object or not.
45
46 There may be multiple weak pointers with the same key.  In this
47 case, the finalizers for each of these weak pointers will all be
48 run in some arbitrary order, or perhaps concurrently, when the key
49 dies.  If the programmer specifies a finalizer that assumes it has
50 the only reference to an object (for example, a file that it wishes
51 to close), then the programmer must ensure that there is only one
52 such finalizer.
53
54 If there are no other threads to run, the runtime system will check
55 for runnable finalizers before declaring the system to be deadlocked.
56 -}
57 data Weak v = Weak (Weak# v)
58
59 -- | Establishes a weak pointer to @k@, with value @v@ and a finalizer.
60 --
61 -- This is the most general interface for building a weak pointer.
62 --
63 mkWeak  :: k                            -- ^ key
64         -> v                            -- ^ value
65         -> Maybe (IO ())                -- ^ finalizer
66         -> IO (Weak v)                  -- ^ returns: a weak pointer object
67
68 mkWeak key val (Just finalizer) = IO $ \s ->
69    case mkWeak# key val finalizer s of { (# s1, w #) -> (# s1, Weak w #) }
70 mkWeak key val Nothing = IO $ \s ->
71    case mkWeak# key val (unsafeCoerce# 0#) s of { (# s1, w #) -> (# s1, Weak w #) }
72
73 {-|
74   A specialised version of 'mkWeak', where the key and the value are the
75   same object:
76
77   > mkWeakPtr key finalizer = mkWeak key key finalizer
78 -}
79 mkWeakPtr :: k -> Maybe (IO ()) -> IO (Weak k)
80 mkWeakPtr key finalizer = mkWeak key key finalizer
81
82 {-|
83   A specialised version of 'mkWeakPtr', where the 'Weak' object
84   returned is simply thrown away (however the finalizer will be
85   remembered by the garbage collector, and will still be run
86   when the key becomes unreachable).
87 -}
88 addFinalizer :: key -> IO () -> IO ()
89 addFinalizer key finalizer = do
90    mkWeakPtr key (Just finalizer)       -- throw it away
91    return ()
92
93 {-
94 Instance Eq (Weak v) where
95   (Weak w1) == (Weak w2) = w1 `sameWeak#` w2
96 -}
97
98
99 -- run a batch of finalizers from the garbage collector.  We're given 
100 -- an array of finalizers and the length of the array, and we just
101 -- call each one in turn.
102 --
103 -- the IO primitives are inlined by hand here to get the optimal
104 -- code (sigh) --SDM.
105
106 runFinalizerBatch :: Int -> Array# (IO ()) -> IO ()
107 runFinalizerBatch (I# n) arr = 
108    let  go m  = IO $ \s ->
109                   case m of 
110                   0# -> (# s, () #)
111                   _  -> let m' = m -# 1# in
112                         case indexArray# arr m' of { (# io #) -> 
113                         case unIO io s of          { (# s, _ #) -> 
114                         unIO (go m') s
115                         }}
116    in
117         go n
118
119 \end{code}