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