Skip to content

Commit f74dbbe

Browse files
authored
Minor ticks (#5287)
* Swap tick anchorpoint * `Guide$build_ticks()` accepts a length value * Add tick arguments * `GuideAxis$extract_key()` can get minor ticks * `GuideAxis$build_ticks()` makes draws minor ticks * Fix bug with unlabelled breaks * Adjust tick spacing * Finishing touches * Add test * Accept tick-ordering changes in snapshots * Add news bullet * Fix expression labels * Document * Update snapshot * minor tick theme options * Revise minor to use theme * Use `rel()` for minor ticks * Biparental inheritance for minor tick length leaf nodes * change minor break extraction * Skip tick calculation with blank elements * clean up axis ticks building * change measurement function to width_cm/height_cm * Remove redundant function
1 parent 1b2c312 commit f74dbbe

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

45 files changed

+622
-313
lines changed

NEWS.md

+1
Original file line numberDiff line numberDiff line change
@@ -114,6 +114,7 @@
114114
* More informative error for mismatched
115115
`direction`/`theme(legend.direction = ...)` arguments (#4364, #4930).
116116
* `guide_coloursteps()` and `guide_bins()` sort breaks (#5152).
117+
* `guide_axis()` gains a `minor.ticks` argument to draw minor ticks (#4387).
117118
* `guide_axis()` gains a `cap` argument that can be used to trim the
118119
axis line to extreme breaks (#4907).
119120
* `guide_colourbar()` and `guide_coloursteps()` merge properly when one

R/guide-.R

+11-5
Original file line numberDiff line numberDiff line change
@@ -351,7 +351,14 @@ Guide <- ggproto(
351351
},
352352

353353
# Renders tickmarks
354-
build_ticks = function(key, elements, params, position = params$position) {
354+
build_ticks = function(key, elements, params, position = params$position,
355+
length = elements$ticks_length) {
356+
if (!inherits(elements, "element")) {
357+
elements <- elements$ticks
358+
}
359+
if (!inherits(elements, "element_line")) {
360+
return(zeroGrob())
361+
}
355362

356363
if (!is.list(key)) {
357364
breaks <- key
@@ -365,8 +372,7 @@ Guide <- ggproto(
365372
return(zeroGrob())
366373
}
367374

368-
tick_len <- rep(elements$ticks_length %||% unit(0.2, "npc"),
369-
length.out = n_breaks)
375+
tick_len <- rep(length %||% unit(0.2, "npc"), length.out = n_breaks)
370376

371377
# Resolve mark
372378
mark <- unit(rep(breaks, each = 2), "npc")
@@ -375,12 +381,12 @@ Guide <- ggproto(
375381
pos <- unname(c(top = 1, bottom = 0, left = 0, right = 1)[position])
376382
dir <- -2 * pos + 1
377383
pos <- unit(rep(pos, 2 * n_breaks), "npc")
378-
dir <- rep(vec_interleave(0, dir), n_breaks) * tick_len
384+
dir <- rep(vec_interleave(dir, 0), n_breaks) * tick_len
379385
tick <- pos + dir
380386

381387
# Build grob
382388
flip_element_grob(
383-
elements$ticks,
389+
elements,
384390
x = tick, y = mark,
385391
id.lengths = rep(2, n_breaks),
386392
flip = position %in% c("top", "bottom")

R/guide-axis.R

+78-21
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,8 @@
1414
#' @param n.dodge The number of rows (for vertical axes) or columns (for
1515
#' horizontal axes) that should be used to render the labels. This is
1616
#' useful for displaying labels that would otherwise overlap.
17+
#' @param minor.ticks Whether to draw the minor ticks (`TRUE`) or not draw
18+
#' minor ticks (`FALSE`, default).
1719
#' @param cap A `character` to cut the axis line back to the last breaks. Can
1820
#' be `"none"` (default) to draw the axis line along the whole panel, or
1921
#' `"upper"` and `"lower"` to draw the axis to the upper or lower break, or
@@ -42,23 +44,23 @@
4244
#' # can also be used to add a duplicate guide
4345
#' p + guides(x = guide_axis(n.dodge = 2), y.sec = guide_axis())
4446
guide_axis <- function(title = waiver(), check.overlap = FALSE, angle = NULL,
45-
n.dodge = 1, cap = "none", order = 0,
46-
position = waiver()) {
47-
47+
n.dodge = 1, minor.ticks = FALSE, cap = "none",
48+
order = 0, position = waiver()) {
49+
check_bool(minor.ticks)
4850
if (is.logical(cap)) {
4951
check_bool(cap)
5052
cap <- if (cap) "both" else "none"
5153
}
5254
cap <- arg_match0(cap, c("none", "both", "upper", "lower"))
5355

54-
5556
new_guide(
5657
title = title,
5758

5859
# customisations
5960
check.overlap = check.overlap,
6061
angle = angle,
6162
n.dodge = n.dodge,
63+
minor.ticks = minor.ticks,
6264
cap = cap,
6365

6466
# parameter
@@ -87,6 +89,7 @@ GuideAxis <- ggproto(
8789
direction = NULL,
8890
angle = NULL,
8991
n.dodge = 1,
92+
minor.ticks = FALSE,
9093
cap = "none",
9194
order = 0,
9295
check.overlap = FALSE
@@ -100,9 +103,37 @@ GuideAxis <- ggproto(
100103
line = "axis.line",
101104
text = "axis.text",
102105
ticks = "axis.ticks",
103-
ticks_length = "axis.ticks.length"
106+
minor = "axis.minor.ticks",
107+
major_length = "axis.ticks.length",
108+
minor_length = "axis.minor.ticks.length"
104109
),
105110

111+
extract_key = function(scale, aesthetic, minor.ticks, ...) {
112+
major <- Guide$extract_key(scale, aesthetic, ...)
113+
if (!minor.ticks) {
114+
return(major)
115+
}
116+
117+
minor_breaks <- scale$get_breaks_minor()
118+
minor_breaks <- setdiff(minor_breaks, major$.value)
119+
minor_breaks <- minor_breaks[is.finite(minor_breaks)]
120+
121+
if (length(minor_breaks) < 1) {
122+
return(major)
123+
}
124+
125+
minor <- data_frame0(!!aesthetic := scale$map(minor_breaks))
126+
minor$.value <- minor_breaks
127+
minor$.type <- "minor"
128+
129+
if (nrow(major) > 0) {
130+
major$.type <- "major"
131+
vec_rbind(major, minor)
132+
} else {
133+
minor
134+
}
135+
},
136+
106137
extract_params = function(scale, params, ...) {
107138
params$name <- paste0(params$name, "_", params$aesthetic)
108139
params
@@ -185,7 +216,7 @@ GuideAxis <- ggproto(
185216
},
186217

187218
setup_elements = function(params, elements, theme) {
188-
axis_elem <- c("line", "text", "ticks", "ticks_length")
219+
axis_elem <- c("line", "text", "ticks", "minor", "major_length", "minor_length")
189220
is_char <- vapply(elements[axis_elem], is.character, logical(1))
190221
axis_elem <- axis_elem[is_char]
191222
elements[axis_elem] <- lapply(
@@ -225,26 +256,17 @@ GuideAxis <- ggproto(
225256
"horizontal"
226257
}
227258

228-
# TODO: delete following comment at some point:
229-
# I found the 'position_*'/'non-position_*' and '*_dim' names confusing.
230-
# For my own understanding, these have been renamed as follows:
231-
# * 'aes' and 'orth_aes' for the aesthetic direction and the direction
232-
# orthogonal to the aesthetic direction, respectively.
233-
# * 'para_sizes' and 'orth_size(s)' for the dimension parallel to the
234-
# aesthetic and orthogonal to the aesthetic respectively.
235-
# I also tried to trim down the verbosity of the variable names a bit
236-
237259
new_params <- c("aes", "orth_aes", "para_sizes", "orth_size", "orth_sizes",
238260
"vertical", "measure_gtable", "measure_text")
239261
if (direction == "vertical") {
240262
params[new_params] <- list(
241263
"y", "x", "heights", "width", "widths",
242-
TRUE, gtable_width, grobWidth
264+
TRUE, gtable_width, width_cm
243265
)
244266
} else {
245267
params[new_params] <- list(
246268
"x", "y", "widths", "height", "heights",
247-
FALSE, gtable_height, grobHeight
269+
FALSE, gtable_height, height_cm
248270
)
249271
}
250272

@@ -275,7 +297,32 @@ GuideAxis <- ggproto(
275297
)
276298
},
277299

300+
build_ticks = function(key, elements, params, position = params$opposite) {
301+
302+
major <- Guide$build_ticks(
303+
vec_slice(key, (key$.type %||% "major") == "major"),
304+
elements$ticks, params, position,
305+
elements$major_length
306+
)
307+
308+
if (!params$minor.ticks) {
309+
return(major)
310+
}
311+
312+
minor <- Guide$build_ticks(
313+
vec_slice(key, (key$.type %||% "major") == "minor"),
314+
elements$minor, params, position,
315+
elements$minor_length
316+
)
317+
grobTree(major, minor, name = "ticks")
318+
},
319+
278320
build_labels = function(key, elements, params) {
321+
322+
if (".type" %in% names(key)) {
323+
key <- vec_slice(key, key$.type == "major")
324+
}
325+
279326
labels <- validate_labels(key$.label)
280327
n_labels <- length(labels)
281328

@@ -309,10 +356,20 @@ GuideAxis <- ggproto(
309356

310357
measure <- params$measure_text
311358

312-
length <- elements$ticks_length
313-
spacer <- max(unit(0, "pt"), -1 * length)
314-
labels <- do.call(unit.c, lapply(grobs$labels, measure))
315-
title <- measure(grobs$title)
359+
# Ticks
360+
major_cm <- convertUnit(elements$major_length, "cm", valueOnly = TRUE)
361+
range <- range(0, major_cm)
362+
if (params$minor.ticks && !inherits(elements$minor, "element_blank")) {
363+
minor_cm <- convertUnit(elements$minor_length, "cm", valueOnly = TRUE)
364+
range <- range(range, minor_cm)
365+
}
366+
367+
length <- unit(range[2], "cm")
368+
spacer <- max(unit(0, "pt"), unit(-1 * diff(range), "cm"))
369+
370+
# Text
371+
labels <- unit(measure(grobs$label), "cm")
372+
title <- unit(measure(grobs$title), "cm")
316373

317374
sizes <- unit.c(length, spacer, labels, title)
318375
if (params$lab_first) {

R/theme-defaults.R

+3
Original file line numberDiff line numberDiff line change
@@ -147,6 +147,7 @@ theme_grey <- function(base_size = 11, base_family = "",
147147
axis.ticks.length.y = NULL,
148148
axis.ticks.length.y.left = NULL,
149149
axis.ticks.length.y.right = NULL,
150+
axis.minor.ticks.length = rel(0.75),
150151
axis.title.x = element_text(
151152
margin = margin(t = half_line / 2),
152153
vjust = 1
@@ -478,6 +479,7 @@ theme_void <- function(base_size = 11, base_family = "",
478479
axis.ticks.length.y = NULL,
479480
axis.ticks.length.y.left = NULL,
480481
axis.ticks.length.y.right = NULL,
482+
axis.minor.ticks.length = unit(0, "pt"),
481483
legend.box = NULL,
482484
legend.key.size = unit(1.2, "lines"),
483485
legend.position = "right",
@@ -559,6 +561,7 @@ theme_test <- function(base_size = 11, base_family = "",
559561
axis.ticks.length.y = NULL,
560562
axis.ticks.length.y.left = NULL,
561563
axis.ticks.length.y.right = NULL,
564+
axis.minor.ticks.length = rel(0.75),
562565
axis.title.x = element_text(
563566
margin = margin(t = half_line / 2),
564567
vjust = 1

R/theme-elements.R

+25
Original file line numberDiff line numberDiff line change
@@ -441,32 +441,57 @@ el_def <- function(class = NULL, inherit = NULL, description = NULL) {
441441
axis.line.y = el_def("element_line", "axis.line"),
442442
axis.line.y.left = el_def("element_line", "axis.line.y"),
443443
axis.line.y.right = el_def("element_line", "axis.line.y"),
444+
444445
axis.text.x = el_def("element_text", "axis.text"),
445446
axis.text.x.top = el_def("element_text", "axis.text.x"),
446447
axis.text.x.bottom = el_def("element_text", "axis.text.x"),
447448
axis.text.y = el_def("element_text", "axis.text"),
448449
axis.text.y.left = el_def("element_text", "axis.text.y"),
449450
axis.text.y.right = el_def("element_text", "axis.text.y"),
451+
450452
axis.ticks.length = el_def("unit"),
451453
axis.ticks.length.x = el_def(c("unit", "rel"), "axis.ticks.length"),
452454
axis.ticks.length.x.top = el_def(c("unit", "rel"), "axis.ticks.length.x"),
453455
axis.ticks.length.x.bottom = el_def(c("unit", "rel"), "axis.ticks.length.x"),
454456
axis.ticks.length.y = el_def(c("unit", "rel"), "axis.ticks.length"),
455457
axis.ticks.length.y.left = el_def(c("unit", "rel"), "axis.ticks.length.y"),
456458
axis.ticks.length.y.right = el_def(c("unit", "rel"), "axis.ticks.length.y"),
459+
457460
axis.ticks.x = el_def("element_line", "axis.ticks"),
458461
axis.ticks.x.top = el_def("element_line", "axis.ticks.x"),
459462
axis.ticks.x.bottom = el_def("element_line", "axis.ticks.x"),
460463
axis.ticks.y = el_def("element_line", "axis.ticks"),
461464
axis.ticks.y.left = el_def("element_line", "axis.ticks.y"),
462465
axis.ticks.y.right = el_def("element_line", "axis.ticks.y"),
466+
463467
axis.title.x = el_def("element_text", "axis.title"),
464468
axis.title.x.top = el_def("element_text", "axis.title.x"),
465469
axis.title.x.bottom = el_def("element_text", "axis.title.x"),
466470
axis.title.y = el_def("element_text", "axis.title"),
467471
axis.title.y.left = el_def("element_text", "axis.title.y"),
468472
axis.title.y.right = el_def("element_text", "axis.title.y"),
469473

474+
axis.minor.ticks.x.top = el_def("element_line", "axis.ticks.x.top"),
475+
axis.minor.ticks.x.bottom = el_def("element_line", "axis.ticks.x.bottom"),
476+
axis.minor.ticks.y.left = el_def("element_line", "axis.ticks.y.left"),
477+
axis.minor.ticks.y.right = el_def("element_line", "axis.ticks.y.right"),
478+
479+
axis.minor.ticks.length = el_def(c("unit", "rel")),
480+
axis.minor.ticks.length.x = el_def(c("unit", "rel"), "axis.minor.ticks.length"),
481+
axis.minor.ticks.length.x.top = el_def(
482+
c("unit", "rel"), c("axis.minor.ticks.length.x", "axis.ticks.length.x.top")
483+
),
484+
axis.minor.ticks.length.x.bottom = el_def(
485+
c("unit", "rel"), c("axis.minor.ticks.length.x", "axis.ticks.length.x.bottom")
486+
),
487+
axis.minor.ticks.length.y = el_def(c("unit", "rel"), "axis.minor.ticks.length"),
488+
axis.minor.ticks.length.y.left = el_def(
489+
c("unit", "rel"), c("axis.minor.ticks.length.y", "axis.ticks.length.y.left")
490+
),
491+
axis.minor.ticks.length.y.right = el_def(
492+
c("unit", "rel"), c("axis.minor.ticks.length.y", "axis.ticks.length.y.right")
493+
),
494+
470495
legend.background = el_def("element_rect", "rect"),
471496
legend.margin = el_def("margin"),
472497
legend.spacing = el_def("unit"),

R/theme.R

+16
Original file line numberDiff line numberDiff line change
@@ -48,8 +48,13 @@
4848
#' `axis.ticks.y.left`, `axis.ticks.y.right`). `axis.ticks.*.*` inherits from
4949
#' `axis.ticks.*` which inherits from `axis.ticks`, which in turn inherits
5050
#' from `line`
51+
#' @param axis.minor.ticks.x.top,axis.minor.ticks.x.bottom,axis.minor.ticks.y.left,axis.minor.ticks.y.right,
52+
#' minor tick marks along axes ([element_line()]). `axis.minor.ticks.*.*`
53+
#' inherit from the corresponding major ticks `axis.ticks.*.*`.
5154
#' @param axis.ticks.length,axis.ticks.length.x,axis.ticks.length.x.top,axis.ticks.length.x.bottom,axis.ticks.length.y,axis.ticks.length.y.left,axis.ticks.length.y.right
5255
#' length of tick marks (`unit`)
56+
#' @param axis.minor.ticks.length,axis.minor.ticks.length.x,axis.minor.ticks.length.x.top,axis.minor.ticks.length.x.bottom,axis.minor.ticks.length.y,axis.minor.ticks.length.y.left,axis.minor.ticks.length.y.right
57+
#' length of minor tick marks (`unit`), or relative to `axis.ticks.length` when provided with `rel()`.
5358
#' @param axis.line,axis.line.x,axis.line.x.top,axis.line.x.bottom,axis.line.y,axis.line.y.left,axis.line.y.right
5459
#' lines along axes ([element_line()]). Specify lines along all axes (`axis.line`),
5560
#' lines for each plane (using `axis.line.x` or `axis.line.y`), or individually
@@ -302,13 +307,24 @@ theme <- function(line,
302307
axis.ticks.y,
303308
axis.ticks.y.left,
304309
axis.ticks.y.right,
310+
axis.minor.ticks.x.top,
311+
axis.minor.ticks.x.bottom,
312+
axis.minor.ticks.y.left,
313+
axis.minor.ticks.y.right,
305314
axis.ticks.length,
306315
axis.ticks.length.x,
307316
axis.ticks.length.x.top,
308317
axis.ticks.length.x.bottom,
309318
axis.ticks.length.y,
310319
axis.ticks.length.y.left,
311320
axis.ticks.length.y.right,
321+
axis.minor.ticks.length,
322+
axis.minor.ticks.length.x,
323+
axis.minor.ticks.length.x.top,
324+
axis.minor.ticks.length.x.bottom,
325+
axis.minor.ticks.length.y,
326+
axis.minor.ticks.length.y.left,
327+
axis.minor.ticks.length.y.right,
312328
axis.line,
313329
axis.line.x,
314330
axis.line.x.top,

man/guide_axis.Rd

+4
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

0 commit comments

Comments
 (0)