module Base.SCC (scc) where
import qualified Data.Set as Set (empty, member, insert)
data Node a b = Node { key :: Int, bvs :: [b], fvs :: [b], node :: a }
instance Eq (Node a b) where
n1 == n2 = key n1 == key n2
instance Ord (Node b a) where
n1 `compare` n2 = key n1 `compare` key n2
scc :: Eq b => (a -> [b])
-> (a -> [b])
-> [a]
-> [[a]]
scc bvs' fvs' = map (map node) . tsort' . tsort . zipWith wrap [0 ..]
where wrap i n = Node i (bvs' n) (fvs' n) n
tsort :: Eq b => [Node a b] -> [Node a b]
tsort xs = snd (dfs xs Set.empty []) where
dfs [] marks stack = (marks,stack)
dfs (x : xs') marks stack
| x `Set.member` marks = dfs xs' marks stack
| otherwise = dfs xs' marks' (x : stack')
where (marks',stack') = dfs (defs x) (x `Set.insert` marks) stack
defs x1 = filter (any (`elem` fvs x1) . bvs) xs
tsort' :: Eq b => [Node a b] -> [[Node a b]]
tsort' xs = snd (dfs xs Set.empty []) where
dfs [] marks stack = (marks,stack)
dfs (x : xs') marks stack
| x `Set.member` marks = dfs xs' marks stack
| otherwise = dfs xs' marks' ((x : concat stack') : stack)
where (marks',stack') = dfs (uses x) (x `Set.insert` marks) []
uses x1 = filter (any (`elem` bvs x1) . fvs) xs