d7cfaaca7597ba18568acc7cf41669d6b414ab12
[ghc-hetmet.git] / ghc / lib / std / PrelWeak.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1998
3 %
4
5 \section[PrelWeak]{Module @PrelWeak@}
6
7 \begin{code}
8 {-# OPTIONS -fno-implicit-prelude #-}
9
10 module PrelWeak where
11
12 import PrelGHC
13 import PrelBase
14 import PrelMaybe
15 -- NOTE: To break a cycle, ForeignObj is not in PrelForeign, but PrelIOBase!
16 import PrelIOBase       ( IO(..), unIO, ForeignObj(..) )
17
18 #ifndef __PARALLEL_HASKELL__
19
20 data Weak v = Weak (Weak# v)
21
22 mkWeak  :: k                            -- key
23         -> v                            -- value
24         -> Maybe (IO ())                -- finalizer
25         -> IO (Weak v)                  -- weak pointer
26
27 mkWeak key val (Just finalizer) = IO $ \s ->
28    case mkWeak# key val finalizer s of { (# s1, w #) -> (# s1, Weak w #) }
29 mkWeak key val Nothing = IO $ \s ->
30    case mkWeak# key val (unsafeCoerce# 0#) s of { (# s1, w #) -> (# s1, Weak w #) }
31
32 mkWeakPtr :: k -> Maybe (IO ()) -> IO (Weak k)
33 mkWeakPtr key finalizer = mkWeak key key finalizer
34
35 addFinalizer :: key -> IO () -> IO ()
36 addFinalizer key finalizer = do
37    mkWeakPtr key (Just finalizer)       -- throw it away
38    return ()
39
40 addForeignFinalizer :: ForeignObj -> IO () -> IO ()
41 addForeignFinalizer (ForeignObj fo) finalizer = addFinalizer fo finalizer
42
43 {-
44 Instance Eq (Weak v) where
45   (Weak w1) == (Weak w2) = w1 `sameWeak#` w2
46 -}
47
48
49 -- run a batch of finalizers from the garbage collector.  We're given 
50 -- an array of finalizers and the length of the array, and we just
51 -- call each one in turn.
52 --
53 -- the IO primitives are inlined by hand here to get the optimal
54 -- code (sigh) --SDM.
55
56 runFinalizerBatch :: Int -> Array# (IO ()) -> IO ()
57 runFinalizerBatch (I# n) arr = 
58    let  go m  = IO $ \s ->
59                   case m of 
60                   0# -> (# s, () #)
61                   _  -> let m' = m -# 1# in
62                         case indexArray# arr m' of { (# io #) -> 
63                         case unIO io s of          { (# s, _ #) -> 
64                         unIO (go m') s
65                         }}
66    in
67         go n
68
69 #endif
70
71 \end{code}