Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / System / Mem / Weak.hs
1 {-# LANGUAGE CPP #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  System.Mem.Weak
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  experimental
11 -- Portability :  non-portable
12 --
13 -- In general terms, a weak pointer is a reference to an object that is
14 -- not followed by the garbage collector - that is, the existence of a
15 -- weak pointer to an object has no effect on the lifetime of that
16 -- object.  A weak pointer can be de-referenced to find out
17 -- whether the object it refers to is still alive or not, and if so
18 -- to return the object itself.
19 -- 
20 -- Weak pointers are particularly useful for caches and memo tables.
21 -- To build a memo table, you build a data structure 
22 -- mapping from the function argument (the key) to its result (the
23 -- value).  When you apply the function to a new argument you first
24 -- check whether the key\/value pair is already in the memo table.
25 -- The key point is that the memo table itself should not keep the
26 -- key and value alive.  So the table should contain a weak pointer
27 -- to the key, not an ordinary pointer.  The pointer to the value must
28 -- not be weak, because the only reference to the value might indeed be
29 -- from the memo table.   
30 -- 
31 -- So it looks as if the memo table will keep all its values
32 -- alive for ever.  One way to solve this is to purge the table
33 -- occasionally, by deleting entries whose keys have died.
34 -- 
35 -- The weak pointers in this library
36 -- support another approach, called /finalization/.
37 -- When the key referred to by a weak pointer dies, the storage manager
38 -- arranges to run a programmer-specified finalizer.  In the case of memo
39 -- tables, for example, the finalizer could remove the key\/value pair
40 -- from the memo table.  
41 -- 
42 -- Another difficulty with the memo table is that the value of a
43 -- key\/value pair might itself contain a pointer to the key.
44 -- So the memo table keeps the value alive, which keeps the key alive,
45 -- even though there may be no other references to the key so both should
46 -- die.  The weak pointers in this library provide a slight 
47 -- generalisation of the basic weak-pointer idea, in which each
48 -- weak pointer actually contains both a key and a value.
49 --
50 -----------------------------------------------------------------------------
51
52 module System.Mem.Weak (
53         -- * The @Weak@ type
54         Weak,                   -- abstract
55
56         -- * The general interface
57         mkWeak,                 -- :: k -> v -> Maybe (IO ()) -> IO (Weak v)
58         deRefWeak,              -- :: Weak v -> IO (Maybe v)
59         finalize,               -- :: Weak v -> IO ()
60
61         -- * Specialised versions
62         mkWeakPtr,              -- :: k -> Maybe (IO ()) -> IO (Weak k)
63         addFinalizer,           -- :: key -> IO () -> IO ()
64         mkWeakPair,             -- :: k -> v -> Maybe (IO ()) -> IO (Weak (k,v))
65         -- replaceFinaliser     -- :: Weak v -> IO () -> IO ()
66
67         -- * A precise semantics
68         
69         -- $precise
70    ) where
71
72 #ifdef __HUGS__
73 import Hugs.Weak
74 import Prelude
75 #endif
76
77 #ifdef __GLASGOW_HASKELL__
78 import GHC.Weak
79 #endif
80
81 -- | A specialised version of 'mkWeak', where the key and the value are
82 -- the same object:
83 --
84 -- > mkWeakPtr key finalizer = mkWeak key key finalizer
85 --
86 mkWeakPtr :: k -> Maybe (IO ()) -> IO (Weak k)
87 mkWeakPtr key finalizer = mkWeak key key finalizer
88
89 {-|
90   A specialised version of 'mkWeakPtr', where the 'Weak' object
91   returned is simply thrown away (however the finalizer will be
92   remembered by the garbage collector, and will still be run
93   when the key becomes unreachable).
94
95   Note: adding a finalizer to a 'Foreign.ForeignPtr.ForeignPtr' using
96   'addFinalizer' won't work as well as using the specialised version
97   'Foreign.ForeignPtr.addForeignPtrFinalizer' because the latter
98   version adds the finalizer to the primitive 'ForeignPtr#' object
99   inside, whereas the generic 'addFinalizer' will add the finalizer to
100   the box.  Optimisations tend to remove the box, which may cause the
101   finalizer to run earlier than you intended.  The same motivation
102   justifies the existence of
103   'Control.Concurrent.MVar.addMVarFinalizer' and
104   'Data.IORef.mkWeakIORef' (the non-uniformity is accidental).
105 -}
106 addFinalizer :: key -> IO () -> IO ()
107 addFinalizer key finalizer = do
108    _ <- mkWeakPtr key (Just finalizer) -- throw it away
109    return ()
110
111 -- | A specialised version of 'mkWeak' where the value is actually a pair
112 -- of the key and value passed to 'mkWeakPair':
113 --
114 -- > mkWeakPair key val finalizer = mkWeak key (key,val) finalizer
115 --
116 -- The advantage of this is that the key can be retrieved by 'deRefWeak'
117 -- in addition to the value.
118 mkWeakPair :: k -> v -> Maybe (IO ()) -> IO (Weak (k,v))
119 mkWeakPair key val finalizer = mkWeak key (key,val) finalizer
120
121
122 {- $precise
123
124 The above informal specification is fine for simple situations, but
125 matters can get complicated.  In particular, it needs to be clear
126 exactly when a key dies, so that any weak pointers that refer to it
127 can be finalized.  Suppose, for example, the value of one weak pointer
128 refers to the key of another...does that keep the key alive?
129
130 The behaviour is simply this:
131
132  *  If a weak pointer (object) refers to an /unreachable/
133     key, it may be finalized.
134
135  *  Finalization means (a) arrange that subsequent calls
136     to 'deRefWeak' return 'Nothing'; and (b) run the finalizer.
137
138 This behaviour depends on what it means for a key to be reachable.
139 Informally, something is reachable if it can be reached by following
140 ordinary pointers from the root set, but not following weak pointers.
141 We define reachability more precisely as follows A heap object is
142 reachable if:
143
144  * It is a member of the /root set/.
145
146  * It is directly pointed to by a reachable object, other than
147    a weak pointer object.
148
149  * It is a weak pointer object whose key is reachable.
150
151  * It is the value or finalizer of an object whose key is reachable.
152 -}