Skip to content

Commit 2bc13a4

Browse files
author
Dominique Quatravaux
committed
[improve] Treat “classful” properties separately
This lets the `stopifnot` check become bi-directional.
1 parent e715b79 commit 2bc13a4

File tree

1 file changed

+39
-10
lines changed

1 file changed

+39
-10
lines changed

confluence.R

Lines changed: 39 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -38,17 +38,18 @@ confluence_id <- function (node_or_nodeset) {
3838
xml_text
3939
}
4040

41-
#' Format the “props” of each node in a nodeset, into a tibble
41+
#' Format the classless “props” of each node in a nodeset, into a tibble
4242
#'
4343
#' @param objects_nodeset An XML nodeset (*not* a list of many
4444
#' nodesets)
4545
#' @return A tibble with as many rows as there are objects in
4646
#' objects_nodeset. The columns of the returned tibble are the XML
47-
#' “name” attributes of any property nodes found, and the values
48-
#' are the XML texts found within said property nodes.
47+
#' “name” attributes of any `property` sub-nodes that do *not*
48+
#' have a `class` attribute; and the values are the XML texts
49+
#' found within said property nodes.
4950
props_tibble <- function(objects_nodeset) {
5051
objects_nodeset %>%
51-
xml_find_all('property', flatten=FALSE) %>%
52+
xml_find_all('property[not(@class)]', flatten=FALSE) %>%
5253
tibble(row = seq_along(.),
5354
props = .) %>%
5455
rowwise() %>%
@@ -60,6 +61,32 @@ props_tibble <- function(objects_nodeset) {
6061
select(-row)
6162
}
6263

64+
#' Format the “props” that have a `class` for each node in a nodeset, into a tibble
65+
#'
66+
#' @param objects_nodeset An XML nodeset (*not* a list of many
67+
#' nodesets)
68+
#' @return A tibble with as many rows as there are objects in
69+
#' objects_nodeset. The columns of the returned tibble are named
70+
#' as `foo.Bar`, where `foo` (e.g. "content") is the `name`
71+
#' attribute, and `Bar` is the `class` attribute, of any
72+
#' `property` sub-nodes that have a `class` attribute; and the
73+
#' values are the XML texts found within said property nodes.
74+
classful_props_tibble <- function(objects_nodeset) {
75+
objects_nodeset %>%
76+
xml_find_all('property[@class]', flatten=FALSE) %>%
77+
tibble(row = seq_along(.),
78+
props = .) %>%
79+
rowwise() %>%
80+
reframe(
81+
row = row,
82+
pnames = xml_attr(props, 'name'),
83+
pclasses = xml_attr(props, 'class'),
84+
pvals = xml_text(props)) %>%
85+
mutate(pkeys=paste(pnames, pclasses, sep="."), .keep = "unused") %>%
86+
pivot_wider(names_from = pkeys, values_from = pvals) %>%
87+
select(-row)
88+
}
89+
6390
## Again, stuff like
6491
##
6592
## object_pages <- entities %>%
@@ -74,6 +101,7 @@ page_versions <- {
74101
ns <- entities_xml %>% xml_find_all('//object[@class="Page"]')
75102
tibble(content_id = ns %>% confluence_id) %>%
76103
mutate(ns %>% props_tibble) %>%
104+
mutate(ns %>% classful_props_tibble) %>%
77105
mutate(ns %>%
78106
xml_find_all(c('collection[@name="contentProperties"]',
79107
'element[@class="ContentProperty"]',
@@ -88,21 +116,22 @@ content_properties <- {
88116
ns <- entities_xml %>% xml_find_all('//object[@class="ContentProperty"]')
89117
tibble(property_id = ns %>% confluence_id) %>%
90118
mutate(ns %>% props_tibble) %>%
91-
rename(content_id = content)
119+
mutate(ns %>% classful_props_tibble)
92120
}
93121

94122
## page_versions$content_property_ids (as a “multivalued foreign key”)
95-
## ought to be a subset of content_properties[c("content.Page",
96-
## "property_id")]:
123+
## ought to contain the same information as
124+
## content_properties[c("content.Page", "property_id")]:
97125
stopifnot({
98126
relation1 <-
99127
page_versions %>%
100128
transmute(content_id, property_id = content_property_ids) %>%
101129
unnest_longer(property_id)
102130
relation2 <-
103131
content_properties %>%
132+
filter(! is.na(content.Page)) %>%
104133
transmute(content_id = content.Page, property_id)
105-
## The opposite is not true, because some properties are for objects
106-
## other than pages:
107-
anti_join(relation1, relation2, by = join_by(content_id, property_id)) %>% nrow == 0
134+
by <- join_by(content_id, property_id)
135+
anti_join(relation1, relation2, by = by) %>% nrow == 0 &&
136+
anti_join(relation2, relation1, by = by) %>% nrow == 0
108137
})

0 commit comments

Comments
 (0)