Skip to content

Commit

Permalink
Merge 94e30f8 into 1f4437b
Browse files Browse the repository at this point in the history
  • Loading branch information
IndrajeetPatil authored Sep 27, 2022
2 parents 1f4437b + 94e30f8 commit fa98f9c
Show file tree
Hide file tree
Showing 31 changed files with 575 additions and 572 deletions.
1 change: 1 addition & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@ Imports:
rprojroot (>= 1.1),
tibble (>= 1.4.2),
tools,
vctrs (>= 0.4.1),
withr (>= 1.0.0),
Suggests:
data.tree (>= 0.1.6),
Expand Down
2 changes: 1 addition & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,6 @@ export(style_text)
export(tidyverse_math_token_spacing)
export(tidyverse_reindention)
export(tidyverse_style)
import(tibble)
importFrom(magrittr,"%>%")
importFrom(magrittr,or)
importFrom(magrittr,set_names)
Expand All @@ -43,6 +42,7 @@ importFrom(rlang,is_installed)
importFrom(rlang,seq2)
importFrom(rlang,warn)
importFrom(rlang,with_handlers)
importFrom(tibble,tribble)
importFrom(utils,capture.output)
importFrom(utils,tail)
importFrom(utils,write.table)
4 changes: 2 additions & 2 deletions R/compat-dplyr.R
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ arrange_pos_id <- function(data) {

bind_rows <- function(x, y = NULL, ...) {
if (is.null(x) && is.null(y)) {
return(new_tibble(list()))
return(new_styler_df(list()))
}
if (is.null(x)) {
if (inherits(y, "data.frame")) {
Expand Down Expand Up @@ -62,7 +62,7 @@ left_join <- function(x, y, by) {

res <- merge(x, y, by.x = by_x, by.y = by_y, all.x = TRUE, sort = FALSE) %>%
arrange_pos_id()
res <- new_tibble(res)
res <- new_styler_df(res)
# dplyr::left_join set unknown list columns to NULL, merge sets them
# to NA
if (exists("child", res) && anyNA(res$child)) {
Expand Down
2 changes: 1 addition & 1 deletion R/compat-tidyr.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,5 +6,5 @@ nest_ <- function(data, key_col, nest_cols = character()) {
res <- list()
res[[key_column]] <- key_levels
res[[key_col]] <- split(data[, nest_cols], key_factor)
new_tibble(res)
new_styler_df(res)
}
4 changes: 2 additions & 2 deletions R/nest.R
Original file line number Diff line number Diff line change
Expand Up @@ -249,7 +249,7 @@ add_terminal_token_after <- function(pd_flat) {
filter(terminal) %>%
arrange_pos_id()

rhs <- new_tibble(
rhs <- new_styler_df(
list(
pos_id = terminals$pos_id,
token_after = lead(terminals$token, default = "")
Expand All @@ -266,7 +266,7 @@ add_terminal_token_before <- function(pd_flat) {
filter(terminal) %>%
arrange_pos_id()

rhs <- new_tibble(
rhs <- new_styler_df(
list(
id = terminals$id,
token_before = lag(terminals$token, default = "")
Expand Down
1 change: 1 addition & 0 deletions R/nested-to-tree.R
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ create_tree_from_pd_with_default_style_attributes <- function(pd,
structure_only = FALSE) {
pd %>%
create_node_from_nested_root(structure_only) %>%
# don't use `styler_df()` here; `vctrs::data_frame()` only accepts a vector, not a <Node/R6> object
as.data.frame()
}

Expand Down
4 changes: 2 additions & 2 deletions R/parse.R
Original file line number Diff line number Diff line change
Expand Up @@ -94,7 +94,7 @@ get_parse_data <- function(text, include_text = TRUE, ...) {
# avoid https://bugs.r-project.org/bugzilla3/show_bug.cgi?id=16041
parse_safely(text, keep.source = TRUE)
parsed <- parse_safely(text, keep.source = TRUE)
pd <- as_tibble(
pd <- styler_df(
utils::getParseData(parsed, includeText = include_text),
.name_repair = "minimal"
)
Expand Down Expand Up @@ -163,7 +163,7 @@ ensure_correct_txt <- function(pd, text) {
by.y = "id",
suffixes = c("", "parent")
) %>%
as_tibble(.name_repair = "minimal")
styler_df(.name_repair = "minimal")

if (!lines_and_cols_match(new_text)) {
abort(paste(
Expand Down
2 changes: 1 addition & 1 deletion R/style-guides.R
Original file line number Diff line number Diff line change
Expand Up @@ -315,7 +315,7 @@ tidyverse_style <- function(scope = "tokens",
#' }
#' set_line_break_before_curly_opening_style <- function() {
#' create_style_guide(
#' line_break = tibble::lst(set_line_break_before_curly_opening),
#' line_break = list(set_line_break_before_curly_opening),
#' style_guide_name = "some-style-guide",
#' style_guide_version = "some-version"
#' )
Expand Down
4 changes: 2 additions & 2 deletions R/stylerignore.R
Original file line number Diff line number Diff line change
Expand Up @@ -123,8 +123,8 @@ apply_stylerignore <- function(flattened_pd) {
env_current$stylerignore[, colnames_required_apply_stylerignore],
by.x = "pos_id", by.y = "first_pos_id_in_segment", all.x = TRUE,
sort = FALSE
) %>%
as_tibble()
)

flattened_pd %>%
stylerignore_consolidate_col("lag_newlines") %>%
stylerignore_consolidate_col("lag_spaces") %>%
Expand Down
2 changes: 1 addition & 1 deletion R/token-create.R
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ create_tokens <- function(tokens,
block = NA,
is_cached = FALSE) {
len_text <- length(texts)
new_tibble(
new_styler_df(
list(
token = tokens,
text = texts,
Expand Down
2 changes: 1 addition & 1 deletion R/token-define.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
token <- tribble(
token <- tibble::tribble(
~text, ~class, ~token,
"&", "logical", "AND",
"&&", "logical", "AND2",
Expand Down
2 changes: 1 addition & 1 deletion R/transform-files.R
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ transform_files <- function(files,
)
communicate_summary(changed, max_char)
communicate_warning(changed, transformers)
new_tibble(list(file = files, changed = changed))
new_styler_df(list(file = files, changed = changed))
}

#' Transform a file and output a customized message
Expand Down
9 changes: 5 additions & 4 deletions R/ui-caching.R
Original file line number Diff line number Diff line change
Expand Up @@ -75,15 +75,16 @@ cache_info <- function(cache_name = NULL, format = "both") {
rlang::arg_match(format, c("tabular", "lucid", "both"))
path_cache <- cache_find_path(cache_name)
files <- list.files(path_cache, full.names = TRUE)
file_info <- file.info(files) %>%
as_tibble()
tbl <- tibble(
file_info <- file.info(files)

tbl <- styler_df(
n = nrow(file_info),
size = sum(file_info$size),
last_modified = suppressWarnings(max(file_info$mtime)),
created = file.info(path_cache)$ctime,
location = path_cache,
activated = cache_is_activated(cache_name)
activated = cache_is_activated(cache_name),
stringsAsFactors = FALSE
)
if (any(c("lucid", "both") == format)) {
cat(
Expand Down
2 changes: 1 addition & 1 deletion R/ui-styling.R
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
#' @keywords api
#' @import tibble
#' @importFrom tibble tribble
#' @importFrom magrittr %>%
NULL

Expand Down
15 changes: 14 additions & 1 deletion R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,19 @@ line_col_names <- function() {
c("line1", "line2", "col1", "col2")
}

#' Wrapper functions to encapsulate data frame creation
#' @keywords internal
#' @noRd
styler_df <- function(..., .size = NULL, .name_repair = "minimal") {
vctrs::data_frame(..., .size = .size, .name_repair = .name_repair)
}

#' @keywords internal
#' @noRd
new_styler_df <- function(x) {
vctrs::new_data_frame(x)
}

#' Ensure there is one (and only one) blank line at the end of a vector
#' @examples
#' styler:::ensure_last_n_empty("")
Expand Down Expand Up @@ -85,7 +98,7 @@ option_read <- function(x, default = NULL, error_if_not_found = TRUE) {
}
}


#' @keywords internal
unwhich <- function(x, length) {
x_ <- rep(FALSE, length)
x_[x] <- TRUE
Expand Down
1 change: 1 addition & 0 deletions inst/WORDLIST
Original file line number Diff line number Diff line change
Expand Up @@ -271,6 +271,7 @@ upsetjs
usethis
utf
Uwe
vctrs
VignetteBuilder
Visit'em
walthert
Expand Down
2 changes: 1 addition & 1 deletion man/create_style_guide.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

18 changes: 6 additions & 12 deletions tests/testthat/_snaps/cache-with-r-cache.md
Original file line number Diff line number Diff line change
Expand Up @@ -3,28 +3,22 @@
Code
cache_info[, c("n", "size", "last_modified", "activated")]
Output
# A tibble: 1 x 4
n size last_modified activated
<int> <dbl> <dttm> <lgl>
1 0 0 -Inf -Inf FALSE
n size last_modified activated
1 0 0 -Inf FALSE

---

Code
cache_info[, c("n", "size", "activated")]
Output
# A tibble: 1 x 3
n size activated
<int> <dbl> <lgl>
1 1 0 TRUE
n size activated
1 1 0 TRUE

---

Code
cache_info[, c("n", "size", "activated")]
Output
# A tibble: 1 x 3
n size activated
<int> <dbl> <lgl>
1 2 0 TRUE
n size activated
1 2 0 TRUE

Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@
#' }
#' }
#' set_line_break_before_curly_opening_style <- function() {
#' create_style_guide(line_break = tibble::lst(set_line_break_before_curly_opening))
#' create_style_guide(line_break = list(set_line_break_before_curly_opening))
#' }
#' @examples
#' \dontrun{
Expand All @@ -32,9 +32,9 @@ create_style_guide <- function(initialize = default_style_guide_attributes,
indention = NULL,
use_raw_indention = FALSE,
reindention = tidyverse_reindention()) {
lst(
list(
# transformer functions
initialize = lst(initialize),
initialize = list(initialize),
line_break,
space,
token,
Expand Down Expand Up @@ -63,7 +63,7 @@ create_style_guide <- function(initialize = default_style_guide_attributes,
#' }
#' }
#' set_line_break_before_curly_opening_style <- function() {
#' create_style_guide(line_break= tibble::lst(set_line_break_before_curly_opening))
#' create_style_guide(line_break= list(set_line_break_before_curly_opening))
#' }
#' @examples
#' \donttest{style_text("a <- function(x) { x }
Expand All @@ -78,9 +78,9 @@ create_style_guide <- function(initialize = default_style_guide_attributes,
indention = NULL,
use_raw_indention = FALSE,
reindention = tidyverse_reindention()) {
lst(
list(
#transformer functions
initialize = lst(initialize),
initialize = list(initialize),
line_break,
space,
token,
Expand Down
Loading

0 comments on commit fa98f9c

Please sign in to comment.