diff --git a/DESCRIPTION b/DESCRIPTION
index f4df370..d243d66 100644
--- a/DESCRIPTION
+++ b/DESCRIPTION
@@ -52,7 +52,8 @@ Imports:
markdown,
lifecycle,
rlang,
- stats
+ stats,
+ fontawesome
RoxygenNote: 7.2.3
Suggests:
testthat,
diff --git a/NAMESPACE b/NAMESPACE
index bf59d4f..7cc4ac3 100644
--- a/NAMESPACE
+++ b/NAMESPACE
@@ -18,6 +18,7 @@ export(mod_title_page_server)
export(mod_title_page_ui)
export(mod_xml_report_server)
export(mod_xml_report_ui)
+export(print_conflict_statement)
export(print_contrib_affil)
export(print_credit_roles)
export(print_funding)
diff --git a/R/app_server.R b/R/app_server.R
index a02e95f..d5571ae 100644
--- a/R/app_server.R
+++ b/R/app_server.R
@@ -45,6 +45,9 @@ app_server <- function(input, output,session) {
# Show funding information in viewer window
mod_funding_information_server("funding_information", input_data = read_out$data)
+ # Show conflict of interest statement
+ mod_conflict_statement_server("conflict_statement", input_data = read_out$data)
+
# Hide on launch waiter screen
waiter::waiter_hide()
}
diff --git a/R/app_ui.R b/R/app_ui.R
index 7873636..15491a0 100644
--- a/R/app_ui.R
+++ b/R/app_ui.R
@@ -5,6 +5,17 @@ app_ui <- function() {
golem_add_external_resources(),
navbarPage(
+ # Header
+ header = tagList(
+ div(id = "support-div",
+ a(id = "support-btn",
+ class = "btn",
+ href = "https://opencollective.com/tenzing",
+ target = "_blank",
+ "Support us",
+ )
+ )
+ ),
# Title
title = list(
div(
@@ -30,7 +41,7 @@ app_ui <- function() {
div(
class = "help-icon-container",
title = "Copy the contributors table template in Google Drive. Go to File -> Make a copy",
- icon("far fa-question-circle", lib = "font-awesome", class = "help-icon")
+ fontawesome::fa_i(name = "fas fa-circle-question", style = "color: #D45F68; font-size: 2em;")
)
),
wellPanel(
@@ -40,7 +51,8 @@ app_ui <- function() {
tags$a(href = "https://docs.google.com/spreadsheets/d/1Gl0cwqN_nTsdFH9yhSvi9NypBfDCEhViGq4A3MnBrG8/edit?usp=sharing",
"contributors table template",
target="_blank",
- style = "display: inline; color: #ffdf57; text-decoration: underline;")
+ style = "display: inline; color: #ffdf57; text-decoration: underline;",
+ class = "link")
)
),
# Second step
@@ -55,7 +67,7 @@ app_ui <- function() {
div(
class = "help-icon-container",
title = "Use the share URL of the filled out contributors table and click on the upload button. OR upload your contributors table in a .csv, .tsv or .xlsx format.",
- icon("far fa-question-circle", lib = "font-awesome", class = "help-icon")
+ fontawesome::fa_i(name = "fas fa-circle-question", style = "color: #D45F68; font-size: 2em;")
)
),
wellPanel(
@@ -76,7 +88,7 @@ app_ui <- function() {
div(
class = "help-icon-container",
title = "You need a valid contributors table to generate the outputs. Once you have it, click on one of the output buttons to preview and download the output.",
- icon("far fa-question-circle", lib = "font-awesome", class = "help-icon")
+ fontawesome::fa_i(name = "fas fa-circle-question", style = "color: #D45F68; font-size: 2em;")
)
),
wellPanel(
@@ -85,21 +97,17 @@ app_ui <- function() {
mod_title_page_ui("title_page"),
mod_xml_report_ui("xml_report"),
mod_show_yaml_ui("show_yaml"),
- mod_funding_information_ui("funding_information")
+ mod_funding_information_ui("funding_information"),
+ mod_conflict_statement_ui("conflict_statement")
)
),
# Citation
HTML(
"
Citation:
- Kovacs, M., Holcombe, A., Aust, F., & Aczel, B. (2021). Tenzing and the importance of tool development for research efficiency. Information Services & Use, 41, 123-130.
-
- Holcombe, A. O., Kovacs, M., Aust, F., & Aczel, B. (2020). Documenting contributions to scholarly articles using CRediT and tenzing. PLOS ONE, 15(12), e0244611.
"
+ Kovacs, M., Holcombe, A., Aust, F., & Aczel, B. (2021). Tenzing and the importance of tool development for research efficiency. Information Services & Use, 41, 123-130.
+
+ Holcombe, A. O., Kovacs, M., Aust, F., & Aczel, B. (2020). Documenting contributions to scholarly articles using CRediT and tenzing. PLOS ONE, 15(12), e0244611."
),
- # Donation
- HTML(
- "Donation:
- Open Collective
"
- ),
# Privacy notice
HTML("Privacy:
To get a sense of how many users we have, we log a masked version of IP addresses. You are not identifiable by the logged information.
")
diff --git a/R/mod_conflict_statement.R b/R/mod_conflict_statement.R
new file mode 100644
index 0000000..e860f05
--- /dev/null
+++ b/R/mod_conflict_statement.R
@@ -0,0 +1,154 @@
+#' conflict_statement UI Function
+#'
+#' @description A shiny Module.
+#'
+#' @param id,input,output,session Internal parameters for {shiny}.
+#'
+#' @noRd
+#'
+#' @importFrom shiny NS tagList
+mod_conflict_statement_ui <- function(id){
+
+ tagList(
+ div(class = "out-btn",
+ actionButton(
+ NS(id, "show_report"),
+ label = "Show conflict of interest statement",
+ class = "btn btn-primary btn-validate")
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click show', 'Conflict information'])"
+ )
+ )
+}
+
+#' conflict_statement Server Function
+#'
+#' @noRd
+mod_conflict_statement_server <- function(id, input_data){
+
+ moduleServer(id, function(input, output, session) {
+ ns <- session$ns
+ # Preview ---------------------------
+ ## Render preview
+ output$preview <- renderUI({
+ if(all(is.na(input_data()[["Conflict of interest"]]))) {
+ "There are no conflict of interest statements provided for any of the contributors."
+ } else {
+ HTML(print_conflict_statement(contributors_table = input_data(), initials = input$initials))
+ }
+ })
+
+ ## Build modal
+ modal <- function() {
+ modalDialog(
+ rclipboard::rclipboardSetup(),
+ h3("Conflict of interest statement"),
+ # Toggle between initials and full names
+ div(
+ shinyWidgets::materialSwitch(
+ NS(id, "initials"),
+ label = "Full names",
+ inline = TRUE),
+ span("Initials")
+ ),
+ hr(),
+ uiOutput(NS(id, "preview")),
+ easyClose = TRUE,
+ footer = tagList(
+ div(
+ style = "display: inline-block",
+ uiOutput(session$ns("clip"))
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click clip', 'Conflict information'])"
+ ),
+ div(
+ style = "display: inline-block",
+ downloadButton(
+ NS(id, "report"),
+ label = "Download file",
+ class = "download-report"
+ )
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click download', 'Conflict information'])"
+ ),
+ modalButton("Close")
+ )
+ )
+ }
+
+ ## Show preview modal
+ observeEvent(input$show_report, {
+ showModal(modal())
+ })
+
+ # Download ---------------------------
+ ## Set up loading bar
+ waitress <- waiter::Waitress$new(theme = "overlay", infinite = TRUE)
+
+ ## Restructure dataframe for the output
+ to_download_and_clip <- reactive({
+ if(all(is.na(input_data()[["Funding"]]))) {
+ "There are no conflict of interest statements provided for any of the contributors."
+ } else {
+ print_conflict_statement(contributors_table = input_data(), initials = input$initials)
+ }
+ })
+
+ ## Set up parameters to pass to Rmd document
+ params <- reactive({
+ list(conflict_statement = to_download_and_clip())
+ })
+
+ ## Render output Rmd
+ output$report <- downloadHandler(
+ # Set filename
+ filename = function() {
+ paste0("conflict_statement_", Sys.Date(), ".doc")
+ },
+ # Set content of the file
+ content = function(file) {
+ # Start progress bar
+ waitress$notify()
+ # Copy the report file to a temporary directory before processing it
+ file_path <- file.path("inst/app/www/", "conflict_statement.Rmd")
+ file.copy("conflict_statement.Rmd", file_path, overwrite = TRUE)
+
+ # Knit the document
+ callr::r(
+ render_report,
+ list(input = file_path, output = file, format = "word_document", params = params())
+ )
+ # Stop progress bar
+ waitress$close()
+ }
+ )
+
+ # Clip ---------------------------
+ ## Add clipboard buttons
+ output$clip <- renderUI({
+ rclipboard::rclipButton(
+ inputId = "clip_btn",
+ label = "Copy output to clipboard",
+ clipText = to_download_and_clip(),
+ icon = icon("clipboard"),
+ modal = TRUE)
+ })
+
+ ## Workaround for execution within RStudio version < 1.2
+ observeEvent(input$clip_btn, clipr::write_clip(to_download_and_clip()))
+ })
+
+}
+
+## To be copied in the UI
+# mod_conflict_statement_ui("conflict_statement")
+
+## To be copied in the server
+# mod_conflict_statement_server("conflict_statement")
+
diff --git a/R/mod_credit_roles.R b/R/mod_credit_roles.R
index c498e78..1779ef2 100644
--- a/R/mod_credit_roles.R
+++ b/R/mod_credit_roles.R
@@ -25,7 +25,7 @@ mod_credit_roles_ui <- function(id){
tagAppendAttributes(
# Track click event with Matomo
onclick = "_paq.push(['trackEvent', 'Output', 'Click show', 'Author information'])"
- )
+ )
)
}
@@ -80,12 +80,23 @@ mod_credit_roles_server <- function(id, input_data){
div(
style = "display: inline-block",
uiOutput(session$ns("clip"))
- ),
- downloadButton(
- NS(id, "report"),
- label = "Download file",
- class = "download-report"
- ),
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click clip', 'Author information'])"
+ ),
+ div(
+ style = "display: inline-block",
+ downloadButton(
+ NS(id, "report"),
+ label = "Download file",
+ class = "download-report"
+ )
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click download', 'Author information'])"
+ ),
modalButton("Close")
)
)
@@ -154,7 +165,12 @@ mod_credit_roles_server <- function(id, input_data){
## Add clipboard buttons
output$clip <- renderUI({
- rclipboard::rclipButton("clip_btn", "Copy output to clipboard", to_clip(), icon("clipboard"), modal = TRUE)
+ rclipboard::rclipButton(
+ inputId = "clip_btn",
+ label = "Copy output to clipboard",
+ clipText = to_clip(),
+ icon = icon("clipboard"),
+ modal = TRUE)
})
## Workaround for execution within RStudio version < 1.2
diff --git a/R/mod_funding_information.R b/R/mod_funding_information.R
index 8bfe807..6bda63b 100644
--- a/R/mod_funding_information.R
+++ b/R/mod_funding_information.R
@@ -15,6 +15,10 @@ mod_funding_information_ui <- function(id){
NS(id, "show_report"),
label = "Show funding information",
class = "btn btn-primary btn-validate")
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click show', 'Funding information'])"
)
)
}
@@ -56,12 +60,23 @@ mod_funding_information_server <- function(id, input_data){
div(
style = "display: inline-block",
uiOutput(session$ns("clip"))
- ),
- downloadButton(
- NS(id, "report"),
- label = "Download file",
- class = "download-report"
- ),
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click clip', 'Funding information'])"
+ ),
+ div(
+ style = "display: inline-block",
+ downloadButton(
+ NS(id, "report"),
+ label = "Download file",
+ class = "download-report"
+ )
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click download', 'Funding information'])"
+ ),
modalButton("Close")
)
)
@@ -117,7 +132,12 @@ mod_funding_information_server <- function(id, input_data){
# Clip ---------------------------
## Add clipboard buttons
output$clip <- renderUI({
- rclipboard::rclipButton("clip_btn", "Copy output to clipboard", to_download_and_clip(), icon("clipboard"), modal = TRUE)
+ rclipboard::rclipButton(
+ inputId = "clip_btn",
+ label = "Copy output to clipboard",
+ clipText = to_download_and_clip(),
+ icon = icon("clipboard"),
+ modal = TRUE)
})
## Workaround for execution within RStudio version < 1.2
diff --git a/R/mod_read_spreadsheet.R b/R/mod_read_spreadsheet.R
index e711c64..36baf99 100644
--- a/R/mod_read_spreadsheet.R
+++ b/R/mod_read_spreadsheet.R
@@ -19,6 +19,16 @@ mod_read_spreadsheet_ui <- function(id){
tabsetPanel(
id = NS(id, "which_input"),
type = "tabs",
+ tabPanel(
+ "URL",
+ h5("Paste the url of a shared googlesheet and click the upload button", class = "main-steps-desc"),
+ textInput(
+ NS(id, "url"),
+ label = NULL,
+ value = "",
+ width = NULL,
+ placeholder = "https://docs.google.com/spreadsheets/d/.../edit?usp=sharing")
+ ),
tabPanel(
"Local file",
h5("Choose the spreadsheet on your computer", class = "main-steps-desc"),
@@ -30,16 +40,6 @@ mod_read_spreadsheet_ui <- function(id){
'.tsv',
'.xlsx'),
multiple = FALSE)
- ),
- tabPanel(
- "URL",
- h5("Paste the url of a shared googlesheet and click the upload button", class = "main-steps-desc"),
- textInput(
- NS(id, "url"),
- label = NULL,
- value = "",
- width = NULL,
- placeholder = "https://docs.google.com/spreadsheets/d/.../edit?usp=sharing")
)
),
actionButton(
@@ -95,8 +95,8 @@ mod_read_spreadsheet_server <- function(id) {
list(error = read_output$error[["message"]],
warning = ""))
return(NULL)
- } else { #have successfully read the file or Google Sheet
- message("File or Google Sheet has been uploaded.") #Print message for logfile so we know when people have uploaded a contributor table
+ } else { # Have successfully read the file or Google Sheet
+ message("File or Google Sheet has been uploaded.") # Print message for logfile so we know when people have uploaded a contributor table
return(read_output$result)
}
})
diff --git a/R/mod_show_spreadsheet.R b/R/mod_show_spreadsheet.R
index c230fba..6694802 100644
--- a/R/mod_show_spreadsheet.R
+++ b/R/mod_show_spreadsheet.R
@@ -18,7 +18,6 @@ mod_show_spreadsheet_ui <- function(id) {
tagList(
div(
# style = "display: block; text-align: right;",
- title = "Click to upload from file",
id = "show-div",
actionButton(
NS(id, "show_data"),
@@ -27,6 +26,10 @@ mod_show_spreadsheet_ui <- function(id) {
icon("fas fa-eye", lib = "font-awesome")
),
class = "btn-primary")
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Input', 'Click show', 'Table'])"
)
)
}
diff --git a/R/mod_show_yaml.R b/R/mod_show_yaml.R
index 5045fc5..3d68a67 100644
--- a/R/mod_show_yaml.R
+++ b/R/mod_show_yaml.R
@@ -18,11 +18,16 @@ mod_show_yaml_ui <- function(id) {
tagList(
div(class = "out-btn",
- actionButton(inputId = NS(id, "show_yaml"),
- label = HTML("Show papaja YAML"),
- class = "btn btn-primary btn-validate")
+ actionButton(
+ inputId = NS(id, "show_yaml"),
+ label = HTML("Show papaja YAML"),
+ class = "btn btn-primary btn-validate")
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click show', 'YAML information'])"
+ )
)
- )
}
# Module Server
@@ -68,7 +73,12 @@ mod_show_yaml_server <- function(id, input_data) {
# Add clipboard buttons
output$yaml_clip <- renderUI({
- rclipboard::rclipButton("yaml_clip_btn", "Copy YAML to clipboard", author_yaml(), icon("clipboard"), modal = TRUE)
+ rclipboard::rclipButton(
+ inputId = "yaml_clip_btn",
+ label = "Copy YAML to clipboard",
+ clipText = author_yaml(),
+ icon = icon("clipboard"),
+ modal = TRUE)
})
## Workaround for execution within RStudio version < 1.2
@@ -93,12 +103,23 @@ mod_show_yaml_server <- function(id, input_data) {
div(
style = "display: inline-block",
uiOutput(session$ns("yaml_clip"))
- ),
- downloadButton(
- NS(id, "report"),
- label = "Download YAML file",
- class = "download-report"
- ),
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click clip', 'YAML information'])"
+ ),
+ div(
+ style = "display: inline-block",
+ downloadButton(
+ NS(id, "report"),
+ label = "Download YAML file",
+ class = "download-report"
+ )
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click download', 'YAML information'])"
+ ),
modalButton("Close")
)
)
diff --git a/R/mod_title_page.R b/R/mod_title_page.R
index b9bfede..5e0ddc6 100644
--- a/R/mod_title_page.R
+++ b/R/mod_title_page.R
@@ -21,6 +21,10 @@ mod_title_page_ui <- function(id){
NS(id, "show_report"),
label = "Show author list with affiliations",
class = "btn btn-primary btn-validate")
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click show', 'Title information'])"
)
)
}
@@ -53,12 +57,23 @@ mod_title_page_server <- function(id, input_data){
div(
style = "display: inline-block",
uiOutput(session$ns("clip"))
- ),
- downloadButton(
- NS(id, "report"),
- label = "Download file",
- class = "download-report"
- ),
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click clip', 'Title information'])"
+ ),
+ div(
+ style = "display: inline-block",
+ downloadButton(
+ NS(id, "report"),
+ label = "Download file",
+ class = "download-report"
+ )
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click download', 'Title information'])"
+ ),
modalButton("Close")
)
)
@@ -115,7 +130,12 @@ mod_title_page_server <- function(id, input_data){
## Add clipboard buttons
output$clip <- renderUI({
- rclipboard::rclipButton("clip_btn", "Copy output to clipboard", to_clip(), icon("clipboard"), modal = TRUE)
+ rclipboard::rclipButton(
+ inputId = "clip_btn",
+ label = "Copy output to clipboard",
+ clipText = to_clip(),
+ icon = icon("clipboard"),
+ modal = TRUE)
})
## Workaround for execution within RStudio version < 1.2
diff --git a/R/mod_xml_report.R b/R/mod_xml_report.R
index 6a2140e..f87cb90 100644
--- a/R/mod_xml_report.R
+++ b/R/mod_xml_report.R
@@ -20,6 +20,10 @@ mod_xml_report_ui <- function(id){
actionButton(NS(id, "show_report"),
label = "Show XML file (for publisher use)",
class = "btn btn-primary btn-validate")
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click show', 'XML information'])"
)
)
}
@@ -68,7 +72,12 @@ mod_xml_report_server <- function(id, input_data){
# Add clipboard buttons
output$clip <- renderUI({
- rclipboard::rclipButton("clip_btn", "Copy output to clipboard", to_print(), icon("clipboard"), modal = TRUE)
+ rclipboard::rclipButton(
+ inputId = "clip_btn",
+ label = "Copy output to clipboard",
+ clipText = to_print(),
+ icon = icon("clipboard"),
+ modal = TRUE)
})
## Workaround for execution within RStudio version < 1.2
@@ -87,12 +96,23 @@ mod_xml_report_server <- function(id, input_data){
div(
style = "display: inline-block",
uiOutput(session$ns("clip"))
- ),
- downloadButton(
- NS(id, "report"),
- label = "Download file",
- class = "download-report"
- ),
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click clip', 'XML information'])"
+ ),
+ div(
+ style = "display: inline-block",
+ downloadButton(
+ NS(id, "report"),
+ label = "Download file",
+ class = "download-report"
+ )
+ ) %>%
+ tagAppendAttributes(
+ # Track click event with Matomo
+ onclick = "_paq.push(['trackEvent', 'Output', 'Click download', 'XML information'])"
+ ),
modalButton("Close")
)
)
diff --git a/R/print_conflict_statement.R b/R/print_conflict_statement.R
new file mode 100644
index 0000000..a7a1437
--- /dev/null
+++ b/R/print_conflict_statement.R
@@ -0,0 +1,64 @@
+#' Generate human readable report of the conflict of interest statements
+#'
+#' The functions generates the conflict of interest statement section of the manuscript.
+#' The output is generated from an contributors_table validated with
+#' the [validate_contributors_table()] function.
+#' The contributors_table must be based on the [contributors_table_template()].
+#'
+#' @family output functions
+#'
+#' @param contributors_table validated contributors_table
+#' @param initials Logical. If true initials will be included instead of full
+#' names in the output
+#'
+#' @return The function returns a string.
+#' @export
+#' @examples
+#' example_contributors_table <- read_contributors_table(
+#' contributors_table = system.file("extdata",
+#' "contributors_table_example.csv", package = "tenzing", mustWork = TRUE))
+#' validate_contributors_table(contributors_table = example_contributors_table)
+#' print_conflict_statement(contributors_table = example_contributors_table, initials = FALSE)
+#'
+#' @importFrom rlang .data
+print_conflict_statement <- function(contributors_table, initials = FALSE) {
+ # Validate input ---------------------------
+ if (all(is.na(contributors_table[["Conflict of interest"]]))) stop("There are no conflict of interest statements provided for any of the contributors.")
+
+ # Restructure dataframe ---------------------------
+ if (initials) {
+ coi_data <-
+ contributors_table %>%
+ dplyr::mutate_at(
+ dplyr::vars(.data$Firstname, .data$`Middle name`, .data$Surname),
+ as.character) %>%
+ add_initials() %>%
+ dplyr::rename(Name = .data$abbrev_name)
+ } else {
+ coi_data <-
+ contributors_table %>%
+ abbreviate_middle_names_df() %>%
+ dplyr::mutate(Name = dplyr::if_else(is.na(.data$`Middle name`),
+ paste(.data$Firstname, .data$Surname),
+ paste(.data$Firstname, .data$`Middle name`, .data$Surname)))
+ }
+
+ coi_data <-
+ coi_data %>%
+ dplyr::select(.data$Name, .data[["Conflict of interest"]]) %>%
+ dplyr::filter(!is.na(.data[["Conflict of interest"]]) & .data[["Conflict of interest"]] != "") %>%
+ dplyr::group_by(.data[["Conflict of interest"]]) %>%
+ dplyr::summarise(Names = glue_oxford_collapse(.data$Name),
+ n_names = dplyr::n())
+
+ # Format output string ---------------------------
+ res <-
+ coi_data %>%
+ dplyr::transmute(
+ out = glue::glue("{Names} {dplyr::if_else(n_names > 1, 'declare', 'declares')} {`Conflict of interest`}")) %>%
+ dplyr::summarise(out = glue::glue_collapse(.data$out, sep = "; ")) %>%
+ dplyr::mutate(out = stringr::str_c(.data$out, "."))
+
+ res %>%
+ dplyr::pull(.data$out)
+}
diff --git a/R/validate_contributors_table.R b/R/validate_contributors_table.R
index 3953749..692e1f9 100644
--- a/R/validate_contributors_table.R
+++ b/R/validate_contributors_table.R
@@ -8,7 +8,7 @@
#'
#' @section The function checks the following statements:
#' \itemize{
-#' \item error, the provided contributors_table is a dataframe
+#' \item error, the provided contributors_table is not a dataframe
#' \item error, the provided contributors_table does not have the same column names as the template
#' \item error, the provided contributors_table is empty
#' \item warning, `Firstname` variable has missing value for one or more of the contributors
@@ -22,6 +22,7 @@
#' \item warning, there is no corresponding author added
#' \item warning, email address is missing for the corresponding author
#' \item warning, there is at least one CRediT role provided for all contributors
+#' \item warning, author has missing conflict on interest statement
#' }
#'
#' @param contributors_table dataframe, filled out contributors_table
@@ -292,6 +293,26 @@ validate_contributors_table <- function(contributors_table) {
message = "All authors have at least one CRediT statement checked.")
}
}
+
+ # Check if there is missing conflict of interest statement ---------------------------
+ check_coi <- function(x) {
+ if (any(is.na(x[, "Conflict of interest"]))) {
+ missing <-
+ x %>%
+ tibble::rownames_to_column(var = "rowname") %>%
+ dplyr::filter(is.na(.data[["Conflict of interest"]]))
+
+ list(
+ type = "warning",
+ message = glue::glue("The conflict of interest statement is missing for row number(s): ", glue::glue_collapse(missing$rowname, sep = ", ", last = " and "))
+ )
+ } else {
+ list(
+ type = "success",
+ message = "There are no missing conflict of interest statements."
+ )
+ }
+ }
# Return output ---------------------------
res <- list(
@@ -303,7 +324,8 @@ validate_contributors_table <- function(contributors_table) {
duplicate_order = check_duplicate_order(contributors_table_clean),
missing_affiliation = check_affiliation(contributors_table_clean),
missing_corresponding = check_missing_corresponding(contributors_table_clean),
- missing_credit = check_credit(contributors_table_clean)
+ missing_credit = check_credit(contributors_table_clean),
+ missing_coi = check_coi(contributors_table_clean)
)
if(res$missing_corresponding$type == "success") {
diff --git a/dev/02_dev.R b/dev/02_dev.R
index 92cae13..230444d 100644
--- a/dev/02_dev.R
+++ b/dev/02_dev.R
@@ -40,6 +40,7 @@ usethis::use_package("markdown")
usethis::use_package("lifecycle")
usethis::use_package("rlang")
usethis::use_package("stats")
+usethis::use_package("fontawesome")
# usethis::use_package("covr", "Suggests")
usethis::use_pipe()
diff --git a/inst/app/www/about.Rmd b/inst/app/www/about.Rmd
index 82ff9c3..eb112ba 100644
--- a/inst/app/www/about.Rmd
+++ b/inst/app/www/about.Rmd
@@ -3,13 +3,13 @@ title: ""
output: html_document
---
-tenzing is a project of the [contributorship collaboration](https://tenzing-contrib.github.io/).
+tenzing is a project of the Contributorship Collaboration.
_tenzing_ is named after the Nepali-Indian Sherpa Tenzing Norgay, who was one of the first two people to reach the summit of Mount Everest. Despite his essential contribution, the achievement is often credited less to him than to his partner, the New Zealand mountaineer Edmund Hillary.
### About CRediT
-[CRediT](http://credit.niso.org/) (Contributor Roles Taxonomy) is a high-level taxonomy of 14 roles that indicate some of the roles played by contributors to scientific scholarly output. The roles describe each contributor’s specific contribution to the scholarly output.
+CRediT (Contributor Roles Taxonomy) is a high-level taxonomy of 14 roles that indicate some of the roles played by contributors to scientific scholarly output. The roles describe each contributor’s specific contribution to the scholarly output.
### Contributors
@@ -17,14 +17,17 @@ Marton Kovacs, Alex Holcombe, Balazs Aczel, Frederik Aust, Julien Colomb.
### Related papers
-Kovacs, M., Holcombe, A., Aust, F., & Aczel, B. (2021). [Tenzing and the importance of tool development for research efficiency](https://doi.org/10.3233/ISU-210109). Information Services & Use, 41, 123–130. DOI:10.3233/ISU-210109
-
-Holcombe, A. O., Kovacs, M., Aust, F., & Aczel, B. (2020). [Documenting contributions to scholarly articles using CRediT and tenzing](https://doi.org/10.1371/journal.pone.0244611). _PLOS ONE, 15_(12), e0244611. DOI:10.1371/journal.pone.0244611
+Holcombe, A. O., Kovacs, M., Aust, F., & Aczel, B. (2020). Documenting contributions to scholarly articles using CRediT and tenzing. *Plos one, 15*(12), e0244611.
+Kovacs, M., Holcombe, A., Aust, F., & Aczel, B. (2021). Tenzing and the importance of tool development for research efficiency. Information Services & Use, 41, 123–130. DOI:10.3233/ISU-210109
### Groups that recommend tenzing
-[DORA](https://sfdora.org/resource-library/?_resource_type=tools), [UKRN](https://ukrn.org), [Collabra: Psychology](https://www.collabra.org/)
+Collabra: Psychology
+
+DORA
+
+UKRN
### Contact
-If you have comments or questions, please add to the [issues on Github](https://github.com/marton-balazs-kovacs/tenzing), email Marton: marton.balazs.kovacs@gmail.com, or message us [on Mastodon](https://neuromatch.social/@tenzingContrib).
+If you have any questions or comments, please add to the issues on Github, email Marton: marton.balazs.kovacs@gmail.com, or message us on Mastodon.
\ No newline at end of file
diff --git a/inst/app/www/about.html b/inst/app/www/about.html
index fdaec36..1fedd66 100644
--- a/inst/app/www/about.html
+++ b/inst/app/www/about.html
@@ -13,34 +13,228 @@
about.knit
-
-
+
+
-
-
-
-
+
+
+
+
-
-
+h1.title {font-size: 38px;}
+h2 {font-size: 30px;}
+h3 {font-size: 24px;}
+h4 {font-size: 18px;}
+h5 {font-size: 16px;}
+h6 {font-size: 12px;}
+code {color: inherit; background-color: rgba(0, 0, 0, 0.04);}
+pre:not([class]) { background-color: white }
+
+
+code{white-space: pre-wrap;}
+span.smallcaps{font-variant: small-caps;}
+span.underline{text-decoration: underline;}
+div.column{display: inline-block; vertical-align: top; width: 50%;}
+div.hanging-indent{margin-left: 1.5em; text-indent: -1.5em;}
+ul.task-list{list-style: none;}
+