[project @ 2001-02-22 16:10:12 by rrt]
[ghc-hetmet.git] / ghc / lib / std / PrelWeak.lhs
index 354332b..76f4c8c 100644 (file)
@@ -1,5 +1,7 @@
+% ------------------------------------------------------------------------------
+% $Id: PrelWeak.lhs,v 1.15 2001/01/11 17:25:57 simonmar Exp $
 %
-% (c) The AQUA Project, Glasgow University, 1998
+% (c) The University of Glasgow, 1998-2000
 %
 
 \section[PrelWeak]{Module @PrelWeak@}
@@ -7,15 +9,14 @@
 \begin{code}
 {-# OPTIONS -fno-implicit-prelude #-}
 
-#ifndef __PARALLEL_HASKELL__
-
 module PrelWeak where
 
 import PrelGHC
 import PrelBase
 import PrelMaybe
-import PrelIOBase
-import PrelForeign
+import PrelIOBase      ( IO(..), unIO )
+
+#ifndef __PARALLEL_HASKELL__
 
 data Weak v = Weak (Weak# v)
 
@@ -37,14 +38,32 @@ addFinalizer key finalizer = do
    mkWeakPtr key (Just finalizer)      -- throw it away
    return ()
 
-addForeignFinalizer :: ForeignObj -> IO () -> IO ()
-addForeignFinalizer (ForeignObj fo) finalizer = addFinalizer fo finalizer
-
 {-
-instance Eq (Weak v) where
+Instance Eq (Weak v) where
   (Weak w1) == (Weak w2) = w1 `sameWeak#` w2
 -}
 
+
+-- run a batch of finalizers from the garbage collector.  We're given 
+-- an array of finalizers and the length of the array, and we just
+-- call each one in turn.
+--
+-- the IO primitives are inlined by hand here to get the optimal
+-- code (sigh) --SDM.
+
+runFinalizerBatch :: Int -> Array# (IO ()) -> IO ()
+runFinalizerBatch (I# n) arr = 
+   let  go m  = IO $ \s ->
+                 case m of 
+                 0# -> (# s, () #)
+                 _  -> let m' = m -# 1# in
+                       case indexArray# arr m' of { (# io #) -> 
+                       case unIO io s of          { (# s, _ #) -> 
+                       unIO (go m') s
+                       }}
+   in
+        go n
+
 #endif
 
 \end{code}