Weak graph is working

This commit is contained in:
Ryan Trinkle 2023-04-07 21:48:29 -04:00
parent a671900c9b
commit e49fb1ef18

157
main.hs
View File

@ -23,6 +23,10 @@ import Data.Foldable
main :: IO () main :: IO ()
main = do main = do
testDualWeak testDualWeak
testWeakChain
testGraphChain
testGraphX
testGraphO
-- Demonstrate that a Weak's key keeps its value alive, even if the Weak is dead -- Demonstrate that a Weak's key keeps its value alive, even if the Weak is dead
testWeakChain :: IO () testWeakChain :: IO ()
@ -30,9 +34,9 @@ testWeakChain = do
a <- newIORef () a <- newIORef ()
b <- newIORef () b <- newIORef ()
_ <- mkWeakWithIORefKey a b _ <- mkWeakWithIORefKey a b
w <- mkWeakWithIORefKey b "Still Alive" w <- mkWeakWithIORefKey b "b is still alive"
performGCUntilFinalizersQuiesce performGCUntilFinalizersQuiesce
print =<< deRefWeak w Just "b is still alive" <- deRefWeak w
touch a touch a
testGraphChain :: IO () testGraphChain :: IO ()
@ -40,18 +44,18 @@ testGraphChain = do
do do
(nai, neo) <- buildGraphChain (nai, neo) <- buildGraphChain
performGCUntilFinalizersQuiesce performGCUntilFinalizersQuiesce
print =<< findForward nai ["a", "b", "c", "d", "e"] <- toList <$> findForwardVals nai
print =<< findBackward neo ["a", "b", "c", "d", "e"] <- toList <$> findBackwardVals neo
touch (nai, neo) touch (nai, neo)
do do
(nai, _) <- buildGraphChain (nai, _) <- buildGraphChain
performGCUntilFinalizersQuiesce performGCUntilFinalizersQuiesce
print =<< findForward nai [] <- toList <$> findForwardVals nai
touch nai touch nai
do do
(_, neo) <- buildGraphChain (_, neo) <- buildGraphChain
performGCUntilFinalizersQuiesce performGCUntilFinalizersQuiesce
print =<< findBackward neo [] <- toList <$> findBackwardVals neo
touch neo touch neo
buildGraphChain :: IO (NodeInput String, NodeOutput String) buildGraphChain :: IO (NodeInput String, NodeOutput String)
@ -67,8 +71,8 @@ buildGraphChain = do
link ndo nei link ndo nei
pure (nai, neo) pure (nai, neo)
testGraphX :: IO () buildGraphX :: IO (NodeInput String, NodeInput String, NodeOutput String, NodeOutput String)
testGraphX = do buildGraphX = do
(nai, nao) <- newNode "a" (nai, nao) <- newNode "a"
(nbi, nbo) <- newNode "b" (nbi, nbo) <- newNode "b"
(nci, nco) <- newNode "c" (nci, nco) <- newNode "c"
@ -78,50 +82,72 @@ testGraphX = do
link nbo nci link nbo nci
link nco ndi link nco ndi
link nco nei link nco nei
pure (nai, nbi, ndo, neo)
testGraphX :: IO ()
testGraphX = do
do
(nai, nbi, ndo, neo) <- buildGraphX
performGCUntilFinalizersQuiesce performGCUntilFinalizersQuiesce
print =<< findForward nai ["a", "c", "d", "e"] <- toList <$> findForwardVals nai
print =<< findForward nbi ["b", "c", "d", "e"] <- toList <$> findForwardVals nbi
print =<< findBackward ndo ["a", "b", "c", "d"] <- toList <$> findBackwardVals ndo
print =<< findBackward neo ["a", "b", "c", "e"] <- toList <$> findBackwardVals neo
touch (nai, nbi, ndo, neo) touch (nai, nbi, ndo, neo)
do
(nai, nbi, ndo, neo) <- buildGraphX
performGCUntilFinalizersQuiesce performGCUntilFinalizersQuiesce
print =<< findForward nai ["a", "c", "d"] <- toList <$> findForwardVals nai
print =<< findForward nbi ["b", "c", "d"] <- toList <$> findForwardVals nbi
touch ndo touch (nai, nbi, ndo)
do
(nai, nbi, ndo, neo) <- buildGraphX
performGCUntilFinalizersQuiesce performGCUntilFinalizersQuiesce
print =<< findForward nai [] <- toList <$> findForwardVals nai
print =<< findForward nbi [] <- toList <$> findForwardVals nbi
touch (nai, nbi)
testGraphO :: IO () testGraphO :: IO ()
testGraphO = do testGraphO = do
do
(nai, nao) <- buildGraphO
performGCUntilFinalizersQuiesce
["a", "b", "c"] <- toList <$> findBackward nao
["a", "b", "c"] <- toList <$> findForward nai
touch (nai, nao)
do
(_, nao) <- buildGraphO
performGCUntilFinalizersQuiesce
[] <- toList <$> findBackward nao
touch nao
do
(nai, _) <- buildGraphO
performGCUntilFinalizersQuiesce
[] <- toList <$> findForward nai
touch nai
buildGraphO :: IO (NodeInput String, NodeOutput String)
buildGraphO = do
(nai, nao) <- newNode "a" (nai, nao) <- newNode "a"
(nbi, nbo) <- newNode "b" (nbi, nbo) <- newNode "b"
(nci, nco) <- newNode "c" (nci, nco) <- newNode "c"
link nao nbi link nao nbi
link nbo nci link nbo nci
link nco nai link nco nai
performGCUntilFinalizersQuiesce pure (nai, nao)
[] <- toList <$> findForward nai
pure ()
data NodeContents a = NodeContents
{ _nodeContents_key :: !Int
, _nodeContents_value :: a
, _nodeContents_forwardLinks :: !(IORef (IntMap (NodeInput a)))
, _nodeContents_backLinks :: !(IORef (IntMap (NodeOutput a)))
}
data NodeInput a = NodeInput data NodeInput a = NodeInput
{ _nodeInput_key :: !Int { _nodeInput_key :: !Int
, _nodeInput_contents :: !(DualWeak (NodeContents a)) , _nodeInput_contents :: !(Weak (IORef (Maybe a)))
, _nodeInput_ticket :: !Ticket , _nodeInput_forwardLinks :: !(IORef (IntMap (NodeInput a)))
, _nodeInput_backLinks :: !(Weak (IORef (IntMap (NodeOutput a))))
} }
data NodeOutput a = NodeOutput data NodeOutput a = NodeOutput
{ _nodeOutput_key :: !Int { _nodeOutput_key :: !Int
, _nodeOutput_contents :: !(DualWeak (NodeContents a)) , _nodeOutput_contents :: !(Weak (IORef (Maybe a)))
-- , _nodeOutput_backLinks :: !(IORef (IntMap (NodeOutput a))) , _nodeOutput_forwardLinks :: !(Weak (IORef (IntMap (NodeInput a))))
, _nodeOutput_ticket :: !Ticket , _nodeOutput_backLinks :: !(IORef (IntMap (NodeOutput a)))
} }
{-# NOINLINE globalNodeIdRef #-} {-# NOINLINE globalNodeIdRef #-}
@ -136,35 +162,50 @@ newNode v = do
nodeId <- newNodeId nodeId <- newNodeId
backLinks <- newIORef mempty backLinks <- newIORef mempty
forwardLinks <- newIORef mempty forwardLinks <- newIORef mempty
(w, tBackward, tForward) <- newDualWeak $ NodeContents contentsRef <- newIORef $ Just v
{ _nodeContents_key = nodeId w <- mkWeakWithIORefKey backLinks contentsRef
, _nodeContents_value = v wBack <- mkWeakWithIORefKey backLinks backLinks
, _nodeContents_backLinks = backLinks wForward <- mkWeakWithIORefKeyWithFinalizer forwardLinks forwardLinks $ do
, _nodeContents_forwardLinks = forwardLinks writeIORef finalizerDidRunRef True
} deRefWeak w >>= \case
Nothing -> pure ()
Just contentsRef' -> do
writeIORef contentsRef' Nothing
deRefWeak wBack >>= \case
Nothing -> pure ()
Just backLinks' -> do
writeIORef backLinks' mempty
--TODO: Clear out all the nodes forward of us
pure pure
( NodeInput ( NodeInput
{ _nodeInput_key = nodeId { _nodeInput_key = nodeId
, _nodeInput_contents = w , _nodeInput_contents = w
, _nodeInput_ticket = tForward , _nodeInput_backLinks = wBack
, _nodeInput_forwardLinks = forwardLinks
} }
, NodeOutput , NodeOutput
{ _nodeOutput_key = nodeId { _nodeOutput_key = nodeId
, _nodeOutput_contents = w , _nodeOutput_contents = w
-- , _nodeOutput_backLinks = backLinks , _nodeOutput_backLinks = backLinks
, _nodeOutput_ticket = tBackward , _nodeOutput_forwardLinks = wForward
} }
) )
getNodeContents :: Weak (IORef (Maybe a)) -> IO (Maybe a)
getNodeContents w = do
deRefWeak w >>= \case
Nothing -> pure Nothing
Just r -> readIORef r
link :: NodeOutput a -> NodeInput a -> IO () link :: NodeOutput a -> NodeInput a -> IO ()
link aOut bIn = do link aOut bIn = do
getDualWeak (_nodeOutput_contents aOut) >>= \case deRefWeak (_nodeInput_backLinks bIn) >>= \case
Nothing -> pure () -- Linking to a dead node does nothing Nothing -> pure ()
Just a -> getDualWeak (_nodeInput_contents bIn) >>= \case Just backLinks -> deRefWeak (_nodeOutput_forwardLinks aOut) >>= \case
Nothing -> pure () -- Linking to a dead node does nothing Nothing -> pure ()
Just b -> do Just forwardLinks -> do
atomicModifyIORef' (_nodeContents_forwardLinks a) $ \m -> (IntMap.insert (_nodeContents_key b) bIn m, ()) atomicModifyIORef' forwardLinks $ \m -> (IntMap.insert (_nodeInput_key bIn) bIn m, ())
atomicModifyIORef' (_nodeContents_backLinks b) $ \m -> (IntMap.insert (_nodeContents_key a) aOut m, ()) atomicModifyIORef' backLinks $ \m -> (IntMap.insert (_nodeOutput_key aOut) aOut m, ())
findForwardVals :: Ord a => NodeInput a -> IO (Set a) findForwardVals :: Ord a => NodeInput a -> IO (Set a)
findForwardVals i = Set.fromList . IntMap.elems <$> findForward i findForwardVals i = Set.fromList . IntMap.elems <$> findForward i
@ -176,11 +217,14 @@ findForward i = go mempty (IntMap.singleton (_nodeInput_key i) i)
go found toSearch = case IntMap.minViewWithKey toSearch of go found toSearch = case IntMap.minViewWithKey toSearch of
Nothing -> pure found Nothing -> pure found
Just ((k, thisIn), restToSearch) -> do Just ((k, thisIn), restToSearch) -> do
getDualWeak (_nodeInput_contents thisIn :: DualWeak (NodeContents a)) >>= \case getNodeContents (_nodeInput_contents thisIn) >>= \case
Nothing -> go found restToSearch Nothing -> go found restToSearch
Just this -> do Just this -> do
newLinks <- readIORef (_nodeContents_forwardLinks this) newLinks <- readIORef (_nodeInput_forwardLinks thisIn)
go (IntMap.insert k (_nodeContents_value this) found) (IntMap.union restToSearch (newLinks `IntMap.difference` found)) go (IntMap.insert k this found) (IntMap.union restToSearch (newLinks `IntMap.difference` found))
findBackwardVals :: Ord a => NodeOutput a -> IO (Set a)
findBackwardVals i = Set.fromList . IntMap.elems <$> findBackward i
findBackward :: forall a. NodeOutput a -> IO (IntMap a) findBackward :: forall a. NodeOutput a -> IO (IntMap a)
findBackward o = go mempty (IntMap.singleton (_nodeOutput_key o) o) findBackward o = go mempty (IntMap.singleton (_nodeOutput_key o) o)
@ -188,17 +232,16 @@ findBackward o = go mempty (IntMap.singleton (_nodeOutput_key o) o)
go :: IntMap a -> IntMap (NodeOutput a) -> IO (IntMap a) go :: IntMap a -> IntMap (NodeOutput a) -> IO (IntMap a)
go found toSearch = case IntMap.minViewWithKey toSearch of go found toSearch = case IntMap.minViewWithKey toSearch of
Nothing -> pure found Nothing -> pure found
Just ((k, thisIn), restToSearch) -> do Just ((k, thisOut), restToSearch) -> do
getDualWeak (_nodeOutput_contents thisIn :: DualWeak (NodeContents a)) >>= \case getNodeContents (_nodeOutput_contents thisOut) >>= \case
Nothing -> go found restToSearch Nothing -> go found restToSearch
Just this -> do Just this -> do
newLinks <- readIORef (_nodeContents_backLinks this) newLinks <- readIORef (_nodeOutput_backLinks thisOut)
go (IntMap.insert k (_nodeContents_value this) found) (IntMap.union restToSearch (newLinks `IntMap.difference` found)) go (IntMap.insert k this found) (IntMap.union restToSearch (newLinks `IntMap.difference` found))
testDualWeak :: IO () testDualWeak :: IO ()
testDualWeak = do testDualWeak = do
do do
putStrLn "A"
target <- newIORef () target <- newIORef ()
r <- mkWeakWithIORefKey target () r <- mkWeakWithIORefKey target ()
(w, a, b) <- newDualWeak target (w, a, b) <- newDualWeak target
@ -209,7 +252,6 @@ testDualWeak = do
touch (a, b) touch (a, b)
performGCUntilFinalizersQuiesce performGCUntilFinalizersQuiesce
do do
putStrLn "B"
target <- newIORef () target <- newIORef ()
r <- mkWeakWithIORefKey target () r <- mkWeakWithIORefKey target ()
(w, a, _) <- newDualWeak target (w, a, _) <- newDualWeak target
@ -220,7 +262,6 @@ testDualWeak = do
touch a touch a
performGCUntilFinalizersQuiesce performGCUntilFinalizersQuiesce
do do
putStrLn "C"
target <- newIORef () target <- newIORef ()
r <- mkWeakWithIORefKey target () r <- mkWeakWithIORefKey target ()
(w, _, b) <- newDualWeak target (w, _, b) <- newDualWeak target