Skip to content

Commit 8d453ae

Browse files
replacing create_filler
Replacing create_filler with initialize_attributes() and split it up further.
1 parent 5c5e352 commit 8d453ae

15 files changed

+136
-73
lines changed

DESCRIPTION

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -35,10 +35,10 @@ RoxygenNote: 6.0.1.9000
3535
VignetteBuilder: knitr
3636
Collate:
3737
'addins.R'
38+
'initialize.R'
3839
'modify_pd.R'
3940
'nested.R'
4041
'nested_to_tree.R'
41-
'parsed.R'
4242
'reindent.R'
4343
'token.R'
4444
'relevel.R'

R/initialize.R

Lines changed: 64 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,64 @@
1+
#' Enrich parse table with space and line break information
2+
#'
3+
#' This function computes difference (as column and line difference) between two
4+
#' entries in the parse table and adds this information to the table.
5+
#' @param pd_flat A parse table.
6+
#' @importFrom utils tail
7+
initialize_attributes <- function(pd_flat) {
8+
9+
init_pd <-
10+
initialize_newlines(pd_flat) %>%
11+
initialize_spaces() %>%
12+
initialize_multi_line() %>%
13+
initialize_indention_ref_id() %>%
14+
initialize_indent() %>%
15+
validate_parse_data()
16+
init_pd
17+
}
18+
19+
#' @describeIn initialize_attributes Initializes `newlines` and `lag_newlines`.
20+
initialize_newlines <- function(pd_flat) {
21+
pd_flat$line3 <- lead(pd_flat$line1, default = tail(pd_flat$line2, 1))
22+
pd_flat$newlines <- pd_flat$line3 - pd_flat$line2
23+
pd_flat$lag_newlines <- lag(pd_flat$newlines, default = 0L)
24+
pd_flat$line3 <- NULL
25+
pd_flat
26+
}
27+
28+
#' @describeIn initialize_attributes Initializes `spaces`.
29+
initialize_spaces <- function(pd_flat) {
30+
pd_flat$col3 <- lead(pd_flat$col1, default = tail(pd_flat$col2, 1) + 1L)
31+
pd_flat$col2_nl <- if_else(pd_flat$newlines > 0L, 0L, pd_flat$col2)
32+
pd_flat$spaces <- pd_flat$col3 - pd_flat$col2_nl - 1L
33+
pd_flat$col3 <- NULL
34+
pd_flat$col2_nl <- NULL
35+
pd_flat
36+
}
37+
38+
#' @describeIn initialize_attributes Initializes `multi_line`.
39+
initialize_multi_line <- function(pd_flat) {
40+
pd_flat$multi_line <- ifelse(pd_flat$terminal, FALSE, NA)
41+
pd_flat
42+
}
43+
44+
#' @describeIn initialize_attributes Initializes `indention_ref_ind`.
45+
initialize_indention_ref_id <- function(pd_flat) {
46+
pd_flat$indention_ref_id <- NA
47+
pd_flat
48+
}
49+
50+
#' @describeIn initialize_attributes Initializes `indent`.
51+
initialize_indent <- function(pd_flat) {
52+
if (!("indent" %in% names(pd_flat))) {
53+
pd_flat$indent <- 0
54+
}
55+
pd_flat
56+
}
57+
58+
#' @describeIn initialize_attributes validates the parse data.
59+
validate_parse_data <- function(pd_flat) {
60+
if (any(pd_flat$spaces < 0L)) {
61+
stop("Invalid parse data")
62+
}
63+
pd_flat
64+
}

R/modify_pd.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
#' Update indention information of parse data
22
#'
33
#' @param pd A nested or flat parse table that is already enhanced with
4-
#' line break and space information via [create_filler()].
4+
#' line break and space information via [initialize_attributes()].
55
#' @param indent_by How many spaces should be added after the token of interest.
66
#' @param token The token the indention should be based on.
77
#' @name update_indention

