Skip to content

Commit b2d6b24

Browse files
authored
feat : Add Iterative Deepening DFS (#262)
1 parent 8c10f6a commit b2d6b24

File tree

1 file changed

+199
-0
lines changed

1 file changed

+199
-0
lines changed

graph_algorithms/iddfs.r

Lines changed: 199 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,199 @@
1+
# Iterative Deepening Depth-First Search (IDDFS)
2+
#
3+
# IDDFS performs repeated depth-limited DFS from depth = 0..max_depth until a target
4+
# is found. It combines the optimality (in terms of shallowest solution) of BFS with
5+
# the space efficiency of DFS.
6+
#
7+
# Time Complexity: O(b^d) in the worst case, where b is branching factor and d depth
8+
# Space Complexity: O(d) recursion/stack depth
9+
10+
# Formatting
11+
LINE_WIDTH <- 60
12+
13+
print_line <- function(char = "-", width = LINE_WIDTH) {
14+
cat(strrep(char, width), "\n", sep = "")
15+
}
16+
17+
#' Normalize adjacency list graph
18+
#'
19+
#' Ensures graph is a named list with names "1".."N" where N is the maximum vertex id,
20+
#' and that all adjacency entries are integer vectors (possibly empty). Missing vertices
21+
#' are added with empty adjacency.
22+
#' @param graph A list mapping vertex id (character or numeric) to numeric neighbor vector
23+
#' @return A normalized adjacency list with names "1".."N"
24+
normalize_graph <- function(graph) {
25+
if (!is.list(graph)) stop("graph must be a list")
26+
# Collect vertices from names and neighbors
27+
name_ids <- as.integer(names(graph))
28+
if (any(is.na(name_ids))) {
29+
bad_names <- names(graph)[is.na(name_ids)]
30+
stop(
31+
sprintf(
32+
"graph names must be coercible to integers (e.g., '1','2',...). Problematic names: %s",
33+
paste(bad_names, collapse = ", ")
34+
)
35+
)
36+
}
37+
neighbor_ids <- unlist(graph, use.names = FALSE)
38+
if (length(neighbor_ids) == 0) neighbor_ids <- integer(0)
39+
if (!is.integer(neighbor_ids)) neighbor_ids <- as.integer(neighbor_ids)
40+
if (any(is.na(neighbor_ids))) stop("neighbors must be numeric/integer ids")
41+
max_id <- max(c(0L, name_ids, neighbor_ids))
42+
if (max_id < 1L) {
43+
# empty graph
44+
return(setNames(vector("list", 0L), character(0L)))
45+
}
46+
adj <- vector("list", max_id)
47+
for (i in seq_len(max_id)) adj[[i]] <- integer(0)
48+
# Fill from provided graph
49+
for (i in seq_along(graph)) {
50+
vid <- name_ids[i]
51+
if (!length(graph[[i]])) {
52+
adj[[vid]] <- integer(0)
53+
} else {
54+
nbrs <- as.integer(graph[[i]])
55+
if (any(is.na(nbrs))) stop("neighbors must be numeric/integer ids")
56+
# Filter out-of-range neighbors gracefully but warn
57+
if (length(nbrs)) {
58+
out_of_range <- nbrs < 1L
59+
if (any(out_of_range)) {
60+
warning("Removed neighbors < 1: ", paste(nbrs[out_of_range], collapse = ", "))
61+
nbrs <- nbrs[!out_of_range]
62+
}
63+
}
64+
adj[[vid]] <- nbrs
65+
}
66+
}
67+
names(adj) <- as.character(seq_len(max_id))
68+
adj
69+
}
70+
71+
#' Depth-Limited Search (recursive)
72+
#'
73+
#' This version avoids global state and only prevents cycles along the current path.
74+
#' @param graph Normalized adjacency list from normalize_graph
75+
#' @param current Current vertex (integer)
76+
#' @param target Target vertex (integer)
77+
#' @param limit Remaining depth limit (integer >= 0)
78+
#' @param path Vector of vertices along the current path (for cycle avoidance)
79+
#' @return list(found=logical, path=integer vector when found)
80+
.depth_limited_search <- function(graph, current, target, limit, path) {
81+
# Visit current
82+
new_path <- c(path, current)
83+
if (current == target) {
84+
return(list(found = TRUE, path = new_path))
85+
}
86+
if (limit == 0L) {
87+
return(list(found = FALSE, path = integer(0)))
88+
}
89+
# Explore neighbors
90+
nbrs <- graph[[current]]
91+
for (nbr in nbrs) {
92+
# Avoid cycles within the current path
93+
if (!(nbr %in% new_path)) {
94+
res <- .depth_limited_search(graph, nbr, target, limit - 1L, new_path)
95+
if (res$found) return(res)
96+
}
97+
}
98+
return(list(found = FALSE, path = integer(0)))
99+
}
100+
101+
#' Iterative Deepening DFS (IDDFS)
102+
#'
103+
#' @param graph A named list adjacency: names are vertices ("1","2",...), values are integer neighbors
104+
#' @param start Start vertex (integer)
105+
#' @param target Target vertex (integer)
106+
#' @param max_depth Maximum depth to search (integer >= 0)
107+
#' @param verbose If TRUE, prints progress; otherwise silent
108+
#' @return list(found=logical, depth=integer if found, path=integer vector when found)
109+
#' @examples
110+
#' g <- list("1"=c(2,3), "2"=c(4), "3"=c(5), "4"=c(), "5"=c())
111+
#' iddfs(g, start=1, target=5, max_depth=5, verbose=TRUE)
112+
iddfs <- function(graph, start, target, max_depth, verbose = TRUE) {
113+
adj <- normalize_graph(graph)
114+
if (!is.numeric(start) || !is.numeric(target)) {
115+
stop("start and target must be numeric/integer")
116+
}
117+
start <- as.integer(start)
118+
target <- as.integer(target)
119+
if (length(adj) == 0L) return(list(found = FALSE, depth = NA_integer_, path = integer(0)))
120+
n <- length(adj)
121+
if (start < 1L || start > n || target < 1L || target > n) {
122+
stop(sprintf("start and target must be in [1, %d]", n))
123+
}
124+
if (!is.numeric(max_depth) || max_depth < 0) stop("max_depth must be integer >= 0")
125+
max_depth <- as.integer(max_depth)
126+
127+
if (verbose) {
128+
cat("Iterative Deepening DFS\n")
129+
print_line("=")
130+
}
131+
132+
# Early exit if start is target
133+
if (start == target) {
134+
if (verbose) {
135+
cat(sprintf("✓ Target %d found at depth 0\n", target))
136+
print_line("-")
137+
}
138+
return(list(found = TRUE, depth = 0L, path = c(start)))
139+
}
140+
141+
for (depth in 0:max_depth) {
142+
if (verbose) cat(sprintf("Searching at depth limit: %d\n", depth))
143+
res <- .depth_limited_search(adj, start, target, depth, integer(0))
144+
if (res$found) {
145+
if (verbose) {
146+
cat(sprintf("✓ Target %d found at depth %d\n", target, depth))
147+
print_line("-")
148+
}
149+
return(list(found = TRUE, depth = depth, path = res$path))
150+
}
151+
}
152+
153+
if (verbose) {
154+
cat(sprintf("✗ Target %d not found up to depth %d\n", target, max_depth))
155+
print_line("-")
156+
}
157+
return(list(found = FALSE, depth = NA_integer_, path = integer(0)))
158+
}
159+
160+
#' Example demonstrations for IDDFS
161+
#' @return NULL (prints results)
162+
example_iddfs <- function() {
163+
cat("\n========== Example 1: Simple Directed Graph ==========\n")
164+
graph1 <- list(
165+
"1" = c(2, 3),
166+
"2" = c(4),
167+
"3" = c(5),
168+
"4" = c(),
169+
"5" = c()
170+
)
171+
print(iddfs(graph1, start = 1, target = 5, max_depth = 5, verbose = TRUE))
172+
173+
cat("\n========== Example 2: Target Not Found ==========\n")
174+
graph2 <- list(
175+
"1" = c(2),
176+
"2" = c(3),
177+
"3" = c()
178+
)
179+
print(iddfs(graph2, start = 1, target = 6, max_depth = 3, verbose = TRUE))
180+
181+
cat("\n========== Example 3: Larger Graph ==========\n")
182+
graph3 <- list(
183+
"1" = c(2, 3, 4),
184+
"2" = c(5, 6),
185+
"3" = c(7),
186+
"4" = c(8),
187+
"5" = c(),
188+
"6" = c(),
189+
"7" = c(9),
190+
"8" = c(),
191+
"9" = c()
192+
)
193+
print(iddfs(graph3, start = 1, target = 9, max_depth = 5, verbose = TRUE))
194+
195+
invisible(NULL)
196+
}
197+
198+
# Uncomment to run examples when sourcing this file interactively
199+
# if (interactive()) example_iddfs()

0 commit comments

Comments
 (0)