Skip to content

Commit

Permalink
fixes #322: allows Rmd chunks using {lang} engine format (#350)
Browse files Browse the repository at this point in the history
Allow Rmd chunks using {lang} engine format

Rmarkdown format allows the use of code blocks in the following format

```{some_engine}
# not necessarily R syntax
foo = bar
```

These blocks should be filtered out before linting the remaining R-code blocks.

A couple of python blocks were added to test.Rmd: one with R-like syntax and one with syntax that can't be parsed as R.

The function `defines_knitr_engine` was extracted from `extract_r_source` and extended. This tests for the presence of {r engine = some_engine} and {some_engine} in the start line of a code chunk. The names of valid engines are obtained from `knitr::knit_engines`

Fixes #322
  • Loading branch information
russHyde authored and jimhester committed Sep 19, 2018
1 parent 754aa56 commit 4ade1fc
Show file tree
Hide file tree
Showing 3 changed files with 36 additions and 4 deletions.
1 change: 1 addition & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@
* Allow for any number of `#` to start a comment. Useful in ESS (#299, @prosoitos)
* New equals_na_linter() (#143, #326, @jabranham)
* Fixed plain-code-block bug in Rmarkdown (#252, @russHyde)
* Fixed bug where non-R chunks using {lang} `engine format` were parsed from R-markdown (#322, @russHyde)

# lintr 1.0.2 #
* Fix tests to work with upcoming testthat release.
Expand Down
23 changes: 19 additions & 4 deletions R/extract.R
Original file line number Diff line number Diff line change
Expand Up @@ -26,13 +26,12 @@ extract_r_source <- function(filename, lines) {
Map(
function(start, end) {
if (

# block contains at least one line of code
start + 1 < end &&

# block does not set an engine (so is r code)
!rex::re_matches(lines[start],
rex::rex(boundary, "engine", any_spaces, "="))) {
!defines_knitr_engine(lines[start])
) {
output[seq(start + 1, end - 1)] <<- lines[seq(start + 1, end - 1)]
}
},
Expand Down Expand Up @@ -68,13 +67,29 @@ filter_chunk_end_positions <- function(starts, ends) {
}

positions <- sort(c(starts = starts, ends = ends))
code_start_indexes <- which(grepl("starts", names(positions)))
code_start_indexes <- grep("starts", names(positions))
code_ends <- positions[1 + code_start_indexes]

stopifnot(all(grepl("ends", names(code_ends))))
code_ends
}

defines_knitr_engine <- function(line) {
engines <- names(knitr::knit_engines$get())

# {some_engine}, {some_engine label, ...} or {some_engine, ...}
bare_engine_pattern <- rex::rex(
"{", or(engines), one_of("}", " ", ",")
)
# {... engine = "some_engine" ...}
explicit_engine_pattern <- rex::rex(
boundary, "engine", any_spaces, "="
)

rex::re_matches(line, explicit_engine_pattern) ||
rex::re_matches(line, bare_engine_pattern)
}

replace_prefix <- function(lines, prefix_pattern) {
if (is.null(prefix_pattern)) {
return(lines)
Expand Down
16 changes: 16 additions & 0 deletions tests/testthat/knitr_formats/test.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -34,3 +34,19 @@ a[0]=1
Plain code blocks can be written after three or more backticks
- R Markdown: The Definitive Guide. Xie, Allaire and Grolemund (2.5.2)
```

Calls to a non-R knitr-engine using {engine_name} syntax.

```{python}
# Python that looks like R
a = list()
b = {2}
print(a)
```

```{python}
# Python that's definitely not R
a = []
a.append(2)
print(a)
```

0 comments on commit 4ade1fc

Please sign in to comment.