[project @ 2005-02-03 10:32:11 by ross]
[ghc-base.git] / GHC / Weak.lhs
1 \begin{code}
2 {-# OPTIONS_GHC -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 -- #hide
18 module GHC.Weak where
19
20 import GHC.Base
21 import Data.Maybe
22 import GHC.IOBase       ( IO(..), unIO )
23 import Data.Typeable    ( Typeable1(..), mkTyCon, mkTyConApp )
24
25 {-|
26 A weak pointer object with a key and a value.  The value has type @v@.
27
28 A weak pointer expresses a relationship between two objects, the
29 /key/ and the /value/:  if the key is considered to be alive by the
30 garbage collector, then the value is also alive.  A reference from
31 the value to the key does /not/ keep the key alive.
32
33 A weak pointer may also have a finalizer of type @IO ()@; if it does,
34 then the finalizer will be run at most once, at a time after the key
35 has become unreachable by the program (\"dead\").  The storage manager
36 attempts to run the finalizer(s) for an object soon after the object
37 dies, but promptness is not guaranteed.  
38
39 It is not guaranteed that a finalizer will eventually run, and no
40 attempt is made to run outstanding finalizers when the program exits.
41 Therefore finalizers should not be relied on to clean up resources -
42 other methods (eg. exception handlers) should be employed, possibly in
43 addition to finalisers.
44
45 References from the finalizer to the key are treated in the same way
46 as references from the value to the key: they do not keep the key
47 alive.  A finalizer may therefore ressurrect the key, perhaps by
48 storing it in the same data structure.
49
50 The finalizer, and the relationship between the key and the value,
51 exist regardless of whether the program keeps a reference to the
52 'Weak' object or not.
53
54 There may be multiple weak pointers with the same key.  In this
55 case, the finalizers for each of these weak pointers will all be
56 run in some arbitrary order, or perhaps concurrently, when the key
57 dies.  If the programmer specifies a finalizer that assumes it has
58 the only reference to an object (for example, a file that it wishes
59 to close), then the programmer must ensure that there is only one
60 such finalizer.
61
62 If there are no other threads to run, the runtime system will check
63 for runnable finalizers before declaring the system to be deadlocked.
64 -}
65 data Weak v = Weak (Weak# v)
66
67 #include "Typeable.h"
68 INSTANCE_TYPEABLE1(Weak,weakTc,"Weak")
69
70 -- | Establishes a weak pointer to @k@, with value @v@ and a finalizer.
71 --
72 -- This is the most general interface for building a weak pointer.
73 --
74 mkWeak  :: k                            -- ^ key
75         -> v                            -- ^ value
76         -> Maybe (IO ())                -- ^ finalizer
77         -> IO (Weak v)                  -- ^ returns: a weak pointer object
78
79 mkWeak key val (Just finalizer) = IO $ \s ->
80    case mkWeak# key val finalizer s of { (# s1, w #) -> (# s1, Weak w #) }
81 mkWeak key val Nothing = IO $ \s ->
82    case mkWeak# key val (unsafeCoerce# 0#) s of { (# s1, w #) -> (# s1, Weak w #) }
83
84 {-|
85 Dereferences a weak pointer.  If the key is still alive, then
86 @'Just' v@ is returned (where @v@ is the /value/ in the weak pointer), otherwise
87 'Nothing' is returned.
88
89 The return value of 'deRefWeak' depends on when the garbage collector
90 runs, hence it is in the 'IO' monad.
91 -}
92 deRefWeak :: Weak v -> IO (Maybe v)
93 deRefWeak (Weak w) = IO $ \s ->
94    case deRefWeak# w s of
95         (# s1, flag, p #) -> case flag of
96                                 0# -> (# s1, Nothing #)
97                                 _  -> (# s1, Just p #)
98
99 -- | Causes a the finalizer associated with a weak pointer to be run
100 -- immediately.
101 finalize :: Weak v -> IO ()
102 finalize (Weak w) = IO $ \s ->
103    case finalizeWeak# w s of
104         (# s1, 0#, _ #) -> (# s1, () #) -- already dead, or no finaliser
105         (# s1, _,  f #) -> f s1
106
107 {-
108 Instance Eq (Weak v) where
109   (Weak w1) == (Weak w2) = w1 `sameWeak#` w2
110 -}
111
112
113 -- run a batch of finalizers from the garbage collector.  We're given 
114 -- an array of finalizers and the length of the array, and we just
115 -- call each one in turn.
116 --
117 -- the IO primitives are inlined by hand here to get the optimal
118 -- code (sigh) --SDM.
119
120 runFinalizerBatch :: Int -> Array# (IO ()) -> IO ()
121 runFinalizerBatch (I# n) arr = 
122    let  go m  = IO $ \s ->
123                   case m of 
124                   0# -> (# s, () #)
125                   _  -> let m' = m -# 1# in
126                         case indexArray# arr m' of { (# io #) -> 
127                         case unIO io s of          { (# s, _ #) -> 
128                         unIO (go m') s
129                         }}
130    in
131         go n
132
133 \end{code}