{-# language LambdaCase #-}
module Algebra.Graph.AdjacencyIntMap.Algorithm (
bfsForest, bfs, dfsForest, dfsForestFrom, dfs, reachable,
topSort, isAcyclic,
isDfsForestOf, isTopSortOf,
Cycle
) where
import Control.Monad
import Control.Monad.Cont
import Control.Monad.State.Strict
import Data.Either
import Data.List.NonEmpty (NonEmpty(..),(<|))
import Data.Tree
import Algebra.Graph.AdjacencyIntMap
import qualified Data.List as List
import qualified Data.IntMap.Strict as IntMap
import qualified Data.IntSet as IntSet
bfsForest :: [Int] -> AdjacencyIntMap -> Forest Int
bfsForest :: [Int] -> AdjacencyIntMap -> Forest Int
bfsForest [Int]
vs AdjacencyIntMap
g = State IntSet (Forest Int) -> IntSet -> Forest Int
forall s a. State s a -> s -> a
evalState ([Int] -> State IntSet (Forest Int)
explore [ Int
v | Int
v <- [Int]
vs, Int -> AdjacencyIntMap -> Bool
hasVertex Int
v AdjacencyIntMap
g ]) IntSet
IntSet.empty where
explore :: [Int] -> State IntSet (Forest Int)
explore = (Int -> StateT IntSet Identity (Int, [Int]))
-> [Int] -> State IntSet (Forest Int)
forall (m :: * -> *) b a.
Monad m =>
(b -> m (a, [b])) -> [b] -> m (Forest a)
unfoldForestM_BF Int -> StateT IntSet Identity (Int, [Int])
walk ([Int] -> State IntSet (Forest Int))
-> ([Int] -> StateT IntSet Identity [Int])
-> [Int]
-> State IntSet (Forest Int)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (Int -> StateT IntSet Identity Bool)
-> [Int] -> StateT IntSet Identity [Int]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM Int -> StateT IntSet Identity Bool
forall (m :: * -> *). MonadState IntSet m => Int -> m Bool
discovered
walk :: Int -> StateT IntSet Identity (Int, [Int])
walk Int
v = (Int
v,) ([Int] -> (Int, [Int]))
-> StateT IntSet Identity [Int]
-> StateT IntSet Identity (Int, [Int])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> StateT IntSet Identity [Int]
adjacentM Int
v
adjacentM :: Int -> StateT IntSet Identity [Int]
adjacentM Int
v = (Int -> StateT IntSet Identity Bool)
-> [Int] -> StateT IntSet Identity [Int]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM Int -> StateT IntSet Identity Bool
forall (m :: * -> *). MonadState IntSet m => Int -> m Bool
discovered ([Int] -> StateT IntSet Identity [Int])
-> [Int] -> StateT IntSet Identity [Int]
forall a b. (a -> b) -> a -> b
$ IntSet -> [Int]
IntSet.toList (Int -> AdjacencyIntMap -> IntSet
postIntSet Int
v AdjacencyIntMap
g)
discovered :: Int -> m Bool
discovered Int
v = do Bool
new <- (IntSet -> Bool) -> m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (Bool -> Bool
not (Bool -> Bool) -> (IntSet -> Bool) -> IntSet -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> IntSet -> Bool
IntSet.member Int
v)
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
new (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ (IntSet -> IntSet) -> m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' (Int -> IntSet -> IntSet
IntSet.insert Int
v)
Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
new
bfs :: [Int] -> AdjacencyIntMap -> [[Int]]
bfs :: [Int] -> AdjacencyIntMap -> [[Int]]
bfs [Int]
vs = ([[Int]] -> [Int]) -> [[[Int]]] -> [[Int]]
forall a b. (a -> b) -> [a] -> [b]
map [[Int]] -> [Int]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[[Int]]] -> [[Int]])
-> (AdjacencyIntMap -> [[[Int]]]) -> AdjacencyIntMap -> [[Int]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Int]]] -> [[[Int]]]
forall a. [[a]] -> [[a]]
List.transpose ([[[Int]]] -> [[[Int]]])
-> (AdjacencyIntMap -> [[[Int]]]) -> AdjacencyIntMap -> [[[Int]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tree Int -> [[Int]]) -> Forest Int -> [[[Int]]]
forall a b. (a -> b) -> [a] -> [b]
map Tree Int -> [[Int]]
forall a. Tree a -> [[a]]
levels (Forest Int -> [[[Int]]])
-> (AdjacencyIntMap -> Forest Int) -> AdjacencyIntMap -> [[[Int]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> AdjacencyIntMap -> Forest Int
bfsForest [Int]
vs
dfsForest :: AdjacencyIntMap -> Forest Int
dfsForest :: AdjacencyIntMap -> Forest Int
dfsForest AdjacencyIntMap
g = [Int] -> AdjacencyIntMap -> Forest Int
dfsForestFrom' (AdjacencyIntMap -> [Int]
vertexList AdjacencyIntMap
g) AdjacencyIntMap
g
dfsForestFrom :: [Int] -> AdjacencyIntMap -> Forest Int
dfsForestFrom :: [Int] -> AdjacencyIntMap -> Forest Int
dfsForestFrom [Int]
vs AdjacencyIntMap
g = [Int] -> AdjacencyIntMap -> Forest Int
dfsForestFrom' [ Int
v | Int
v <- [Int]
vs, Int -> AdjacencyIntMap -> Bool
hasVertex Int
v AdjacencyIntMap
g ] AdjacencyIntMap
g
dfsForestFrom' :: [Int] -> AdjacencyIntMap -> Forest Int
dfsForestFrom' :: [Int] -> AdjacencyIntMap -> Forest Int
dfsForestFrom' [Int]
vs AdjacencyIntMap
g = State IntSet (Forest Int) -> IntSet -> Forest Int
forall s a. State s a -> s -> a
evalState ([Int] -> State IntSet (Forest Int)
explore [Int]
vs) IntSet
IntSet.empty where
explore :: [Int] -> State IntSet (Forest Int)
explore (Int
v:[Int]
vs) = Int -> StateT IntSet Identity Bool
forall (m :: * -> *). MonadState IntSet m => Int -> m Bool
discovered Int
v StateT IntSet Identity Bool
-> (Bool -> State IntSet (Forest Int)) -> State IntSet (Forest Int)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
True -> (:) (Tree Int -> Forest Int -> Forest Int)
-> StateT IntSet Identity (Tree Int)
-> StateT IntSet Identity (Forest Int -> Forest Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> StateT IntSet Identity (Tree Int)
walk Int
v StateT IntSet Identity (Forest Int -> Forest Int)
-> State IntSet (Forest Int) -> State IntSet (Forest Int)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Int] -> State IntSet (Forest Int)
explore [Int]
vs
Bool
False -> [Int] -> State IntSet (Forest Int)
explore [Int]
vs
explore [] = Forest Int -> State IntSet (Forest Int)
forall (m :: * -> *) a. Monad m => a -> m a
return []
walk :: Int -> StateT IntSet Identity (Tree Int)
walk Int
v = Int -> Forest Int -> Tree Int
forall a. a -> Forest a -> Tree a
Node Int
v (Forest Int -> Tree Int)
-> State IntSet (Forest Int) -> StateT IntSet Identity (Tree Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Int] -> State IntSet (Forest Int)
explore (Int -> [Int]
adjacent Int
v)
adjacent :: Int -> [Int]
adjacent Int
v = IntSet -> [Int]
IntSet.toList (Int -> AdjacencyIntMap -> IntSet
postIntSet Int
v AdjacencyIntMap
g)
discovered :: Int -> m Bool
discovered Int
v = do Bool
new <- (IntSet -> Bool) -> m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (Bool -> Bool
not (Bool -> Bool) -> (IntSet -> Bool) -> IntSet -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> IntSet -> Bool
IntSet.member Int
v)
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
new (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ (IntSet -> IntSet) -> m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' (Int -> IntSet -> IntSet
IntSet.insert Int
v)
Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
new
dfs :: [Int] -> AdjacencyIntMap -> [Int]
dfs :: [Int] -> AdjacencyIntMap -> [Int]
dfs [Int]
vs = [Int] -> AdjacencyIntMap -> Forest Int
dfsForestFrom [Int]
vs (AdjacencyIntMap -> Forest Int)
-> (Tree Int -> [Int]) -> AdjacencyIntMap -> [Int]
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Tree Int -> [Int]
forall a. Tree a -> [a]
flatten
reachable :: Int -> AdjacencyIntMap -> [Int]
reachable :: Int -> AdjacencyIntMap -> [Int]
reachable Int
x = [Int] -> AdjacencyIntMap -> [Int]
dfs [Int
x]
type Cycle = NonEmpty
data NodeState = Entered | Exited
data S = S { S -> IntMap Int
parent :: IntMap.IntMap Int
, S -> IntMap NodeState
entry :: IntMap.IntMap NodeState
, S -> [Int]
order :: [Int] }
topSort' :: (MonadState S m, MonadCont m)
=> AdjacencyIntMap -> m (Either (Cycle Int) [Int])
topSort' :: AdjacencyIntMap -> m (Either (Cycle Int) [Int])
topSort' AdjacencyIntMap
g = ((Either (Cycle Int) [Int] -> m ())
-> m (Either (Cycle Int) [Int]))
-> m (Either (Cycle Int) [Int])
forall (m :: * -> *) a b. MonadCont m => ((a -> m b) -> m a) -> m a
callCC (((Either (Cycle Int) [Int] -> m ())
-> m (Either (Cycle Int) [Int]))
-> m (Either (Cycle Int) [Int]))
-> ((Either (Cycle Int) [Int] -> m ())
-> m (Either (Cycle Int) [Int]))
-> m (Either (Cycle Int) [Int])
forall a b. (a -> b) -> a -> b
$ \Either (Cycle Int) [Int] -> m ()
cyclic ->
do let vertices :: [Int]
vertices = ((Int, IntSet) -> Int) -> [(Int, IntSet)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int, IntSet) -> Int
forall a b. (a, b) -> a
fst ([(Int, IntSet)] -> [Int]) -> [(Int, IntSet)] -> [Int]
forall a b. (a -> b) -> a -> b
$ IntMap IntSet -> [(Int, IntSet)]
forall a. IntMap a -> [(Int, a)]
IntMap.toDescList (IntMap IntSet -> [(Int, IntSet)])
-> IntMap IntSet -> [(Int, IntSet)]
forall a b. (a -> b) -> a -> b
$ AdjacencyIntMap -> IntMap IntSet
adjacencyIntMap AdjacencyIntMap
g
adjacent :: Int -> [Int]
adjacent = IntSet -> [Int]
IntSet.toDescList (IntSet -> [Int]) -> (Int -> IntSet) -> Int -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> AdjacencyIntMap -> IntSet)
-> AdjacencyIntMap -> Int -> IntSet
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> AdjacencyIntMap -> IntSet
postIntSet AdjacencyIntMap
g
dfsRoot :: Int -> m ()
dfsRoot Int
x = Int -> m (Maybe NodeState)
forall (m :: * -> *). MonadState S m => Int -> m (Maybe NodeState)
nodeState Int
x m (Maybe NodeState) -> (Maybe NodeState -> m ()) -> m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe NodeState
Nothing -> Int -> m ()
forall (m :: * -> *). MonadState S m => Int -> m ()
enterRoot Int
x m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> m ()
dfs Int
x m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> m ()
forall (m :: * -> *). MonadState S m => Int -> m ()
exit Int
x
Maybe NodeState
_ -> () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
dfs :: Int -> m ()
dfs Int
x = [Int] -> (Int -> m ()) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (Int -> [Int]
adjacent Int
x) ((Int -> m ()) -> m ()) -> (Int -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \Int
y ->
Int -> m (Maybe NodeState)
forall (m :: * -> *). MonadState S m => Int -> m (Maybe NodeState)
nodeState Int
y m (Maybe NodeState) -> (Maybe NodeState -> m ()) -> m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe NodeState
Nothing -> Int -> Int -> m ()
forall (m :: * -> *). MonadState S m => Int -> Int -> m ()
enter Int
x Int
y m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> m ()
dfs Int
y m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> m ()
forall (m :: * -> *). MonadState S m => Int -> m ()
exit Int
y
Just NodeState
Exited -> () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just NodeState
Entered -> Either (Cycle Int) [Int] -> m ()
cyclic (Either (Cycle Int) [Int] -> m ())
-> (IntMap Int -> Either (Cycle Int) [Int]) -> IntMap Int -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cycle Int -> Either (Cycle Int) [Int]
forall a b. a -> Either a b
Left (Cycle Int -> Either (Cycle Int) [Int])
-> (IntMap Int -> Cycle Int)
-> IntMap Int
-> Either (Cycle Int) [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> IntMap Int -> Cycle Int
retrace Int
x Int
y (IntMap Int -> m ()) -> m (IntMap Int) -> m ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (S -> IntMap Int) -> m (IntMap Int)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets S -> IntMap Int
parent
[Int] -> (Int -> m ()) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int]
vertices Int -> m ()
dfsRoot
[Int] -> Either (Cycle Int) [Int]
forall a b. b -> Either a b
Right ([Int] -> Either (Cycle Int) [Int])
-> m [Int] -> m (Either (Cycle Int) [Int])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (S -> [Int]) -> m [Int]
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets S -> [Int]
order
where
nodeState :: Int -> m (Maybe NodeState)
nodeState Int
v = (S -> Maybe NodeState) -> m (Maybe NodeState)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets (Int -> IntMap NodeState -> Maybe NodeState
forall a. Int -> IntMap a -> Maybe a
IntMap.lookup Int
v (IntMap NodeState -> Maybe NodeState)
-> (S -> IntMap NodeState) -> S -> Maybe NodeState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. S -> IntMap NodeState
entry)
enter :: Int -> Int -> m ()
enter Int
u Int
v = (S -> S) -> m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' (\(S IntMap Int
m IntMap NodeState
n [Int]
vs) -> IntMap Int -> IntMap NodeState -> [Int] -> S
S (Int -> Int -> IntMap Int -> IntMap Int
forall a. Int -> a -> IntMap a -> IntMap a
IntMap.insert Int
v Int
u IntMap Int
m)
(Int -> NodeState -> IntMap NodeState -> IntMap NodeState
forall a. Int -> a -> IntMap a -> IntMap a
IntMap.insert Int
v NodeState
Entered IntMap NodeState
n)
[Int]
vs)
enterRoot :: Int -> m ()
enterRoot Int
v = (S -> S) -> m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' (\(S IntMap Int
m IntMap NodeState
n [Int]
vs) -> IntMap Int -> IntMap NodeState -> [Int] -> S
S IntMap Int
m (Int -> NodeState -> IntMap NodeState -> IntMap NodeState
forall a. Int -> a -> IntMap a -> IntMap a
IntMap.insert Int
v NodeState
Entered IntMap NodeState
n) [Int]
vs)
exit :: Int -> m ()
exit Int
v = (S -> S) -> m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify' (\(S IntMap Int
m IntMap NodeState
n [Int]
vs) -> IntMap Int -> IntMap NodeState -> [Int] -> S
S IntMap Int
m ((Maybe NodeState -> Maybe NodeState)
-> Int -> IntMap NodeState -> IntMap NodeState
forall a. (Maybe a -> Maybe a) -> Int -> IntMap a -> IntMap a
IntMap.alter ((NodeState -> NodeState) -> Maybe NodeState -> Maybe NodeState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NodeState -> NodeState
leave) Int
v IntMap NodeState
n) (Int
vInt -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
vs))
where leave :: NodeState -> NodeState
leave = \case
NodeState
Entered -> NodeState
Exited
NodeState
Exited -> [Char] -> NodeState
forall a. HasCallStack => [Char] -> a
error [Char]
"Internal error: dfs search order violated"
retrace :: Int -> Int -> IntMap Int -> Cycle Int
retrace Int
curr Int
head IntMap Int
parent = Cycle Int -> Cycle Int
aux (Int
curr Int -> [Int] -> Cycle Int
forall a. a -> [a] -> NonEmpty a
:| []) where
aux :: Cycle Int -> Cycle Int
aux xs :: Cycle Int
xs@(Int
curr :| [Int]
_)
| Int
head Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
curr = Cycle Int
xs
| Bool
otherwise = Cycle Int -> Cycle Int
aux (IntMap Int
parent IntMap Int -> Int -> Int
forall a. IntMap a -> Int -> a
IntMap.! Int
curr Int -> Cycle Int -> Cycle Int
forall a. a -> NonEmpty a -> NonEmpty a
<| Cycle Int
xs)
topSort :: AdjacencyIntMap -> Either (Cycle Int) [Int]
topSort :: AdjacencyIntMap -> Either (Cycle Int) [Int]
topSort AdjacencyIntMap
g = ContT [Int] (Either (Cycle Int)) (Either (Cycle Int) [Int])
-> (Either (Cycle Int) [Int] -> Either (Cycle Int) [Int])
-> Either (Cycle Int) [Int]
forall k (r :: k) (m :: k -> *) a. ContT r m a -> (a -> m r) -> m r
runContT (StateT
S (ContT [Int] (Either (Cycle Int))) (Either (Cycle Int) [Int])
-> S -> ContT [Int] (Either (Cycle Int)) (Either (Cycle Int) [Int])
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (AdjacencyIntMap
-> StateT
S (ContT [Int] (Either (Cycle Int))) (Either (Cycle Int) [Int])
forall (m :: * -> *).
(MonadState S m, MonadCont m) =>
AdjacencyIntMap -> m (Either (Cycle Int) [Int])
topSort' AdjacencyIntMap
g) S
initialState) Either (Cycle Int) [Int] -> Either (Cycle Int) [Int]
forall a. a -> a
id where
initialState :: S
initialState = IntMap Int -> IntMap NodeState -> [Int] -> S
S IntMap Int
forall a. IntMap a
IntMap.empty IntMap NodeState
forall a. IntMap a
IntMap.empty []
isAcyclic :: AdjacencyIntMap -> Bool
isAcyclic :: AdjacencyIntMap -> Bool
isAcyclic = Either (Cycle Int) [Int] -> Bool
forall a b. Either a b -> Bool
isRight (Either (Cycle Int) [Int] -> Bool)
-> (AdjacencyIntMap -> Either (Cycle Int) [Int])
-> AdjacencyIntMap
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AdjacencyIntMap -> Either (Cycle Int) [Int]
topSort
isDfsForestOf :: Forest Int -> AdjacencyIntMap -> Bool
isDfsForestOf :: Forest Int -> AdjacencyIntMap -> Bool
isDfsForestOf Forest Int
f AdjacencyIntMap
am = case IntSet -> Forest Int -> Maybe IntSet
go IntSet
IntSet.empty Forest Int
f of
Just IntSet
seen -> IntSet
seen IntSet -> IntSet -> Bool
forall a. Eq a => a -> a -> Bool
== AdjacencyIntMap -> IntSet
vertexIntSet AdjacencyIntMap
am
Maybe IntSet
Nothing -> Bool
False
where
go :: IntSet -> Forest Int -> Maybe IntSet
go IntSet
seen [] = IntSet -> Maybe IntSet
forall a. a -> Maybe a
Just IntSet
seen
go IntSet
seen (Tree Int
t:Forest Int
ts) = do
let root :: Int
root = Tree Int -> Int
forall a. Tree a -> a
rootLabel Tree Int
t
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Int
root Int -> IntSet -> Bool
`IntSet.notMember` IntSet
seen
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and [ Int -> Int -> AdjacencyIntMap -> Bool
hasEdge Int
root (Tree Int -> Int
forall a. Tree a -> a
rootLabel Tree Int
subTree) AdjacencyIntMap
am | Tree Int
subTree <- Tree Int -> Forest Int
forall a. Tree a -> Forest a
subForest Tree Int
t ]
IntSet
newSeen <- IntSet -> Forest Int -> Maybe IntSet
go (Int -> IntSet -> IntSet
IntSet.insert Int
root IntSet
seen) (Tree Int -> Forest Int
forall a. Tree a -> Forest a
subForest Tree Int
t)
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Int -> AdjacencyIntMap -> IntSet
postIntSet Int
root AdjacencyIntMap
am IntSet -> IntSet -> Bool
`IntSet.isSubsetOf` IntSet
newSeen
IntSet -> Forest Int -> Maybe IntSet
go IntSet
newSeen Forest Int
ts
isTopSortOf :: [Int] -> AdjacencyIntMap -> Bool
isTopSortOf :: [Int] -> AdjacencyIntMap -> Bool
isTopSortOf [Int]
xs AdjacencyIntMap
m = IntSet -> [Int] -> Bool
go IntSet
IntSet.empty [Int]
xs
where
go :: IntSet -> [Int] -> Bool
go IntSet
seen [] = IntSet
seen IntSet -> IntSet -> Bool
forall a. Eq a => a -> a -> Bool
== IntMap IntSet -> IntSet
forall a. IntMap a -> IntSet
IntMap.keysSet (AdjacencyIntMap -> IntMap IntSet
adjacencyIntMap AdjacencyIntMap
m)
go IntSet
seen (Int
v:[Int]
vs) = Int -> AdjacencyIntMap -> IntSet
postIntSet Int
v AdjacencyIntMap
m IntSet -> IntSet -> IntSet
`IntSet.intersection` IntSet
newSeen IntSet -> IntSet -> Bool
forall a. Eq a => a -> a -> Bool
== IntSet
IntSet.empty
Bool -> Bool -> Bool
&& IntSet -> [Int] -> Bool
go IntSet
newSeen [Int]
vs
where
newSeen :: IntSet
newSeen = Int -> IntSet -> IntSet
IntSet.insert Int
v IntSet
seen