| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
AtCoder.Extra.Graph
Description
Re-export of the Csr module and additional graph search functions.
Since: 1.1.0.0
Synopsis
- module AtCoder.Internal.Csr
- swapDupe :: Unbox w => Vector (Int, Int, w) -> Vector (Int, Int, w)
- swapDupe' :: Vector (Int, Int) -> Vector (Int, Int)
- scc :: Csr w -> Vector (Vector Int)
- rev :: Unbox w => Csr w -> Csr w
- findCycleDirected :: (HasCallStack, Unbox w) => Csr w -> Maybe (Vector Int, Vector Int)
- findCycleUndirected :: (HasCallStack, Unbox w) => Csr w -> Maybe (Vector Int, Vector Int)
- topSort :: Int -> (Int -> Vector Int) -> Vector Int
- connectedComponents :: Int -> (Int -> Vector Int) -> Vector (Vector Int)
- bipartiteVertexColors :: Int -> (Int -> Vector Int) -> Maybe (Vector Bit)
- blockCut :: Int -> (Int -> Vector Int) -> Csr ()
- blockCutComponents :: Int -> (Int -> Vector Int) -> Vector (Vector Int)
- bfs :: (HasCallStack, Ix0 i, Unbox i, Unbox w, Num w, Eq w) => Bounds0 i -> (i -> Vector (i, w)) -> w -> Vector (i, w) -> Vector w
- trackingBfs :: (HasCallStack, Ix0 i, Unbox i, Unbox w, Num w, Eq w) => Bounds0 i -> (i -> Vector (i, w)) -> w -> Vector (i, w) -> (Vector w, Vector Int)
- bfs01 :: (HasCallStack, Ix0 i, Unbox i) => Bounds0 i -> (i -> Vector (i, Int)) -> Int -> Vector (i, Int) -> Vector Int
- trackingBfs01 :: (HasCallStack, Ix0 i, Unbox i) => Bounds0 i -> (i -> Vector (i, Int)) -> Int -> Vector (i, Int) -> (Vector Int, Vector Int)
- dijkstra :: (HasCallStack, Ix0 i, Ord i, Unbox i, Num w, Ord w, Unbox w) => Bounds0 i -> (i -> Vector (i, w)) -> Int -> w -> Vector (i, w) -> Vector w
- trackingDijkstra :: (HasCallStack, Ix0 i, Ord i, Unbox i, Num w, Ord w, Unbox w) => Bounds0 i -> (i -> Vector (i, w)) -> Int -> w -> Vector (i, w) -> (Vector w, Vector Int)
- bellmanFord :: (HasCallStack, Num w, Ord w, Unbox w) => Int -> (Int -> Vector (Int, w)) -> w -> Vector (Int, w) -> Maybe (Vector w)
- trackingBellmanFord :: (HasCallStack, Num w, Ord w, Unbox w) => Int -> (Int -> Vector (Int, w)) -> w -> Vector (Int, w) -> Maybe (Vector w, Vector Int)
- floydWarshall :: (HasCallStack, Num w, Ord w, Unbox w) => Int -> Vector (Int, Int, w) -> w -> Vector w
- trackingFloydWarshall :: (HasCallStack, Num w, Ord w, Unbox w) => Int -> Vector (Int, Int, w) -> w -> (Vector w, Vector Int)
- newFloydWarshall :: (HasCallStack, PrimMonad m, Num w, Ord w, Unbox w) => Int -> Vector (Int, Int, w) -> w -> m (MVector (PrimState m) w)
- newTrackingFloydWarshall :: (HasCallStack, PrimMonad m, Num w, Ord w, Unbox w) => Int -> Vector (Int, Int, w) -> w -> m (MVector (PrimState m) w, MVector (PrimState m) Int)
- updateEdgeFloydWarshall :: (HasCallStack, PrimMonad m, Num w, Ord w, Unbox w) => MVector (PrimState m) w -> Int -> w -> Int -> Int -> w -> m ()
- updateEdgeTrackingFloydWarshall :: (HasCallStack, PrimMonad m, Num w, Ord w, Unbox w) => MVector (PrimState m) w -> MVector (PrimState m) Int -> Int -> w -> Int -> Int -> w -> m ()
- constructPathFromRoot :: HasCallStack => Vector Int -> Int -> Vector Int
- constructPathToRoot :: HasCallStack => Vector Int -> Int -> Vector Int
- constructPathFromRootMat :: HasCallStack => Vector Int -> Int -> Int -> Vector Int
- constructPathToRootMat :: HasCallStack => Vector Int -> Int -> Int -> Vector Int
- constructPathFromRootMatM :: (HasCallStack, PrimMonad m) => MVector (PrimState m) Int -> Int -> Int -> m (Vector Int)
- constructPathToRootMatM :: (HasCallStack, PrimMonad m) => MVector (PrimState m) Int -> Int -> Int -> m (Vector Int)
Re-export of CSR
The Csr data type and all the functions such as build or adj are re-exported.
See the Csr module for details.
module AtCoder.Internal.Csr
CSR helpers
swapDupe :: Unbox w => Vector (Int, Int, w) -> Vector (Int, Int, w) Source #
\(O(n)\) Converts directed edges into non-directed edges; each edge \((u, v, w)\) is duplicated
to be \((u, v, w)\) and \((v, u, w)\). 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' :: Vector (Int, Int) -> Vector (Int, Int) Source #
\(O(n)\) Converts directed edges into non-directed edges; each edge \((u, v)\) is duplicated
to be \((u, v)\) and \((v, u)\). 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 of a Csr.
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
rev :: Unbox w => Csr w -> Csr w Source #
\(O(n + m)\) Returns a reverse graph, where original edges \((u, v, w)\) are transposed to be
\((v, u, w)\). Reverse graphs are useful for, for example, getting distance to a specific vertex
from every other vertex with dijkstra.
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), (2, 3)]>>>map (Gr.adj gr) [0 .. 3][[1],[0,2],[3],[]]
>>>-- 0 == 1 <- 2 <- 3>>>let revGr = Gr.rev gr>>>map (Gr.adj revGr) [0 .. 3][[1],[0],[1],[2]]
Since: 1.2.3.0
findCycleDirected :: (HasCallStack, Unbox w) => Csr w -> Maybe (Vector Int, Vector Int) Source #
\(O(n + m)\) Given a directed graph, finds a minimal cycle and returns a vector of vertices and
a vector of (vertices, csrEdgeIndices).
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let gr = Gr.build' 4 $ VU.fromList [(0, 1), (1, 2), (2, 3), (3, 1)]>>>findCycleDirected gr -- returns (vs, es)Just ([1,2,3],[1,2,3])
Since: 1.4.0.0
findCycleUndirected :: (HasCallStack, Unbox w) => Csr w -> Maybe (Vector Int, Vector Int) Source #
\(O(n + m)\) Given an undirected graph, finds a minimal cycle and returns a vector of vertices
a vector of (vertices, csrEdgeIndices). A single edge index does not make much sense for an
undirected graph, so map back to the original edge index manually if needed.
Constraints
- The graph must be created with
swapDupeorswapDupe'. Otherwise the returned edge indices could make no sense.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let gr = Gr.build' 4 . Gr.swapDupe' $ VU.fromList [(0, 1), (1, 2), (1, 3), (2, 3)]>>>findCycleUndirected gr -- returns (vs, es)Just ([1,3,2],[3,5,2])
Retrieve original edge indices that makes up the cycle, by recording them in edge weights:
>>>let gr = Gr.build 4 . Gr.swapDupe $ VU.fromList [(0, 1, 0 :: Int), (1, 2, 1), (1, 3, 2), (2, 3, 3)]>>>let Just (vs, es) = findCycleUndirected gr -- returns (vs, es)>>>VU.backpermute (Gr.wCsr gr) es[2,3,1]
It's a bit hacky.
Since: 1.4.0.0
Generic graph functions
Arguments
| :: Int | \(n\): The number of vertices. |
| -> (Int -> Vector Int) | \(g\): Graph function, typically |
| -> Vector Int | Vertices in topological ordering: upstream vertices come first. |
\(O(n \log n + m)\) Returns the lexicographically smallest topological ordering of the given graph.
Constraints
- The graph must be a DAG; there must be no cycle.
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
Arguments
| :: Int | \(n\): The number of vertices. |
| -> (Int -> Vector Int) | \(g\): Graph function, typically |
| -> Vector (Vector Int) | Connected components. |
\(O(n)\) Returns connected components for a non-directed graph.
Constraints
- The graph must be non-directed: both \((u, v)\) and \((v, u)\) edges must exist.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let es = VU.fromList [(0, 1), (1, 2)]>>>let gr = Gr.build' 4 $ Gr.swapDupe' es>>>Gr.connectedComponents 4 (Gr.adj gr)[[0,1,2],[3]]
>>>Gr.connectedComponents 0 (const VU.empty)[]
Since: 1.2.4.0
bipartiteVertexColors Source #
Arguments
| :: Int | \(n\): The number of vertices. |
| -> (Int -> Vector Int) | \(g\): Graph function, typically |
| -> Maybe (Vector Bit) | Bipartite vertex coloring. |
\(O((n + m) \alpha)\) Returns a bipartite vertex coloring for a bipartite graph.
Returns Nothing for a non-bipartite graph.
Constraints
- The graph must not be directed.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let es = VU.fromList [(0, 1), (1, 2)]>>>let gr = Gr.build' 4 es>>>Gr.bipartiteVertexColors 4 (Gr.adj gr)Just [0,1,0,0]
Since: 1.2.4.0
Arguments
| :: Int | \(n\): The number of vertices. |
| -> (Int -> Vector Int) | \(g\): Graph function, typically |
| -> Csr () | Graph that represents a block-cut tree, where super vertices \((n \ge n)\) represent each biconnected component. |
\(O(n + m)\) Returns a block-cut tree where super vertices \((v \ge n)\) 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
Arguments
| :: Int | \(n\): The number of vertices. |
| -> (Int -> Vector Int) | \(g\): Graph function, typically |
| -> Vector (Vector Int) | Block-cut components |
\(O(n + m)\) Returns 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
Shortest path search
Most of the functions are opinionated as the followings:
BFS (breadth-first search)
Constraints:
- Edge weight \(w > 0\)
Arguments
| :: (HasCallStack, Ix0 i, Unbox i, Unbox w, Num w, Eq w) | |
| => Bounds0 i | Zero-based vertex boundary. |
| -> (i -> Vector (i, w)) | Graph function that takes a vertex and returns adjacent vertices with edge weights, where \(w > 0\). |
| -> w | Distance assignment for unreachable vertices. |
| -> Vector (i, w) | Weighted source vertices. |
| -> Vector w | Distance array in one-dimensional index. |
\(O(n + m)\) Opinionated breadth-first search function that returns a distance array.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let es = VU.fromList [(0, 1, 1 :: Int), (1, 2, 10)]>>>let gr = Gr.build 4 es>>>Gr.bfs 4 (Gr.adjW gr) (-1) (VU.singleton (0, 0))[0,1,11,-1]
Since: 1.2.4.0
Arguments
| :: (HasCallStack, Ix0 i, Unbox i, Unbox w, Num w, Eq w) | |
| => Bounds0 i | Zero-based vertex boundary. |
| -> (i -> Vector (i, w)) | Graph function that takes a vertex and returns adjacent vertices with edge weights, where \(w > 0\). |
| -> w | Distance assignment for unreachable vertices. |
| -> Vector (i, w) | Weighted source vertices. |
| -> (Vector w, Vector Int) | A tuple of (Distance vector in one-dimensional index, Predecessor array ( |
\(O(n + m)\) Opinionated breadth-first search function that returns a distance array and a predecessor array.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let es = VU.fromList [(0, 1, 1 :: Int), (1, 2, 10)]>>>let gr = Gr.build 4 es>>>let (!dist, !prev) = Gr.trackingBfs 4 (Gr.adjW gr) (-1) (VU.singleton (0, 0))>>>dist[0,1,11,-1]
>>>Gr.constructPathFromRoot prev 2[0,1,2]
Since: 1.2.4.0
01-BFS
Constraints:
- Edge weight \(w\) is either \(0\) or \(1\) of type
Int.
Arguments
| :: (HasCallStack, Ix0 i, Unbox i) | |
| => Bounds0 i | Zero-based index boundary. |
| -> (i -> Vector (i, Int)) | Graph function that takes the vertexand returns adjacent vertices with edge weights, where \(w > 0\). |
| -> Int | Capacity of deque, often the number of edges \(m\). |
| -> Vector (i, Int) | Weighted source vertices. |
| -> Vector Int | Distance array in one-dimensional index. Unreachable vertices are assigned distance of |
\(O(n + m)\) Opinionated 01-BFS that returns a distance array.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let es = VU.fromList [(0, 1, 10 :: Int), (0, 2, 0), (2, 1, 1)]>>>let gr = Gr.build 4 es>>>let capacity = 10>>>Gr.bfs01 4 (Gr.adjW gr) capacity (VU.singleton (0, 0))[0,1,0,-1]
Since: 1.2.4.0
Arguments
| :: (HasCallStack, Ix0 i, Unbox i) | |
| => Bounds0 i | Zero-based index boundary. |
| -> (i -> Vector (i, Int)) | Graph function that takes the vertex and returns adjacent vertices with edge weights, where \(w > 0\). |
| -> Int | Capacity of deque, often the number of edges \(m\). |
| -> Vector (i, Int) | Weighted source vertices. |
| -> (Vector Int, Vector Int) | A tuple of (distance array in one-dimensional index, predecessor array). Unreachable vertices
are assigned distance of |
\(O(n + m)\) Opinionated 01-BFS that returns a distance array and a predecessor array.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let es = VU.fromList [(0, 1, 10 :: Int), (0, 2, 0), (2, 1, 1)]>>>let gr = Gr.build 4 es>>>let capacity = 10>>>let (!dist, !prev) = Gr.trackingBfs01 4 (Gr.adjW gr) capacity (VU.singleton (0, 0))>>>dist[0,1,0,-1]
>>>Gr.constructPathFromRoot prev 1[0,2,1]
Since: 1.2.4.0
Dijkstra's algorithm
Constraints:
- Edge weight \(w > 0\)
Arguments
| :: (HasCallStack, Ix0 i, Ord i, Unbox i, Num w, Ord w, Unbox w) | |
| => Bounds0 i | Zero-based vertex boundary. |
| -> (i -> Vector (i, w)) | Graph function that takes a vertex and returns adjacent vertices with edge weights, where \(w \ge 0\). |
| -> Int | Capacity of the heap, often the number of edges \(m\). |
| -> w | Distance assignment for unreachable vertices. |
| -> Vector (i, w) | Source vertices with initial weights. |
| -> Vector w | Distance array in one-dimensional index. |
\(O((n + m) \log n)\) Dijkstra's algorithm that returns a distance array.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let es = VU.fromList [(0, 1, 10 :: Int), (1, 2, 20), (2, 3, 1), (1, 3, 40), (4, 3, 0)]>>>let gr = Gr.build 5 es>>>let capacity = 10>>>Gr.dijkstra 5 (Gr.adjW gr) capacity (-1) (VU.singleton (0, 0))[0,10,30,31,-1]
Since: 1.2.4.0
Arguments
| :: (HasCallStack, Ix0 i, Ord i, Unbox i, Num w, Ord w, Unbox w) | |
| => Bounds0 i | Zero-based vertex boundary. |
| -> (i -> Vector (i, w)) | Graph function that takes a vertex and returns adjacent vertices with edge weights, where \(w \ge 0\). |
| -> Int | Capacity of the heap, often the number of edges \(m\). |
| -> w | Distance assignment for unreachable vertices. |
| -> Vector (i, w) | Source vertices with initial weights. |
| -> (Vector w, Vector Int) | A tuple of (distance array in one-dimensional index, predecessor array). |
\(O((n + m) \log n)\) Dijkstra's algorithm that returns a distance array and a predecessor array.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let es = VU.fromList [(0, 1, 10 :: Int), (1, 2, 20), (2, 3, 1), (1, 3, 40), (4, 3, 0)]>>>let gr = Gr.build 5 es>>>let capacity = 10>>>let (!dist, !prev) = Gr.trackingDijkstra 5 (Gr.adjW gr) capacity (-1) (VU.singleton (0, 0))>>>dist[0,10,30,31,-1]
>>>Gr.constructPathFromRoot prev 3[0,1,2,3]
Since: 1.2.4.0
Bellman–Ford algorithm
- Vertex type is restricted to one-dimensional
Int.
Arguments
| :: (HasCallStack, Num w, Ord w, Unbox w) | |
| => Int | The number of vertices. |
| -> (Int -> Vector (Int, w)) | Graph function. Edges weights can be negative. |
| -> w | Distance assignment for unreachable vertices. |
| -> Vector (Int, w) | Source vertex with initial distances. |
| -> Maybe (Vector w) | Distance array in one-dimensional index. |
\(O(nm)\) Bellman–Ford algorithm that returns a distance array, or Nothing on negative loop
detection. Vertices are one-dimensional.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let gr = Gr.build @Int 5 $ VU.fromList [(0, 1, 10), (1, 2, -20), (2, 3, 1), (1, 3, 40), (4, 3, 0)]>>>let undefW = maxBound `div` 2>>>Gr.bellmanFord 5 (Gr.adjW gr) undefW (VU.singleton (0, 0))Just [0,10,-10,-9,4611686018427387903]
It returns Nothing on negative loop detection:
>>>let gr = Gr.build @Int 2 $ VU.fromList [(0, 1, -1), (1, 0, -1)]>>>Gr.bellmanFord 5 (Gr.adjW gr) undefW (VU.singleton (0, 0))Nothing
Since: 1.2.4.0
Arguments
| :: (HasCallStack, Num w, Ord w, Unbox w) | |
| => Int | The number of vertices. |
| -> (Int -> Vector (Int, w)) | Graph function. The weight can be negative. |
| -> w | Distance assignment for unreachable vertices. |
| -> Vector (Int, w) | Source vertex with initial distances. |
| -> Maybe (Vector w, Vector Int) | A tuple of (distance array, predecessor array). |
\(O(nm)\) Bellman–Ford algorithm that returns a distance array and a predecessor array, or
Nothing on negative loop detection. Vertices are one-dimensional.
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let gr = Gr.build @Int 5 $ VU.fromList [(0, 1, 10), (1, 2, -20), (2, 3, 1), (1, 3, 40), (4, 3, 0)]>>>let undefW = maxBound `div` 2>>>let Just (!dist, !prev) = Gr.trackingBellmanFord 5 (Gr.adjW gr) undefW (VU.singleton (0, 0))>>>dist[0,10,-10,-9,4611686018427387903]
>>>Gr.constructPathFromRoot prev 3[0,1,2,3]
It returns Nothing on negative loop detection:
>>>let gr = Gr.build @Int 2 $ VU.fromList [(0, 1, -1), (1, 0, -1)]>>>Gr.trackingBellmanFord 5 (Gr.adjW gr) undefW (VU.singleton (0, 0))Nothing
Since: 1.2.4.0
Floyd–Warshall algorithm
All-pair shortest path.
Arguments
| :: (HasCallStack, Num w, Ord w, Unbox w) | |
| => Int | The number of vertices. |
| -> Vector (Int, Int, w) | Weighted edges. |
| -> w | Distance assignment \(d_0 \gt 0\) for unreachable vertices. It should be |
| -> Vector w | Distance array in one-dimensional index. |
\(O(n^3)\) Floyd–Warshall algorithm that returns a distance matrix \(m\).
- The distance matrix should be accessed as
m VG.! (,index0(n, n) (from, to)) - There's a negative loop if there's any vertex \(v\) where
m VU.! (is negative.index0(n, n) (v, v))
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let es = VU.fromList [(0, 1, 10 :: Int), (1, 2, -20), (2, 3, 1), (1, 3, 40), (4, 3, 0)]>>>let undefW = maxBound `div` 2>>>let dist = Gr.floydWarshall 5 es undefW>>>dist VG.! (5 * 0 + 3) -- from `0` to `3`-9
>>>dist VG.! (5 * 1 + 3) -- from `0` to `3`-19
Negative loop can be detected by testing if there's any vertex \(v\) where
m VU.! (:index0 (n, n) (v, v))
>>>any (\v -> dist VG.! (5 * v + v) < 0) [0 .. 5 - 1]False
>>>let es = VU.fromList [(0, 1, -1 :: Int), (1, 0, -1)]>>>let dist = Gr.floydWarshall 3 es undefW>>>any (\v -> dist VG.! (3 * v + v) < 0) [0 .. 3 - 1]True
Since: 1.2.4.0
trackingFloydWarshall Source #
Arguments
| :: (HasCallStack, Num w, Ord w, Unbox w) | |
| => Int | The number of vertices. |
| -> Vector (Int, Int, w) | Weighted edges. |
| -> w | Distance assignment \(d_0 \gt 0\) for unreachable vertices. It should be |
| -> (Vector w, Vector Int) | Distance array in one-dimensional index. |
\(O(n^3)\) Floyd–Warshall algorithm that returns a distance matrix \(m\) and predecessor matrix \(p\).
- The distance matrix should be accessed as
m VG.! (,index0(n, n) (from, to)) - The predecessor matrix should be accessed as
m VG.! (index0(n, n) (root, v)) - There's a negative loop if there's any vertex \(v\) where
m VU.! (is negative.index0(n, n) (v, v))
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let es = VU.fromList [(0, 1, 10 :: Int), (1, 2, -20), (2, 3, 1), (1, 3, 40), (4, 3, 0)]>>>let undefW = maxBound `div` 2>>>let (!dist, !prev) = Gr.trackingFloydWarshall 5 es undefW>>>dist VG.! (5 * 0 + 3) -- from `0` to `3`-9
>>>Gr.constructPathFromRootMat prev 0 3 -- from `0` to `3`[0,1,2,3]
>>>dist VG.! (5 * 1 + 3) -- from `0` to `3`-19
>>>Gr.constructPathFromRootMat prev 1 3 -- from `1` to `3`[1,2,3]
Negative loop can be detected by testing if there's any vertex \(v\) where
m VU.! (:index0 (n, n) (v, v))
>>>any (\v -> dist VG.! (5 * v + v) < 0) [0 .. 5 - 1]False
>>>let es = VU.fromList [(0, 1, -1 :: Int), (1, 0, -1)]>>>let (!dist, !_) = Gr.trackingFloydWarshall 3 es undefW>>>any (\v -> dist VG.! (3 * v + v) < 0) [0 .. 3 - 1]True
Since: 1.2.4.0
Incremental Floyd–Warshall algorithm
Arguments
| :: (HasCallStack, PrimMonad m, Num w, Ord w, Unbox w) | |
| => Int | The number of vertices. |
| -> Vector (Int, Int, w) | Weighted edges. |
| -> w | Distance assignment for unreachable vertices. |
| -> m (MVector (PrimState m) w) | Distance array in one-dimensional index. |
\(O(n^3)\) Floyd–Warshall algorithm that returns a distance matrix \(m\).
- The distance matrix should be accessed as
m VG.! (,index0(n, n) (from, to)) - There's a negative loop if there's any vertex \(v\) where
m VU.! (is negative.index0(n, n) (v, v))
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let es = VU.fromList [(0, 1, 1 :: Int), (1, 2, 1), (2, 3, 1), (1, 3, 4)]>>>let undefW = -1>>>dist <- Gr.newFloydWarshall 4 es undefW>>>VGM.read dist (4 * 0 + 3)3
>>>updateEdgeFloydWarshall dist 4 undefW 1 3 (-2)>>>VGM.read dist (4 * 0 + 3)-1
Since: 1.2.4.0
newTrackingFloydWarshall Source #
Arguments
| :: (HasCallStack, PrimMonad m, Num w, Ord w, Unbox w) | |
| => Int | The number of vertices. |
| -> Vector (Int, Int, w) | Weighted edges. |
| -> w | Distance assignment for unreachable vertices. |
| -> m (MVector (PrimState m) w, MVector (PrimState m) Int) | Distance array in one-dimensional index. |
\(O(n^3)\) Floyd–Warshall algorithm that returns a distance matrix \(m\) and predecessor matrix.
- The distance matrix should be accessed as
m VG.! (,index0(n, n) (from, to)) - The predecessor matrix should be accessed as
m VG.! (index0(n, n) (root, v)) - There's a negative loop if there's any vertex \(v\) where
m VU.! (is negative.index0(n, n) (v, v))
Example
>>>import AtCoder.Extra.Graph qualified as Gr>>>import Data.Vector.Unboxed qualified as VU>>>let es = VU.fromList [(0, 1, 1 :: Int), (1, 2, 1), (2, 3, 1), (1, 3, 4)]>>>let undefW = -1>>>(!dist, !prev) <- Gr.newTrackingFloydWarshall 4 es undefW>>>VGM.read dist (4 * 0 + 3)3
>>>constructPathFromRootMatM prev 0 3[0,1,2,3]
>>>updateEdgeTrackingFloydWarshall dist prev 4 undefW 1 3 (-2)>>>VGM.read dist (4 * 0 + 3)-1
>>>constructPathFromRootMatM prev 0 3[0,1,3]
Since: 1.2.4.0
updateEdgeFloydWarshall Source #
Arguments
| :: (HasCallStack, PrimMonad m, Num w, Ord w, Unbox w) | |
| => MVector (PrimState m) w | Distance matrix. |
| -> Int | The number of vertices. |
| -> w | Distance assignment \(d_0 \gt 0\) for unreachable vertices. It should be |
| -> Int | Edge information: |
| -> Int | Edge information: |
| -> w | Edge information: |
| -> m () | Distance array in one-dimensional index. |
\(O(n^2)\) Updates distance matrix of Floyd–Warshall on edge weight change or new edge addition.
Since: 1.2.4.0
updateEdgeTrackingFloydWarshall Source #
Arguments
| :: (HasCallStack, PrimMonad m, Num w, Ord w, Unbox w) | |
| => MVector (PrimState m) w | Distance matrix. |
| -> MVector (PrimState m) Int | Predecessor matrix. |
| -> Int | The number of vertices. |
| -> w | Distance assignment \(d_0 \gt 0\) for unreachable vertices. It should be |
| -> Int | Edge information: |
| -> Int | Edge information: |
| -> w | Edge information: |
| -> m () | Distance array in one-dimensional index. |
\(O(n^2)\) Updates distance matrix of Floyd–Warshall on edge weight chaneg or new edge addition.
Since: 1.2.4.0
Path reconstruction
Single source point (root)
Functions for retrieving a path from a predecessor array, where -1 represents none.
constructPathFromRoot :: HasCallStack => Vector Int -> Int -> Vector Int Source #
\(O(n)\) Given a predecessor array, retrieves a path from the root to a vertex.
Constraints
- The path must not make a cycle, otherwise this function loops forever.
- There must be a path from the root to the
sinkvertex, otherwise the returned path is not connected to the root.
Since: 1.2.4.0
constructPathToRoot :: HasCallStack => Vector Int -> Int -> Vector Int Source #
\(O(n)\) Given a predecessor array, retrieves a path from a vertex to the root.
Constraints
- The path must not make a cycle, otherwise this function loops forever.
- There must be a path from the root to the
sinkvertex, otherwise the returned path is not connected to the root.
Since: 1.2.4.0
All-pair
Functions for retrieving a path from a predecessor matrix \(m\).
constructPathFromRootMat Source #
Arguments
| :: HasCallStack | |
| => Vector Int | Predecessor matrix. |
| -> Int | Source vertex. |
| -> Int | Sink vertex. |
| -> Vector Int | Path. |
\(O(n)\) Given a NxN predecessor matrix (created with trackingFloydWarshall), retrieves a
path from the root to a sink vertex.
Constraints
- The path must not make a cycle, otherwise this function loops forever.
- There must be a path from the root to the
sinkvertex, otherwise the returned path is not connected to the root.
Since: 1.2.4.0
constructPathToRootMat Source #
Arguments
| :: HasCallStack | |
| => Vector Int | Predecessor matrix. |
| -> Int | Source vertex. |
| -> Int | Sink vertex. |
| -> Vector Int | Path. |
\(O(n)\) Given a NxN predecessor matrix(created with trackingFloydWarshall), retrieves a
path from a vertex to the root.
Constraints
- The path must not make a cycle, otherwise this function loops forever.
- There must be a path from the root to the
sinkvertex, otherwise the returned path is not connected to the root.
Since: 1.2.4.0
constructPathFromRootMatM Source #
Arguments
| :: (HasCallStack, PrimMonad m) | |
| => MVector (PrimState m) Int | Predecessor matrix. |
| -> Int | Source vertex. |
| -> Int | Sink vertex. |
| -> m (Vector Int) | Path. |
\(O(n)\) Given a NxN predecessor matrix (created with newTrackingFloydWarshall), retrieves a
path from the root to a sink vertex.
Constraints
- The path must not make a cycle, otherwise this function loops forever.
- There must be a path from the root to the
ndvertex, otherwise the returned path is not connected to the root.
Since: 1.2.4.0
constructPathToRootMatM Source #
Arguments
| :: (HasCallStack, PrimMonad m) | |
| => MVector (PrimState m) Int | Predecessor matrix. |
| -> Int | Source vertex. |
| -> Int | Sink vertex. |
| -> m (Vector Int) | Path. |
\(O(n)\) Given a NxN predecessor matrix (created with newTrackingFloydWarshall), retrieves a
path from a vertex to the root.
Constraints
- The path must not make a cycle, otherwise this function loops forever.
- There must be a path from the root to the
sinkvertex, otherwise the returned path is not connected to the root.
Since: 1.2.4.0