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