Skip to content

Commit 8c10f6a

Browse files
authored
Add Dinic’s Algorithm (#249)
1 parent 35936ea commit 8c10f6a

File tree

1 file changed

+398
-0
lines changed

1 file changed

+398
-0
lines changed

graph_algorithms/dinic_max_flow.r

Lines changed: 398 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,398 @@
1+
# Dinic's Algorithm for Maximum Flow
2+
#
3+
# Dinic's algorithm finds the maximum flow in a flow network from source to sink.
4+
# It uses level graphs and blocking flows to achieve better time complexity than
5+
# Ford-Fulkerson. The algorithm repeatedly finds shortest augmenting paths using BFS
6+
# and then uses DFS to send flow along multiple paths in each iteration.
7+
#
8+
# Time Complexity: O(V^2 * E) general case, O(E * sqrt(V)) for unit capacity networks
9+
# Space Complexity: O(V + E) for adjacency list and level array
10+
#
11+
# Applications:
12+
# - Network routing and traffic optimization
13+
# - Bipartite matching problems
14+
# - Image segmentation
15+
# - Airline scheduling
16+
# - Project selection and resource allocation
17+
18+
# Formatting constant
19+
LINE_WIDTH <- 60
20+
21+
#' Create an empty flow network
22+
#' @param n: Number of vertices
23+
#' @return: Flow network structure with adjacency list and capacity matrix
24+
create_flow_network <- function(n) {
25+
# Use environment to allow in-place (by-reference) mutation without superassignment
26+
env <- new.env(parent = emptyenv())
27+
env$n <- n
28+
env$graph <- vector("list", n) # Adjacency list
29+
env$capacity <- matrix(0, nrow = n, ncol = n) # Capacity matrix
30+
env$flow <- matrix(0, nrow = n, ncol = n) # Flow matrix
31+
return(env)
32+
}
33+
34+
#' Add edge to flow network
35+
#' @param network: Flow network structure
36+
#' @param from: Source vertex (1-indexed)
37+
#' @param to: Destination vertex (1-indexed)
38+
#' @param capacity: Edge capacity
39+
#' @return: Updated network
40+
add_edge <- function(network, from, to, capacity) {
41+
# Add forward edge
42+
network$graph[[from]] <- c(network$graph[[from]], to)
43+
network$capacity[from, to] <- network$capacity[from, to] + capacity
44+
45+
# Add reverse edge for residual graph (with 0 capacity initially)
46+
if (!(from %in% network$graph[[to]])) {
47+
network$graph[[to]] <- c(network$graph[[to]], from)
48+
}
49+
50+
return(network)
51+
}
52+
53+
#' Build level graph using BFS
54+
#' @param network: Flow network
55+
#' @param source: Source vertex
56+
#' @param sink: Sink vertex
57+
#' @return: Level array (-1 if vertex not reachable)
58+
bfs_level_graph <- function(network, source, sink) {
59+
n <- network$n
60+
level <- rep(-1, n)
61+
level[source] <- 0
62+
63+
# O(1) queue using head/tail indices; BFS enqueues each vertex at most once
64+
queue <- integer(n)
65+
head <- 1
66+
tail <- 1
67+
queue[tail] <- source
68+
tail <- tail + 1
69+
70+
while (head < tail) {
71+
u <- queue[head]
72+
head <- head + 1
73+
74+
for (v in network$graph[[u]]) {
75+
# Check if edge has residual capacity and v is not visited
76+
residual_capacity <- network$capacity[u, v] - network$flow[u, v]
77+
78+
if (level[v] == -1 && residual_capacity > 0) {
79+
level[v] <- level[u] + 1
80+
queue[tail] <- v
81+
tail <- tail + 1
82+
}
83+
}
84+
}
85+
86+
return(level)
87+
}
88+
89+
#' Send flow using DFS (blocking flow)
90+
#' @param network: Flow network
91+
#' @param u: Current vertex
92+
#' @param sink: Sink vertex
93+
#' @param level: Level array from BFS
94+
#' @param flow: Flow to push
95+
#' @param start: Array tracking next edge to try from each vertex
96+
#' @return: Flow pushed
97+
dfs_send_flow <- function(network, u, sink, level, flow, start) {
98+
# Reached sink
99+
if (u == sink) {
100+
return(flow)
101+
}
102+
103+
# Try all edges from current vertex
104+
while (start[u] <= length(network$graph[[u]])) {
105+
v <- network$graph[[u]][start[u]]
106+
residual_capacity <- network$capacity[u, v] - network$flow[u, v]
107+
108+
# Check if this edge can be used (level increases and has capacity)
109+
if (level[v] == level[u] + 1 && residual_capacity > 0) {
110+
# Recursively send flow
111+
pushed_flow <- dfs_send_flow(
112+
network,
113+
v,
114+
sink,
115+
level,
116+
min(flow, residual_capacity),
117+
start
118+
)
119+
120+
if (pushed_flow > 0) {
121+
# Update flow (environment enables in-place mutation)
122+
network$flow[u, v] <- network$flow[u, v] + pushed_flow
123+
network$flow[v, u] <- network$flow[v, u] - pushed_flow
124+
return(pushed_flow)
125+
}
126+
}
127+
128+
start[u] <- start[u] + 1
129+
}
130+
131+
return(0)
132+
}
133+
134+
#' Dinic's algorithm to find maximum flow
135+
#' @param network: Flow network structure
136+
#' @param source: Source vertex (1-indexed)
137+
#' @param sink: Sink vertex (1-indexed)
138+
#' @return: List with max_flow value, flow matrix, and flow decomposition
139+
dinic_max_flow <- function(network, source, sink) {
140+
if (source < 1 || source > network$n || sink < 1 || sink > network$n) {
141+
stop("Error: Source and sink must be between 1 and n")
142+
}
143+
144+
if (source == sink) {
145+
stop("Error: Source and sink must be different")
146+
}
147+
148+
max_flow <- 0
149+
iterations <- 0
150+
151+
# Repeat until no augmenting path exists
152+
repeat {
153+
iterations <- iterations + 1
154+
155+
# Build level graph using BFS
156+
level <- bfs_level_graph(network, source, sink)
157+
158+
# If sink is not reachable, no more augmenting paths
159+
if (level[sink] == -1) {
160+
break
161+
}
162+
163+
# Send flow using DFS until blocking flow is achieved
164+
start <- rep(1, network$n) # Track next edge to try from each vertex
165+
166+
repeat {
167+
flow <- dfs_send_flow(network, source, sink, level, Inf, start)
168+
169+
if (flow == 0) {
170+
break
171+
}
172+
173+
max_flow <- max_flow + flow
174+
}
175+
}
176+
177+
# Find minimum cut
178+
level_final <- bfs_level_graph(network, source, sink)
179+
source_side <- which(level_final != -1)
180+
sink_side <- which(level_final == -1)
181+
182+
# Find edges in the minimum cut
183+
min_cut_edges <- list()
184+
for (u in source_side) {
185+
for (v in network$graph[[u]]) {
186+
if (v %in% sink_side && network$capacity[u, v] > 0) {
187+
min_cut_edges <- c(min_cut_edges, list(list(from = u, to = v, capacity = network$capacity[u, v])))
188+
}
189+
}
190+
}
191+
192+
return(list(
193+
max_flow = max_flow,
194+
flow_matrix = network$flow,
195+
iterations = iterations,
196+
min_cut_edges = min_cut_edges,
197+
source_partition = source_side,
198+
sink_partition = sink_side
199+
))
200+
}
201+
202+
#' Print maximum flow results
203+
#' @param result: Result from dinic_max_flow
204+
#' @param network: Original network (optional, for displaying edges)
205+
print_max_flow <- function(result, network = NULL) {
206+
cat("Maximum Flow Result:\n")
207+
cat(strrep("=", LINE_WIDTH), "\n\n")
208+
cat(sprintf("Maximum Flow: %g\n", result$max_flow))
209+
cat(sprintf("Iterations: %d\n\n", result$iterations))
210+
211+
cat("Minimum Cut Edges:\n")
212+
cat(strrep("-", LINE_WIDTH), "\n")
213+
if (length(result$min_cut_edges) > 0) {
214+
cat(sprintf("%-15s %-15s %-15s\n", "From", "To", "Capacity"))
215+
cat(strrep("-", LINE_WIDTH), "\n")
216+
total_cut_capacity <- 0
217+
for (edge in result$min_cut_edges) {
218+
cat(sprintf("%-15d %-15d %-15g\n", edge$from, edge$to, edge$capacity))
219+
total_cut_capacity <- total_cut_capacity + edge$capacity
220+
}
221+
cat(strrep("-", LINE_WIDTH), "\n")
222+
cat(sprintf("Total Cut Capacity: %g\n", total_cut_capacity))
223+
} else {
224+
cat("No cut edges found\n")
225+
}
226+
227+
cat(sprintf("\nSource partition: {%s}\n", paste(result$source_partition, collapse = ", ")))
228+
cat(sprintf("Sink partition: {%s}\n", paste(result$sink_partition, collapse = ", ")))
229+
cat("\n")
230+
}
231+
232+
#' Print flow on edges
233+
#' @param network: Flow network with computed flows
234+
print_flow_edges <- function(network) {
235+
cat("Flow on Edges:\n")
236+
cat(strrep("-", LINE_WIDTH), "\n")
237+
cat(sprintf("%-10s %-10s %-12s %-12s\n", "From", "To", "Flow", "Capacity"))
238+
cat(strrep("-", LINE_WIDTH), "\n")
239+
240+
for (u in 1:network$n) {
241+
for (v in network$graph[[u]]) {
242+
if (network$capacity[u, v] > 0 && network$flow[u, v] > 0) {
243+
cat(sprintf("%-10d %-10d %-12g %-12g\n",
244+
u, v, network$flow[u, v], network$capacity[u, v]))
245+
}
246+
}
247+
}
248+
cat(strrep("-", LINE_WIDTH), "\n\n")
249+
}
250+
251+
# ========== Example 1: Basic 6-Vertex Network ==========
252+
253+
cat("========== Example 1: Basic 6-Vertex Flow Network ==========\n\n")
254+
255+
# Create network with 6 vertices
256+
network1 <- create_flow_network(6)
257+
258+
# Add edges (from, to, capacity)
259+
network1 <- add_edge(network1, 1, 2, 16)
260+
network1 <- add_edge(network1, 1, 3, 13)
261+
network1 <- add_edge(network1, 2, 3, 10)
262+
network1 <- add_edge(network1, 2, 4, 12)
263+
network1 <- add_edge(network1, 3, 2, 4)
264+
network1 <- add_edge(network1, 3, 5, 14)
265+
network1 <- add_edge(network1, 4, 3, 9)
266+
network1 <- add_edge(network1, 4, 6, 20)
267+
network1 <- add_edge(network1, 5, 4, 7)
268+
network1 <- add_edge(network1, 5, 6, 4)
269+
270+
cat("Network edges:\n")
271+
cat("1 -> 2 (16), 1 -> 3 (13)\n")
272+
cat("2 -> 3 (10), 2 -> 4 (12)\n")
273+
cat("3 -> 2 (4), 3 -> 5 (14)\n")
274+
cat("4 -> 3 (9), 4 -> 6 (20)\n")
275+
cat("5 -> 4 (7), 5 -> 6 (4)\n\n")
276+
277+
# Find maximum flow from vertex 1 to vertex 6
278+
result1 <- dinic_max_flow(network1, source = 1, sink = 6)
279+
print_max_flow(result1, network1)
280+
print_flow_edges(network1)
281+
282+
# ========== Example 2: Simple Network ==========
283+
284+
cat("========== Example 2: Simple 4-Vertex Network ==========\n\n")
285+
286+
network2 <- create_flow_network(4)
287+
network2 <- add_edge(network2, 1, 2, 10)
288+
network2 <- add_edge(network2, 1, 3, 10)
289+
network2 <- add_edge(network2, 2, 3, 2)
290+
network2 <- add_edge(network2, 2, 4, 4)
291+
network2 <- add_edge(network2, 3, 4, 9)
292+
293+
cat("Network edges:\n")
294+
cat("1 -> 2 (10), 1 -> 3 (10)\n")
295+
cat("2 -> 3 (2), 2 -> 4 (4)\n")
296+
cat("3 -> 4 (9)\n\n")
297+
298+
result2 <- dinic_max_flow(network2, source = 1, sink = 4)
299+
print_max_flow(result2, network2)
300+
print_flow_edges(network2)
301+
302+
# ========== Example 3: Bipartite Matching ==========
303+
304+
cat("========== Example 3: Bipartite Matching (5 workers, 4 jobs) ==========\n\n")
305+
306+
# Create bipartite graph: source(1) -> workers(2-6) -> jobs(7-10) -> sink(11)
307+
network3 <- create_flow_network(11)
308+
309+
# Source to workers (capacity 1 each)
310+
for (i in 2:6) {
311+
network3 <- add_edge(network3, 1, i, 1)
312+
}
313+
314+
# Workers to jobs (based on which jobs they can do)
315+
network3 <- add_edge(network3, 2, 7, 1) # Worker 1 can do Job 1
316+
network3 <- add_edge(network3, 2, 8, 1) # Worker 1 can do Job 2
317+
network3 <- add_edge(network3, 3, 7, 1) # Worker 2 can do Job 1
318+
network3 <- add_edge(network3, 3, 9, 1) # Worker 2 can do Job 3
319+
network3 <- add_edge(network3, 4, 8, 1) # Worker 3 can do Job 2
320+
network3 <- add_edge(network3, 4, 10, 1) # Worker 3 can do Job 4
321+
network3 <- add_edge(network3, 5, 9, 1) # Worker 4 can do Job 3
322+
network3 <- add_edge(network3, 6, 10, 1) # Worker 5 can do Job 4
323+
324+
# Jobs to sink (capacity 1 each)
325+
for (i in 7:10) {
326+
network3 <- add_edge(network3, i, 11, 1)
327+
}
328+
329+
cat("Bipartite matching problem:\n")
330+
cat("Workers: 1-5, Jobs: 1-4\n")
331+
cat("Maximum number of worker-job assignments:\n\n")
332+
333+
result3 <- dinic_max_flow(network3, source = 1, sink = 11)
334+
cat(sprintf("Maximum Matching: %d\n\n", result3$max_flow))
335+
336+
# Show assignments
337+
cat("Worker-Job Assignments:\n")
338+
for (worker in 2:6) {
339+
for (job in 7:10) {
340+
if (network3$flow[worker, job] > 0) {
341+
cat(sprintf("Worker %d -> Job %d\n", worker - 1, job - 6))
342+
}
343+
}
344+
}
345+
cat("\n")
346+
347+
# ========== Example 4: Multi-source Multi-sink ==========
348+
349+
cat("========== Example 4: Multi-Source Multi-Sink Problem ==========\n\n")
350+
351+
# Convert to single source/sink by adding super source and super sink
352+
network4 <- create_flow_network(8)
353+
354+
# Super source (1) to sources (2, 3)
355+
network4 <- add_edge(network4, 1, 2, 10)
356+
network4 <- add_edge(network4, 1, 3, 15)
357+
358+
# Internal edges
359+
network4 <- add_edge(network4, 2, 4, 8)
360+
network4 <- add_edge(network4, 2, 5, 6)
361+
network4 <- add_edge(network4, 3, 4, 5)
362+
network4 <- add_edge(network4, 3, 5, 12)
363+
network4 <- add_edge(network4, 4, 6, 10)
364+
network4 <- add_edge(network4, 5, 7, 9)
365+
366+
# Sinks (6, 7) to super sink (8)
367+
network4 <- add_edge(network4, 6, 8, 15)
368+
network4 <- add_edge(network4, 7, 8, 12)
369+
370+
cat("Multi-source multi-sink converted to single source/sink\n")
371+
cat("Sources: 2, 3 | Sinks: 6, 7\n\n")
372+
373+
result4 <- dinic_max_flow(network4, source = 1, sink = 8)
374+
print_max_flow(result4, network4)
375+
376+
# ========== Algorithm Properties ==========
377+
378+
cat("========== Algorithm Properties ==========\n\n")
379+
cat("1. Dinic's algorithm guarantees finding maximum flow\n")
380+
cat("2. Works on directed graphs with non-negative capacities\n")
381+
cat("3. Faster than Ford-Fulkerson for dense graphs\n")
382+
cat("4. Maximum flow equals minimum cut capacity (Max-Flow Min-Cut Theorem)\n")
383+
cat("5. Each iteration increases distance to sink for at least one vertex\n")
384+
cat("6. Number of iterations is O(V) for unit capacity networks\n\n")
385+
386+
cat("========== Comparison with Other Max Flow Algorithms ==========\n\n")
387+
cat("Ford-Fulkerson:\n")
388+
cat(" Time: O(E * max_flow) - can be slow for large flows\n")
389+
cat(" Method: Find any augmenting path\n\n")
390+
cat("Edmonds-Karp:\n")
391+
cat(" Time: O(V * E^2) - specific Ford-Fulkerson with BFS\n")
392+
cat(" Method: Shortest augmenting path\n\n")
393+
cat("Dinic's Algorithm:\n")
394+
cat(" Time: O(V^2 * E), O(E * sqrt(V)) for unit capacities\n")
395+
cat(" Method: Blocking flows in level graphs\n\n")
396+
cat("Push-Relabel:\n")
397+
cat(" Time: O(V^2 * E) or O(V^3) depending on implementation\n")
398+
cat(" Method: Preflow-push operations\n")

0 commit comments

Comments
 (0)