diff --git a/NAMESPACE b/NAMESPACE index daa97ca16..93da52999 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -253,6 +253,7 @@ importFrom(utils,tail) importFrom(xml2,xml_attr) importFrom(xml2,xml_children) importFrom(xml2,xml_contents) +importFrom(xml2,xml_find_all) importFrom(xml2,xml_name) importFrom(xml2,xml_text) importFrom(xml2,xml_type) diff --git a/NEWS.md b/NEWS.md index 6682a83ca..7b0f807b6 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # roxygen2 (development version) +* Markdown tables with cells that contain multiple elements (e.g. text and code) + are now rendered correctly (#985). + * `@includeRmd` has now an optional second argument, the top level section the included file will go to. It defaults to the details section (#970). diff --git a/R/markdown.R b/R/markdown.R index 1a943729c..45506e609 100644 --- a/R/markdown.R +++ b/R/markdown.R @@ -31,7 +31,7 @@ mdxml_children_to_rd <- function(xml, state) { paste0(out, collapse = "") } -#' @importFrom xml2 xml_name xml_type xml_text xml_contents xml_attr xml_children +#' @importFrom xml2 xml_name xml_type xml_text xml_contents xml_attr xml_children xml_find_all mdxml_node_to_rd <- function(xml, state) { if (!inherits(xml, "xml_node") || ! xml_type(xml) %in% c("text", "element")) { @@ -135,10 +135,11 @@ mdxml_table <- function(xml, state) { head <- xml_children(xml)[[1]] align <- substr(xml_attr(xml_children(head), "align", default = "left"), 1, 1) - rows <- xml_children(xml) - rows <- map(rows, xml_children) - rows_rd <- map(rows, ~ map_chr(xml_children(.x), mdxml_node_to_rd, state = state)) - rows_rd <- map_chr(rows_rd, paste0, collapse = " \\tab ") + rows <- xml_find_all(xml, "d1:table_row|d1:table_header") + cells <- map(rows, xml_find_all, "d1:table_cell") + + cells_rd <- map(cells, ~ map(.x, mdxml_children_to_rd, state = state)) + rows_rd <- map_chr(cells_rd, paste0, collapse = " \\tab ") paste0("\\tabular{", paste(align, collapse = ""), "}{\n", paste(" ", rows_rd, "\\cr\n", collapse = ""), diff --git a/tests/testthat/test-markdown-table.txt b/tests/testthat/test-markdown-table.txt index 28d3ea51b..119ba9bff 100644 --- a/tests/testthat/test-markdown-table.txt +++ b/tests/testthat/test-markdown-table.txt @@ -1,11 +1,32 @@ -> cat(markdown( -+ "\n| x | y |\n| --- | --- |\n| 1 | 2 |\n\n| x | y |\n| :-: | --: |\n| 1 | 2 |\n ")) +> for (table in tables) { ++ cat_line(table) ++ cat_line(markdown(table)) ++ cat_line() ++ } + +| x | y | +| --- | --- | +| 1 | 2 | \tabular{ll}{ x \tab y \cr 1 \tab 2 \cr } + +| x | y | +| :-: | --: | +| 1 | 2 | \tabular{cr}{ x \tab y \cr 1 \tab 2 \cr } +| x | y | +| ----- | --------- | +| 1 _2_ | 3 *4* `5` | + +\tabular{ll}{ + x \tab y \cr + 1 \emph{2} \tab 3 \emph{4} \code{5} \cr +} + + diff --git a/tests/testthat/test-markdown.R b/tests/testthat/test-markdown.R index 02ea07de9..be1dd2aaf 100644 --- a/tests/testthat/test-markdown.R +++ b/tests/testthat/test-markdown.R @@ -228,17 +228,30 @@ test_that("nested lists are OK", { test_that("can convert table to Rd", { + txt <- " + | x | y | + | --- | --- | + | 1 | 2 | + + | x | y | + | :-: | --: | + | 1 | 2 | + + | x | y | + | ----- | --------- | + | 1 _2_ | 3 *4* `5` | + " + txt <- gsub("\n ", "\n", txt) + tables <- strsplit(txt, "\n\n")[[1]] + verify_output( - test_path("test-markdown-table.txt"), - cat(markdown(" -| x | y | -| --- | --- | -| 1 | 2 | - -| x | y | -| :-: | --: | -| 1 | 2 | - ")) + test_path("test-markdown-table.txt"), { + for (table in tables) { + cat_line(table) + cat_line(markdown(table)) + cat_line() + } + } ) })