Skip to content

Commit

Permalink
Prevent parallellism during examples and tests to pass CRAN-prechecks
Browse files Browse the repository at this point in the history
  • Loading branch information
Dvermetten committed Sep 20, 2023
1 parent aad6737 commit 7073928
Show file tree
Hide file tree
Showing 18 changed files with 30 additions and 2 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Package: IOHanalyzer
Type: Package
Title: Data Analysis Part of 'IOHprofiler'
Version: 0.1.8.1
Version: 0.1.8.2
Maintainer: Diederick Vermetten <d.l.vermetten@liacs.leidenuniv.nl>
Authors@R: c(
person("Hao", "Wang", email = "h.wang@liacs.leidenuniv.nl", role = "aut", comment = c(ORCID = "0000-0002-4933-5181")),
Expand Down
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -189,10 +189,12 @@ importFrom(data.table,copy)
importFrom(data.table,data.table)
importFrom(data.table,frank)
importFrom(data.table,fread)
importFrom(data.table,getDTthreads)
importFrom(data.table,is.data.table)
importFrom(data.table,melt)
importFrom(data.table,rbindlist)
importFrom(data.table,setDT)
importFrom(data.table,setDTthreads)
importFrom(data.table,setnames)
importFrom(data.table,setorder)
importFrom(data.table,setorderv)
Expand Down
3 changes: 3 additions & 0 deletions R/DataSetList.R
Original file line number Diff line number Diff line change
Expand Up @@ -1237,6 +1237,7 @@ generate_data.ECDF <- function(dsList, targets, scale_log = F, which = 'by_RT',
#'
#' @export
#' @examples
#' \dontshow{data.table::setDTthreads(1)}
#' generate_data.AUC(dsl, get_ECDF_targets(dsl))
#' generate_data.AUC(NULL, NULL, dt_ecdf = generate_data.ECDF(dsl, get_ECDF_targets(dsl)))
generate_data.AUC <- function(dsList, targets, scale_log = F, which = 'by_RT', dt_ecdf = NULL,
Expand Down Expand Up @@ -1480,6 +1481,7 @@ generate_data.Aggr <- function(dsList, aggr_on = 'funcId', targets = NULL, which
#'
#' @export
#' @examples
#' \dontshow{data.table::setDTthreads(1)}
#' generate_data.ECDF_raw(subset(dsl, funcId == 1), c(10, 15, 16))
generate_data.ECDF_raw <- function(dsList, targets, scale_log = F) {
V1 <- NULL #Set local binding to remove warnings
Expand Down Expand Up @@ -1783,6 +1785,7 @@ generate_data.EAF <- function(dsList, n_sets = 11, subsampling = 100, scale_xlog
#' @param normalize Whether to normalize the resulting integrals to [0,1] (Based on `min_val` and `max_va`)
#' @export
#' @examples
#' \dontshow{data.table::setDTthreads(1)}
#' generate_data.ECDF_From_EAF(generate_data.EAF(subset(dsl, funcId == 1)), 1, 16, maximization = TRUE)
generate_data.ECDF_From_EAF <- function(eaf_table, min_val, max_val, maximization = F,
scale_log = F, normalize = T) {
Expand Down
2 changes: 1 addition & 1 deletion R/IOHanalyzer.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@
#' @importFrom RColorBrewer brewer.pal
#' @importFrom colorRamps primary.colors
#' @importFrom data.table as.data.table rbindlist data.table fread := melt is.data.table
#' @importFrom data.table setorderv frank setnames rbindlist copy transpose setDT setorder
#' @importFrom data.table setorderv frank setnames rbindlist copy transpose setDT setorder getDTthreads setDTthreads
#' @importFrom plotly add_annotations add_trace orca plot_ly rename_ subplot layout
#' @importFrom plotly animation_opts save_image add_polygons hide_colorbar add_contour colorbar
#' @importFrom ggplot2 aes geom_jitter geom_line geom_ribbon geom_violin ggplot element_text
Expand Down
7 changes: 7 additions & 0 deletions R/plotDataSetList.R
Original file line number Diff line number Diff line change
Expand Up @@ -143,6 +143,7 @@ Plot.RT.Histogram <- function(dsList, ftarget, plot_mode = 'overlay', use.equal.
#' the running times of the DataSetList at the target function values
#' @export
#' @examples
#' \dontshow{data.table::setDTthreads(1)}
#' Plot.RT.ECDF_Per_Target(subset(dsl, funcId == 1), 14)
Plot.RT.ECDF_Per_Target <- function(dsList, ftargets, scale.xlog = F)
UseMethod("Plot.RT.ECDF_Per_Target", dsList)
Expand All @@ -160,6 +161,7 @@ Plot.RT.ECDF_Per_Target <- function(dsList, ftargets, scale.xlog = F)
#' the running times of the DataSetList
#' @export
#' @examples
#' \dontshow{data.table::setDTthreads(1)}
#' Plot.RT.ECDF_Single_Func(subset(dsl, funcId == 1))
Plot.RT.ECDF_Single_Func <- function(dsList, fstart = NULL, fstop = NULL,
fstep = NULL, show.per_target = F,
Expand All @@ -175,6 +177,7 @@ Plot.RT.ECDF_Single_Func <- function(dsList, fstart = NULL, fstop = NULL,
#' @return A radarplot of the area under the aggregated ECDF-curve of the DataSetList
#' @export
#' @examples
#' \dontshow{data.table::setDTthreads(1)}
#' Plot.RT.ECDF_AUC(subset(dsl, funcId == 1))
Plot.RT.ECDF_AUC <- function(dsList, fstart = NULL,
fstop = NULL, fstep = NULL,
Expand Down Expand Up @@ -222,6 +225,7 @@ Plot.FV.Histogram <- function(dsList, runtime, plot_mode='overlay', use.equal.bi
#' the fucntion values of the DataSetList at the target runtimes
#' @export
#' @examples
#' \dontshow{data.table::setDTthreads(1)}
#' Plot.FV.ECDF_Per_Target(subset(dsl, funcId == 1), 10)
Plot.FV.ECDF_Per_Target <- function(dsList, runtimes, scale.xlog = F, scale.reverse = F)
UseMethod("Plot.FV.ECDF_Per_Target", dsList)
Expand All @@ -240,6 +244,7 @@ Plot.FV.ECDF_Per_Target <- function(dsList, runtimes, scale.xlog = F, scale.reve
#' the function values of the DataSetList
#' @export
#' @examples
#' \dontshow{data.table::setDTthreads(1)}
#' Plot.FV.ECDF_Single_Func(subset(dsl, funcId == 1))
Plot.FV.ECDF_Single_Func <- function(dsList, rt_min = NULL, rt_max = NULL,
rt_step = NULL, scale.xlog = F,
Expand All @@ -255,6 +260,7 @@ Plot.FV.ECDF_Single_Func <- function(dsList, rt_min = NULL, rt_max = NULL,
#' @return A radarplot of the area under the aggregated ECDF-curve of the DataSetList
#' @export
#' @examples
#' \dontshow{data.table::setDTthreads(1)}
#' Plot.FV.ECDF_AUC(subset(dsl, funcId == 1))
Plot.FV.ECDF_AUC <- function(dsList, rt_min = NULL, rt_max = NULL,
rt_step = NULL) UseMethod("Plot.FV.ECDF_AUC", dsList)
Expand Down Expand Up @@ -316,6 +322,7 @@ Plot.FV.Parameters <- function(dsList, rt_min = NULL, rt_max = NULL,
#' the running times of the DataSetList
#' @export
#' @examples
#' \dontshow{data.table::setDTthreads(1)}
#' Plot.RT.ECDF_Multi_Func(dsl)
Plot.RT.ECDF_Multi_Func <- function(dsList, targets = NULL, scale.xlog = F)
UseMethod("Plot.RT.ECDF_Multi_Func", dsList)
Expand Down
1 change: 1 addition & 0 deletions R/stats.R
Original file line number Diff line number Diff line change
Expand Up @@ -1001,6 +1001,7 @@ get_marg_contrib_ecdf <- function(id, perm, j, dt) {
#'
#' @export
#' @examples
#' \dontshow{data.table::setDTthreads(1)}
#' dsl_sub <- subset(dsl, funcId == 1)
#' get_shapley_values(dsl_sub, get_ECDF_targets(dsl_sub), group_size = 2)
get_shapley_values <- function(dsList, targets, scale.log = T, group_size = 5, max_perm_size = 10, normalize = T){
Expand Down
1 change: 1 addition & 0 deletions man/Plot.FV.ECDF_AUC.Rd

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

1 change: 1 addition & 0 deletions man/Plot.FV.ECDF_Per_Target.Rd

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

1 change: 1 addition & 0 deletions man/Plot.FV.ECDF_Single_Func.Rd

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

1 change: 1 addition & 0 deletions man/Plot.RT.ECDF_AUC.Rd

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

1 change: 1 addition & 0 deletions man/Plot.RT.ECDF_Multi_Func.Rd

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

1 change: 1 addition & 0 deletions man/Plot.RT.ECDF_Per_Target.Rd

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

1 change: 1 addition & 0 deletions man/Plot.RT.ECDF_Single_Func.Rd

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

1 change: 1 addition & 0 deletions man/generate_data.AUC.Rd

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

1 change: 1 addition & 0 deletions man/generate_data.ECDF_From_EAF.Rd

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

1 change: 1 addition & 0 deletions man/generate_data.ECDF_raw.Rd

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

1 change: 1 addition & 0 deletions man/get_shapley_values.Rd

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

4 changes: 4 additions & 0 deletions tests/testthat.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,8 @@
library(testthat)
library(IOHanalyzer)
library(data.table)

threads <- getDTthreads()
setDTthreads(1)
test_check("IOHanalyzer")
setDTthreads(threads)

0 comments on commit 7073928

Please sign in to comment.