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