{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE StandaloneDeriving #-}
# if __GLASGOW_HASKELL__ >= 710
{-# LANGUAGE Safe #-}
# else
{-# LANGUAGE Trustworthy #-}
# endif
#endif

#include "containers.h"

-----------------------------------------------------------------------------
-- |
-- Module      :  Data.Graph
-- Copyright   :  (c) The University of Glasgow 2002
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Portability :  portable
--
-- = Finite Graphs
--
-- The @'Graph'@ type is an adjacency list representation of a finite, directed
-- graph with vertices of type @Int@.
--
-- The @'SCC'@ type represents a
-- <https://en.wikipedia.org/wiki/Strongly_connected_component strongly-connected component>
-- of a graph.
--
-- == Implementation
--
-- The implementation is based on
--
--   * /Structuring Depth-First Search Algorithms in Haskell/,
--     by David King and John Launchbury, <http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.52.6526>
--
-----------------------------------------------------------------------------

module Data.Graph (

    -- * Graphs
      Graph
    , Bounds
    , Edge
    , Vertex
    , Table

    -- ** Graph Construction
    , graphFromEdges
    , graphFromEdges'
    , buildG

    -- ** Graph Properties
    , vertices
    , edges
    , outdegree
    , indegree

    -- ** Graph Transformations
    , transposeG

    -- ** Graph Algorithms
    , dfs
    , dff
    , topSort
    , components
    , scc
    , bcc
    , reachable
    , path


    -- * Strongly Connected Components
    , SCC(..)

    -- ** Construction
    , stronglyConnComp
    , stronglyConnCompR

    -- ** Conversion
    , flattenSCC
    , flattenSCCs

    -- * Trees
    , module Data.Tree

    ) where

#if USE_ST_MONAD
import Control.Monad.ST
import Data.Array.ST.Safe (newArray, readArray, writeArray)
# if USE_UNBOXED_ARRAYS
import Data.Array.ST.Safe (STUArray)
# else
import Data.Array.ST.Safe (STArray)
# endif
#else
import Data.IntSet (IntSet)
import qualified Data.IntSet as Set
#endif
import Data.Tree (Tree(Node), Forest)

-- std interfaces
import Control.Applicative
#if !MIN_VERSION_base(4,8,0)
import qualified Data.Foldable as F
import Data.Traversable
#else
import Data.Foldable as F
#endif
import Control.DeepSeq (NFData(rnf))
import Data.Maybe
import Data.Array
#if USE_UNBOXED_ARRAYS
import qualified Data.Array.Unboxed as UA
import Data.Array.Unboxed ( UArray )
#else
import qualified Data.Array as UA
#endif
import Data.List
#if MIN_VERSION_base(4,9,0)
import Data.Functor.Classes
#endif
#if (!MIN_VERSION_base(4,11,0)) && MIN_VERSION_base(4,9,0)
import Data.Semigroup (Semigroup (..))
#endif
#ifdef __GLASGOW_HASKELL__
import GHC.Generics (Generic, Generic1)
import Data.Data (Data)
import Data.Typeable
#endif

-- Make sure we don't use Integer by mistake.
default ()

-------------------------------------------------------------------------
--                                                                      -
--      Strongly Connected Components
--                                                                      -
-------------------------------------------------------------------------

-- | Strongly connected component.
data SCC vertex = AcyclicSCC vertex     -- ^ A single vertex that is not
                                        -- in any cycle.
                | CyclicSCC  [vertex]   -- ^ A maximal set of mutually
                                        -- reachable vertices.
#if __GLASGOW_HASKELL__ >= 802
  deriving ( Eq   -- ^ @since 0.5.9
           , Show -- ^ @since 0.5.9
           , Read -- ^ @since 0.5.9
           )
#else
  deriving (Eq, Show, Read)
#endif

INSTANCE_TYPEABLE1(SCC)

#ifdef __GLASGOW_HASKELL__
-- | @since 0.5.9
deriving instance Data vertex => Data (SCC vertex)

-- | @since 0.5.9
deriving instance Generic1 SCC

-- | @since 0.5.9
deriving instance Generic (SCC vertex)
#endif

#if MIN_VERSION_base(4,9,0)
-- | @since 0.5.9
instance Eq1 SCC where
  liftEq :: (a -> b -> Bool) -> SCC a -> SCC b -> Bool
liftEq a -> b -> Bool
eq (AcyclicSCC a
v1) (AcyclicSCC b
v2) = a -> b -> Bool
eq a
v1 b
v2
  liftEq a -> b -> Bool
eq (CyclicSCC [a]
vs1) (CyclicSCC [b]
vs2) = (a -> b -> Bool) -> [a] -> [b] -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq [a]
vs1 [b]
vs2
  liftEq a -> b -> Bool
_ SCC a
_ SCC b
_ = Bool
False
-- | @since 0.5.9
instance Show1 SCC where
  liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> SCC a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
_sl Int
d (AcyclicSCC a
v) = (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith Int -> a -> ShowS
sp String
"AcyclicSCC" Int
d a
v
  liftShowsPrec Int -> a -> ShowS
_sp [a] -> ShowS
sl Int
d (CyclicSCC [a]
vs) = (Int -> [a] -> ShowS) -> String -> Int -> [a] -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith (([a] -> ShowS) -> Int -> [a] -> ShowS
forall a b. a -> b -> a
const [a] -> ShowS
sl) String
"CyclicSCC" Int
d [a]
vs
-- | @since 0.5.9
instance Read1 SCC where
  liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (SCC a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl = (String -> ReadS (SCC a)) -> Int -> ReadS (SCC a)
forall a. (String -> ReadS a) -> Int -> ReadS a
readsData ((String -> ReadS (SCC a)) -> Int -> ReadS (SCC a))
-> (String -> ReadS (SCC a)) -> Int -> ReadS (SCC a)
forall a b. (a -> b) -> a -> b
$
    (Int -> ReadS a)
-> String -> (a -> SCC a) -> String -> ReadS (SCC a)
forall a t.
(Int -> ReadS a) -> String -> (a -> t) -> String -> ReadS t
readsUnaryWith Int -> ReadS a
rp String
"AcyclicSCC" a -> SCC a
forall vertex. vertex -> SCC vertex
AcyclicSCC (String -> ReadS (SCC a))
-> (String -> ReadS (SCC a)) -> String -> ReadS (SCC a)
forall a. Semigroup a => a -> a -> a
<>
    (Int -> ReadS [a])
-> String -> ([a] -> SCC a) -> String -> ReadS (SCC a)
forall a t.
(Int -> ReadS a) -> String -> (a -> t) -> String -> ReadS t
readsUnaryWith (ReadS [a] -> Int -> ReadS [a]
forall a b. a -> b -> a
const ReadS [a]
rl) String
"CyclicSCC" [a] -> SCC a
forall vertex. [vertex] -> SCC vertex
CyclicSCC
#endif

-- | @since 0.5.9
instance F.Foldable SCC where
  foldr :: (a -> b -> b) -> b -> SCC a -> b
foldr a -> b -> b
c b
n (AcyclicSCC a
v) = a -> b -> b
c a
v b
n
  foldr a -> b -> b
c b
n (CyclicSCC [a]
vs) = (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> b -> b
c b
n [a]
vs

-- | @since 0.5.9
instance Traversable SCC where
  -- We treat the non-empty cyclic case specially to cut one
  -- fmap application.
  traverse :: (a -> f b) -> SCC a -> f (SCC b)
traverse a -> f b
f (AcyclicSCC a
vertex) = b -> SCC b
forall vertex. vertex -> SCC vertex
AcyclicSCC (b -> SCC b) -> f b -> f (SCC b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
vertex
  traverse a -> f b
_f (CyclicSCC []) = SCC b -> f (SCC b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([b] -> SCC b
forall vertex. [vertex] -> SCC vertex
CyclicSCC [])
  traverse a -> f b
f (CyclicSCC (a
x : [a]
xs)) =
    (b -> [b] -> SCC b) -> f b -> f [b] -> f (SCC b)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\b
x' [b]
xs' -> [b] -> SCC b
forall vertex. [vertex] -> SCC vertex
CyclicSCC (b
x' b -> [b] -> [b]
forall a. a -> [a] -> [a]
: [b]
xs')) (a -> f b
f a
x) ((a -> f b) -> [a] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f [a]
xs)

instance NFData a => NFData (SCC a) where
    rnf :: SCC a -> ()
rnf (AcyclicSCC a
v) = a -> ()
forall a. NFData a => a -> ()
rnf a
v
    rnf (CyclicSCC [a]
vs) = [a] -> ()
forall a. NFData a => a -> ()
rnf [a]
vs

-- | @since 0.5.4
instance Functor SCC where
    fmap :: (a -> b) -> SCC a -> SCC b
fmap a -> b
f (AcyclicSCC a
v) = b -> SCC b
forall vertex. vertex -> SCC vertex
AcyclicSCC (a -> b
f a
v)
    fmap a -> b
f (CyclicSCC [a]
vs) = [b] -> SCC b
forall vertex. [vertex] -> SCC vertex
CyclicSCC ((a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f [a]
vs)

-- | The vertices of a list of strongly connected components.
flattenSCCs :: [SCC a] -> [a]
flattenSCCs :: [SCC a] -> [a]
flattenSCCs = (SCC a -> [a]) -> [SCC a] -> [a]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap SCC a -> [a]
forall a. SCC a -> [a]
flattenSCC

-- | The vertices of a strongly connected component.
flattenSCC :: SCC vertex -> [vertex]
flattenSCC :: SCC vertex -> [vertex]
flattenSCC (AcyclicSCC vertex
v) = [vertex
v]
flattenSCC (CyclicSCC [vertex]
vs) = [vertex]
vs

-- | The strongly connected components of a directed graph, reverse topologically
-- sorted.
--
-- ==== __Examples__
--
-- > stronglyConnComp [("a",0,[1]),("b",1,[2,3]),("c",2,[1]),("d",3,[3])]
-- >   == [CyclicSCC ["d"],CyclicSCC ["b","c"],AcyclicSCC "a"]
stronglyConnComp
        :: Ord key
        => [(node, key, [key])]
                -- ^ The graph: a list of nodes uniquely identified by keys,
                -- with a list of keys of nodes this node has edges to.
                -- The out-list may contain keys that don't correspond to
                -- nodes of the graph; such edges are ignored.
        -> [SCC node]

stronglyConnComp :: [(node, key, [key])] -> [SCC node]
stronglyConnComp [(node, key, [key])]
edges0
  = (SCC (node, key, [key]) -> SCC node)
-> [SCC (node, key, [key])] -> [SCC node]
forall a b. (a -> b) -> [a] -> [b]
map SCC (node, key, [key]) -> SCC node
forall vertex b c. SCC (vertex, b, c) -> SCC vertex
get_node ([(node, key, [key])] -> [SCC (node, key, [key])]
forall key node.
Ord key =>
[(node, key, [key])] -> [SCC (node, key, [key])]
stronglyConnCompR [(node, key, [key])]
edges0)
  where
    get_node :: SCC (vertex, b, c) -> SCC vertex
get_node (AcyclicSCC (vertex
n, b
_, c
_)) = vertex -> SCC vertex
forall vertex. vertex -> SCC vertex
AcyclicSCC vertex
n
    get_node (CyclicSCC [(vertex, b, c)]
triples)     = [vertex] -> SCC vertex
forall vertex. [vertex] -> SCC vertex
CyclicSCC [vertex
n | (vertex
n,b
_,c
_) <- [(vertex, b, c)]
triples]

-- | The strongly connected components of a directed graph, reverse topologically
-- sorted.  The function is the same as 'stronglyConnComp', except that
-- all the information about each node retained.
-- This interface is used when you expect to apply 'SCC' to
-- (some of) the result of 'SCC', so you don't want to lose the
-- dependency information.
--
-- ==== __Examples__
--
-- > stronglyConnCompR [("a",0,[1]),("b",1,[2,3]),("c",2,[1]),("d",3,[3])]
-- >  == [CyclicSCC [("d",3,[3])],CyclicSCC [("b",1,[2,3]),("c",2,[1])],AcyclicSCC ("a",0,[1])]
stronglyConnCompR
        :: Ord key
        => [(node, key, [key])]
                -- ^ The graph: a list of nodes uniquely identified by keys,
                -- with a list of keys of nodes this node has edges to.
                -- The out-list may contain keys that don't correspond to
                -- nodes of the graph; such edges are ignored.
        -> [SCC (node, key, [key])]     -- ^ Reverse topologically sorted

stronglyConnCompR :: [(node, key, [key])] -> [SCC (node, key, [key])]
stronglyConnCompR [] = []  -- added to avoid creating empty array in graphFromEdges -- SOF
stronglyConnCompR [(node, key, [key])]
edges0
  = (Tree Int -> SCC (node, key, [key]))
-> [Tree Int] -> [SCC (node, key, [key])]
forall a b. (a -> b) -> [a] -> [b]
map Tree Int -> SCC (node, key, [key])
decode [Tree Int]
forest
  where
    (Graph
graph, Int -> (node, key, [key])
vertex_fn,key -> Maybe Int
_) = [(node, key, [key])]
-> (Graph, Int -> (node, key, [key]), key -> Maybe Int)
forall key node.
Ord key =>
[(node, key, [key])]
-> (Graph, Int -> (node, key, [key]), key -> Maybe Int)
graphFromEdges [(node, key, [key])]
edges0
    forest :: [Tree Int]
forest             = Graph -> [Tree Int]
scc Graph
graph
    decode :: Tree Int -> SCC (node, key, [key])
decode (Node Int
v []) | Int -> Bool
mentions_itself Int
v = [(node, key, [key])] -> SCC (node, key, [key])
forall vertex. [vertex] -> SCC vertex
CyclicSCC [Int -> (node, key, [key])
vertex_fn Int
v]
                       | Bool
otherwise         = (node, key, [key]) -> SCC (node, key, [key])
forall vertex. vertex -> SCC vertex
AcyclicSCC (Int -> (node, key, [key])
vertex_fn Int
v)
    decode Tree Int
other = [(node, key, [key])] -> SCC (node, key, [key])
forall vertex. [vertex] -> SCC vertex
CyclicSCC (Tree Int -> [(node, key, [key])] -> [(node, key, [key])]
dec Tree Int
other [])
                 where
                   dec :: Tree Int -> [(node, key, [key])] -> [(node, key, [key])]
dec (Node Int
v [Tree Int]
ts) [(node, key, [key])]
vs = Int -> (node, key, [key])
vertex_fn Int
v (node, key, [key]) -> [(node, key, [key])] -> [(node, key, [key])]
forall a. a -> [a] -> [a]
: (Tree Int -> [(node, key, [key])] -> [(node, key, [key])])
-> [(node, key, [key])] -> [Tree Int] -> [(node, key, [key])]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Tree Int -> [(node, key, [key])] -> [(node, key, [key])]
dec [(node, key, [key])]
vs [Tree Int]
ts
    mentions_itself :: Int -> Bool
mentions_itself Int
v = Int
v Int -> [Int] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Graph
graph Graph -> Int -> [Int]
forall i e. Ix i => Array i e -> i -> e
! Int
v)

-------------------------------------------------------------------------
--                                                                      -
--      Graphs
--                                                                      -
-------------------------------------------------------------------------

-- | Abstract representation of vertices.
type Vertex  = Int
-- | Table indexed by a contiguous set of vertices.
--
-- /Note: This is included for backwards compatibility./
type Table a = Array Vertex a
-- | Adjacency list representation of a graph, mapping each vertex to its
-- list of successors.
type Graph   = Array Vertex [Vertex]
-- | The bounds of an @Array@.
type Bounds  = (Vertex, Vertex)
-- | An edge from the first vertex to the second.
type Edge    = (Vertex, Vertex)

#if !USE_UNBOXED_ARRAYS
type UArray i a = Array i a
#endif

-- | Returns the list of vertices in the graph.
--
-- ==== __Examples__
--
-- > vertices (buildG (0,-1) []) == []
--
-- > vertices (buildG (0,2) [(0,1),(1,2)]) == [0,1,2]
vertices :: Graph -> [Vertex]
vertices :: Graph -> [Int]
vertices  = Graph -> [Int]
forall i e. Ix i => Array i e -> [i]
indices

-- | Returns the list of edges in the graph.
--
-- ==== __Examples__
--
-- > edges (buildG (0,-1) []) == []
--
-- > edges (buildG (0,2) [(0,1),(1,2)]) == [(0,1),(1,2)]
edges    :: Graph -> [Edge]
edges :: Graph -> [Edge]
edges Graph
g   = [ (Int
v, Int
w) | Int
v <- Graph -> [Int]
vertices Graph
g, Int
w <- Graph
gGraph -> Int -> [Int]
forall i e. Ix i => Array i e -> i -> e
!Int
v ]

-- | Build a graph from a list of edges.
--
-- Warning: This function will cause a runtime exception if a vertex in the edge
-- list is not within the given @Bounds@.
--
-- ==== __Examples__
--
-- > buildG (0,-1) [] == array (0,-1) []
-- > buildG (0,2) [(0,1), (1,2)] == array (0,1) [(0,[1]),(1,[2])]
-- > buildG (0,2) [(0,1), (0,2), (1,2)] == array (0,2) [(0,[2,1]),(1,[2]),(2,[])]
buildG :: Bounds -> [Edge] -> Graph
buildG :: Edge -> [Edge] -> Graph
buildG Edge
bounds0 [Edge]
edges0 = ([Int] -> Int -> [Int]) -> [Int] -> Edge -> [Edge] -> Graph
forall i e a.
Ix i =>
(e -> a -> e) -> e -> (i, i) -> [(i, a)] -> Array i e
accumArray ((Int -> [Int] -> [Int]) -> [Int] -> Int -> [Int]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (:)) [] Edge
bounds0 [Edge]
edges0

-- | The graph obtained by reversing all edges.
--
-- ==== __Examples__
--
-- > transposeG (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,[]),(1,[0]),(2,[1])]
transposeG  :: Graph -> Graph
transposeG :: Graph -> Graph
transposeG Graph
g = Edge -> [Edge] -> Graph
buildG (Graph -> Edge
forall i e. Array i e -> (i, i)
bounds Graph
g) (Graph -> [Edge]
reverseE Graph
g)

reverseE    :: Graph -> [Edge]
reverseE :: Graph -> [Edge]
reverseE Graph
g   = [ (Int
w, Int
v) | (Int
v, Int
w) <- Graph -> [Edge]
edges Graph
g ]

-- | A table of the count of edges from each node.
--
-- ==== __Examples__
--
-- > outdegree (buildG (0,-1) []) == array (0,-1) []
--
-- > outdegree (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,1),(1,1),(2,0)]
outdegree :: Graph -> Array Vertex Int
-- This is bizarrely lazy. We build an array filled with thunks, instead
-- of actually calculating anything. This is the historical behavior, and I
-- suppose someone *could* be relying on it, but it might be worth finding
-- out. Note that we *can't* be so lazy with indegree.
outdegree :: Graph -> Array Int Int
outdegree  = ([Int] -> Int) -> Graph -> Array Int Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length

-- | A table of the count of edges into each node.
--
-- ==== __Examples__
--
-- > indegree (buildG (0,-1) []) == array (0,-1) []
--
-- > indegree (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,0),(1,1),(2,1)]
indegree :: Graph -> Array Vertex Int
indegree :: Graph -> Array Int Int
indegree Graph
g = (Int -> Int -> Int) -> Int -> Edge -> [Edge] -> Array Int Int
forall i e a.
Ix i =>
(e -> a -> e) -> e -> (i, i) -> [(i, a)] -> Array i e
accumArray Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) Int
0 (Graph -> Edge
forall i e. Array i e -> (i, i)
bounds Graph
g) [(Int
v, Int
1) | (Int
_, [Int]
outs) <- Graph -> [(Int, [Int])]
forall i e. Ix i => Array i e -> [(i, e)]
assocs Graph
g, Int
v <- [Int]
outs]

-- | Identical to 'graphFromEdges', except that the return value
-- does not include the function which maps keys to vertices.  This
-- version of 'graphFromEdges' is for backwards compatibility.
graphFromEdges'
        :: Ord key
        => [(node, key, [key])]
        -> (Graph, Vertex -> (node, key, [key]))
graphFromEdges' :: [(node, key, [key])] -> (Graph, Int -> (node, key, [key]))
graphFromEdges' [(node, key, [key])]
x = (Graph
a,Int -> (node, key, [key])
b) where
    (Graph
a,Int -> (node, key, [key])
b,key -> Maybe Int
_) = [(node, key, [key])]
-> (Graph, Int -> (node, key, [key]), key -> Maybe Int)
forall key node.
Ord key =>
[(node, key, [key])]
-> (Graph, Int -> (node, key, [key]), key -> Maybe Int)
graphFromEdges [(node, key, [key])]
x

-- | Build a graph from a list of nodes uniquely identified by keys,
-- with a list of keys of nodes this node should have edges to.
--
-- This function takes an adjacency list representing a graph with vertices of
-- type @key@ labeled by values of type @node@ and produces a @Graph@-based
-- representation of that list. The @Graph@ result represents the /shape/ of the
-- graph, and the functions describe a) how to retrieve the label and adjacent
-- vertices of a given vertex, and b) how to retrive a vertex given a key.
--
-- @(graph, nodeFromVertex, vertexFromKey) = graphFromEdges edgeList@
--
-- * @graph :: Graph@ is the raw, array based adjacency list for the graph.
-- * @nodeFromVertex :: Vertex -> (node, key, [key])@ returns the node
--   associated with the given 0-based @Int@ vertex; see /warning/ below.
-- * @vertexFromKey :: key -> Maybe Vertex@ returns the @Int@ vertex for the
--   key if it exists in the graph, @Nothing@ otherwise.
--
-- To safely use this API you must either extract the list of vertices directly
-- from the graph or first call @vertexFromKey k@ to check if a vertex
-- corresponds to the key @k@. Once it is known that a vertex exists you can use
-- @nodeFromVertex@ to access the labelled node and adjacent vertices. See below
-- for examples.
--
-- Note: The out-list may contain keys that don't correspond to nodes of the
-- graph; they are ignored.
--
-- Warning: The @nodeFromVertex@ function will cause a runtime exception if the
-- given @Vertex@ does not exist.
--
-- ==== __Examples__
--
-- An empty graph.
--
-- > (graph, nodeFromVertex, vertexFromKey) = graphFromEdges []
-- > graph = array (0,-1) []
--
-- A graph where the out-list references unspecified nodes (@\'c\'@), these are
-- ignored.
--
-- > (graph, _, _) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c'])]
-- > array (0,1) [(0,[1]),(1,[])]
--
--
-- A graph with 3 vertices: ("a") -> ("b") -> ("c")
--
-- > (graph, nodeFromVertex, vertexFromKey) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c']), ("c", 'c', [])]
-- > graph == array (0,2) [(0,[1]),(1,[2]),(2,[])]
-- > nodeFromVertex 0 == ("a",'a',"b")
-- > vertexFromKey 'a' == Just 0
--
-- Get the label for a given key.
--
-- > let getNodePart (n, _, _) = n
-- > (graph, nodeFromVertex, vertexFromKey) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c']), ("c", 'c', [])]
-- > getNodePart . nodeFromVertex <$> vertexFromKey 'a' == Just "A"
--
graphFromEdges
        :: Ord key
        => [(node, key, [key])]
        -> (Graph, Vertex -> (node, key, [key]), key -> Maybe Vertex)
graphFromEdges :: [(node, key, [key])]
-> (Graph, Int -> (node, key, [key]), key -> Maybe Int)
graphFromEdges [(node, key, [key])]
edges0
  = (Graph
graph, \Int
v -> Array Int (node, key, [key])
vertex_map Array Int (node, key, [key]) -> Int -> (node, key, [key])
forall i e. Ix i => Array i e -> i -> e
! Int
v, key -> Maybe Int
key_vertex)
  where
    max_v :: Int
max_v           = [(node, key, [key])] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(node, key, [key])]
edges0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
    bounds0 :: Edge
bounds0         = (Int
0,Int
max_v) :: (Vertex, Vertex)
    sorted_edges :: [(node, key, [key])]
sorted_edges    = ((node, key, [key]) -> (node, key, [key]) -> Ordering)
-> [(node, key, [key])] -> [(node, key, [key])]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (node, key, [key]) -> (node, key, [key]) -> Ordering
forall a a c a c. Ord a => (a, a, c) -> (a, a, c) -> Ordering
lt [(node, key, [key])]
edges0
    edges1 :: [(Int, (node, key, [key]))]
edges1          = (Int -> (node, key, [key]) -> (Int, (node, key, [key])))
-> [Int] -> [(node, key, [key])] -> [(Int, (node, key, [key]))]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (,) [Int
0..] [(node, key, [key])]
sorted_edges

    graph :: Graph
graph           = Edge -> [(Int, [Int])] -> Graph
forall i e. Ix i => (i, i) -> [(i, e)] -> Array i e
array Edge
bounds0 [(,) Int
v ((key -> Maybe Int) -> [key] -> [Int]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe key -> Maybe Int
key_vertex [key]
ks) | (,) Int
v (node
_,    key
_, [key]
ks) <- [(Int, (node, key, [key]))]
edges1]
    key_map :: Array Int key
key_map         = Edge -> [(Int, key)] -> Array Int key
forall i e. Ix i => (i, i) -> [(i, e)] -> Array i e
array Edge
bounds0 [(,) Int
v key
k                       | (,) Int
v (node
_,    key
k, [key]
_ ) <- [(Int, (node, key, [key]))]
edges1]
    vertex_map :: Array Int (node, key, [key])
vertex_map      = Edge -> [(Int, (node, key, [key]))] -> Array Int (node, key, [key])
forall i e. Ix i => (i, i) -> [(i, e)] -> Array i e
array Edge
bounds0 [(Int, (node, key, [key]))]
edges1

    (a
_,a
k1,c
_) lt :: (a, a, c) -> (a, a, c) -> Ordering
`lt` (a
_,a
k2,c
_) = a
k1 a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` a
k2

    -- key_vertex :: key -> Maybe Vertex
    --  returns Nothing for non-interesting vertices
    key_vertex :: key -> Maybe Int
key_vertex key
k   = Int -> Int -> Maybe Int
findVertex Int
0 Int
max_v
                   where
                     findVertex :: Int -> Int -> Maybe Int
findVertex Int
a Int
b | Int
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
b
                              = Maybe Int
forall a. Maybe a
Nothing
                     findVertex Int
a Int
b = case key -> key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare key
k (Array Int key
key_map Array Int key -> Int -> key
forall i e. Ix i => Array i e -> i -> e
! Int
mid) of
                                   Ordering
LT -> Int -> Int -> Maybe Int
findVertex Int
a (Int
midInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
                                   Ordering
EQ -> Int -> Maybe Int
forall a. a -> Maybe a
Just Int
mid
                                   Ordering
GT -> Int -> Int -> Maybe Int
findVertex (Int
midInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
b
                              where
                                mid :: Int
mid = Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
b Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
a) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2

-------------------------------------------------------------------------
--                                                                      -
--      Depth first search
--                                                                      -
-------------------------------------------------------------------------

-- | A spanning forest of the graph, obtained from a depth-first search of
-- the graph starting from each vertex in an unspecified order.
dff          :: Graph -> Forest Vertex
dff :: Graph -> [Tree Int]
dff Graph
g         = Graph -> [Int] -> [Tree Int]
dfs Graph
g (Graph -> [Int]
vertices Graph
g)

-- | A spanning forest of the part of the graph reachable from the listed
-- vertices, obtained from a depth-first search of the graph starting at
-- each of the listed vertices in order.
dfs          :: Graph -> [Vertex] -> Forest Vertex
dfs :: Graph -> [Int] -> [Tree Int]
dfs Graph
g [Int]
vs      = Edge -> [Tree Int] -> [Tree Int]
prune (Graph -> Edge
forall i e. Array i e -> (i, i)
bounds Graph
g) ((Int -> Tree Int) -> [Int] -> [Tree Int]
forall a b. (a -> b) -> [a] -> [b]
map (Graph -> Int -> Tree Int
generate Graph
g) [Int]
vs)

generate     :: Graph -> Vertex -> Tree Vertex
generate :: Graph -> Int -> Tree Int
generate Graph
g Int
v  = Int -> [Tree Int] -> Tree Int
forall a. a -> Forest a -> Tree a
Node Int
v ((Int -> Tree Int) -> [Int] -> [Tree Int]
forall a b. (a -> b) -> [a] -> [b]
map (Graph -> Int -> Tree Int
generate Graph
g) (Graph
gGraph -> Int -> [Int]
forall i e. Ix i => Array i e -> i -> e
!Int
v))

prune        :: Bounds -> Forest Vertex -> Forest Vertex
prune :: Edge -> [Tree Int] -> [Tree Int]
prune Edge
bnds [Tree Int]
ts = Edge -> (forall s. SetM s [Tree Int]) -> [Tree Int]
forall a. Edge -> (forall s. SetM s a) -> a
run Edge
bnds ([Tree Int] -> SetM s [Tree Int]
forall s. [Tree Int] -> SetM s [Tree Int]
chop [Tree Int]
ts)

chop         :: Forest Vertex -> SetM s (Forest Vertex)
chop :: [Tree Int] -> SetM s [Tree Int]
chop []       = [Tree Int] -> SetM s [Tree Int]
forall (m :: * -> *) a. Monad m => a -> m a
return []
chop (Node Int
v [Tree Int]
ts : [Tree Int]
us)
              = do
                Bool
visited <- Int -> SetM s Bool
forall s. Int -> SetM s Bool
contains Int
v
                if Bool
visited then
                  [Tree Int] -> SetM s [Tree Int]
forall s. [Tree Int] -> SetM s [Tree Int]
chop [Tree Int]
us
                 else do
                  Int -> SetM s ()
forall s. Int -> SetM s ()
include Int
v
                  [Tree Int]
as <- [Tree Int] -> SetM s [Tree Int]
forall s. [Tree Int] -> SetM s [Tree Int]
chop [Tree Int]
ts
                  [Tree Int]
bs <- [Tree Int] -> SetM s [Tree Int]
forall s. [Tree Int] -> SetM s [Tree Int]
chop [Tree Int]
us
                  [Tree Int] -> SetM s [Tree Int]
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> [Tree Int] -> Tree Int
forall a. a -> Forest a -> Tree a
Node Int
v [Tree Int]
as Tree Int -> [Tree Int] -> [Tree Int]
forall a. a -> [a] -> [a]
: [Tree Int]
bs)

-- A monad holding a set of vertices visited so far.
#if USE_ST_MONAD

-- Use the ST monad if available, for constant-time primitives.

#if USE_UNBOXED_ARRAYS
newtype SetM s a = SetM { SetM s a -> STUArray s Int Bool -> ST s a
runSetM :: STUArray s Vertex Bool -> ST s a }
#else
newtype SetM s a = SetM { runSetM :: STArray  s Vertex Bool -> ST s a }
#endif

instance Monad (SetM s) where
    return :: a -> SetM s a
return = a -> SetM s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
    {-# INLINE return #-}
    SetM STUArray s Int Bool -> ST s a
v >>= :: SetM s a -> (a -> SetM s b) -> SetM s b
>>= a -> SetM s b
f = (STUArray s Int Bool -> ST s b) -> SetM s b
forall s a. (STUArray s Int Bool -> ST s a) -> SetM s a
SetM ((STUArray s Int Bool -> ST s b) -> SetM s b)
-> (STUArray s Int Bool -> ST s b) -> SetM s b
forall a b. (a -> b) -> a -> b
$ \STUArray s Int Bool
s -> do { a
x <- STUArray s Int Bool -> ST s a
v STUArray s Int Bool
s; SetM s b -> STUArray s Int Bool -> ST s b
forall s a. SetM s a -> STUArray s Int Bool -> ST s a
runSetM (a -> SetM s b
f a
x) STUArray s Int Bool
s }
    {-# INLINE (>>=) #-}

instance Functor (SetM s) where
    a -> b
f fmap :: (a -> b) -> SetM s a -> SetM s b
`fmap` SetM STUArray s Int Bool -> ST s a
v = (STUArray s Int Bool -> ST s b) -> SetM s b
forall s a. (STUArray s Int Bool -> ST s a) -> SetM s a
SetM ((STUArray s Int Bool -> ST s b) -> SetM s b)
-> (STUArray s Int Bool -> ST s b) -> SetM s b
forall a b. (a -> b) -> a -> b
$ \STUArray s Int Bool
s -> a -> b
f (a -> b) -> ST s a -> ST s b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` STUArray s Int Bool -> ST s a
v STUArray s Int Bool
s
    {-# INLINE fmap #-}

instance Applicative (SetM s) where
    pure :: a -> SetM s a
pure a
x = (STUArray s Int Bool -> ST s a) -> SetM s a
forall s a. (STUArray s Int Bool -> ST s a) -> SetM s a
SetM ((STUArray s Int Bool -> ST s a) -> SetM s a)
-> (STUArray s Int Bool -> ST s a) -> SetM s a
forall a b. (a -> b) -> a -> b
$ ST s a -> STUArray s Int Bool -> ST s a
forall a b. a -> b -> a
const (a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x)
    {-# INLINE pure #-}
    SetM STUArray s Int Bool -> ST s (a -> b)
f <*> :: SetM s (a -> b) -> SetM s a -> SetM s b
<*> SetM STUArray s Int Bool -> ST s a
v = (STUArray s Int Bool -> ST s b) -> SetM s b
forall s a. (STUArray s Int Bool -> ST s a) -> SetM s a
SetM ((STUArray s Int Bool -> ST s b) -> SetM s b)
-> (STUArray s Int Bool -> ST s b) -> SetM s b
forall a b. (a -> b) -> a -> b
$ \STUArray s Int Bool
s -> STUArray s Int Bool -> ST s (a -> b)
f STUArray s Int Bool
s ST s (a -> b) -> ((a -> b) -> ST s b) -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ((a -> b) -> ST s a -> ST s b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` STUArray s Int Bool -> ST s a
v STUArray s Int Bool
s)
    -- We could also use the following definition
    --   SetM f <*> SetM v = SetM $ \s -> f s <*> v s
    -- but Applicative (ST s) instance is present only in GHC 7.2+
    {-# INLINE (<*>) #-}

run          :: Bounds -> (forall s. SetM s a) -> a
run :: Edge -> (forall s. SetM s a) -> a
run Edge
bnds forall s. SetM s a
act  = (forall s. ST s a) -> a
forall a. (forall s. ST s a) -> a
runST (Edge -> Bool -> ST s (STUArray s Int Bool)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
newArray Edge
bnds Bool
False ST s (STUArray s Int Bool)
-> (STUArray s Int Bool -> ST s a) -> ST s a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= SetM s a -> STUArray s Int Bool -> ST s a
forall s a. SetM s a -> STUArray s Int Bool -> ST s a
runSetM SetM s a
forall s. SetM s a
act)

contains     :: Vertex -> SetM s Bool
contains :: Int -> SetM s Bool
contains Int
v    = (STUArray s Int Bool -> ST s Bool) -> SetM s Bool
forall s a. (STUArray s Int Bool -> ST s a) -> SetM s a
SetM ((STUArray s Int Bool -> ST s Bool) -> SetM s Bool)
-> (STUArray s Int Bool -> ST s Bool) -> SetM s Bool
forall a b. (a -> b) -> a -> b
$ \ STUArray s Int Bool
m -> STUArray s Int Bool -> Int -> ST s Bool
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Bool
m Int
v

include      :: Vertex -> SetM s ()
include :: Int -> SetM s ()
include Int
v     = (STUArray s Int Bool -> ST s ()) -> SetM s ()
forall s a. (STUArray s Int Bool -> ST s a) -> SetM s a
SetM ((STUArray s Int Bool -> ST s ()) -> SetM s ())
-> (STUArray s Int Bool -> ST s ()) -> SetM s ()
forall a b. (a -> b) -> a -> b
$ \ STUArray s Int Bool
m -> STUArray s Int Bool -> Int -> Bool -> ST s ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Bool
m Int
v Bool
True

#else /* !USE_ST_MONAD */

-- Portable implementation using IntSet.

newtype SetM s a = SetM { runSetM :: IntSet -> (a, IntSet) }

instance Monad (SetM s) where
    return x     = SetM $ \s -> (x, s)
    SetM v >>= f = SetM $ \s -> case v s of (x, s') -> runSetM (f x) s'

instance Functor (SetM s) where
    f `fmap` SetM v = SetM $ \s -> case v s of (x, s') -> (f x, s')
    {-# INLINE fmap #-}

instance Applicative (SetM s) where
    pure x = SetM $ \s -> (x, s)
    {-# INLINE pure #-}
    SetM f <*> SetM v = SetM $ \s -> case f s of (k, s') -> case v s' of (x, s'') -> (k x, s'')
    {-# INLINE (<*>) #-}

run          :: Bounds -> SetM s a -> a
run _ act     = fst (runSetM act Set.empty)

contains     :: Vertex -> SetM s Bool
contains v    = SetM $ \ m -> (Set.member v m, m)

include      :: Vertex -> SetM s ()
include v     = SetM $ \ m -> ((), Set.insert v m)

#endif /* !USE_ST_MONAD */

-------------------------------------------------------------------------
--                                                                      -
--      Algorithms
--                                                                      -
-------------------------------------------------------------------------

------------------------------------------------------------
-- Algorithm 1: depth first search numbering
------------------------------------------------------------

preorder' :: Tree a -> [a] -> [a]
preorder' :: Tree a -> [a] -> [a]
preorder' (Node a
a Forest a
ts) = (a
a a -> [a] -> [a]
forall a. a -> [a] -> [a]
:) ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Forest a -> [a] -> [a]
forall a. Forest a -> [a] -> [a]
preorderF' Forest a
ts

preorderF' :: Forest a -> [a] -> [a]
preorderF' :: Forest a -> [a] -> [a]
preorderF' Forest a
ts = (([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a])
-> ([a] -> [a]) -> [[a] -> [a]] -> [a] -> [a]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) [a] -> [a]
forall a. a -> a
id ([[a] -> [a]] -> [a] -> [a]) -> [[a] -> [a]] -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ (Tree a -> [a] -> [a]) -> Forest a -> [[a] -> [a]]
forall a b. (a -> b) -> [a] -> [b]
map Tree a -> [a] -> [a]
forall a. Tree a -> [a] -> [a]
preorder' Forest a
ts

preorderF :: Forest a -> [a]
preorderF :: Forest a -> [a]
preorderF Forest a
ts = Forest a -> [a] -> [a]
forall a. Forest a -> [a] -> [a]
preorderF' Forest a
ts []

tabulate        :: Bounds -> [Vertex] -> UArray Vertex Int
tabulate :: Edge -> [Int] -> UArray Int Int
tabulate Edge
bnds [Int]
vs = Edge -> [Edge] -> UArray Int Int
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
UA.array Edge
bnds ((Int -> Int -> Edge) -> [Int] -> [Int] -> [Edge]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith ((Int -> Int -> Edge) -> Int -> Int -> Edge
forall a b c. (a -> b -> c) -> b -> a -> c
flip (,)) [Int
1..] [Int]
vs)
-- Why zipWith (flip (,)) instead of just using zip with the
-- arguments in the other order? We want the [1..] to fuse
-- away, and these days that only happens when it's the first
-- list argument.

preArr          :: Bounds -> Forest Vertex -> UArray Vertex Int
preArr :: Edge -> [Tree Int] -> UArray Int Int
preArr Edge
bnds      = Edge -> [Int] -> UArray Int Int
tabulate Edge
bnds ([Int] -> UArray Int Int)
-> ([Tree Int] -> [Int]) -> [Tree Int] -> UArray Int Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tree Int] -> [Int]
forall a. Forest a -> [a]
preorderF

------------------------------------------------------------
-- Algorithm 2: topological sorting
------------------------------------------------------------

postorder :: Tree a -> [a] -> [a]
postorder :: Tree a -> [a] -> [a]
postorder (Node a
a Forest a
ts) = Forest a -> [a] -> [a]
forall a. Forest a -> [a] -> [a]
postorderF Forest a
ts ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a
a a -> [a] -> [a]
forall a. a -> [a] -> [a]
:)

postorderF   :: Forest a -> [a] -> [a]
postorderF :: Forest a -> [a] -> [a]
postorderF Forest a
ts = (([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a])
-> ([a] -> [a]) -> [[a] -> [a]] -> [a] -> [a]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) [a] -> [a]
forall a. a -> a
id ([[a] -> [a]] -> [a] -> [a]) -> [[a] -> [a]] -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ (Tree a -> [a] -> [a]) -> Forest a -> [[a] -> [a]]
forall a b. (a -> b) -> [a] -> [b]
map Tree a -> [a] -> [a]
forall a. Tree a -> [a] -> [a]
postorder Forest a
ts

postOrd :: Graph -> [Vertex]
postOrd :: Graph -> [Int]
postOrd Graph
g = [Tree Int] -> [Int] -> [Int]
forall a. Forest a -> [a] -> [a]
postorderF (Graph -> [Tree Int]
dff Graph
g) []

-- | A topological sort of the graph.
-- The order is partially specified by the condition that a vertex /i/
-- precedes /j/ whenever /j/ is reachable from /i/ but not vice versa.
topSort      :: Graph -> [Vertex]
topSort :: Graph -> [Int]
topSort       = [Int] -> [Int]
forall a. [a] -> [a]
reverse ([Int] -> [Int]) -> (Graph -> [Int]) -> Graph -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Graph -> [Int]
postOrd

------------------------------------------------------------
-- Algorithm 3: connected components
------------------------------------------------------------

-- | The connected components of a graph.
-- Two vertices are connected if there is a path between them, traversing
-- edges in either direction.
components   :: Graph -> Forest Vertex
components :: Graph -> [Tree Int]
components    = Graph -> [Tree Int]
dff (Graph -> [Tree Int]) -> (Graph -> Graph) -> Graph -> [Tree Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Graph -> Graph
undirected

undirected   :: Graph -> Graph
undirected :: Graph -> Graph
undirected Graph
g  = Edge -> [Edge] -> Graph
buildG (Graph -> Edge
forall i e. Array i e -> (i, i)
bounds Graph
g) (Graph -> [Edge]
edges Graph
g [Edge] -> [Edge] -> [Edge]
forall a. [a] -> [a] -> [a]
++ Graph -> [Edge]
reverseE Graph
g)

-- Algorithm 4: strongly connected components

-- | The strongly connected components of a graph, in reverse topological order.
--
-- ==== __Examples__
--
-- > scc (buildG (0,3) [(3,1),(1,2),(2,0),(0,1)])
-- >   == [Node {rootLabel = 0, subForest = [Node {rootLabel = 1, subForest = [Node {rootLabel = 2, subForest = []}]}]}
-- >      ,Node {rootLabel = 3, subForest = []}]

scc  :: Graph -> Forest Vertex
scc :: Graph -> [Tree Int]
scc Graph
g = Graph -> [Int] -> [Tree Int]
dfs Graph
g ([Int] -> [Int]
forall a. [a] -> [a]
reverse (Graph -> [Int]
postOrd (Graph -> Graph
transposeG Graph
g)))

------------------------------------------------------------
-- Algorithm 5: Classifying edges
------------------------------------------------------------

{-
XXX unused code

tree              :: Bounds -> Forest Vertex -> Graph
tree bnds ts       = buildG bnds (concat (map flat ts))
 where flat (Node v ts') = [ (v, w) | Node w _us <- ts' ]
                        ++ concat (map flat ts')

back              :: Graph -> Table Int -> Graph
back g post        = mapT select g
 where select v ws = [ w | w <- ws, post!v < post!w ]

cross             :: Graph -> Table Int -> Table Int -> Graph
cross g pre post   = mapT select g
 where select v ws = [ w | w <- ws, post!v > post!w, pre!v > pre!w ]

forward           :: Graph -> Graph -> Table Int -> Graph
forward g tree' pre = mapT select g
 where select v ws = [ w | w <- ws, pre!v < pre!w ] \\ tree' ! v

mapT    :: (Vertex -> a -> b) -> Array Vertex a -> Array Vertex b
mapT f t = array (bounds t) [ (,) v (f v (t!v)) | v <- indices t ]
-}

------------------------------------------------------------
-- Algorithm 6: Finding reachable vertices
------------------------------------------------------------

-- | Returns the list of vertices reachable from a given vertex.
--
-- ==== __Examples__
--
-- > reachable (buildG (0,0) []) 0 == [0]
--
-- > reachable (buildG (0,2) [(0,1), (1,2)]) 0 == [0,1,2]
reachable :: Graph -> Vertex -> [Vertex]
reachable :: Graph -> Int -> [Int]
reachable Graph
g Int
v = [Tree Int] -> [Int]
forall a. Forest a -> [a]
preorderF (Graph -> [Int] -> [Tree Int]
dfs Graph
g [Int
v])

-- | Returns @True@ if the second vertex reachable from the first.
--
-- ==== __Examples__
--
-- > path (buildG (0,0) []) 0 0 == True
--
-- > path (buildG (0,2) [(0,1), (1,2)]) 0 2 == True
--
-- > path (buildG (0,2) [(0,1), (1,2)]) 2 0 == False
path :: Graph -> Vertex -> Vertex -> Bool
path :: Graph -> Int -> Int -> Bool
path Graph
g Int
v Int
w    = Int
w Int -> [Int] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Graph -> Int -> [Int]
reachable Graph
g Int
v)

------------------------------------------------------------
-- Algorithm 7: Biconnected components
------------------------------------------------------------

-- | The biconnected components of a graph.
-- An undirected graph is biconnected if the deletion of any vertex
-- leaves it connected.
bcc :: Graph -> Forest [Vertex]
bcc :: Graph -> Forest [Int]
bcc Graph
g = ([Forest [Int]] -> Forest [Int]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([Forest [Int]] -> Forest [Int])
-> ([Tree Int] -> [Forest [Int]]) -> [Tree Int] -> Forest [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tree (Int, Int, Int) -> Forest [Int])
-> [Tree (Int, Int, Int)] -> [Forest [Int]]
forall a b. (a -> b) -> [a] -> [b]
map Tree (Int, Int, Int) -> Forest [Int]
bicomps ([Tree (Int, Int, Int)] -> [Forest [Int]])
-> ([Tree Int] -> [Tree (Int, Int, Int)])
-> [Tree Int]
-> [Forest [Int]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tree Int -> Tree (Int, Int, Int))
-> [Tree Int] -> [Tree (Int, Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (Graph -> UArray Int Int -> Tree Int -> Tree (Int, Int, Int)
do_label Graph
g UArray Int Int
dnum)) [Tree Int]
forest
 where forest :: [Tree Int]
forest = Graph -> [Tree Int]
dff Graph
g
       dnum :: UArray Int Int
dnum   = Edge -> [Tree Int] -> UArray Int Int
preArr (Graph -> Edge
forall i e. Array i e -> (i, i)
bounds Graph
g) [Tree Int]
forest

do_label :: Graph -> UArray Vertex Int -> Tree Vertex -> Tree (Vertex,Int,Int)
do_label :: Graph -> UArray Int Int -> Tree Int -> Tree (Int, Int, Int)
do_label Graph
g UArray Int Int
dnum (Node Int
v [Tree Int]
ts) = (Int, Int, Int) -> [Tree (Int, Int, Int)] -> Tree (Int, Int, Int)
forall a. a -> Forest a -> Tree a
Node (Int
v, UArray Int Int
dnum UArray Int Int -> Int -> Int
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
UA.! Int
v, Int
lv) [Tree (Int, Int, Int)]
us
 where us :: [Tree (Int, Int, Int)]
us = (Tree Int -> Tree (Int, Int, Int))
-> [Tree Int] -> [Tree (Int, Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (Graph -> UArray Int Int -> Tree Int -> Tree (Int, Int, Int)
do_label Graph
g UArray Int Int
dnum) [Tree Int]
ts
       lv :: Int
lv = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum ([UArray Int Int
dnum UArray Int Int -> Int -> Int
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
UA.! Int
v] [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ [UArray Int Int
dnum UArray Int Int -> Int -> Int
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
UA.! Int
w | Int
w <- Graph
gGraph -> Int -> [Int]
forall i e. Ix i => Array i e -> i -> e
!Int
v]
                     [Int] -> [Int] -> [Int]
forall a. [a] -> [a] -> [a]
++ [Int
lu | Node (Int
_,Int
_,Int
lu) [Tree (Int, Int, Int)]
_ <- [Tree (Int, Int, Int)]
us])

bicomps :: Tree (Vertex,Int,Int) -> Forest [Vertex]
bicomps :: Tree (Int, Int, Int) -> Forest [Int]
bicomps (Node (Int
v,Int
_,Int
_) [Tree (Int, Int, Int)]
ts)
      = [ [Int] -> Forest [Int] -> Tree [Int]
forall a. a -> Forest a -> Tree a
Node (Int
vInt -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
vs) Forest [Int]
us | (Int
_,Node [Int]
vs Forest [Int]
us) <- (Tree (Int, Int, Int) -> (Int, Tree [Int]))
-> [Tree (Int, Int, Int)] -> [(Int, Tree [Int])]
forall a b. (a -> b) -> [a] -> [b]
map Tree (Int, Int, Int) -> (Int, Tree [Int])
collect [Tree (Int, Int, Int)]
ts]

collect :: Tree (Vertex,Int,Int) -> (Int, Tree [Vertex])
collect :: Tree (Int, Int, Int) -> (Int, Tree [Int])
collect (Node (Int
v,Int
dv,Int
lv) [Tree (Int, Int, Int)]
ts) = (Int
lv, [Int] -> Forest [Int] -> Tree [Int]
forall a. a -> Forest a -> Tree a
Node (Int
vInt -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
vs) Forest [Int]
cs)
 where collected :: [(Int, Tree [Int])]
collected = (Tree (Int, Int, Int) -> (Int, Tree [Int]))
-> [Tree (Int, Int, Int)] -> [(Int, Tree [Int])]
forall a b. (a -> b) -> [a] -> [b]
map Tree (Int, Int, Int) -> (Int, Tree [Int])
collect [Tree (Int, Int, Int)]
ts
       vs :: [Int]
vs = [[Int]] -> [Int]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [Int]
ws | (Int
lw, Node [Int]
ws Forest [Int]
_) <- [(Int, Tree [Int])]
collected, Int
lwInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
dv]
       cs :: Forest [Int]
cs = [Forest [Int]] -> Forest [Int]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ if Int
lwInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<Int
dv then Forest [Int]
us else [[Int] -> Forest [Int] -> Tree [Int]
forall a. a -> Forest a -> Tree a
Node (Int
vInt -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
ws) Forest [Int]
us]
                        | (Int
lw, Node [Int]
ws Forest [Int]
us) <- [(Int, Tree [Int])]
collected ]