Skip to content

Commit

Permalink
Finally made it through the automated CRAN checks. Data.table caused …
Browse files Browse the repository at this point in the history
…issues with using too many cores. Fixed tests, examples and vignette
  • Loading branch information
OskarGauffin committed Jan 12, 2024
1 parent 3a20f21 commit abdb0fe
Show file tree
Hide file tree
Showing 11 changed files with 57 additions and 41 deletions.
4 changes: 2 additions & 2 deletions CRAN-SUBMISSION
Original file line number Diff line number Diff line change
@@ -1,3 +1,3 @@
Version: 0.0.1
Date: 2024-01-12 12:49:03 UTC
SHA: af9c5217de39fdca012e03540660464fbe197d98
Date: 2024-01-12 20:49:19 UTC
SHA: 3a20f21681a92d66a1a7240916bc7c27bc7f4076
15 changes: 11 additions & 4 deletions R/lower_level_disprop_analysis.R
Original file line number Diff line number Diff line change
Expand Up @@ -171,8 +171,9 @@ count_expected_ror <- function(count_dt) {
#' @return A tibble with three columns (point estimate and credibility bounds).
#'
#' @examples
#' \dontrun{
#' ic(obs = 20, exp = 10)
#'
#' }
#' # Note that obs and exp can be vectors (of equal length, no recycling allowed)
#' ic(obs = c(20, 30), exp = c(10, 10))
#' @importFrom Rdpack reprompt
Expand Down Expand Up @@ -254,21 +255,23 @@ ic <- function(obs = NULL,
#' Number of rows equals length of inputs obs, n_drug, n_event_prr and n_tot_prr.
#'
#' @examples
#'
#' pvda::prr(
#' \dontrun{
#' prr(
#' obs = 5,
#' n_drug = 10,
#' n_event_prr = 20,
#' n_tot_prr = 10000
#' )
#'
#'
#' # Note that input parameters can be vectors (of equal length, no recycling)
#' pvda::prr(
#' obs = c(5, 10),
#' n_drug = c(10, 20),
#' n_event_prr = c(15, 30),
#' n_tot_prr = c(10000, 10000)
#' )
#' }
#' @references
#' \insertRef{Montastruc_2011}{pvda}
#'
Expand Down Expand Up @@ -348,7 +351,8 @@ prr <- function(obs = NULL,
#'
#' @examples
#'
#' pvda::ror(
#' \dontrun{
#' ror(
#' a = 5,
#' b = 10,
#' c = 20,
Expand All @@ -362,6 +366,7 @@ prr <- function(obs = NULL,
#' c = c(15, 30),
#' d = c(10000, 10000)
#' )
#' }
#' @references
#' \insertRef{Montastruc_2011}{pvda}
#' @export
Expand Down Expand Up @@ -407,7 +412,9 @@ ror <- function(a = NULL,
#' Default is 0.95 (i.e. 95 \% confidence interval).
#' @return A list with two numerical vectors, "lower" and "upper".
#' @examples
#' \dontrun{
#' conf_lvl_to_quantile_prob(0.95)
#' }
#' @export
conf_lvl_to_quantile_prob <- function(conf_lvl = 0.95) {
checkmate::qassert(conf_lvl, "N1[0,1]")
Expand Down
11 changes: 6 additions & 5 deletions R/onLoad.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,9 @@
# base::packageStartupMessage("Under development. Report issues at https://github.com/OskarGauffin/pvda")
# }

.onLoad <- function(libname, pkgname) {
# CRAN OMP THREAD LIMIT
Sys.setenv("OMP_THREAD_LIMIT" = 2)

}
# .onLoad <- function(libname, pkgname) {
# # CRAN OMP THREAD LIMIT
# # This did not, on it's own, prevent NOTEs about too many cores being used by data.table, when
# # submitting to CRAN.
# Sys.setenv("OMP_THREAD_LIMIT" = 2)
# }
23 changes: 4 additions & 19 deletions cran-comments.md
Original file line number Diff line number Diff line change
@@ -1,25 +1,10 @@
## Resubmission

This is a resubmission. In this version I have:
This is a resubmission. In this version I have tried to adress NOTES about data.table using too many cores, e.g. "Re-building vignettes had CPU time 7.4 times elapsed time" by:

* Adressed the first NOTE by wrapping time consuming examples in the noted functions with \dontrun.

* For the other two notes:

"Running R code in ‘testthat.R’ had CPU time 10.2 times elapsed time"
"Re-building vignettes had CPU time 7.3 times elapsed time"

I've followed advice from stack overflow and included an onLoad-function which limits the number of cores used (OMP_THREAD_LIMIT" = 2).

For completeness, this is the post I followed https://stackoverflow.com/questions/77323811/r-package-to-cran-had-cpu-time-5-times-elapsed-time
and this post suggests that it should cover the vignette note as well:
https://www.mail-archive.com/r-package-devel@r-project.org/msg08734.html

I've also:

* Corrected four URLs in the README.md file. An old github repo name caused an "possibly invalid URL" as those URLs were redirected automatically to the new github repo name.

* Listed a misplaced Rmd-file in .RBuildignore (it was not noted as a problem.)
* Wrapping all examples with \dontrun.
* Set the Sys.setenv("OMP_THREAD_LIMIT" = 2) in my testthat.R-file
* Set data.table::setDTthreads(1) in the beginning of the vignette.

------------------------------------------------------

Expand Down
2 changes: 2 additions & 0 deletions man/conf_lvl_to_quantile_prob.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

3 changes: 2 additions & 1 deletion man/ic.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

6 changes: 4 additions & 2 deletions man/prr.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 3 additions & 1 deletion man/ror.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 2 additions & 0 deletions tests/testthat.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,8 @@
# * https://r-pkgs.org/tests.html
# * https://testthat.r-lib.org/reference/test_package.html#special-files

Sys.setenv("OMP_THREAD_LIMIT" = 2)

library(testthat)
library(pvda)

Expand Down
23 changes: 16 additions & 7 deletions tests/testthat/test-disprop_analysis.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ test_that("1-3. Function ic works", {
expect_equal(test_df[, 2], expected_output[, 2])
expect_equal(test_df[, 3], expected_output[, 3])
})

test_that("4. Function ror works", {
test_df <- ror(1:2, 2:3, 3:4, 4:5)

Expand All @@ -25,6 +26,7 @@ test_that("4. Function ror works", {
expect_equal(test_df[, 2], expected_output[, 2])
# expect_equal(test_df[, 3], expected_output[, 3])
})

test_that("5-10. Function add_expected_count works", {
df_colnames <- list(
report_id = "report_id",
Expand All @@ -39,9 +41,9 @@ test_that("5-10. Function add_expected_count works", {
})

produced_output <- pvda::add_expected_counts(pvda::drug_event_df,
df_colnames,
df_syms = df_syms,
expected_count_estimators = c("rrr", "prr", "ror")
df_colnames,
df_syms = df_syms,
expected_count_estimators = c("rrr", "prr", "ror")
)

# Should return as many rows as there are unique report_ids in drug_event_df
Expand All @@ -59,6 +61,7 @@ test_that("5-10. Function add_expected_count works", {
expect_equal(first_row$n_event_prr, first_row$c)
expect_equal(first_row$n_tot_prr, diff(as.numeric(first_row[, c("n_drug", "n_tot")])))
})

test_that("11. The whole disproportionality function chain runs without NA output except in PRR and ROR", {
output <- pvda::drug_event_df |>
pvda::da() |>
Expand All @@ -69,6 +72,7 @@ test_that("11. The whole disproportionality function chain runs without NA outpu

expect_equal(FALSE, any(is.na(output)))
})

test_that("12. The grouping functionality runs", {
drug_event_df_with_grouping <- pvda::drug_event_df |>
dplyr::mutate("group" = report_id %% 2)
Expand All @@ -91,6 +95,7 @@ test_that("12. The grouping functionality runs", {

expect_equal(first_row_ic_group_0, manual_calc_ic_first_row_group_0)
})

test_that("13. Custom column names can be passed through the df_colnames list", {
drug_event_df_custom_names <- pvda::drug_event_df |>
dplyr::rename(RepId = report_id, Drug = drug, Event = event)
Expand All @@ -107,6 +112,7 @@ test_that("13. Custom column names can be passed through the df_colnames list",

expect_equal(custom_colnames, c("Drug", "Event"))
})

test_that("14. Sorting works as expected", {
# Repeated from test above on grouping
da_1 <- drug_event_df |>
Expand Down Expand Up @@ -144,26 +150,29 @@ test_that("14. Sorting works as expected", {
dplyr::pull("ic2.5") |>
(\(x){
all(x == da_1 |>
dplyr::filter(n == 1) |>
dplyr::pull(ic2.5))
dplyr::filter(n == 1) |>
dplyr::pull(ic2.5))
})()
expect_equal(c(desc_order_status, group_order_status), c(TRUE, TRUE))
})

test_that("15. Summary table contains a prr2.5 by default", {
suppressMessages(invisible(capture.output(summary_output <- summary.da(pvda::drug_event_df |> pvda::da()))))
has_prr2.5 <- as.character(summary_output[, 1]) |> stringr::str_detect("prr2.5")

expect_equal(has_prr2.5, TRUE)
})
test_that("16. print function runs and has the same number of characters in first row as it has before", {


suppressMessages(invisible(printed <- capture.output(print(pvda::drug_event_df |> pvda::da()))))
expect_equal(nchar(printed[2]), 80L)
})

test_that("17. Grouped output from summary function works.", {
summary_output <- pvda::drug_event_df |>
da(df_colnames = list(group_by = "group")) |>
summary(print = FALSE)
da(df_colnames = list(group_by = "group")) |>
summary(print = FALSE)

expect_equal(2L, ncol(summary_output))
})
5 changes: 5 additions & 0 deletions vignettes/Disproportionality_analysis.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,11 @@ editor_options:
---
# Introduction
```{r, include=FALSE}
# There are notes about data.table using too many cores when you try to submit a table with data.table-dependencies
# to cran. This is supposed to prevent that note. Also included in tests.
data.table::setDTthreads(1)
library(pvda)
knitr::opts_chunk$set(echo = FALSE)
```
Expand Down

0 comments on commit abdb0fe

Please sign in to comment.