Skip to content

Commit 4056ae9

Browse files
Merge pull request #54 from angelina-momin/create-list-venues-subcat
Create list venues subcat
2 parents e3d40ed + 7289064 commit 4056ae9

20 files changed

+574
-69
lines changed

DESCRIPTION

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
Package: codecheck
22
Title: Helper Functions for CODECHECK Project
3-
Version: 0.5.0
3+
Version: 0.6.0
44
Authors@R:
55
c(person(given = "Stephen",
66
family = "Eglen",

R/utils_render_reigster_html.r

Lines changed: 6 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -59,10 +59,10 @@ generate_html_document_yml <- function(output_dir) {
5959
#' @param register_table_name The register table name. If this is NULL we are generating list of venues/ codecheckers
6060
#'
6161
#' @importFrom whisker whisker.render
62-
create_index_postfix_html <- function(output_dir, filter, register_table_name = NULL){
62+
create_index_postfix_html <- function(output_dir, filter, register_table_name, is_reg_table){
6363

6464
# When we have register table names, we are handling the case of reg tables
65-
if (!is.null(register_table_name)){
65+
if (is_reg_table){
6666
postfix_template <- readLines(CONFIG$TEMPLATE_DIR[["reg"]][["postfix"]], warn = FALSE)
6767
# Render the template with the correct hrefs
6868
hrefs <- generate_html_postfix_hrefs_reg(filter, register_table_name)
@@ -71,9 +71,7 @@ create_index_postfix_html <- function(output_dir, filter, register_table_name =
7171
# Generating the postfix for non-register table pages (e.g. list of venues and codecheckers)
7272
else{
7373
postfix_template <- readLines(CONFIG$TEMPLATE_DIR[["non_reg"]][["postfix"]], warn = FALSE)
74-
hrefs <- list(
75-
json_href = paste0("https://codecheck.org.uk/register/", filter, "/index.json")
76-
)
74+
hrefs <- generate_html_postfix_hrefs_non_reg(filter, register_table_name)
7775
}
7876

7977
output <- whisker.render(postfix_template, hrefs)
@@ -168,8 +166,8 @@ generate_href <- function(filter, register_table_name, href_type) {
168166
#' @param output_dir The output directory of the section files
169167
#' @param filter The filter name
170168
#' @param register_table_name The register table name
171-
create_index_section_files <- function(output_dir, filter, register_table_name = NULL) {
172-
create_index_postfix_html(output_dir, filter, register_table_name)
169+
create_index_section_files <- function(output_dir, filter, register_table_name, is_reg_table) {
170+
create_index_postfix_html(output_dir, filter, register_table_name, is_reg_table)
173171
create_index_prefix_html(output_dir)
174172
create_index_header_html(output_dir)
175173
}
@@ -185,7 +183,7 @@ render_register_html <- function(filter, register_table, register_table_name){
185183
register_table <- add_repository_links_html(register_table)
186184

187185
# Dynamically create the index header, prefix and postfix files
188-
create_index_section_files(output_dir, filter, register_table_name)
186+
create_index_section_files(output_dir, filter, register_table_name, is_reg_table = TRUE)
189187
generate_html_document_yml(output_dir)
190188

191189
# Capture the HTML output from a markdown file
Lines changed: 207 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -1,46 +1,72 @@
1-
#' Renders non-register pages such as codecheckers or venues page.
1+
#' Renders non-register tables such as list of venues, codecheckers
2+
#'
3+
#' @param list_reg_tables The list of register tables
4+
#' @param page_type The HTML page type that needs to rendered.
5+
#' @return A list of register tables. The entries in the list are the names of the table
6+
render_non_register_tables_html <- function(list_reg_tables, page_type){
7+
8+
output <- switch(page_type,
9+
"codecheckers" = render_table_codecheckers_html(list_reg_tables),
10+
"venues" = render_tables_venues_html(list_reg_tables),
11+
stop("Unsupported non-register table page type")
12+
)
13+
14+
# Ensuring output is a list, wrapping it if necessary
15+
# This is needed when the render function returns a single table which is the
16+
# case when there are not subcategory tables such as the case for codecheckers
17+
if (is.data.frame(output)){
18+
output <- setNames(list(output), page_type)
19+
}
20+
return(output)
21+
}
22+
23+
#' Renders non-register html pages such as codecheckers or venues page.
224
#'
325
#' @param list_reg_tables The list of register tables to link to in this html page
26+
#' @param page_type The HTML page type that needs to rendered.
427
render_non_register_htmls <- function(list_reg_tables, page_type){
5-
output_dir <- paste0("docs/", page_type, "/")
6-
extra_text <- ""
28+
list_tables <- render_non_register_tables_html(list_reg_tables, page_type)
729

8-
if (page_type == "codecheckers"){
9-
table <- render_table_codecheckers_html(list_reg_tables)
10-
# Counting number of codecheckers based of number of codechecker reg tables
11-
# The table is a kable table and hence we cannot count rows
12-
no_codecheckers <- length(list_reg_tables)
13-
# Using number of codechecks from CONFIG instead of "no. of codechecks" column to avoid double count
14-
subtext <- paste("In total,", no_codecheckers, "codecheckers contributed", CONFIG$NO_CODECHECKS, "codechecks*")
15-
16-
# Extra text to explain why total_codechecks != SUM(no.of codechecks)
17-
extra_text <- "<i>\\*Note that the total codechecks is less than the collective sum of
18-
individual codecheckers' number of codechecks.
19-
This is because some codechecks involved more than one codechecker.</i>"
20-
}
30+
for (table_name in names(list_tables)){
31+
table <- list_tables[[table_name]]
2132

22-
else if (page_type == "venues") {
23-
table <- render_table_venues_html(list_reg_tables)
33+
# Case where we are dealing with venue subcategories
34+
if (page_type == "venues" & table_name != "all_venues"){
35+
output_dir <- paste0("docs/", page_type, "/", table_name, "/")
36+
}
37+
38+
else{
39+
output_dir <- paste0("docs/", page_type, "/")
40+
}
2441

25-
no_venues <- length(list_reg_tables)
26-
subtext <- paste("In total,", CONFIG$NO_CODECHECKS, "codechecks were completed for", no_venues, "venues")
42+
html_data <- generate_html_data(table, page_type, table_name)
43+
generate_non_reg_html(table, table_name, page_type, html_data, output_dir)
2744
}
45+
}
2846

29-
# Creating and adjusting the markdown table
47+
#' Generates non register html page.
48+
#'
49+
#' @param table The table to showcase in the html
50+
#' @param table_name The name of the table
51+
#' @param page_type The HTML page type that needs to rendered.
52+
#' @param html_data A list containing the title, subtext, extra text of the html page
53+
#' @param output_dir The directory where the html needs to be saved
54+
generate_non_reg_html <- function(table, table_name, page_type, html_data, output_dir){
3055
table <- kable(table)
56+
57+
# Creating and adjusting the markdown table
3158
md_table <- load_md_template(CONFIG$TEMPLATE_DIR[["non_reg"]][["md_template"]])
32-
title <- paste0("CODECHECK List of ", page_type)
33-
md_table <- gsub("\\$title\\$", title, md_table)
34-
md_table <- gsub("\\$subtitle\\$", subtext, md_table)
59+
md_table <- gsub("\\$title\\$", html_data[["title"]], md_table)
60+
md_table <- gsub("\\$subtitle\\$", html_data[["subtext"]], md_table)
3561
md_table <- gsub("\\$content\\$", paste(table, collapse = "\n"), md_table)
36-
md_table <- gsub("\\$extra_text\\$", extra_text, md_table)
62+
md_table <- gsub("\\$extra_text\\$", html_data[["extra_text"]], md_table)
3763

3864
# Saving the table to a temp md file
3965
temp_md_path <- paste0(output_dir, "temp.md")
4066
writeLines(md_table, temp_md_path)
4167

4268
# Creating the correct html yaml and index files
43-
create_index_section_files(output_dir, page_type)
69+
create_index_section_files(output_dir, page_type, table_name, is_reg_table = FALSE)
4470
generate_html_document_yml(output_dir)
4571
yaml_path <- normalizePath(file.path(getwd(), paste0(output_dir, "html_document.yml")))
4672

@@ -67,20 +93,168 @@ render_non_register_htmls <- function(list_reg_tables, page_type){
6793
#' Renders JSON file of non register tables such as list of venues, list of codecheckers
6894
#'
6995
#' @param list_reg_tables The list of register tables needed for the information.
96+
#' @param page_type The HTML page type that needs to rendered.
7097
render_non_register_jsons <- function(list_reg_tables, page_type){
71-
output_dir <- paste0("docs/", page_type, "/")
98+
if (page_type == "codecheckers"){
99+
list_tables <- list("codecheckers" = render_table_codecheckers_json(list_reg_tables))
100+
}
101+
102+
else if (page_type == "venues") {
103+
list_tables <- render_tables_venues_json(list_reg_tables)
104+
}
105+
106+
for (table_name in names(list_tables)){
107+
table <- list_tables[[table_name]]
108+
output_dir <- paste0("docs/", page_type, "/")
109+
110+
# Case where we are dealing with venue subcategories
111+
if (page_type == "venues" & table_name != "all_venues"){
112+
output_dir <- paste0("docs/", page_type, "/", table_name, "/")
113+
}
114+
115+
jsonlite::write_json(
116+
table,
117+
path = paste0(output_dir, "index.json"),
118+
pretty = TRUE
119+
)
120+
}
121+
}
122+
123+
#' Generates the titles of the HTML pages for non registers
124+
#'
125+
#' @param page_type The HTML page type that needs to rendered
126+
#' @param table_name The name of the table
127+
#' @return The title to put on the html page
128+
generate_html_title_non_registers <- function(page_type, table_name){
129+
title_base <- "CODECHECK List of"
130+
131+
# Adjusting title for venues subcategory
132+
if (page_type == "venues" & table_name != "all_venues"){
133+
# Replacing the word with plural
134+
plural_subcategory <- switch (table_name,
135+
"conference" = "conferences",
136+
"journal" = "journals",
137+
"community" = "communities"
138+
)
139+
title <- paste(title_base, plural_subcategory)
140+
}
72141

142+
else{
143+
# The base title is "CODECHECK List of venues/ codecheckers"
144+
title <- paste(title_base, page_type)
145+
}
146+
147+
return(title)
148+
}
149+
150+
#' Generates the extra text of the HTML pages for non registers.
151+
#' This extra text is to be placed under the table.
152+
#' There is only extra text for the codecheckers HTML page to explain
153+
#' the reason for discrepancy between total_codechecks != SUM(no.of codechecks)
154+
#'
155+
#' @param page_type The HTML page type that needs to rendered
156+
#' @return The extra text to place under the table
157+
generate_html_extra_text_non_register <- function(page_type){
158+
extra_text <- ""
159+
160+
# Extra text to explain why total_codechecks != SUM(no.of codechecks) in the codechecker table
73161
if (page_type == "codecheckers"){
74-
table <- render_table_codecheckers_json(list_reg_tables)
162+
extra_text <- "<i>\\*Note that the total codechecks is less than the collective sum of
163+
individual codecheckers' number of codechecks.
164+
This is because some codechecks involved more than one codechecker.</i>"
165+
}
166+
167+
return(extra_text)
168+
}
169+
170+
#' Generates the subtext of the HTML pages for non registers with a summary of
171+
#' the number of codechecks and number of codechecks/ venues etc.
172+
#'
173+
#' @param table The table to showcase in the html
174+
#' @param page_type The HTML page type that needs to rendered
175+
#' @param table_name The name of the table
176+
#' @return The subtext to put under the html title
177+
generate_html_subtext_non_register <- function(table, page_type, table_name){
178+
179+
# Setting the codecheck word to be plural or singular
180+
total_codechecks <- CONFIG$NO_CODECHECKS
181+
codecheck_word <- if (total_codechecks == 1) "codecheck" else "codechecks"
182+
extra_text <- ""
183+
184+
if (page_type == "codecheckers"){
185+
no_codecheckers <- nrow(table)
186+
# Adding asterik to refer to the extra text at the bottom of the page
187+
codecheck_word <- paste0(codecheck_word, "*")
188+
subtext <- paste("In total,", no_codecheckers, "codecheckers contributed", total_codechecks, codecheck_word)
75189
}
76190

77191
else if (page_type == "venues"){
78-
table <- render_table_venues_json(list_reg_tables)
192+
# For the general venues list
193+
if (table_name == "all_venues"){
194+
no_venues <- nrow(table)
195+
subtext <- paste("In total,", total_codechecks, codecheck_word, "were completed for", no_venues, "venues")
196+
}
197+
198+
else{
199+
no_venues_subcat <- nrow(table)
200+
venue_name_subtext <- table_name
201+
total_codechecks <- CONFIG$NO_CODECHECKS_VENUE_SUBCAT[[venue_name_subtext]]
202+
codecheck_word <- if (total_codechecks == 1) "codecheck" else "codechecks"
203+
204+
if (no_venues_subcat > 1){
205+
venue_name_subtext <- switch (table_name,
206+
"conference" = "conferences",
207+
"journal" = "journals",
208+
"community" = "communities"
209+
)
210+
}
211+
subtext <- paste("In total,", total_codechecks, codecheck_word, "were completed for", no_venues_subcat, venue_name_subtext)
212+
}
79213
}
80214

81-
jsonlite::write_json(
82-
table,
83-
path = paste0(output_dir, "index.json"),
84-
pretty = TRUE
215+
return(subtext)
216+
}
217+
218+
#' Generates a list of data for the html. The list contains the html
219+
#' title, subtext and extra text.
220+
#'
221+
#' @param table The table to showcase in the html
222+
#' @param page_type The HTML page type that needs to rendered
223+
#' @param table_name The name of the table
224+
#' @return A list of the html data such as title, subtext etc
225+
generate_html_data <- function(table, page_type, table_name){
226+
227+
html_data <- list(
228+
"title" = generate_html_title_non_registers(page_type, table_name),
229+
"subtext" = generate_html_subtext_non_register(table, page_type, table_name),
230+
"extra_text" = generate_html_extra_text_non_register(page_type)
85231
)
232+
233+
return(html_data)
234+
}
235+
236+
#' Generates postfix hrefs for the venues/ codecheckers list pages
237+
#'
238+
#' @param filter The filter being used such as "venues" or "codecheckers"
239+
#' @param table_name The name of the table
240+
#' @return A list of the hrefs.
241+
generate_html_postfix_hrefs_non_reg <- function(filter, table_name){
242+
243+
# For register tables that arent of subcategories of a filter type, the
244+
# json url link is register/filter/index.json
245+
if (table_name %in% list("all_venues", "codecheckers")){
246+
hrefs <- list(
247+
json_href = paste0("https://codecheck.org.uk/register/", filter, "/index.json")
248+
)
249+
}
250+
251+
# For pages of the filter subcategories, the json url is of form
252+
# filter/register_table_name/index.json where register_table_name is the subcategory name
253+
else{
254+
hrefs <- list(
255+
json_href = paste0("https://codecheck.org.uk/register/", filter, "/", table_name,"/index.json")
256+
)
257+
}
258+
259+
return(hrefs)
86260
}

0 commit comments

Comments
 (0)