R/nested_to_tree.R

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@
66
#' @importFrom purrr when
77
create_tree <- function(text) {
88
compute_parse_data_nested(text) %>%
9-
pre_visit(c(create_filler)) %>%
9+
pre_visit(c(initialize_attributes)) %>%
1010
create_node_from_nested_root() %>%
1111
as.data.frame()
1212
}
@@ -19,7 +19,7 @@ create_tree <- function(text) {
1919
#' @examples
2020
#' code <- "a <- function(x) { if(x > 1) { 1+1 } else {x} }"
2121
#' nested_pd <- styler:::compute_parse_data_nested(code)
22-
#' initialized <- styler:::pre_visit(nested_pd, c(styler:::create_filler))
22+
#' initialized <- styler:::pre_visit(nested_pd, c(styler:::initialize_attributes))
2323
#' styler:::create_node_from_nested_root(initialized)
2424
create_node_from_nested_root <- function(pd_nested) {
2525
n <- data.tree::Node$new("ROOT (token: short_text [lag_newlines/spaces] {id})")

R/parsed.R

Lines changed: 0 additions & 32 deletions
This file was deleted.

R/serialized_tests.R

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -137,7 +137,7 @@ NULL
137137
style_empty <- function(text) {
138138
transformers <- list(
139139
# transformer functions
140-
filler = create_filler,
140+
initialize = initialize_attributes,
141141
line_break = NULL,
142142
space = NULL,
143143
token = NULL,
@@ -156,7 +156,7 @@ style_indent_curly <- function(text) {
156156

157157
transformers <- list(
158158
# transformer functions
159-
filler = create_filler,
159+
initialize = initialize_attributes,
160160
line_break = NULL,
161161
space = partial(indent_curly, indent_by = 2),
162162
token = NULL,
@@ -175,7 +175,7 @@ style_indent_curly <- function(text) {
175175
style_indent_curly_round <- function(text) {
176176
transformers <- list(
177177
# transformer functions
178-
filler = create_filler,
178+
initialize = initialize_attributes,
179179
line_break = NULL,
180180
space = c(partial(indent_curly, indent_by = 2),
181181
partial(indent_round, indent_by = 2)),
@@ -195,7 +195,7 @@ style_op <- function(text) {
195195

196196
transformers <- list(
197197
# transformer functions
198-
filler = create_filler,
198+
initialize = initialize_attributes,
199199
line_break = NULL,
200200
space = partial(indent_op, indent_by = 2),
201201
token = NULL,

R/style_guides.R

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -124,7 +124,7 @@ tidyverse_style <- function(scope = "tokens",
124124

125125
create_style_guide(
126126
# transformer functions
127-
filler = create_filler,
127+
initialize = initialize_attributes,
128128
line_break = line_break_manipulators,
129129
space = space_manipulators,
130130
token = token_manipulators,
@@ -141,7 +141,7 @@ tidyverse_style <- function(scope = "tokens",
141141
#' transformer function corresponds to one styling rule. The output of this
142142
#' function can be used as an argument for \code{style} in top level functions
143143
#' like [style_text()] and friends.
144-
#' @param filler A filler function that initializes various variables on each
144+
#' @param initialize A function that initializes various variables on each
145145
#' level of nesting.
146146
#' @param line_break A list of transformer functions that manipulate line_break
147147
#' information.
@@ -152,15 +152,15 @@ tidyverse_style <- function(scope = "tokens",
152152
#' @param use_raw_indention Boolean indicating whether or not the raw indention
153153
#' should be used.
154154
#' @export
155-
create_style_guide <- function(filler = create_filler,
155+
create_style_guide <- function(initialize = initialize_attributes,
156156
line_break = NULL,
157157
space = NULL,
158158
token = NULL,
159159
indention = NULL,
160160
use_raw_indention = FALSE) {
161161
lst(
162162
# transformer functions
163-
filler,
163+
initialize,
164164
line_break,
165165
space,
166166
token,

R/transform.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -110,7 +110,7 @@ parse_transform_serialize <- function(text, transformers) {
110110
apply_transformers <- function(pd_nested, transformers) {
111111
transformed_line_breaks <- pre_visit(
112112
pd_nested,
113-
c(transformers$filler,
113+
c(transformers$initialize,
114114
transformers$line_break)
115115
)
116116

man/create_filler.Rd

Lines changed: 0 additions & 19 deletions
This file was deleted.

man/create_node_from_nested_root.Rd

Lines changed: 1 addition & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/create_style_guide.Rd

Lines changed: 2 additions & 2 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/initialize_attributes.Rd

Lines changed: 48 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/update_indention.Rd

Lines changed: 1 addition & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

vignettes/customizing_styler.Rmd

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -73,12 +73,12 @@ table"):
7373
```{r}
7474
string_to_format <- "call( 3)"
7575
pd <- styler:::compute_parse_data_nested(string_to_format) %>%
76-
styler:::pre_visit(c(styler:::create_filler))
76+
styler:::pre_visit(c(styler:::initialize_attributes))
7777
pd$child[[1]] %>%
7878
select(token, terminal, text, newlines, spaces)
7979
```
8080

81-
`create_filler()` is called to initialize some variables, it does not actually
81+
`initialize_attributes()` is called to initialize some variables, it does not actually
8282
transform the parse table.
8383

8484
All the function `remove_space_after_opening_paren()` now does is to look for
@@ -155,7 +155,7 @@ respectively, so we need both.
155155
The sequence in which styler applies rules on each level of nesting is given in
156156
the list below:
157157

158-
* call `create_filler()` to initialize some variables.
158+
* call `initialize_attributes()` to initialize some variables.
159159
* modify the line breaks (modifying `lag_newlines` only based on
160160
`token`, `token_before`, `token_after` and `text`).
161161
* modify the spaces (modifying `spaces` only based on `lag_newlines`,

vignettes/gsoc_proposal/manipulating_nested_parse_data.Rmd

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -22,11 +22,13 @@ In order to compute the white space information in a nested data structure, we
2222
use a [visitor approach](https://en.wikipedia.org/wiki/Visitor_pattern) to
2323
separate the algorithm (computing white space information and later apply
2424
transformations) from the object (nested data structure).
25-
The function `create_filler()` can then be used to compute current
25+
The function `create_filler()` (name depreciated, now called
26+
`initialize_attributes()`) can then be used to compute current
2627
white space information on every level of nesting within the nested parse data
2728
if applied in combination with the visitor. In the sequel, a parse table at
2829
one level of nesting will be denoted with the term *nest*, which always
29-
represents a complete expression. Our visiting functions `pre_visit()` and `post_visit()` take an object to
30+
represents a complete expression. Our visiting functions `pre_visit()` and
31+
`post_visit()` take an object to
3032
operate on and a list of functions. Concretely, the object is the
3133
nested parse table. Each function is applied at each level of
3234
nesting nesting before the next level of nesting is entered. You can find out

0 commit comments

Comments
 (0)