Skip to content

Commit 8c3471e

Browse files
committed
convert margin to S7
1 parent 68fe80b commit 8c3471e

File tree

9 files changed

+62
-34
lines changed

9 files changed

+62
-34
lines changed

DESCRIPTION

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -177,6 +177,7 @@ Collate:
177177
'grob-null.R'
178178
'grouping.R'
179179
'properties.R'
180+
'margins.R'
180181
'theme-elements.R'
181182
'guide-.R'
182183
'guide-axis.R'
@@ -201,7 +202,6 @@ Collate:
201202
'layer-sf.R'
202203
'layout.R'
203204
'limits.R'
204-
'margins.R'
205205
'performance.R'
206206
'plot-build.R'
207207
'plot-construction.R'

R/geom-label.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -87,7 +87,7 @@ GeomLabel <- ggproto("GeomLabel", Geom,
8787
data <- coord$transform(data, panel_params)
8888
data$vjust <- compute_just(data$vjust, data$y, data$x, data$angle)
8989
data$hjust <- compute_just(data$hjust, data$x, data$y, data$angle)
90-
if (!is.margin("margin")) {
90+
if (!is.margin(label.padding)) {
9191
label.padding <- rep(label.padding, length.out = 4)
9292
}
9393

R/guide-legend.R

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -697,7 +697,9 @@ position_margin <- function(position, margin = NULL, gap = unit(0, "pt")) {
697697
left = replace(margin, 2, margin[2] + gap),
698698
right = replace(margin, 4, margin[4] + gap)
699699
)
700-
class(margin) <- union("margin", class(margin))
700+
# We have to manually reconstitute the class because the 'simpleUnit' class
701+
# might be dropped by the replacement operation.
702+
class(margin) <- c("ggplot2::margin", class(margin), "S7_object")
701703
margin
702704
}
703705

R/margins.R

Lines changed: 16 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,23 @@
1+
#' @include properties.R
2+
13
#' @param t,r,b,l Dimensions of each margin. (To remember order, think trouble).
24
#' @param unit Default units of dimensions. Defaults to "pt" so it
35
#' can be most easily scaled with the text.
46
#' @rdname element
57
#' @export
6-
margin <- function(t = 0, r = 0, b = 0, l = 0, unit = "pt") {
7-
u <- unit(c(t, r, b, l), unit)
8-
class(u) <- c("margin", class(u))
9-
u
10-
}
8+
margin <- S7::new_class(
9+
"margin", parent = S7::new_S3_class(c("simpleUnit", "unit", "unit_v2")),
10+
constructor = function(t = 0, r = 0, b = 0, l = 0, unit = "pt") {
11+
u <- unit(c(t, r, b, l), unit)
12+
S7::new_object(u)
13+
},
14+
properties = list(
15+
top = property_index(1L),
16+
right = property_index(2L),
17+
bottom = property_index(3L),
18+
left = property_index(4L)
19+
)
20+
)
1121

1222
#' @rdname element
1323
#' @export
@@ -23,7 +33,7 @@ margin_auto <- function(t = 0, r = t, b = t, l = r, unit = "pt") {
2333

2434
#' @export
2535
#' @rdname is_tests
26-
is.margin <- function(x) inherits(x, "margin")
36+
is.margin <- function(x) S7::S7_inherits(x, margin)
2737

2838
#' Create a text grob with the proper location and margins
2939
#'

R/properties.R

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -43,3 +43,16 @@ property_nullable <- function(class = S7::class_any, ...) {
4343
...
4444
)
4545
}
46+
47+
property_index <- function(i) {
48+
force(i)
49+
S7::new_property(
50+
getter = function(self) {
51+
self[i]
52+
},
53+
setter = function(self, value) {
54+
self[i] <- value
55+
self
56+
}
57+
)
58+
}

R/theme-elements.R

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -87,8 +87,11 @@ element <- S7::new_class("element", abstract = TRUE)
8787
#' @rdname element
8888
element_blank <- S7::new_class("element_blank", parent = element)
8989

90+
9091
# All properties are listed here so they can easily be recycled in the different
9192
# element classes
93+
#' @include properties.R
94+
#' @include margins.R
9295
element_props <- list(
9396
fill = property_nullable(S7::class_character | S7::new_S3_class("GridPattern") | S7::class_logical),
9497
colour = property_nullable(S7::class_character | S7::class_logical),

R/theme.R

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -867,7 +867,7 @@ S7::method(merge_element, list(element, S7::class_any)) <-
867867
new
868868
}
869869

870-
S7::method(merge_element, list(S7::new_S3_class("margin"), S7::class_any)) <-
870+
S7::method(merge_element, list(margin, S7::class_any)) <-
871871
function(new, old, ...) {
872872
if (is.null(old) || S7::S7_inherits(old, element_blank)) {
873873
return(new)
@@ -911,7 +911,7 @@ combine_elements <- function(e1, e2) {
911911
return(e1)
912912
}
913913

914-
if (inherits(e1, "margin") && inherits(e2, "margin")) {
914+
if (is.margin(e1) && is.margin(e2)) {
915915
if (anyNA(e2)) {
916916
e2[is.na(e2)] <- unit(0, "pt")
917917
}
@@ -921,7 +921,7 @@ combine_elements <- function(e1, e2) {
921921
}
922922

923923
# If neither of e1 or e2 are element_* objects, return e1
924-
if (!S7::S7_inherits(e1, element) && !S7::S7_inherits(e2, element)) {
924+
if (!is.theme_element(e1) && !is.theme_element(e2)) {
925925
return(e1)
926926
}
927927

@@ -949,7 +949,7 @@ combine_elements <- function(e1, e2) {
949949
e1@linewidth <- e2@linewidth * unclass(e1@linewidth)
950950
}
951951

952-
if (inherits(e1, "element_text")) {
952+
if (S7::S7_inherits(e1, element_text)) {
953953
e1@margin <- combine_elements(e1@margin, e2@margin)
954954
}
955955

man/element.Rd

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

man/is_tests.Rd

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

0 commit comments

Comments
 (0)