diff --git a/R/register.R b/R/register.R index 3ea10d52..5022e801 100644 --- a/R/register.R +++ b/R/register.R @@ -77,7 +77,6 @@ cpp_register <- function(path = ".", quiet = !is_interactive(), extension = c(". cli::cli_alert_success("generated file {.file {basename(r_path)}}") } - call_entries <- get_call_entries(path, funs$name, package) cpp_function_registration <- glue::glue_data(funs, ' {{ @@ -85,9 +84,9 @@ cpp_register <- function(path = ".", quiet = !is_interactive(), extension = c(". n_args = viapply(funs$args, nrow) ) - cpp_function_registration <- glue::glue_collapse(cpp_function_registration, sep = "\n") + cpp_function_registration <- glue::glue_collapse(cpp_function_registration, sep = "\n") - extra_includes <- character() + extra_includes <- character() if (pkg_links_to_rcpp(path)) { extra_includes <- c(extra_includes, "#include ", "#include ", "using namespace Rcpp;") } @@ -215,35 +214,75 @@ generate_init_functions <- function(funs) { } generate_r_functions <- function(funs, package = "cpp11", use_package = FALSE) { - funs <- funs[c("name", "return_type", "args")] + funs <- funs[c("name", "return_type", "args", "file", "line", "decoration")] if (use_package) { package_call <- glue::glue(', PACKAGE = "{package}"') package_names <- glue::glue_data(funs, '"_{package}_{name}"') } else { - package_names <- glue::glue_data(funs, '`_{package}_{name}`') + package_names <- glue::glue_data(funs, "`_{package}_{name}`") package_call <- "" } - funs$package <- package funs$package_call <- package_call funs$list_params <- vcapply(funs$args, glue_collapse_data, "{name}") funs$params <- vcapply(funs$list_params, function(x) if (nzchar(x)) paste0(", ", x) else x) is_void <- funs$return_type == "void" funs$calls <- ifelse(is_void, - glue::glue_data(funs, 'invisible(.Call({package_names}{params}{package_call}))'), - glue::glue_data(funs, '.Call({package_names}{params}{package_call})') + glue::glue_data(funs, "invisible(.Call({package_names}{params}{package_call}))"), + glue::glue_data(funs, ".Call({package_names}{params}{package_call})") ) - out <- glue::glue_data(funs, ' - {name} <- function({list_params}) {{ - {calls} - }} - ') + # Parse and associate Roxygen comments + funs$roxygen_comment <- mapply(function(file, line) { + if (file.exists(file)) { + comments <- extract_roxygen_comments(file) + matched_comment <- "" + for (comment in comments) { + # Check if the comment directly precedes the function without gaps + if (line == comment$line + 1) { + matched_comment <- comment$text + break + } + } + matched_comment + } else { + "" + } + }, funs$file, funs$line, SIMPLIFY = TRUE) + + # Generate R functions with or without Roxygen comments + out <- mapply(function(name, list_params, calls, roxygen_comment) { + if (nzchar(roxygen_comment)) { + glue::glue("{roxygen_comment}\n{name} <- function({list_params}) {{\n\t{calls}\n}}") + } else { + glue::glue("{name} <- function({list_params}) {{\n {calls}\n}}") + } + }, funs$name, funs$list_params, funs$calls, funs$roxygen_comment, SIMPLIFY = TRUE) + + out <- glue::trim(out) out <- glue::glue_collapse(out, sep = "\n\n") unclass(out) } +extract_roxygen_comments <- function(file) { + lines <- readLines(file) + roxygen_start <- grep("^/\\* roxygen start", lines) + roxygen_end <- grep("roxygen end \\*/$", lines) + + if (length(roxygen_start) == 0 || length(roxygen_end) == 0) { + return(list()) + } + + roxygen_comments <- mapply(function(start, end) { + roxygen_lines <- lines[(start + 1):(end - 1)] + roxygen_lines <- sub("^", "#' ", roxygen_lines) + list(line = end, text = paste(roxygen_lines, collapse = "\n")) + }, roxygen_start, roxygen_end, SIMPLIFY = FALSE) + + roxygen_comments +} + wrap_call <- function(name, return_type, args) { call <- glue::glue('{name}({list_params})', list_params = glue_collapse_data(args, "cpp11::as_cpp>({name})")) if (return_type == "void") { diff --git a/cpp11test/DESCRIPTION b/cpp11test/DESCRIPTION index d1d05665..70c5649f 100644 --- a/cpp11test/DESCRIPTION +++ b/cpp11test/DESCRIPTION @@ -20,4 +20,4 @@ Suggests: xml2 LazyData: true Roxygen: list(markdown = TRUE) -RoxygenNote: 7.1.1 +RoxygenNote: 7.3.2 diff --git a/cpp11test/NAMESPACE b/cpp11test/NAMESPACE index 0cb4a22d..90d018a1 100644 --- a/cpp11test/NAMESPACE +++ b/cpp11test/NAMESPACE @@ -1,5 +1,10 @@ # Generated by roxygen2: do not edit by hand +export(roxcpp2_) +export(roxcpp3_) +export(roxcpp4_) +export(roxcpp5_) +export(roxcpp7_) export(run_tests) exportPattern("_$") importFrom(Rcpp,sourceCpp) diff --git a/cpp11test/R/cpp11.R b/cpp11test/R/cpp11.R index 038e7b76..d5ae1ab2 100644 --- a/cpp11test/R/cpp11.R +++ b/cpp11test/R/cpp11.R @@ -156,6 +156,63 @@ rcpp_release_ <- function(n) { invisible(.Call(`_cpp11test_rcpp_release_`, n)) } +notroxcpp1_ <- function(x) { + .Call(`_cpp11test_notroxcpp1_`, x) +} + +#' @title Roxygenise C++ function II +#' @param x numeric value +#' @description Dummy function to test roxygen2. It adds 2.0 to a double. +#' @export +#' @examples roxcpp2_(1.0) +roxcpp2_ <- function(x) { + .Call(`_cpp11test_roxcpp2_`, x) +} + +#' @title Roxygenise C++ function III +#' @param x numeric value +#' @description Dummy function to test roxygen2. It adds 3.0 to a double. +#' @export +#' @examples roxcpp3_(1.0) +roxcpp3_ <- function(x) { + .Call(`_cpp11test_roxcpp3_`, x) +} + +#' @title Roxygenise C++ function IV +#' @param x numeric value +#' @description Dummy function to test roxygen2. It adds 4.0 to a double. +#' @export +#' @examples roxcpp4_(1.0) +roxcpp4_ <- function(x) { + .Call(`_cpp11test_roxcpp4_`, x) +} + +#' @title Roxygenise C++ function V +#' @param x numeric value +#' @description Dummy function to test roxygen2. It adds 5.0 to a double. +#' @export +#' @examples roxcpp5_(1.0) +roxcpp5_ <- function(x) { + .Call(`_cpp11test_roxcpp5_`, x) +} + +notroxcpp6_ <- function(x) { + .Call(`_cpp11test_notroxcpp6_`, x) +} + +#' @title Roxygenise C++ function VII +#' @param x numeric value +#' @description Dummy function to test roxygen2. It adds 7.0 to a double. +#' @export +#' @examples +#' my_fun <- function(x) { +#' roxcpp7_(x) +#' } +#' @seealso \code{\link{roxcpp1_}} +roxcpp7_ <- function(x) { + .Call(`_cpp11test_roxcpp7_`, x) +} + cpp11_safe_ <- function(x_sxp) { .Call(`_cpp11test_cpp11_safe_`, x_sxp) } diff --git a/cpp11test/man/roxcpp2_.Rd b/cpp11test/man/roxcpp2_.Rd new file mode 100644 index 00000000..dd000a0f --- /dev/null +++ b/cpp11test/man/roxcpp2_.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/cpp11.R +\name{roxcpp2_} +\alias{roxcpp2_} +\title{Roxygenise C++ function II} +\usage{ +roxcpp2_(x) +} +\arguments{ +\item{x}{numeric value} +} +\description{ +Dummy function to test roxygen2. It adds 2.0 to a double. +} +\examples{ +roxcpp2_(1.0) +} diff --git a/cpp11test/man/roxcpp3_.Rd b/cpp11test/man/roxcpp3_.Rd new file mode 100644 index 00000000..3d31d143 --- /dev/null +++ b/cpp11test/man/roxcpp3_.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/cpp11.R +\name{roxcpp3_} +\alias{roxcpp3_} +\title{Roxygenise C++ function III} +\usage{ +roxcpp3_(x) +} +\arguments{ +\item{x}{numeric value} +} +\description{ +Dummy function to test roxygen2. It adds 3.0 to a double. +} +\examples{ +roxcpp3_(1.0) +} diff --git a/cpp11test/man/roxcpp4_.Rd b/cpp11test/man/roxcpp4_.Rd new file mode 100644 index 00000000..f9cbb022 --- /dev/null +++ b/cpp11test/man/roxcpp4_.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/cpp11.R +\name{roxcpp4_} +\alias{roxcpp4_} +\title{Roxygenise C++ function IV} +\usage{ +roxcpp4_(x) +} +\arguments{ +\item{x}{numeric value} +} +\description{ +Dummy function to test roxygen2. It adds 4.0 to a double. +} +\examples{ +roxcpp4_(1.0) +} diff --git a/cpp11test/man/roxcpp5_.Rd b/cpp11test/man/roxcpp5_.Rd new file mode 100644 index 00000000..ada8f9ee --- /dev/null +++ b/cpp11test/man/roxcpp5_.Rd @@ -0,0 +1,17 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/cpp11.R +\name{roxcpp5_} +\alias{roxcpp5_} +\title{Roxygenise C++ function V} +\usage{ +roxcpp5_(x) +} +\arguments{ +\item{x}{numeric value} +} +\description{ +Dummy function to test roxygen2. It adds 5.0 to a double. +} +\examples{ +roxcpp5_(1.0) +} diff --git a/cpp11test/man/roxcpp7_.Rd b/cpp11test/man/roxcpp7_.Rd new file mode 100644 index 00000000..17466bf6 --- /dev/null +++ b/cpp11test/man/roxcpp7_.Rd @@ -0,0 +1,22 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/cpp11.R +\name{roxcpp7_} +\alias{roxcpp7_} +\title{Roxygenise C++ function VII} +\usage{ +roxcpp7_(x) +} +\arguments{ +\item{x}{numeric value} +} +\description{ +Dummy function to test roxygen2. It adds 7.0 to a double. +} +\examples{ +my_fun <- function(x) { + roxcpp7_(x) +} +} +\seealso{ +\code{\link{roxcpp1_}} +} diff --git a/cpp11test/src/cpp11.cpp b/cpp11test/src/cpp11.cpp index 421de637..4f4f84d0 100644 --- a/cpp11test/src/cpp11.cpp +++ b/cpp11test/src/cpp11.cpp @@ -303,6 +303,55 @@ extern "C" SEXP _cpp11test_rcpp_release_(SEXP n) { return R_NilValue; END_CPP11 } +// roxygen1.cpp +double notroxcpp1_(double x); +extern "C" SEXP _cpp11test_notroxcpp1_(SEXP x) { + BEGIN_CPP11 + return cpp11::as_sexp(notroxcpp1_(cpp11::as_cpp>(x))); + END_CPP11 +} +// roxygen1.cpp +double roxcpp2_(double x); +extern "C" SEXP _cpp11test_roxcpp2_(SEXP x) { + BEGIN_CPP11 + return cpp11::as_sexp(roxcpp2_(cpp11::as_cpp>(x))); + END_CPP11 +} +// roxygen2.cpp +double roxcpp3_(double x); +extern "C" SEXP _cpp11test_roxcpp3_(SEXP x) { + BEGIN_CPP11 + return cpp11::as_sexp(roxcpp3_(cpp11::as_cpp>(x))); + END_CPP11 +} +// roxygen2.cpp +double roxcpp4_(double x); +extern "C" SEXP _cpp11test_roxcpp4_(SEXP x) { + BEGIN_CPP11 + return cpp11::as_sexp(roxcpp4_(cpp11::as_cpp>(x))); + END_CPP11 +} +// roxygen3.cpp +double roxcpp5_(double x); +extern "C" SEXP _cpp11test_roxcpp5_(SEXP x) { + BEGIN_CPP11 + return cpp11::as_sexp(roxcpp5_(cpp11::as_cpp>(x))); + END_CPP11 +} +// roxygen3.cpp +double notroxcpp6_(double x); +extern "C" SEXP _cpp11test_notroxcpp6_(SEXP x) { + BEGIN_CPP11 + return cpp11::as_sexp(notroxcpp6_(cpp11::as_cpp>(x))); + END_CPP11 +} +// roxygen3.cpp +double roxcpp7_(double x); +extern "C" SEXP _cpp11test_roxcpp7_(SEXP x) { + BEGIN_CPP11 + return cpp11::as_sexp(roxcpp7_(cpp11::as_cpp>(x))); + END_CPP11 +} // safe.cpp SEXP cpp11_safe_(SEXP x_sxp); extern "C" SEXP _cpp11test_cpp11_safe_(SEXP x_sxp) { @@ -500,6 +549,8 @@ static const R_CallMethodDef CallEntries[] = { {"_cpp11test_my_warning_n1", (DL_FUNC) &_cpp11test_my_warning_n1, 1}, {"_cpp11test_my_warning_n1fmt", (DL_FUNC) &_cpp11test_my_warning_n1fmt, 1}, {"_cpp11test_my_warning_n2fmt", (DL_FUNC) &_cpp11test_my_warning_n2fmt, 2}, + {"_cpp11test_notroxcpp1_", (DL_FUNC) &_cpp11test_notroxcpp1_, 1}, + {"_cpp11test_notroxcpp6_", (DL_FUNC) &_cpp11test_notroxcpp6_, 1}, {"_cpp11test_protect_many_", (DL_FUNC) &_cpp11test_protect_many_, 1}, {"_cpp11test_protect_many_cpp11_", (DL_FUNC) &_cpp11test_protect_many_cpp11_, 1}, {"_cpp11test_protect_many_preserve_", (DL_FUNC) &_cpp11test_protect_many_preserve_, 1}, @@ -518,6 +569,11 @@ static const R_CallMethodDef CallEntries[] = { {"_cpp11test_rcpp_sum_int_for_", (DL_FUNC) &_cpp11test_rcpp_sum_int_for_, 1}, {"_cpp11test_remove_altrep", (DL_FUNC) &_cpp11test_remove_altrep, 1}, {"_cpp11test_row_sums", (DL_FUNC) &_cpp11test_row_sums, 1}, + {"_cpp11test_roxcpp2_", (DL_FUNC) &_cpp11test_roxcpp2_, 1}, + {"_cpp11test_roxcpp3_", (DL_FUNC) &_cpp11test_roxcpp3_, 1}, + {"_cpp11test_roxcpp4_", (DL_FUNC) &_cpp11test_roxcpp4_, 1}, + {"_cpp11test_roxcpp5_", (DL_FUNC) &_cpp11test_roxcpp5_, 1}, + {"_cpp11test_roxcpp7_", (DL_FUNC) &_cpp11test_roxcpp7_, 1}, {"_cpp11test_string_proxy_assignment_", (DL_FUNC) &_cpp11test_string_proxy_assignment_, 0}, {"_cpp11test_string_push_back_", (DL_FUNC) &_cpp11test_string_push_back_, 0}, {"_cpp11test_sum_dbl_accumulate2_", (DL_FUNC) &_cpp11test_sum_dbl_accumulate2_, 1}, diff --git a/cpp11test/src/roxygen1.cpp b/cpp11test/src/roxygen1.cpp new file mode 100644 index 00000000..6ce5dea8 --- /dev/null +++ b/cpp11test/src/roxygen1.cpp @@ -0,0 +1,22 @@ +#include "cpp11/doubles.hpp" +using namespace cpp11; + +// Test: not documented + documented + +// Not Roxygenised C++ function I +[[cpp11::register]] double notroxcpp1_(double x) { + double y = x + 1.0; + return y; +} + +/* roxygen start +@title Roxygenise C++ function II +@param x numeric value +@description Dummy function to test roxygen2. It adds 2.0 to a double. +@export +@examples roxcpp2_(1.0) +roxygen end */ +[[cpp11::register]] double roxcpp2_(double x) { + double y = x + 2.0; + return y; +} diff --git a/cpp11test/src/roxygen2.cpp b/cpp11test/src/roxygen2.cpp new file mode 100644 index 00000000..ecd50221 --- /dev/null +++ b/cpp11test/src/roxygen2.cpp @@ -0,0 +1,28 @@ +#include "cpp11/doubles.hpp" +using namespace cpp11; + +// Test: documented + documented + +/* roxygen start +@title Roxygenise C++ function III +@param x numeric value +@description Dummy function to test roxygen2. It adds 3.0 to a double. +@export +@examples roxcpp3_(1.0) +roxygen end */ +[[cpp11::register]] double roxcpp3_(double x) { + double y = x + 3.0; + return y; +} + +/* roxygen start +@title Roxygenise C++ function IV +@param x numeric value +@description Dummy function to test roxygen2. It adds 4.0 to a double. +@export +@examples roxcpp4_(1.0) +roxygen end */ +[[cpp11::register]] double roxcpp4_(double x) { + double y = x + 4.0; + return y; +} diff --git a/cpp11test/src/roxygen3.cpp b/cpp11test/src/roxygen3.cpp new file mode 100644 index 00000000..7ede7a08 --- /dev/null +++ b/cpp11test/src/roxygen3.cpp @@ -0,0 +1,38 @@ +#include "cpp11/doubles.hpp" +using namespace cpp11; + +// Test: documented + not documented + documented + +/* roxygen start +@title Roxygenise C++ function V +@param x numeric value +@description Dummy function to test roxygen2. It adds 5.0 to a double. +@export +@examples roxcpp5_(1.0) +roxygen end */ +[[cpp11::register]] double roxcpp5_(double x) { + double y = x + 5.0; + return y; +} + +// Not Roxygenised C++ function VI +[[cpp11::register]] double notroxcpp6_(double x) { + double y = x + 6.0; + return y; +} + +/* roxygen start +@title Roxygenise C++ function VII +@param x numeric value +@description Dummy function to test roxygen2. It adds 7.0 to a double. +@export +@examples +my_fun <- function(x) { + roxcpp7_(x) +} +@seealso \code{\link{roxcpp1_}} +roxygen end */ +[[cpp11::register]] double roxcpp7_(double x) { + double y = x + 7.0; + return y; +} diff --git a/vignettes/converting.Rmd b/vignettes/converting.Rmd index 4a30dfd2..31507ca1 100644 --- a/vignettes/converting.Rmd +++ b/vignettes/converting.Rmd @@ -119,7 +119,6 @@ as_tibble(x, ".rows"_nm = num_rows, ".name_repair"_nm = name_repair); - Some parts of [Attributes](https://CRAN.R-project.org/package=Rcpp/vignettes/Rcpp-attributes.pdf) - No dependencies - No random number generator restoration - - No support for roxygen2 comments - No interfaces ### RNGs diff --git a/vignettes/cpp11.Rmd b/vignettes/cpp11.Rmd index 5f10fcc6..741a0ca1 100644 --- a/vignettes/cpp11.Rmd +++ b/vignettes/cpp11.Rmd @@ -349,6 +349,35 @@ For the remainder of this vignette C++ code will be presented stand-alone rather If you want to try compiling and/or modifying the examples you should paste them into a C++ source file that includes the elements described above. This is easy to do in RMarkdown by using `{cpp11}` instead of `{r}` at the beginning of your code blocks. +## Roxygen support + +It is possible to use `roxygen2` to document your C++ functions. Here is an +example of how to do this: + +```{cpp11, eval = FALSE} +/* roxygen start +@title Mean of a numeric vector +@param x A numeric vector +@return The mean of the input vector +@examples mean_cpp(1:10) +@export +roxygen end */ +[[cpp11::register]] +double mean_roxygenised_cpp(doubles x) { + int n = x.size(); + double total = 0; + for(double value : x) { + total += value; + } + return total / n; +} +``` + +Unlike R scripts, you need to use `/* roxygen start` and `roxygen end */` to +delimit the roxygen comments. The logic behind this is that C++ compilers +understand `/*` and `*/` as multi-linecomments, and therefore it is not required +to prepend `#' ` to each line of the roxygen comments as in R scripts. + ### Exercises 1. With the basics of C++ in hand, it's now a great time to practice by reading and writing some simple C++ functions. For each of the following functions, read the code and figure out what the corresponding base R function is. You might not understand every part of the code yet, but you should be able to figure out the basics of what the function does.