diff --git a/NAMESPACE b/NAMESPACE index 29c0ec2cb0..e030be3b03 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -491,6 +491,7 @@ export(has_eulerian_cycle) export(has_eulerian_path) export(head_of) export(head_print) +export(hex_lattice) export(hierarchical_sbm) export(hierarchy) export(hits_scores) @@ -665,6 +666,7 @@ export(make_full_citation_graph) export(make_full_graph) export(make_full_multipartite) export(make_graph) +export(make_hex_lattice) export(make_kautz_graph) export(make_lattice) export(make_line_graph) diff --git a/R/aaa-auto.R b/R/aaa-auto.R index 70f7868202..e2c404d713 100644 --- a/R/aaa-auto.R +++ b/R/aaa-auto.R @@ -412,6 +412,28 @@ triangular_lattice_impl <- function( res } +hexagonal_lattice_impl <- function( + dimvector, + directed = FALSE, + mutual = FALSE +) { + # Argument checks + dimvector <- as.numeric(dimvector) + directed <- as.logical(directed) + mutual <- as.logical(mutual) + + on.exit(.Call(R_igraph_finalizer)) + # Function call + res <- .Call( + R_igraph_hexagonal_lattice, + dimvector, + directed, + mutual + ) + + res +} + path_graph_impl <- function( n, directed = FALSE, diff --git a/R/make.R b/R/make.R index b4a7d94f2b..78e26c6f29 100644 --- a/R/make.R +++ b/R/make.R @@ -2028,6 +2028,80 @@ lattice <- function(...) constructor_spec(make_lattice, ...) ## ----------------------------------------------------------------- +#' Create a hexagonal lattice graph +#' +#' `r lifecycle::badge("experimental")` +#' +#' `make_hex_lattice()` creates a hexagonal lattice where each interior vertex +#' has degree 3. The hexagonal lattice and triangular lattice are different +#' structures; they are planar duals of each other. See `igraph_triangular_lattice()` +#' in the C library for the triangular lattice. +#' +#' @details +#' A hexagonal lattice is a lattice structure where each interior vertex +#' (not on the boundary) has degree 3. The function supports creating lattices +#' with different boundary shapes. +#' +#' The `dims` parameter determines the boundary shape of the lattice: +#' \itemize{ +#' \item If `dims` is a single number, the lattice has a triangular boundary +#' where each side contains `dims` vertices. +#' \item If `dims` is a vector of length 2, the lattice has a rectangular +#' boundary with sides containing `dims[1]` and `dims[2]` vertices. +#' \item If `dims` is a vector of length 3, the lattice has a hexagonal +#' boundary where the sides contain `dims[1]`, `dims[2]`, and `dims[3]` +#' vertices. +#' } +#' +#' @param dims Integer vector, defines the shape of the lattice. See details below. +#' @param ... These dots are for future extensions and must be empty. +#' @param directed Logical scalar, whether to create a directed graph. +#' @param mutual Logical scalar, if the graph is directed this parameter +#' controls whether edges are mutual (bidirectional). +#' @return An igraph graph. +#' +#' @family deterministic constructors +#' @export +#' @examples +#' # Triangular shape with 5 vertices on each side +#' g1 <- make_hex_lattice(5) +#' plot(g1) +#' +#' # Rectangular shape +#' g2 <- make_hex_lattice(c(3, 4)) +#' plot(g2) +#' +#' # Hexagonal shape +#' g3 <- make_hex_lattice(c(3, 3, 3)) +#' plot(g3) +#' @cdocs igraph_hexagonal_lattice +make_hex_lattice <- function(dims, ..., directed = FALSE, mutual = FALSE) { + check_dots_empty() + + graph <- hexagonal_lattice_impl( + dimvector = dims, + directed = directed, + mutual = mutual + ) + + if (igraph_opt("add.params")) { + graph <- set_graph_attr(graph, "name", "Hexagonal lattice") + graph <- set_graph_attr(graph, "dimvector", dims) + graph <- set_graph_attr(graph, "directed", directed) + graph <- set_graph_attr(graph, "mutual", mutual) + } + graph +} + +#' @rdname make_hex_lattice +#' @export +hex_lattice <- function(dims, ..., directed = FALSE, mutual = FALSE) { + check_dots_empty() + constructor_spec(make_hex_lattice, dims = dims, directed = directed, mutual = mutual) +} + +## ----------------------------------------------------------------- + #' Create a ring graph #' #' A ring is a one-dimensional lattice and this function is a special case diff --git a/man/graph_from_atlas.Rd b/man/graph_from_atlas.Rd index eb3b3d7885..aadedec366 100644 --- a/man/graph_from_atlas.Rd +++ b/man/graph_from_atlas.Rd @@ -50,6 +50,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/man/graph_from_edgelist.Rd b/man/graph_from_edgelist.Rd index 198a763543..4d7261cdf5 100644 --- a/man/graph_from_edgelist.Rd +++ b/man/graph_from_edgelist.Rd @@ -46,6 +46,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/man/graph_from_literal.Rd b/man/graph_from_literal.Rd index c17966e3bc..e888d6f5b9 100644 --- a/man/graph_from_literal.Rd +++ b/man/graph_from_literal.Rd @@ -137,6 +137,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/man/make_.Rd b/man/make_.Rd index 1dbd908e67..cf7a62fd79 100644 --- a/man/make_.Rd +++ b/man/make_.Rd @@ -53,6 +53,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/man/make_chordal_ring.Rd b/man/make_chordal_ring.Rd index 8633eec00f..b2ed5e2417 100644 --- a/man/make_chordal_ring.Rd +++ b/man/make_chordal_ring.Rd @@ -53,6 +53,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/man/make_circulant.Rd b/man/make_circulant.Rd index f3d3afcb94..32b6376d3e 100644 --- a/man/make_circulant.Rd +++ b/man/make_circulant.Rd @@ -51,6 +51,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/man/make_empty_graph.Rd b/man/make_empty_graph.Rd index f59cbc19e4..7b07bc4097 100644 --- a/man/make_empty_graph.Rd +++ b/man/make_empty_graph.Rd @@ -38,6 +38,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/man/make_full_citation_graph.Rd b/man/make_full_citation_graph.Rd index 85d301f909..4e30f7b611 100644 --- a/man/make_full_citation_graph.Rd +++ b/man/make_full_citation_graph.Rd @@ -39,6 +39,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/man/make_full_graph.Rd b/man/make_full_graph.Rd index ea9bcda9ca..f2c9d5c40c 100644 --- a/man/make_full_graph.Rd +++ b/man/make_full_graph.Rd @@ -40,6 +40,7 @@ Other deterministic constructors: \code{\link{make_full_citation_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/man/make_full_multipartite.Rd b/man/make_full_multipartite.Rd index e0cedcb710..7fb27a21ac 100644 --- a/man/make_full_multipartite.Rd +++ b/man/make_full_multipartite.Rd @@ -53,6 +53,7 @@ Other deterministic constructors: \code{\link{make_full_citation_graph}()}, \code{\link{make_full_graph}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/man/make_graph.Rd b/man/make_graph.Rd index a3c78f6328..49be839160 100644 --- a/man/make_graph.Rd +++ b/man/make_graph.Rd @@ -249,6 +249,7 @@ Other deterministic constructors: \code{\link{make_full_citation_graph}()}, \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/man/make_hex_lattice.Rd b/man/make_hex_lattice.Rd new file mode 100644 index 0000000000..729d4fe02e --- /dev/null +++ b/man/make_hex_lattice.Rd @@ -0,0 +1,83 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/make.R +\name{make_hex_lattice} +\alias{make_hex_lattice} +\alias{hex_lattice} +\title{Create a hexagonal lattice graph} +\usage{ +make_hex_lattice(dims, ..., directed = FALSE, mutual = FALSE) + +hex_lattice(dims, ..., directed = FALSE, mutual = FALSE) +} +\arguments{ +\item{dims}{Integer vector, defines the shape of the lattice. See details below.} + +\item{...}{These dots are for future extensions and must be empty.} + +\item{directed}{Logical scalar, whether to create a directed graph.} + +\item{mutual}{Logical scalar, if the graph is directed this parameter +controls whether edges are mutual (bidirectional).} +} +\value{ +An igraph graph. +} +\description{ +\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} +} +\details{ +\code{make_hex_lattice()} creates a hexagonal lattice where each interior vertex +has degree 3. The hexagonal lattice and triangular lattice are different +structures; they are planar duals of each other. See \code{igraph_triangular_lattice()} +in the C library for the triangular lattice. + +A hexagonal lattice is a lattice structure where each interior vertex +(not on the boundary) has degree 3. The function supports creating lattices +with different boundary shapes. + +The \code{dims} parameter determines the boundary shape of the lattice: +\itemize{ +\item If \code{dims} is a single number, the lattice has a triangular boundary +where each side contains \code{dims} vertices. +\item If \code{dims} is a vector of length 2, the lattice has a rectangular +boundary with sides containing \code{dims[1]} and \code{dims[2]} vertices. +\item If \code{dims} is a vector of length 3, the lattice has a hexagonal +boundary where the sides contain \code{dims[1]}, \code{dims[2]}, and \code{dims[3]} +vertices. +} +} +\examples{ +# Triangular shape with 5 vertices on each side +g1 <- make_hex_lattice(5) +plot(g1) + +# Rectangular shape +g2 <- make_hex_lattice(c(3, 4)) +plot(g2) + +# Hexagonal shape +g3 <- make_hex_lattice(c(3, 3, 3)) +plot(g3) +} +\seealso{ +Other deterministic constructors: +\code{\link{graph_from_atlas}()}, +\code{\link{graph_from_edgelist}()}, +\code{\link{graph_from_literal}()}, +\code{\link{make_}()}, +\code{\link{make_chordal_ring}()}, +\code{\link{make_circulant}()}, +\code{\link{make_empty_graph}()}, +\code{\link{make_full_citation_graph}()}, +\code{\link{make_full_graph}()}, +\code{\link{make_full_multipartite}()}, +\code{\link{make_graph}()}, +\code{\link{make_lattice}()}, +\code{\link{make_ring}()}, +\code{\link{make_star}()}, +\code{\link{make_tree}()}, +\code{\link{make_turan}()} +} +\concept{deterministic constructors} +\section{Related documentation in the C library}{\href{https://igraph.org/c/html/latest/igraph-Generators.html#igraph_hexagonal_lattice}{\code{hexagonal_lattice()}}.} + diff --git a/man/make_lattice.Rd b/man/make_lattice.Rd index 8a9c80bc0d..5a9dd0866c 100644 --- a/man/make_lattice.Rd +++ b/man/make_lattice.Rd @@ -70,6 +70,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, \code{\link{make_tree}()}, diff --git a/man/make_ring.Rd b/man/make_ring.Rd index f02131b934..dfacb96781 100644 --- a/man/make_ring.Rd +++ b/man/make_ring.Rd @@ -47,6 +47,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_star}()}, \code{\link{make_tree}()}, diff --git a/man/make_star.Rd b/man/make_star.Rd index 27b1d5ab7e..f8611d299b 100644 --- a/man/make_star.Rd +++ b/man/make_star.Rd @@ -46,6 +46,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_tree}()}, diff --git a/man/make_tree.Rd b/man/make_tree.Rd index 3999a4e725..2dfa435682 100644 --- a/man/make_tree.Rd +++ b/man/make_tree.Rd @@ -47,6 +47,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/man/make_turan.Rd b/man/make_turan.Rd index 6431e0f76b..921369d2ff 100644 --- a/man/make_turan.Rd +++ b/man/make_turan.Rd @@ -53,6 +53,7 @@ Other deterministic constructors: \code{\link{make_full_graph}()}, \code{\link{make_full_multipartite}()}, \code{\link{make_graph}()}, +\code{\link{make_hex_lattice}()}, \code{\link{make_lattice}()}, \code{\link{make_ring}()}, \code{\link{make_star}()}, diff --git a/src/cpp11.cpp b/src/cpp11.cpp index b8774dc926..d5679865b8 100644 --- a/src/cpp11.cpp +++ b/src/cpp11.cpp @@ -209,6 +209,7 @@ extern SEXP R_igraph_harmonic_centrality_cutoff(SEXP, SEXP, SEXP, SEXP, SEXP, SE extern SEXP R_igraph_has_loop(SEXP); extern SEXP R_igraph_has_multiple(SEXP); extern SEXP R_igraph_has_mutual(SEXP, SEXP); +extern SEXP R_igraph_hexagonal_lattice(SEXP, SEXP, SEXP); extern SEXP R_igraph_hrg_consensus(SEXP, SEXP, SEXP, SEXP); extern SEXP R_igraph_hrg_create(SEXP, SEXP); extern SEXP R_igraph_hrg_fit(SEXP, SEXP, SEXP, SEXP); @@ -735,6 +736,7 @@ static const R_CallMethodDef CallEntries[] = { {"R_igraph_has_loop", (DL_FUNC) &R_igraph_has_loop, 1}, {"R_igraph_has_multiple", (DL_FUNC) &R_igraph_has_multiple, 1}, {"R_igraph_has_mutual", (DL_FUNC) &R_igraph_has_mutual, 2}, + {"R_igraph_hexagonal_lattice", (DL_FUNC) &R_igraph_hexagonal_lattice, 3}, {"R_igraph_hrg_consensus", (DL_FUNC) &R_igraph_hrg_consensus, 4}, {"R_igraph_hrg_create", (DL_FUNC) &R_igraph_hrg_create, 2}, {"R_igraph_hrg_fit", (DL_FUNC) &R_igraph_hrg_fit, 4}, diff --git a/src/rinterface.c b/src/rinterface.c index a2218afcc6..588e42fc22 100644 --- a/src/rinterface.c +++ b/src/rinterface.c @@ -697,6 +697,41 @@ SEXP R_igraph_triangular_lattice(SEXP dimvector, SEXP directed, SEXP mutual) { return(r_result); } +/*-------------------------------------------/ +/ igraph_hexagonal_lattice / +/-------------------------------------------*/ +SEXP R_igraph_hexagonal_lattice(SEXP dimvector, SEXP directed, SEXP mutual) { + /* Declarations */ + igraph_t c_graph; + igraph_vector_int_t c_dimvector; + igraph_bool_t c_directed; + igraph_bool_t c_mutual; + SEXP graph; + + SEXP r_result; + /* Convert input */ + IGRAPH_R_CHECK(R_SEXP_to_vector_int_copy(dimvector, &c_dimvector)); + IGRAPH_FINALLY(igraph_vector_int_destroy, &c_dimvector); + IGRAPH_R_CHECK_BOOL(directed); + c_directed = LOGICAL(directed)[0]; + IGRAPH_R_CHECK_BOOL(mutual); + c_mutual = LOGICAL(mutual)[0]; + /* Call igraph */ + IGRAPH_R_CHECK(igraph_hexagonal_lattice(&c_graph, &c_dimvector, c_directed, c_mutual)); + + /* Convert output */ + IGRAPH_FINALLY(igraph_destroy, &c_graph); + PROTECT(graph=R_igraph_to_SEXP(&c_graph)); + IGRAPH_I_DESTROY(&c_graph); + IGRAPH_FINALLY_CLEAN(1); + igraph_vector_int_destroy(&c_dimvector); + IGRAPH_FINALLY_CLEAN(1); + r_result = graph; + + UNPROTECT(1); + return(r_result); +} + /*-------------------------------------------/ / igraph_path_graph / /-------------------------------------------*/ diff --git a/tests/testthat/_snaps/aaa-auto.md b/tests/testthat/_snaps/aaa-auto.md index e95f747329..b09357c6b0 100644 --- a/tests/testthat/_snaps/aaa-auto.md +++ b/tests/testthat/_snaps/aaa-auto.md @@ -236,6 +236,36 @@ Error in `triangular_lattice_impl()`: ! At vendor/cigraph/src/constructors/lattices.c:xx : Invalid dimension vector. Invalid value +# hexagonal_lattice_impl basic + + Code + hexagonal_lattice_impl(dimvector = c(2, 2)) + Output + IGRAPH U--- 16 19 -- + + edges: + [1] 1-- 2 1-- 7 2-- 3 3-- 4 3-- 9 4-- 5 5--11 6-- 7 6--12 7-- 8 + [11] 8-- 9 8--14 9--10 10--11 10--16 12--13 13--14 14--15 15--16 + +--- + + Code + hexagonal_lattice_impl(dimvector = c(2, 2), directed = TRUE, mutual = TRUE) + Output + IGRAPH D--- 16 38 -- + + edges: + [1] 1-> 2 2-> 1 1-> 7 7-> 1 2-> 3 3-> 2 3-> 4 4-> 3 3-> 9 9-> 3 + [11] 4-> 5 5-> 4 5->11 11-> 5 6-> 7 7-> 6 6->12 12-> 6 7-> 8 8-> 7 + [21] 8-> 9 9-> 8 8->14 14-> 8 9->10 10-> 9 10->11 11->10 10->16 16->10 + [31] 12->13 13->12 13->14 14->13 14->15 15->14 15->16 16->15 + +# hexagonal_lattice_impl errors + + Code + hexagonal_lattice_impl(dimvector = -1) + Condition + Error in `hexagonal_lattice_impl()`: + ! At vendor/cigraph/src/constructors/lattices.c:xx : Invalid dimension vector. Invalid value + # path_graph_impl basic Code diff --git a/tests/testthat/test-aaa-auto.R b/tests/testthat/test-aaa-auto.R index c1a5e38860..3e4215f1fb 100644 --- a/tests/testthat/test-aaa-auto.R +++ b/tests/testthat/test-aaa-auto.R @@ -344,6 +344,29 @@ test_that("triangular_lattice_impl errors", { )) }) +# 11b. hexagonal_lattice_impl + +test_that("hexagonal_lattice_impl basic", { + withr::local_seed(20250909) + local_igraph_options(print.id = FALSE) + expect_snapshot(hexagonal_lattice_impl( + dimvector = c(2, 2) + )) + expect_snapshot(hexagonal_lattice_impl( + dimvector = c(2, 2), + directed = TRUE, + mutual = TRUE + )) +}) + +test_that("hexagonal_lattice_impl errors", { + withr::local_seed(20250909) + local_igraph_options(print.id = FALSE) + expect_snapshot_igraph_error(hexagonal_lattice_impl( + dimvector = -1 + )) +}) + # 12. path_graph_impl test_that("path_graph_impl basic", { diff --git a/tests/testthat/test-make.R b/tests/testthat/test-make.R index eafcc645d3..a252804e84 100644 --- a/tests/testthat/test-make.R +++ b/tests/testthat/test-make.R @@ -484,6 +484,48 @@ test_that("graph_from_lcf() works", { expect_isomorphic(g1, g2) }) +test_that("make_hex_lattice works", { + # Test triangular shape (1D) + g1 <- make_hex_lattice(3) + expect_equal(vcount(g1), 22) + expect_equal(ecount(g1), 27) + expect_false(is_directed(g1)) + + # Test rectangular shape (2D) + g2 <- make_hex_lattice(c(3, 4)) + expect_equal(vcount(g2), 38) + expect_equal(ecount(g2), 49) + + # Test hexagonal shape (3D) + g3 <- make_hex_lattice(c(2, 2, 2)) + expect_equal(vcount(g3), 24) + expect_equal(ecount(g3), 30) + + # Test directed graph + g4 <- make_hex_lattice(3, directed = TRUE, mutual = FALSE) + expect_true(is_directed(g4)) + + # Test mutual edges + g5 <- make_hex_lattice(3, directed = TRUE, mutual = TRUE) + expect_true(is_directed(g5)) + # Check that edges come in pairs (mutual) + expect_equal(ecount(g5), 54) # Should have double the edges +}) + +test_that("hex_lattice works with make_()", { + # Test basic usage with make_() + g1 <- make_(hex_lattice(3)) + expect_equal(vcount(g1), 22) + expect_equal(ecount(g1), 27) + + # Test with different dimensions + g2 <- make_(hex_lattice(c(3, 4))) + expect_equal(vcount(g2), 38) + + g3 <- make_(hex_lattice(c(2, 2, 2))) + expect_equal(vcount(g3), 24) +}) + test_that("make_full_multipartite() works", { # Test basic multipartite graph g <- make_full_multipartite(c(2, 3, 4)) diff --git a/tools/stimulus/functions-R.yaml b/tools/stimulus/functions-R.yaml index 7470eaf8f5..02811c97b8 100644 --- a/tools/stimulus/functions-R.yaml +++ b/tools/stimulus/functions-R.yaml @@ -131,6 +131,12 @@ igraph_turan: name: Turan graph GATTR-PARAM: n, r +igraph_hexagonal_lattice: + R: + GATTR: + name: Hexagonal lattice + GATTR-PARAM: dimvector, directed, mutual + # TODO: temporarily disabled igraph_weighted_sparsemat: IGNORE: RR, RC