module MarkCompact.TwoFinger where
+import Debug.Trace
import Data.List (sortBy)
import Data.Function (on)
import Data.Array
collect :: GcM ()
collect = do
+ traceShowM "mark!!!"
markFromRoots
compact
let indicesToUnmark = fmap fst $ takeWhile (\(_, marked) -> marked) $ assocs bm
free' = if indicesToUnmark == [] then free else maximum indicesToUnmark
bm' = bm // [(i, False) | i <- indicesToUnmark]
- put $ gc { bitmap = bm' }
+ put $ gc { bitmap = traceShow (free', indicesToUnmark) bm' }
let
findIndexStep marked (ok, idx)
| not marked && idx > free' = (ok, idx - 1)
| otherwise = (True, idx)
- scan' = snd $ foldr findIndexStep (False, scan) bm
+ scan' = snd $ foldr findIndexStep (False, scan) bm'
if scan' > free' then do
put $ gc { bitmap = bm' // [(scan', False)]}
let
res = flip runState initState $ unGcM $ do
ptr <- new (IntVal 1)
+
+ writeToRoots 1 ptr
+
ptr2 <- new (IntVal 2)
ptr3 <- new (IntVal 3)
ptr4 <- new (IntVal 4)
ptr7 <- new (IntVal 7)
ptr8 <- new (IntVal 8)
- writeToRoots 1 ptr
collect