Skip to content

Commit

Permalink
more raw strings
Browse files Browse the repository at this point in the history
  • Loading branch information
IndrajeetPatil committed Jun 29, 2024
1 parent a539ba8 commit aa9bf83
Show file tree
Hide file tree
Showing 3 changed files with 6 additions and 10 deletions.
4 changes: 2 additions & 2 deletions R/detect-alignment.R
Original file line number Diff line number Diff line change
Expand Up @@ -141,8 +141,8 @@ token_is_on_aligned_line <- function(pd_flat) {
is_aligned <- length(unique(current_col)) == 1L
if (!is_aligned || length(current_col) < 2L) {
# check 2: left aligned after , (comma to next token)
current_col <- "^(,[\\s\\t]*)[^ ]*.*$" %>%
gsub("\\1", by_line, perl = TRUE) %>%
current_col <-
gsub(R"(^(,[\s\t]*)[^ ]*.*$)", R"(\1)", by_line, perl = TRUE) %>%
nchar() %>%
magrittr::subtract(1L)

Expand Down
8 changes: 2 additions & 6 deletions R/roxygen-examples-add-remove.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,12 +12,8 @@ remove_dont_mask <- function(roxygen) {
)
}

remove_blank_lines <- function(code) {
code[code != "\n"]
}

remove_roxygen_mask <- function(text) {
code_with_header <- gsub(pattern = "^#'\\s?", "", text)
code_with_header <- gsub(pattern = R"(^#'\s?)", "", text)
remove_roxygen_header(code_with_header)
}

Expand All @@ -29,7 +25,7 @@ remove_roxygen_mask <- function(text) {
#' #' @examples c(1, 2)
#' @keywords internal
remove_roxygen_header <- function(text) {
gsub("^[\\s\t]*@examples(If)?(\\s|\t)*", "", text, perl = TRUE)
gsub(R"(^[\s\t]*@examples(If)?(\s|\t)*)", "", text, perl = TRUE)
}

#' Add the roxygen mask to code
Expand Down
4 changes: 2 additions & 2 deletions R/roxygen-examples-find.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,13 @@
#' @param text A text consisting of code and/or roxygen comments.
#' @keywords internal
identify_start_to_stop_of_roxygen_examples_from_text <- function(text) {
starts <- grep("^#'(\\s|\t)*@examples(If\\s|\\s|\t|$)", text, perl = TRUE)
starts <- grep(R"{^#'(\s|\t)*@examples(If\s|\s|\t|$)}", text, perl = TRUE)
if (length(starts) < 1L) {
return(integer())
}
stop_candidates <- which(magrittr::or(
# starts with code or a tag
grepl("(^[^#]|^#'[\\s\t]*@)", text, perl = TRUE),
grepl(R"{(^[^#]|^#'[\s\t]*@)}", text, perl = TRUE),
# starts with a roxygen comment with a blank line after
grepl("^ *\t*$", text) & grepl("^#' *", lead(text))
)) %>%
Expand Down

0 comments on commit aa9bf83

Please sign in to comment.