Skip to content

Commit

Permalink
Replace registry repository column (#66)
Browse files Browse the repository at this point in the history
* Add preprocessing fn add-paper-links

* Remove add repository link function

* Update register columns and filter column function

* Add check for url in paper reference

* Change stop to warning in codecheck validation

* Remove extra lines in paper titles and links

* Fix render_register_md

* Removed add_repository_links_md

* Updating documentation with Roxygen

* align list entries for readability

* Remove loading config in register_check

* Replace preprocess next with if else

* Add render_register output_type default

* Add config$register_columns for html and md

* increase "check date" column width

* Adjust register paper title column width

* Update function documentation

* test github job run without cache

* Revert changes to workflow file

* Fix failing tests

* Bump version

---------

Co-authored-by: Daniel Nüst <[email protected]>
  • Loading branch information
angelina-momin and nuest authored Sep 23, 2024
1 parent 5368a52 commit bff47f1
Show file tree
Hide file tree
Showing 29 changed files with 122 additions and 205 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: codecheck
Title: Helper Functions for CODECHECK Project
Version: 0.8.0
Version: 0.9.0
Authors@R:
c(person(given = "Stephen",
family = "Eglen",
Expand Down
11 changes: 7 additions & 4 deletions R/configuration.R
Original file line number Diff line number Diff line change
Expand Up @@ -78,10 +78,7 @@ get_codecheck_yml_osf <- function(x) {
#' @importFrom httr GET content
#' @importFrom yaml yaml.load
get_codecheck_yml_gitlab <- function(x) {
# Loading config.R file which is needed for the hyperlink
source(system.file("extdata", "config.R", package = "codecheck"))

link <- paste0(CONFIG$HYPERLINKS[["gitlab"]], x, "/-/raw/main/codecheck.yml?inline=false")
link <- paste0("https://gitlab.com/", x, "/-/raw/main/codecheck.yml?inline=false")
response <- httr::GET(link)

if (response$status == 200) {
Expand Down Expand Up @@ -189,6 +186,12 @@ validate_codecheck_yml <- function(configuration) {
# the report MUST be a valid DOI
assertthat::assert_that(codecheck_yml$report %in% rorcid::check_dois(codecheck_yml$report)$good,
msg = paste0(codecheck_yml$report, " is not a valid DOI"))

# Check if the paper_link contains a valid URL. We only check that it starts with https?://
url_regex <- "^https?://"
if (!grepl(url_regex, codecheck_yml$paper$reference)) {
warning("The paper reference in the codecheck.yml is not a valid URL")
}

# if ORCID are used, they must be without URL prefix and valid form, actual checking requires login, see #11
orcid_regex <- "^(\\d{4}\\-\\d{4}\\-\\d{4}\\-\\d{3}(\\d|X))$"
Expand Down
3 changes: 3 additions & 0 deletions R/register.R
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,9 @@ register_render <- function(register = read.csv("register.csv", as.is = TRUE),
register_check <- function(register = read.csv("register.csv", as.is = TRUE),
from = 1,
to = nrow(register)) {
# Loading config.R file
source(system.file("extdata", "config.R", package = "codecheck"))

for (i in seq(from = from, to = to)) {
cat("Checking", toString(register[i, ]), "\n")
entry <- register[i, ]
Expand Down
2 changes: 1 addition & 1 deletion R/utils_create_filtered_register_csvs.R
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ create_filtered_reg_csvs <- function(register, filter_by){
register_key <- register_keys[[filter_col_name]][i]
filtered_register <- filtered_register_list[[i]]
table_details <- generate_table_details(register_key, filtered_register, filter)
filtered_register <- filter_and_drop_register_columns(filtered_register, filter)
filtered_register <- filter_and_drop_register_columns(filtered_register, filter, file_type = "csv")
output_dir <- paste0(table_details[["output_dir"]], "register.csv")
write.csv(filtered_register, output_dir, row.names=FALSE)
}
Expand Down
46 changes: 46 additions & 0 deletions R/utils_preprocess_register.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,51 @@ register_clear_cache <- function() {
unlink(path, recursive = TRUE)
}

#' Function for adding clickable links to the paper for each entry in the register table.
#'
#' @param register_table The register table
#' @param register The register from the register.csv file
#' @return The adjusted register table
add_paper_links <- function(register_table, register){
list_hyperlinks <- c()

# Looping over the entries in the register
for (i in seq_len(nrow(register))) {
# Retrieving the link to the paper
config_yml <- get_codecheck_yml(register[i, ]$Repo)
paper_link <- config_yml[["paper"]][["reference"]]
paper_title <- config_yml[["paper"]][["title"]]

# Removing new lines from paper title and link
paper_title <- gsub("\n", " ", paper_title)
paper_link <- gsub("\n$", "", paper_link)

# Checking if there is a valid url for the paper. If not we just add the title as it is
url_regex <- "^https?://"
if (!grepl(url_regex, paper_link)){
warning("The codecheck_yml's paper reference is not a valid url.")
list_hyperlinks <- c(list_hyperlinks, paper_title)
}

# If we have a valid url we add hyperlink
else{
paper_hyperlink <- paste0(
"[",
paper_title,
"](",
paper_link,
")"
)
list_hyperlinks <- c(list_hyperlinks, paper_hyperlink)
}
}
# Creating a new "Paper Title" column and moving it next to the "Repository" column
register_table <- register_table %>%
mutate(`Paper Title` = list_hyperlinks) %>%
relocate(`Paper Title`, .after = Repository)
return(register_table)
}

#' Function for adding clickable links to the report for each entry in the register table.
#'
#' @param register_table The register table
Expand Down Expand Up @@ -144,5 +189,6 @@ preprocess_register <- function(register, filter_by) {
register_table <- add_report_links(register_table, register)
register_table <- add_issue_number_links(register_table, register)
register_table <- add_check_time(register_table, register)
register_table <- add_paper_links(register_table, register)
return(register_table)
}
16 changes: 8 additions & 8 deletions R/utils_render_register_general.r
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,6 @@ create_original_register_files <- function(register_table, outputs){
for (output_type in outputs){
table_details <- list(is_reg_table = TRUE)
table_details[["output_dir"]] <- generate_output_dir(filter, table_details)
register_table <- filter_and_drop_register_columns(register_table, filter)
render_register(register_table, table_details, filter, output_type)
}
}
Expand All @@ -30,7 +29,6 @@ create_register_files <- function(register_table, filter_by, outputs){

# Creating the original register file
create_original_register_files(register_table, outputs)

# Generating filtered register table files
# For each filter type we created the nested register tables first
for (filter in filter_by){
Expand Down Expand Up @@ -58,7 +56,6 @@ create_register_files <- function(register_table, filter_by, outputs){

# Get the group names (keys) based on the filter names
register_keys <- grouped_registers %>% group_keys()

# Looping over each of the output types
for (output_type in outputs){
for (i in seq_along(filtered_register_list)) {
Expand All @@ -68,8 +65,6 @@ create_register_files <- function(register_table, filter_by, outputs){

table_details <- generate_table_details(register_key, filtered_table, filter)

# Dropping columns that are redundant
filtered_table <- filter_and_drop_register_columns(filtered_table, filter)
render_register(filtered_table, table_details, filter, output_type)
}
}
Expand All @@ -84,12 +79,14 @@ create_register_files <- function(register_table, filter_by, outputs){
#'
#' @param register_table The register table
#' @param filter A string specifying the filter to apply (e.g., "venues", "codecheckers").
#' @param file_type The type of file we need to render the register for.
#' The columns to keep depend on the file type
#'
#' @return The filtered register table with only the necessary columns retained.
filter_and_drop_register_columns <- function(register_table, filter) {
filter_and_drop_register_columns <- function(register_table, filter, file_type) {

# Step 1: Columns that we want to keep
columns_to_keep <- CONFIG$REGISTER_COLUMNS
columns_to_keep <- CONFIG$REGISTER_COLUMNS[[file_type]]

# Initialize final columns to columns_to_keep in case no filter is applied
final_columns <- intersect(columns_to_keep, names(register_table))
Expand Down Expand Up @@ -149,10 +146,13 @@ generate_table_details <- function(table_key, table, filter, is_reg_table = TRUE
#' @param register_table The register table that needs to be rendered into different files.
#' @param table_details A list of details related to the table (e.g., output directory, metadata).
#' @param filter A string specifying the filter applied to the register data.
#' @param output_type A string specifying the desired output format ("md" for Markdown, "html" for HTML, "json" for JSON).
#' @param output_type A string specifying the desired output format "json" for JSON,
#' "csv" for CSVs, "md" for MD and "html" for HTMLs.
#'
#' @return None. The function generates a file in the specified format.
render_register <- function(register_table, table_details, filter, output_type){
register_table <- filter_and_drop_register_columns(register_table, filter, output_type)

switch(output_type,
"md" = render_register_md(register_table, table_details, filter),
"html" = render_html(register_table, table_details, filter),
Expand Down
35 changes: 2 additions & 33 deletions R/utils_render_register_htmls.R
Original file line number Diff line number Diff line change
@@ -1,35 +1,3 @@
#' Function for adding repository links in the register table for the creation of the html file.
#'
#' @param register_table The register table
#' @return Register table with adjusted repository links
add_repository_links_html <- function(register_table) {
register_table$Repository <- sapply(
X = register_table$Repository,
FUN = function(repository) {
spec <- parse_repository_spec(repository)
# ! Needs refactoring
if (!any(is.na(spec))) {
urrl <- "#"
if (spec[["type"]] == "github") {
urrl <- paste0(CONFIG$HYPERLINKS[["github"]], spec[["repo"]])
paste0("<i class='fa fa-github'></i>&nbsp;[", spec[["repo"]], "](", urrl, ")")
} else if (spec[["type"]] == "osf") {
urrl <- paste0(CONFIG$HYPERLINKS[["osf"]], spec[["repo"]])
paste0("<i class='ai ai-osf'></i>&nbsp;[", spec[["repo"]], "](", urrl, ")")
} else if (spec[["type"]] == "gitlab") {
urrl <- paste0(CONFIG$HYPERLINKS[["gitlab"]], spec[["repo"]])
paste0("<i class='fa fa-gitlab'></i>&nbsp;[", spec[["repo"]], "](", urrl, ")")
} else {
repository
}
} else {
repository
}
}
)
return(register_table)
}

#' Dynamically generates a html_document.yml with the full paths to the index header, prefix
#' and postfix.html files.
#'
Expand Down Expand Up @@ -164,7 +132,8 @@ render_html <- function(table, table_details, filter){

# Creating md file from which HTML file is made
if (table_details[["is_reg_table"]]){
render_register_md(table, table_details, filter, for_html_file = TRUE)
table_details[["for_html_file"]] <- TRUE
render_register_md(table, table_details, filter)
}

else{
Expand Down
66 changes: 3 additions & 63 deletions R/utils_render_register_mds.R
Original file line number Diff line number Diff line change
Expand Up @@ -23,79 +23,19 @@ add_markdown_title <- function(table_details, md_table, filter){
return(md_table)
}

#' Function for adding repository links in the register table for the creation of the markdown file.
#'
#' @param register_table The register table
#' @return Register table with adjusted repository links
add_repository_links_md <- function(register_table) {
register_table$Repository <- sapply(
X = register_table$Repository,
FUN = function(repository) {
spec <- parse_repository_spec(repository)
if (!any(is.na(spec))) {
urrl <- "#"
# ! Needs refactoring
switch(spec["type"],
"github" = {
urrl <- paste0(CONFIG$HYPERLINKS[["github"]], spec[["repo"]])
paste0("[", spec[["repo"]], "](", urrl, ")")
},
"osf" = {
urrl <- paste0(CONFIG$HYPERLINKS[["osf"]], spec[["repo"]])
paste0("[", spec[["repo"]], "](", urrl, ")")
},
"gitlab" = {
urrl <- paste0(CONFIG$HYPERLINKS[["gitlab"]], spec[["repo"]])
paste0("[", spec[["repo"]], "](", urrl, ")")
},

# Type is none of the above
{
repository
}
)
} else {
repository
}
}
)
return(register_table)
}

#' Renders register md for a single register_table
#'
#' @param register_table The register table
#' @param table_details List containing details such as the table name, subcat name.
#' @param filter The filter
#' @param for_html_file Flag for whether we are rendering register md for html file.
#' Set to FALSE by default. If TRUE, no repo links are added to the repository table.
render_register_md <- function(register_table, table_details, filter, for_html_file=FALSE) {

# If rendering md for html file, we add repo links of the appropriate format
register_table <- if (for_html_file) {
add_repository_links_html(register_table)
} else {
add_repository_links_md(register_table)
}
render_register_md <- function(register_table, table_details, filter) {

# Fill in the content
md_table <- create_md_table(register_table, table_details, filter)
output_dir <- table_details[["output_dir"]]
save_md_table(output_dir, md_table, for_html_file)
}

#' Save markdown table to a file
#'
#' The file is saved as either a temporary file (`temp.md`) or as `register.md` depending on
#' whether it is being rendered for an HTML file.
#'
#' @param output_dir The output_dir
#' @param md_table The markdown table to be saved.
#' @param for_html_file A logical flag indicating whether the markdown is being rendered for an HTML file.
#' If TRUE, the file is saved as `temp.md`. Default is FALSE.
save_md_table <- function(output_dir, md_table, for_html_file){
# If rendering md for html file we create a temp file
if (for_html_file){
# Saving the md file
if ("for_html_file" %in% names(table_details)){
output_dir <- paste0(output_dir, "temp.md")
}

Expand Down
2 changes: 1 addition & 1 deletion R/utils_render_table_non_registers.R
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ generate_table_details_non_reg <- function(table, filter, subcat = NULL){
#' Generates postfix hrefs for the venues/ codecheckers list pages
#'
#' @param filter The filter being used such as "venues" or "codecheckers"
#' @param table_details
#' @param table_details A list of metadata about the table (e.g., title, subtext, extra text).
#' @return A list of the hrefs.
generate_html_postfix_hrefs_non_reg <- function(filter, table_details){
# Case we do not have subcat
Expand Down
11 changes: 9 additions & 2 deletions inst/extdata/config.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ CONFIG <- new.env()
# For filters other than venues we use the general column widths
CONFIG$MD_TABLE_COLUMN_WIDTHS <- list(
reg = list(
general = "|:-------|:--------------------------------|:------------------|:------------------|:---|:--------------------------|:----------|",
general = "|:-------|:---------------------------------------------|:------------------|:------------------|:---|:--------------------------|:------------------|",
venues = "|:-------|:--------------------------------|:---|:--------------------------|:----------|"
),

Expand All @@ -18,7 +18,14 @@ CONFIG$MD_TABLE_COLUMN_WIDTHS <- list(
)
)

CONFIG$REGISTER_COLUMNS <- list("Certificate", "Repository", "Type", "Venue", "Issue", "Report", "Check date")
# These are the columns to keep in the register table
CONFIG$REGISTER_COLUMNS <- list(
html = c("Certificate", "Paper Title", "Type", "Venue", "Issue", "Report", "Check date"),
md = c("Certificate", "Paper Title", "Type", "Venue", "Issue", "Report", "Check date"),
csv = c("Certificate", "Repository", "Type", "Venue", "Issue", "Report", "Check date"),
json = c("Certificate", "Repository", "Type", "Venue", "Issue", "Report", "Check date")
)

CONFIG$DIR_TEMP_REGISTER_CODECHECKER <- "docs/temp_register_codechecker.csv"
CONFIG$FILTER_COLUMN_NAMES <- list(
"venues" = "Venue",
Expand Down
4 changes: 1 addition & 3 deletions inst/extdata/templates/codecheck.yml
Original file line number Diff line number Diff line change
Expand Up @@ -9,9 +9,7 @@ paper:
- name: Roland J. Baddeley
- name: Leslie S. Smith
ORCID: 0000-0002-3716-8013
reference: >
Network (1992) 3:61-70
http://pdfs.semanticscholar.org/7dcf/a42cfe3b59becb441844b72558b361693608.pdf
reference: http://pdfs.semanticscholar.org/7dcf/a42cfe3b59becb441844b72558b361693608.pdf

manifest:
- file: Figure2.png
Expand Down
4 changes: 1 addition & 3 deletions inst/tinytest/yaml/author_name_missing/codecheck.yml
Original file line number Diff line number Diff line change
Expand Up @@ -9,9 +9,7 @@ paper:
- name: Roland J. Baddeley
- n: Leslie S. Smith
ORCID: 0000-0002-3716-8013
reference: >
Network (1992) 3:61-70
http://pdfs.semanticscholar.org/7dcf/a42cfe3b59becb441844b72558b361693608.pdf
reference: http://pdfs.semanticscholar.org/7dcf/a42cfe3b59becb441844b72558b361693608.pdf

manifest:
- file: Figure2.png
Expand Down
4 changes: 1 addition & 3 deletions inst/tinytest/yaml/codecheck.yml
Original file line number Diff line number Diff line change
Expand Up @@ -9,9 +9,7 @@ paper:
- name: Roland J. Baddeley
- name: Leslie S. Smith
ORCID: 0000-0002-3716-8013
reference: >
Network (1992) 3:61-70
http://pdfs.semanticscholar.org/7dcf/a42cfe3b59becb441844b72558b361693608.pdf
reference: http://pdfs.semanticscholar.org/7dcf/a42cfe3b59becb441844b72558b361693608.pdf

manifest:
- file: Figure2.png
Expand Down
4 changes: 1 addition & 3 deletions inst/tinytest/yaml/codechecker_name_missing/codecheck.yml
Original file line number Diff line number Diff line change
Expand Up @@ -9,9 +9,7 @@ paper:
- name: Roland J. Baddeley
- name: Leslie S. Smith
ORCID: 0000-0002-3716-8013
reference: >
Network (1992) 3:61-70
http://pdfs.semanticscholar.org/7dcf/a42cfe3b59becb441844b72558b361693608.pdf
reference: http://pdfs.semanticscholar.org/7dcf/a42cfe3b59becb441844b72558b361693608.pdf

manifest:
- file: Figure2.png
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -9,9 +9,7 @@ paper:
- name: Roland J. Baddeley
- name: Leslie S. Smith
ORCID: 0000-0002-3716-8013
reference: >
Network (1992) 3:61-70
http://pdfs.semanticscholar.org/7dcf/a42cfe3b59becb441844b72558b361693608.pdf
reference: http://pdfs.semanticscholar.org/7dcf/a42cfe3b59becb441844b72558b361693608.pdf

manifest:
- file: Figure2.png
Expand Down
Loading

0 comments on commit bff47f1

Please sign in to comment.