| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | GHC2021 | 
AtCoder.Extra.Graph
Description
Re-export of the Csr module and generic graph search functions.
Since: 1.1.0.0
Synopsis
- module AtCoder.Internal.Csr
- swapDupe :: Unbox (Int, Int, w) => Vector (Int, Int, w) -> Vector (Int, Int, w)
- swapDupe' :: Unbox (Int, Int) => Vector (Int, Int) -> Vector (Int, Int)
- scc :: Csr w -> Vector (Vector Int)
- topSort :: Int -> (Int -> Vector Int) -> Vector Int
- blockCut :: Int -> (Int -> Vector Int) -> Csr ()
- blockCutComponents :: Int -> (Int -> Vector Int) -> Vector (Vector Int)
Re-export of CSR
module AtCoder.Internal.Csr
CSR helpers
swapDupe :: Unbox (Int, Int, w) => Vector (Int, Int, w) -> Vector (Int, Int, w) Source #
\(O(n)\) Converts non-directed edges into directional edges. This is a convenient function for
 making an input to build.
Example
swapDupe duplicates each edge reversing the direction:
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>Gr.swapDupe $ VU.fromList [(0, 1, ()), (1, 2, ())][(0,1,()),(1,0,()),(1,2,()),(2,1,())]
Create a non-directed graph:
>>>let gr = Gr.build 3 . Gr.swapDupe $ VU.fromList [(0, 1, ()), (1, 2, ())]>>>gr `Gr.adj` 0[1]
>>>gr `Gr.adj` 1[0,2]
>>>gr `Gr.adj` 2[1]
Since: 1.1.0.0
swapDupe' :: Unbox (Int, Int) => Vector (Int, Int) -> Vector (Int, Int) Source #
\(O(n)\) Converts non-directed edges into directional edges. This is a convenient function for
 making an input to build'.
Example
swapDupe' duplicates each edge reversing the direction:
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>Gr.swapDupe' $ VU.fromList [(0, 1), (1, 2)][(0,1),(1,0),(1,2),(2,1)]
Create a non-directed graph:
>>>let gr = Gr.build' 3 . Gr.swapDupe' $ VU.fromList [(0, 1), (1, 2)]>>>gr `Gr.adj` 0[1]
>>>gr `Gr.adj` 1[0,2]
>>>gr `Gr.adj` 2[1]
Since: 1.1.0.0
scc :: Csr w -> Vector (Vector Int) Source #
\(O(n + m)\) Returns the strongly connected components.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>-- 0 == 1 -> 2 3>>>let gr = Gr.build' 4 $ VU.fromList [(0, 1), (1, 0), (1, 2)]>>>Gr.scc gr[[3],[0,1],[2]]
Since: 1.1.0.0
Graph search
topSort :: Int -> (Int -> Vector Int) -> Vector Int Source #
\(O(n \log n + m)\) Returns the lexicographically smallest topological ordering of the given graph.
Constraints
- The graph must be a DAG.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let n = 5>>>let gr = Gr.build' n $ VU.fromList [(1, 2), (4, 0), (0, 3)]>>>Gr.topSort n (gr `Gr.adj`)[1,2,4,0,3]
Since: 1.1.0.0
blockCut :: Int -> (Int -> Vector Int) -> Csr () Source #
\(O(n + m)\) Returns a block cut tree where super vertices represent each biconnected component.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>-- 0---3---2>>>-- +-1-+>>>let n = 4>>>let gr = Gr.build' n . Gr.swapDupe' $ VU.fromList [(0, 3), (0, 1), (1, 3), (3, 2)]>>>let bct = blockCut n (gr `Gr.adj`)>>>bctCsr {nCsr = 6, mCsr = 5, startCsr = [0,0,0,0,0,2,5], adjCsr = [3,2,0,3,1], wCsr = [(),(),(),(),()]}
>>>V.generate (Gr.nCsr bct - n) ((bct `Gr.adj`) . (+ n))[[3,2],[0,3,1]]
Since: 1.1.1.0
blockCutComponents :: Int -> (Int -> Vector Int) -> Vector (Vector Int) Source #
\(O(n + m)\) Returns a blocks (biconnected comopnents) of the graph.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>-- 0---3---2>>>-- +-1-+>>>let n = 4>>>let gr = Gr.build' n . Gr.swapDupe' $ VU.fromList [(0, 3), (0, 1), (1, 3), (3, 2)]>>>Gr.blockCutComponents n (gr `Gr.adj`)[[3,2],[0,3,1]]
Since: 1.1.1.0