diff --git a/R/available_r.R b/R/available_r.R index fa955d4d..99a4e39b 100644 --- a/R/available_r.R +++ b/R/available_r.R @@ -21,8 +21,10 @@ available_df <- function() { #' available_r() available_r <- function() { r_versions <- unique(available_df()$`R.version`) - c("bleeding-edge", "frozen-edge", "r-devel", "bioc-devel", - "r-devel-bioc-devel", "latest-upstream", r_versions) + c( + "bleeding-edge", "frozen-edge", "r-devel", "bioc-devel", + "r-devel-bioc-devel", "latest-upstream", r_versions + ) } #' List available dates. diff --git a/R/fetchers.R b/R/fetchers.R index 3f87ea68..32535567 100644 --- a/R/fetchers.R +++ b/R/fetchers.R @@ -12,13 +12,56 @@ fetchgit <- function(git_pkg) { output <- get_sri_hash_deps(repo_url, commit) sri_hash <- output$sri_hash - imports <- output$deps - imports <- unlist(strsplit(imports, split = " ")) + # If package has no remote dependencies + + imports <- output$deps$imports imports <- paste(c("", imports), collapse = "\n ") + remotes <- output$deps$remotes + + main_package_expression <- generate_git_nix_expression( + package_name, + repo_url, + commit, + sri_hash, + imports, + remotes + ) + + if (is.null(remotes)) { # if no remote dependencies + + output <- main_package_expression + } else { # if there are remote dependencies, start over + remote_packages_expressions <- fetchgits(remotes) + + output <- paste0(remote_packages_expressions, + main_package_expression, + collapse = "\n" + ) + } + + output +} + + +generate_git_nix_expression <- function(package_name, + repo_url, + commit, + sri_hash, + imports, + remote_deps = NULL) { + # If there are remote dependencies, pass this string + flag_remote_deps <- if (is.null(remote_deps)) { + "" + } else { + # Extract package names + remote_pkgs_names <- sapply(remote_deps, function(x) x$package_name) + paste0(" ++ [ ", paste0(remote_pkgs_names, collapse = " "), " ]") + } + sprintf( ' - (pkgs.rPackages.buildRPackage { + %s = (pkgs.rPackages.buildRPackage { name = \"%s\"; src = pkgs.fetchgit { url = \"%s\"; @@ -27,14 +70,16 @@ fetchgit <- function(git_pkg) { }; propagatedBuildInputs = builtins.attrValues { inherit (pkgs.rPackages) %s; - }; - }) + }%s; + }); ', + package_name, package_name, repo_url, commit, sri_hash, - imports + imports, + flag_remote_deps ) } @@ -60,8 +105,7 @@ fetchzip <- function(archive_pkg, sri_hash = NULL) { if (is.null(sri_hash)) { output <- get_sri_hash_deps(repo_url, commit = NULL) sri_hash <- output$sri_hash - imports <- output$deps - imports <- unlist(strsplit(imports, split = " ")) + imports <- output$deps$imports imports <- paste(c("", imports), collapse = "\n ") } else { sri_hash <- sri_hash @@ -70,7 +114,7 @@ fetchzip <- function(archive_pkg, sri_hash = NULL) { sprintf( ' - (pkgs.rPackages.buildRPackage { + %s = (pkgs.rPackages.buildRPackage { name = \"%s\"; src = pkgs.fetchzip { url = \"%s\"; @@ -79,8 +123,9 @@ fetchzip <- function(archive_pkg, sri_hash = NULL) { propagatedBuildInputs = builtins.attrValues { inherit (pkgs.rPackages) %s; }; - }) + }), ', + package_name, package_name, repo_url, sri_hash, @@ -105,7 +150,7 @@ remove_base <- function(list_imports) { list_imports ) - paste(na.omit(imports_nobase), collapse = " ") + na.omit(imports_nobase) } @@ -145,11 +190,59 @@ get_imports <- function(path) { columns_of_interest <- c("Depends", "Imports", "LinkingTo") - imports <- as.data.frame(read.dcf(desc_path)) - - existing_columns <- intersect(columns_of_interest, colnames(imports)) + imports_df <- as.data.frame(read.dcf(desc_path)) + + existing_columns <- intersect(columns_of_interest, colnames(imports_df)) + + imports <- imports_df[, existing_columns, drop = FALSE] + + existing_remotes <- intersect("Remotes", colnames(imports_df)) + + if (!identical(existing_remotes, character(0))) { + remotes <- imports_df[, existing_remotes, drop = FALSE] + # remotes are of the form username/packagename so we need + # to only keep packagename + remotes <- gsub("\n", "", x = unlist(strsplit(remotes$Remotes, ","))) + # Get user names + remote_pkgs_usernames <- strsplit(remotes, "/") |> + sapply(function(x) x[[1]]) + + # Now remove user name and + # split at "@" or "#" character to get name and commit or PR separated + remote_pkgs_names_and_refs <- sub(".*?/", "", remotes) + remote_pkgs_names_and_refs <- strsplit(remote_pkgs_names_and_refs, "(@|#)") + + remote_pkgs_names <- remote_pkgs_names_and_refs |> + sapply(function(x) x[[1]]) + + # Check if we have a list of lists of two elements: a package name + # and a ref. If not, add "HEAD" to it. + remote_pkgs_refs <- lapply(remote_pkgs_names_and_refs, function(sublist) { + if (length(sublist) == 1) { + c(sublist, "HEAD") + } else { + sublist + } + }) |> + sapply(function(x) x[[2]]) + + urls <- paste0( + "https://github.com/", + remote_pkgs_usernames, "/", + remote_pkgs_names + ) - imports <- imports[, existing_columns, drop = FALSE] + remote_pkgs <- lapply(seq_along(remote_pkgs_names), function(i) { + list( + "package_name" = remote_pkgs_names[i], + "repo_url" = urls[i], + "commit" = remote_pkgs_refs[i] + ) + }) + } else { + remote_pkgs_names <- character(0) + remote_pkgs <- NULL + } if (!is.null(imports) && length(imports) > 0) { output <- unname(trimws(unlist(strsplit(unlist(imports), split = ",")))) @@ -165,7 +258,17 @@ get_imports <- function(path) { output <- remove_base(unique(output)) - gsub("\\.", "_", output) + output <- gsub("\\.", "_", output) + + # Remote packages are included in imports, so we need + # remove remotes from imports + output_imports <- setdiff(output, remote_pkgs_names) + + list( + "package" = imports_df$Package, + "imports" = output_imports, + "remotes" = remote_pkgs + ) } @@ -282,18 +385,39 @@ fetchzips <- function(archive_pkgs) { } } -#' fetchpkgs Downloads and installs packages hosted in the CRAN archives or -#' Github. -#' @param git_pkgs A list of three elements: "package_name", the name of the -#' package, "repo_url", the repository's url and "commit", the commit hash of -#' interest. This argument can also be a list of lists of these four elements. -#' @param archive_pkgs A character, or an atomic vector of characters. -#' @return A character. The Nix definition to download and build the R package -#' from the CRAN archives. +#' fetchpkgs Downloads and installs packages from CRAN archives or Github +#' @param git_pkgs List of Git packages with name, url and commit +#' @param archive_pkgs Vector of CRAN archive package names +#' @return Nix definition string for building the packages #' @noRd fetchpkgs <- function(git_pkgs, archive_pkgs) { - paste(fetchgits(git_pkgs), + # Only include git packages that aren't already remote dependencies + if (all(sapply(git_pkgs, is.list))) { + all_remotes <- unique(unlist(lapply(git_pkgs, get_remote))) + git_pkgs <- git_pkgs[!sapply(git_pkgs, function(pkg) { + pkg$package_name %in% all_remotes + })] + } + + # Combine git and archive package definitions + paste( + fetchgits(git_pkgs), fetchzips(archive_pkgs), collapse = "\n" ) } + +#' get_remote Retrieves the names of remote dependencies for a given Git package +#' @param git_pkg A list of three elements: "package_name", the name of the +#' package, "repo_url", the repository's URL, and "commit", the commit hash of +#' interest. +#' @return A character vector containing the names of remote dependencies. +#' @noRd +get_remote <- function(git_pkg) { + repo_url <- git_pkg$repo_url + commit <- git_pkg$commit + output <- get_sri_hash_deps(repo_url, commit) + remotes <- output$deps$remotes + remote_package_names <- sapply(remotes, `[[`, "package_name") + return(remote_package_names) +} diff --git a/R/get_latest.R b/R/get_latest.R index ffce87a2..8b3f0e8e 100644 --- a/R/get_latest.R +++ b/R/get_latest.R @@ -36,9 +36,11 @@ get_latest <- function(r_version) { "'bleeding-edge' and 'frozen-edge'." ) } else if ( - !(r_version %in% c("r-devel-bioc-devel", "r-devel", "bioc-devel", - "bleeding-edge", "frozen-edge", available_r())) - ) { + !(r_version %in% c( + "r-devel-bioc-devel", "r-devel", "bioc-devel", + "bleeding-edge", "frozen-edge", available_r() + )) + ) { stop( "The provided R version is too recent,\nand not yet included in `nixpkgs`.\n", "You can list available versions using `available_r()`.\n", diff --git a/R/nix_hash.R b/R/nix_hash.R index 8fcac21b..b2292ce5 100644 --- a/R/nix_hash.R +++ b/R/nix_hash.R @@ -5,7 +5,7 @@ #' @return list with following elements: #' - `sri_hash`: string with SRI hash of the NAR serialization of a Github repo #' at a given deterministic git commit ID (SHA-1) -#' - `deps`: string with R package dependencies separarated by space. +#' - `deps`: list with three elements: 'package', its 'imports' and its 'remotes' #' @noRd nix_hash <- function(repo_url, commit) { if (grepl("(github)|(gitlab)", repo_url)) { @@ -27,7 +27,7 @@ nix_hash <- function(repo_url, commit) { #' @return list with following elements: #' - `sri_hash`: string with SRI hash of the NAR serialization of a Github repo #' at a given deterministic git commit ID (SHA-1) -#' - `deps`: string with R package dependencies separarated by space. +#' - `deps`: list with three elements: 'package', its 'imports' and its 'remotes' #' @noRd hash_url <- function(url) { tdir <- tempdir() @@ -195,7 +195,7 @@ hash_cran <- function(repo_url) { #' @return list with following elements: #' - `sri_hash`: string with SRI hash of the NAR serialization of a Github repo #' at a given deterministic git commit ID (SHA-1) -#' - `deps`: string with R package dependencies separarated by space. +#' - `deps`: list with three elements: 'package', its 'imports' and its 'remotes' #' @noRd hash_git <- function(repo_url, commit) { trailing_slash <- grepl("/$", repo_url) @@ -226,7 +226,7 @@ hash_git <- function(repo_url, commit) { #' sake, NULL for archived CRAN packages. #' @return list with following elements: #' - `sri_hash`: string with SRI hash of the NAR serialization of a Github repo -#' - `deps`: string with R package dependencies separarated by space. +#' - `deps`: list with three elements: 'package', its 'imports' and its 'remotes' #' @noRd nix_hash_online <- function(repo_url, commit) { # handle to get error for status code 404 @@ -269,7 +269,7 @@ nix_hash_online <- function(repo_url, commit) { #' @return list with following elements: #' - `sri_hash`: string with SRI hash of the NAR serialization of a Github repo #' at a given deterministic git commit ID (SHA-1) -#' - `deps`: string with R package dependencies separarated by space. +#' - `deps`: list with three elements: 'package', its 'imports' and its 'remotes' #' @noRd get_sri_hash_deps <- function(repo_url, commit) { # if no `options(rix.sri_hash=)` is set, default is `"check_nix"` diff --git a/R/rix.R b/R/rix.R index 54d750ab..9327a1aa 100644 --- a/R/rix.R +++ b/R/rix.R @@ -282,9 +282,26 @@ for more details." # If there are R packages from Git, passes the string "git_archive_pkgs" to buildInputs flag_git_archive <- if ( - !is.null(cran_pkgs$archive_pkgs) || !is.null(git_pkgs) + !is.null(git_pkgs) || !is.null(cran_pkgs$archive_pkgs) ) { - "git_archive_pkgs" + # If git_pkgs is a list of lists, then sapply will succeed + # if not, then we can access "package_name" directly + git_pkgs_names <- if (!is.null(git_pkgs)) { + tryCatch( + sapply(git_pkgs, function(x) x$package_name), + error = function(e) git_pkgs$package_name + ) + } + # CRAN archive pkgs are written as "AER@123" + # so we need to split at the '@' character and then + # walk through the list to grab the first element + # which will be the name of the package + cran_archive_names <- if (!is.null(cran_pkgs$archive_pkgs)) { + pkgs <- strsplit(cran_pkgs$archive_pkgs, split = "@") + sapply(pkgs, function(x) x[[1]]) + } + + paste0(c(git_pkgs_names, cran_archive_names), collapse = " ") } else { "" } diff --git a/R/rix_helpers.R b/R/rix_helpers.R index 2c619887..cb674426 100644 --- a/R/rix_helpers.R +++ b/R/rix_helpers.R @@ -242,8 +242,7 @@ generate_git_archived_pkgs <- function(git_pkgs, if (flag_git_archive == "") { NULL } else { - sprintf(" - git_archive_pkgs = [%s ];\n", fetchpkgs(git_pkgs, archive_pkgs)) + fetchpkgs(git_pkgs, archive_pkgs) } } diff --git a/tests/testthat/_snaps/renv_helpers/default_datathin.nix b/tests/testthat/_snaps/renv_helpers/default_datathin.nix new file mode 100644 index 00000000..c67774fb --- /dev/null +++ b/tests/testthat/_snaps/renv_helpers/default_datathin.nix @@ -0,0 +1,413 @@ + +let + pkgs = import (fetchTarball "https://github.com/rstats-on-nix/nixpkgs/archive/2024-12-14.tar.gz") {}; + + rpkgs = builtins.attrValues { + inherit (pkgs.rPackages) + AsioHeaders + BH + Biobase + BiocGenerics + BiocManager + BiocVersion + DBI + DT + DiceDesign + FNN + GPfit + ICD10gm + KMsurv + KernSmooth + LambertW + MASS + Matrix + MatrixModels + Polychrome + R_cache + R_methodsS3 + R_oo + R_utils + R6 + RANN + RApiSerialize + RColorBrewer + ROCR + RProtoBufLib + RSpectra + Rcpp + RcppAnnoy + RcppArmadillo + RcppEigen + RcppHNSW + RcppParallel + RcppProgress + RcppTOML + Rhdf5lib + Rtsne + S4Vectors + SQUAREM + Seurat + SeuratObject + SoupX + SparseM + VGAM + WRS2 + abind + askpass + backports + base64enc + bestNormalize + bit + bit64 + bitops + blob + boot + brew + brio + broom + bslib + butcher + caTools + cachem + callr + car + carData + cellranger + class + cli + clipr + clock + cluster + codetools + collections + colorspace + commonmark + conflicted + corrplot + cowplot + cpp11 + crayon + crosstalk + curl + cyclocomp + cytolib + data_table + datawizard + dbplyr + deldir + desc + diagram + dials + dichromat + diffobj + digest + doFuture + doMC + doParallel + doRNG + dotCall64 + dplyr + dqrng + dtplyr + ellipsis + emmeans + estimability + evaluate + exactRankTests + extraDistr + fansi + farver + fastDummies + fastmap + finetune + fitdistrplus + flowCore + fontawesome + forcats + foreach + fs + furrr + future + future_apply + fuzzyjoin + gargle + generics + geosphere + ggplot2 + ggpubr + ggrepel + ggridges + ggsci + ggsignif + ggtext + glmnet + globals + glue + goftest + googledrive + googlesheets4 + gower + gplots + gridExtra + gridtext + gtable + gtools + hardhat + haven + here + highr + hms + htmltools + htmlwidgets + httpgd + httpuv + httr + ica + ids + igraph + infer + insight + ipred + irlba + isoband + iterators + janitor + jomo + jpeg + jquerylib + jsonlite + km_ci + knitr + labeling + lamW + languageserver + later + lattice + lava + lazyeval + leiden + lhs + lifecycle + lintr + listenv + lme4 + lmtest + lobstr + lubridate + magrittr + mapproj + maps + markdown + matrixStats + maxstat + mclust + memoise + mgcv + mice + mime + miniUI + minqa + mitml + modeldata + modelenv + modelr + munsell + mvtnorm + nlme + nloptr + nnet + nortest + numDeriv + openssl + ordinal + pals + pan + parallelly + parsnip + patchwork + pbapply + pbkrtest + pheatmap + pillar + pkgbuild + pkgconfig + pkgload + plotly + plyr + png + polyclip + polynom + praise + prettyunits + processx + prodlim + progress + progressr + promises + ps + purrr + qs + quantreg + ragg + rappdirs + readr + readxl + recipes + rematch + rematch2 + remotes + renv + repr + reprex + reshape + reshape2 + reticulate + rex + rlang + rmarkdown + rngtools + roxygen2 + rpart + rprojroot + rsample + rstatix + rstudioapi + rvest + sass + scales + scattermore + scatterplot3d + sctransform + selectr + shape + shiny + sitmo + skimr + slider + snakecase + sourcetools + sp + spam + spatstat_data + spatstat_explore + spatstat_geom + spatstat_random + spatstat_sparse + spatstat_utils + stringdist + stringfish + stringi + stringr + styler + survMisc + survival + survminer + sys + systemfonts + tensor + testthat + textshaping + tibble + tidymodels + tidyr + tidyselect + tidyverse + timeDate + timechange + tinytex + tune + tzdb + ucminf + unigd + utf8 + uuid + uwot + vctrs + vip + viridis + viridisLite + vroom + waldo + warp + withr + workflows + workflowsets + writexl + xfun + xgboost + xml2 + xmlparsedata + xtable + yaml + yardstick + zoo; + }; + + datathin = (pkgs.rPackages.buildRPackage { + name = "datathin"; + src = pkgs.fetchgit { + url = "https://github.com/anna-neufeld/datathin"; + rev = "HEAD"; + sha256 = "sha256-rtRpwFI+JggX8SwnfH4SPDaMPK2yLhJFTgzvWT+Zll4="; + }; + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + VGAM + knitr + extraDistr + mvtnorm; + }; + }); + + CSFAtlasTools = (pkgs.rPackages.buildRPackage { + name = "CSFAtlasTools"; + src = pkgs.fetchgit { + url = "https://github.com/mihem/CSFAtlasTools"; + rev = "02d485896d383e2a876f0f3bbae7265c017e7e92"; + sha256 = "sha256-q9qBYrGrn96lG5I9xUuWCLw0CSnh7BA5Qs9AAcRtz0E="; + }; + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + dplyr + glue + readr + ggplot2 + tidyr + RColorBrewer + bestNormalize + pheatmap + recipes + tibble + viridis + broom + WRS2 + Seurat + abind + mclust + tune + yardstick + ggsignif; + } ++ [ datathin ]; + }); + + system_packages = builtins.attrValues { + inherit (pkgs) + R + glibcLocales + nix; + }; + +in + +pkgs.mkShell { + LOCALE_ARCHIVE = if pkgs.system == "x86_64-linux" then "${pkgs.glibcLocales}/lib/locale/locale-archive" else ""; + LANG = "en_US.UTF-8"; + LC_ALL = "en_US.UTF-8"; + LC_TIME = "en_US.UTF-8"; + LC_MONETARY = "en_US.UTF-8"; + LC_PAPER = "en_US.UTF-8"; + LC_MEASUREMENT = "en_US.UTF-8"; + + buildInputs = [ CSFAtlasTools datathin rpkgs system_packages ]; + +} diff --git a/tests/testthat/_snaps/renv_helpers/default_v0-14-0.nix b/tests/testthat/_snaps/renv_helpers/default_v0-14-0.nix index 6f5833ea..386ace20 100644 --- a/tests/testthat/_snaps/renv_helpers/default_v0-14-0.nix +++ b/tests/testthat/_snaps/renv_helpers/default_v0-14-0.nix @@ -167,8 +167,7 @@ let zip; }; - git_archive_pkgs = [ - (pkgs.rPackages.buildRPackage { + colourScaleR = (pkgs.rPackages.buildRPackage { name = "colourScaleR"; src = pkgs.fetchgit { url = "https://github.com/richardjacton/colourScaleR"; @@ -185,9 +184,8 @@ let gridExtra purrr; }; - }) - ]; - + }); + system_packages = builtins.attrValues { inherit (pkgs) R @@ -206,6 +204,6 @@ pkgs.mkShell { LC_PAPER = "en_US.UTF-8"; LC_MEASUREMENT = "en_US.UTF-8"; - buildInputs = [ git_archive_pkgs rpkgs system_packages ]; + buildInputs = [ colourScaleR rpkgs system_packages ]; } diff --git a/tests/testthat/_snaps/renv_helpers/default_v0-15-5.nix b/tests/testthat/_snaps/renv_helpers/default_v0-15-5.nix index 52c8d571..928fd0ad 100644 --- a/tests/testthat/_snaps/renv_helpers/default_v0-15-5.nix +++ b/tests/testthat/_snaps/renv_helpers/default_v0-15-5.nix @@ -135,8 +135,7 @@ let zip; }; - git_archive_pkgs = [ - (pkgs.rPackages.buildRPackage { + colorblindr = (pkgs.rPackages.buildRPackage { name = "colorblindr"; src = pkgs.fetchgit { url = "https://github.com/clauswilke/colorblindr"; @@ -151,10 +150,10 @@ let shiny scales; }; - }) + }); - (pkgs.rPackages.buildRPackage { + colourScaleR = (pkgs.rPackages.buildRPackage { name = "colourScaleR"; src = pkgs.fetchgit { url = "https://github.com/RichardJActon/colourScaleR"; @@ -171,9 +170,8 @@ let gridExtra purrr; }; - }) - ]; - + }); + system_packages = builtins.attrValues { inherit (pkgs) R @@ -192,6 +190,6 @@ pkgs.mkShell { LC_PAPER = "en_US.UTF-8"; LC_MEASUREMENT = "en_US.UTF-8"; - buildInputs = [ git_archive_pkgs rpkgs system_packages ]; + buildInputs = [ colorblindr colourScaleR rpkgs system_packages ]; } diff --git a/tests/testthat/_snaps/renv_helpers/default_v0-17-3.nix b/tests/testthat/_snaps/renv_helpers/default_v0-17-3.nix index 018d304f..d4079db5 100644 --- a/tests/testthat/_snaps/renv_helpers/default_v0-17-3.nix +++ b/tests/testthat/_snaps/renv_helpers/default_v0-17-3.nix @@ -132,8 +132,7 @@ let zip; }; - git_archive_pkgs = [ - (pkgs.rPackages.buildRPackage { + emo = (pkgs.rPackages.buildRPackage { name = "emo"; src = pkgs.fetchgit { url = "https://github.com/hadley/emo"; @@ -151,9 +150,8 @@ let rlang purrr; }; - }) - ]; - + }); + system_packages = builtins.attrValues { inherit (pkgs) R @@ -172,6 +170,6 @@ pkgs.mkShell { LC_PAPER = "en_US.UTF-8"; LC_MEASUREMENT = "en_US.UTF-8"; - buildInputs = [ git_archive_pkgs rpkgs system_packages ]; + buildInputs = [ emo rpkgs system_packages ]; } diff --git a/tests/testthat/_snaps/rix/bleeding-edge_default.nix b/tests/testthat/_snaps/rix/bleeding-edge_default.nix index e97eefee..fb62e039 100644 --- a/tests/testthat/_snaps/rix/bleeding-edge_default.nix +++ b/tests/testthat/_snaps/rix/bleeding-edge_default.nix @@ -9,8 +9,7 @@ let quarto; }; - git_archive_pkgs = [ - (pkgs.rPackages.buildRPackage { + fusen = (pkgs.rPackages.buildRPackage { name = "fusen"; src = pkgs.fetchgit { url = "https://github.com/ThinkR-open/fusen"; @@ -34,10 +33,10 @@ let usethis yaml; }; - }) + }); - (pkgs.rPackages.buildRPackage { + housing = (pkgs.rPackages.buildRPackage { name = "housing"; src = pkgs.fetchgit { url = "https://github.com/rap4all/housing/"; @@ -56,9 +55,9 @@ let stringr tidyr; }; - }) + }); - (pkgs.rPackages.buildRPackage { + AER = (pkgs.rPackages.buildRPackage { name = "AER"; src = pkgs.fetchzip { url = "https://cran.r-project.org/src/contrib/Archive/AER/AER_1.2-8.tar.gz"; @@ -73,8 +72,7 @@ let zoo Formula; }; - }) - ]; + }), tex = (pkgs.texlive.combine { inherit (pkgs.texlive) @@ -102,6 +100,6 @@ pkgs.mkShell { LC_PAPER = "en_US.UTF-8"; LC_MEASUREMENT = "en_US.UTF-8"; - buildInputs = [ git_archive_pkgs rpkgs tex system_packages ]; + buildInputs = [ housing fusen AER rpkgs tex system_packages ]; } diff --git a/tests/testthat/_snaps/rix/code_default.nix b/tests/testthat/_snaps/rix/code_default.nix index ac15f813..4e757041 100644 --- a/tests/testthat/_snaps/rix/code_default.nix +++ b/tests/testthat/_snaps/rix/code_default.nix @@ -10,8 +10,7 @@ let quarto; }; - git_archive_pkgs = [ - (pkgs.rPackages.buildRPackage { + fusen = (pkgs.rPackages.buildRPackage { name = "fusen"; src = pkgs.fetchgit { url = "https://github.com/ThinkR-open/fusen"; @@ -35,10 +34,10 @@ let usethis yaml; }; - }) + }); - (pkgs.rPackages.buildRPackage { + housing = (pkgs.rPackages.buildRPackage { name = "housing"; src = pkgs.fetchgit { url = "https://github.com/rap4all/housing/"; @@ -57,9 +56,9 @@ let stringr tidyr; }; - }) + }); - (pkgs.rPackages.buildRPackage { + AER = (pkgs.rPackages.buildRPackage { name = "AER"; src = pkgs.fetchzip { url = "https://cran.r-project.org/src/contrib/Archive/AER/AER_1.2-8.tar.gz"; @@ -74,8 +73,7 @@ let zoo Formula; }; - }) - ]; + }), tex = (pkgs.texlive.combine { inherit (pkgs.texlive) @@ -102,6 +100,6 @@ pkgs.mkShell { LC_PAPER = "en_US.UTF-8"; LC_MEASUREMENT = "en_US.UTF-8"; - buildInputs = [ git_archive_pkgs rpkgs tex system_packages ]; + buildInputs = [ housing fusen AER rpkgs tex system_packages ]; } diff --git a/tests/testthat/_snaps/rix/date_default.nix b/tests/testthat/_snaps/rix/date_default.nix index 646fdd9a..39c0c46d 100644 --- a/tests/testthat/_snaps/rix/date_default.nix +++ b/tests/testthat/_snaps/rix/date_default.nix @@ -9,8 +9,7 @@ let quarto; }; - git_archive_pkgs = [ - (pkgs.rPackages.buildRPackage { + fusen = (pkgs.rPackages.buildRPackage { name = "fusen"; src = pkgs.fetchgit { url = "https://github.com/ThinkR-open/fusen"; @@ -34,10 +33,10 @@ let usethis yaml; }; - }) + }); - (pkgs.rPackages.buildRPackage { + housing = (pkgs.rPackages.buildRPackage { name = "housing"; src = pkgs.fetchgit { url = "https://github.com/rap4all/housing/"; @@ -56,9 +55,9 @@ let stringr tidyr; }; - }) + }); - (pkgs.rPackages.buildRPackage { + AER = (pkgs.rPackages.buildRPackage { name = "AER"; src = pkgs.fetchzip { url = "https://cran.r-project.org/src/contrib/Archive/AER/AER_1.2-8.tar.gz"; @@ -73,8 +72,7 @@ let zoo Formula; }; - }) - ]; + }), tex = (pkgs.texlive.combine { inherit (pkgs.texlive) @@ -102,6 +100,6 @@ pkgs.mkShell { LC_PAPER = "en_US.UTF-8"; LC_MEASUREMENT = "en_US.UTF-8"; - buildInputs = [ git_archive_pkgs rpkgs tex system_packages ]; + buildInputs = [ housing fusen AER rpkgs tex system_packages ]; } diff --git a/tests/testthat/_snaps/rix/frozen-edge_default.nix b/tests/testthat/_snaps/rix/frozen-edge_default.nix index 1b706b46..5169f364 100644 --- a/tests/testthat/_snaps/rix/frozen-edge_default.nix +++ b/tests/testthat/_snaps/rix/frozen-edge_default.nix @@ -9,8 +9,7 @@ let quarto; }; - git_archive_pkgs = [ - (pkgs.rPackages.buildRPackage { + fusen = (pkgs.rPackages.buildRPackage { name = "fusen"; src = pkgs.fetchgit { url = "https://github.com/ThinkR-open/fusen"; @@ -34,10 +33,10 @@ let usethis yaml; }; - }) + }); - (pkgs.rPackages.buildRPackage { + housing = (pkgs.rPackages.buildRPackage { name = "housing"; src = pkgs.fetchgit { url = "https://github.com/rap4all/housing/"; @@ -56,9 +55,9 @@ let stringr tidyr; }; - }) + }); - (pkgs.rPackages.buildRPackage { + AER = (pkgs.rPackages.buildRPackage { name = "AER"; src = pkgs.fetchzip { url = "https://cran.r-project.org/src/contrib/Archive/AER/AER_1.2-8.tar.gz"; @@ -73,8 +72,7 @@ let zoo Formula; }; - }) - ]; + }), tex = (pkgs.texlive.combine { inherit (pkgs.texlive) @@ -101,6 +99,6 @@ pkgs.mkShell { LC_PAPER = "en_US.UTF-8"; LC_MEASUREMENT = "en_US.UTF-8"; - buildInputs = [ git_archive_pkgs rpkgs tex system_packages ]; + buildInputs = [ housing fusen AER rpkgs tex system_packages ]; } diff --git a/tests/testthat/_snaps/rix/one_git_default.nix b/tests/testthat/_snaps/rix/one_git_default.nix index 46fc9698..0f688b46 100644 --- a/tests/testthat/_snaps/rix/one_git_default.nix +++ b/tests/testthat/_snaps/rix/one_git_default.nix @@ -2,31 +2,27 @@ let pkgs = import (fetchTarball "https://github.com/rstats-on-nix/nixpkgs/archive/2023-10-30.tar.gz") {}; - git_archive_pkgs = [ - (pkgs.rPackages.buildRPackage { - name = "lookup"; + housing = (pkgs.rPackages.buildRPackage { + name = "housing"; src = pkgs.fetchgit { - url = "https://github.com/jimhester/lookup/"; - rev = "eba63db477dd2f20153b75e2949eb333a36cccfc"; - sha256 = "sha256-arl7LVxL8xGUW3LhuDCSUjcfswX0rdofL/7v8Klw8FM="; + url = "https://github.com/rap4all/housing/"; + rev = "1c860959310b80e67c41f7bbdc3e84cef00df18e"; + sha256 = "sha256-s4KGtfKQ7hL0sfDhGb4BpBpspfefBN6hf+XlslqyEn4="; }; propagatedBuildInputs = builtins.attrValues { inherit (pkgs.rPackages) - gh - memoise - Rcpp - codetools - crayon - rex - highlite - jsonlite - rstudioapi - withr - httr; + dplyr + ggplot2 + janitor + purrr + readxl + rlang + rvest + stringr + tidyr; }; - }) - ]; - + }); + system_packages = builtins.attrValues { inherit (pkgs) R @@ -45,6 +41,6 @@ pkgs.mkShell { LC_PAPER = "en_US.UTF-8"; LC_MEASUREMENT = "en_US.UTF-8"; - buildInputs = [ git_archive_pkgs system_packages ]; + buildInputs = [ housing system_packages ]; } diff --git a/tests/testthat/_snaps/rix/other_default.nix b/tests/testthat/_snaps/rix/other_default.nix index db4b417a..b6ae5141 100644 --- a/tests/testthat/_snaps/rix/other_default.nix +++ b/tests/testthat/_snaps/rix/other_default.nix @@ -9,8 +9,7 @@ let quarto; }; - git_archive_pkgs = [ - (pkgs.rPackages.buildRPackage { + fusen = (pkgs.rPackages.buildRPackage { name = "fusen"; src = pkgs.fetchgit { url = "https://github.com/ThinkR-open/fusen"; @@ -34,10 +33,10 @@ let usethis yaml; }; - }) + }); - (pkgs.rPackages.buildRPackage { + housing = (pkgs.rPackages.buildRPackage { name = "housing"; src = pkgs.fetchgit { url = "https://github.com/rap4all/housing/"; @@ -56,9 +55,9 @@ let stringr tidyr; }; - }) + }); - (pkgs.rPackages.buildRPackage { + AER = (pkgs.rPackages.buildRPackage { name = "AER"; src = pkgs.fetchzip { url = "https://cran.r-project.org/src/contrib/Archive/AER/AER_1.2-8.tar.gz"; @@ -73,8 +72,7 @@ let zoo Formula; }; - }) - ]; + }), tex = (pkgs.texlive.combine { inherit (pkgs.texlive) @@ -101,6 +99,6 @@ pkgs.mkShell { LC_PAPER = "en_US.UTF-8"; LC_MEASUREMENT = "en_US.UTF-8"; - buildInputs = [ git_archive_pkgs rpkgs tex system_packages ]; + buildInputs = [ housing fusen AER rpkgs tex system_packages ]; } diff --git a/tests/testthat/_snaps/rix/rstudio_default.nix b/tests/testthat/_snaps/rix/rstudio_default.nix index 1177817b..b91e9a4d 100644 --- a/tests/testthat/_snaps/rix/rstudio_default.nix +++ b/tests/testthat/_snaps/rix/rstudio_default.nix @@ -9,8 +9,7 @@ let quarto; }; - git_archive_pkgs = [ - (pkgs.rPackages.buildRPackage { + fusen = (pkgs.rPackages.buildRPackage { name = "fusen"; src = pkgs.fetchgit { url = "https://github.com/ThinkR-open/fusen"; @@ -34,10 +33,10 @@ let usethis yaml; }; - }) + }); - (pkgs.rPackages.buildRPackage { + housing = (pkgs.rPackages.buildRPackage { name = "housing"; src = pkgs.fetchgit { url = "https://github.com/rap4all/housing/"; @@ -56,9 +55,9 @@ let stringr tidyr; }; - }) + }); - (pkgs.rPackages.buildRPackage { + AER = (pkgs.rPackages.buildRPackage { name = "AER"; src = pkgs.fetchzip { url = "https://cran.r-project.org/src/contrib/Archive/AER/AER_1.2-8.tar.gz"; @@ -73,8 +72,7 @@ let zoo Formula; }; - }) - ]; + }), tex = (pkgs.texlive.combine { inherit (pkgs.texlive) @@ -91,7 +89,7 @@ let }; wrapped_pkgs = pkgs.rstudioWrapper.override { - packages = [ git_archive_pkgs rpkgs ]; + packages = [ housing fusen AER rpkgs ]; }; in @@ -105,6 +103,6 @@ pkgs.mkShell { LC_PAPER = "en_US.UTF-8"; LC_MEASUREMENT = "en_US.UTF-8"; - buildInputs = [ git_archive_pkgs rpkgs tex system_packages wrapped_pkgs ]; + buildInputs = [ housing fusen AER rpkgs tex system_packages wrapped_pkgs ]; } diff --git a/tests/testthat/test-fetchers.R b/tests/testthat/test-fetchers.R index ce1f6e68..29747980 100644 --- a/tests/testthat/test-fetchers.R +++ b/tests/testthat/test-fetchers.R @@ -8,7 +8,7 @@ testthat::test_that("Test fetchgit works", { commit = "1c860959310b80e67c41f7bbdc3e84cef00df18e" ) ), - "\n (pkgs.rPackages.buildRPackage {\n name = \"housing\";\n src = pkgs.fetchgit {\n url = \"https://github.com/rap4all/housing/\";\n rev = \"1c860959310b80e67c41f7bbdc3e84cef00df18e\";\n sha256 = \"sha256-s4KGtfKQ7hL0sfDhGb4BpBpspfefBN6hf+XlslqyEn4=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n dplyr\n ggplot2\n janitor\n purrr\n readxl\n rlang\n rvest\n stringr\n tidyr;\n };\n })\n" + "\n housing = (pkgs.rPackages.buildRPackage {\n name = \"housing\";\n src = pkgs.fetchgit {\n url = \"https://github.com/rap4all/housing/\";\n rev = \"1c860959310b80e67c41f7bbdc3e84cef00df18e\";\n sha256 = \"sha256-s4KGtfKQ7hL0sfDhGb4BpBpspfefBN6hf+XlslqyEn4=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n dplyr\n ggplot2\n janitor\n purrr\n readxl\n rlang\n rvest\n stringr\n tidyr;\n };\n });\n" ) }) @@ -35,7 +35,7 @@ testthat::test_that("Test fetchgit works with gitlab packages", { commit = "9442aa63d352d3c900f1c6f5a06f7930cdf702c4" ) ), - "\n (pkgs.rPackages.buildRPackage {\n name = \"housing\";\n src = pkgs.fetchgit {\n url = \"https://gitlab.com/b-rodrigues/housing/\";\n rev = \"9442aa63d352d3c900f1c6f5a06f7930cdf702c4\";\n sha256 = \"sha256-3V9XbNbq/YpbgnzkEu3XH7QKSDY8yNNd1vpOeR9ER0w=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n dplyr\n ggplot2\n janitor\n purrr\n readxl\n rlang\n rvest\n stringr\n tidyr;\n };\n })\n" + "\n housing = (pkgs.rPackages.buildRPackage {\n name = \"housing\";\n src = pkgs.fetchgit {\n url = \"https://gitlab.com/b-rodrigues/housing/\";\n rev = \"9442aa63d352d3c900f1c6f5a06f7930cdf702c4\";\n sha256 = \"sha256-3V9XbNbq/YpbgnzkEu3XH7QKSDY8yNNd1vpOeR9ER0w=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n dplyr\n ggplot2\n janitor\n purrr\n readxl\n rlang\n rvest\n stringr\n tidyr;\n };\n });\n" ) }) @@ -49,7 +49,7 @@ testthat::test_that("Test fetchgit works with packages with empty imports", { commit = "48ceefdfb4858743454ede71d19999c2e6b38ed2" ) ), - "\n (pkgs.rPackages.buildRPackage {\n name = \"helloworld\";\n src = pkgs.fetchgit {\n url = \"https://github.com/jrosell/helloworld/\";\n rev = \"48ceefdfb4858743454ede71d19999c2e6b38ed2\";\n sha256 = \"sha256-vaO7ItKMO6PfvNDhWNDdw5ST/K081HplyW3RoQhNsEs=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) ;\n };\n })\n" + "\n helloworld = (pkgs.rPackages.buildRPackage {\n name = \"helloworld\";\n src = pkgs.fetchgit {\n url = \"https://github.com/jrosell/helloworld/\";\n rev = \"48ceefdfb4858743454ede71d19999c2e6b38ed2\";\n sha256 = \"sha256-vaO7ItKMO6PfvNDhWNDdw5ST/K081HplyW3RoQhNsEs=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) ;\n };\n });\n" ) }) @@ -57,7 +57,7 @@ testthat::test_that("Test fetchzip works", { testthat::skip_on_cran() testthat::expect_equal( fetchzip("AER@1.2-8"), - "\n (pkgs.rPackages.buildRPackage {\n name = \"AER\";\n src = pkgs.fetchzip {\n url = \"https://cran.r-project.org/src/contrib/Archive/AER/AER_1.2-8.tar.gz\";\n sha256 = \"sha256-OqxXcnUX/2C6wfD5fuNayc8OU+mstI3tt4eBVGQZ2S0=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n car\n lmtest\n sandwich\n survival\n zoo\n Formula;\n };\n })\n" + "\n AER = (pkgs.rPackages.buildRPackage {\n name = \"AER\";\n src = pkgs.fetchzip {\n url = \"https://cran.r-project.org/src/contrib/Archive/AER/AER_1.2-8.tar.gz\";\n sha256 = \"sha256-OqxXcnUX/2C6wfD5fuNayc8OU+mstI3tt4eBVGQZ2S0=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n car\n lmtest\n sandwich\n survival\n zoo\n Formula;\n };\n }),\n" ) }) @@ -86,7 +86,7 @@ testthat::test_that("Test fetchgits", { ) ) ), - "\n (pkgs.rPackages.buildRPackage {\n name = \"fusen\";\n src = pkgs.fetchgit {\n url = \"https://github.com/ThinkR-open/fusen\";\n rev = \"d617172447d2947efb20ad6a4463742b8a5d79dc\";\n sha256 = \"sha256-TOHA1ymLUSgZMYIA1a2yvuv0799svaDOl3zOhNRxcmw=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n attachment\n cli\n desc\n devtools\n glue\n here\n magrittr\n parsermd\n roxygen2\n stringi\n tibble\n tidyr\n usethis\n yaml;\n };\n })\n\n\n (pkgs.rPackages.buildRPackage {\n name = \"housing\";\n src = pkgs.fetchgit {\n url = \"https://github.com/rap4all/housing/\";\n rev = \"1c860959310b80e67c41f7bbdc3e84cef00df18e\";\n sha256 = \"sha256-s4KGtfKQ7hL0sfDhGb4BpBpspfefBN6hf+XlslqyEn4=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n dplyr\n ggplot2\n janitor\n purrr\n readxl\n rlang\n rvest\n stringr\n tidyr;\n };\n })\n" + "\n fusen = (pkgs.rPackages.buildRPackage {\n name = \"fusen\";\n src = pkgs.fetchgit {\n url = \"https://github.com/ThinkR-open/fusen\";\n rev = \"d617172447d2947efb20ad6a4463742b8a5d79dc\";\n sha256 = \"sha256-TOHA1ymLUSgZMYIA1a2yvuv0799svaDOl3zOhNRxcmw=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n attachment\n cli\n desc\n devtools\n glue\n here\n magrittr\n parsermd\n roxygen2\n stringi\n tibble\n tidyr\n usethis\n yaml;\n };\n });\n\n\n housing = (pkgs.rPackages.buildRPackage {\n name = \"housing\";\n src = pkgs.fetchgit {\n url = \"https://github.com/rap4all/housing/\";\n rev = \"1c860959310b80e67c41f7bbdc3e84cef00df18e\";\n sha256 = \"sha256-s4KGtfKQ7hL0sfDhGb4BpBpspfefBN6hf+XlslqyEn4=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n dplyr\n ggplot2\n janitor\n purrr\n readxl\n rlang\n rvest\n stringr\n tidyr;\n };\n });\n" ) }) @@ -96,11 +96,10 @@ testthat::test_that("Test fetchzips works", { fetchzips( c("dplyr@0.8.0", "AER@1.2-8") ), - "\n (pkgs.rPackages.buildRPackage {\n name = \"AER\";\n src = pkgs.fetchzip {\n url = \"https://cran.r-project.org/src/contrib/Archive/AER/AER_1.2-8.tar.gz\";\n sha256 = \"sha256-OqxXcnUX/2C6wfD5fuNayc8OU+mstI3tt4eBVGQZ2S0=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n car\n lmtest\n sandwich\n survival\n zoo\n Formula;\n };\n })\n\n\n (pkgs.rPackages.buildRPackage {\n name = \"dplyr\";\n src = pkgs.fetchzip {\n url = \"https://cran.r-project.org/src/contrib/Archive/dplyr/dplyr_0.8.0.tar.gz\";\n sha256 = \"sha256-f30raalLd9KoZKZSxeTN71PG6BczXRIiP6g7EZeH09U=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n assertthat\n glue\n magrittr\n pkgconfig\n R6\n Rcpp\n rlang\n tibble\n tidyselect\n BH\n plogr;\n };\n })\n" + "\n AER = (pkgs.rPackages.buildRPackage {\n name = \"AER\";\n src = pkgs.fetchzip {\n url = \"https://cran.r-project.org/src/contrib/Archive/AER/AER_1.2-8.tar.gz\";\n sha256 = \"sha256-OqxXcnUX/2C6wfD5fuNayc8OU+mstI3tt4eBVGQZ2S0=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n car\n lmtest\n sandwich\n survival\n zoo\n Formula;\n };\n }),\n\n\n dplyr = (pkgs.rPackages.buildRPackage {\n name = \"dplyr\";\n src = pkgs.fetchzip {\n url = \"https://cran.r-project.org/src/contrib/Archive/dplyr/dplyr_0.8.0.tar.gz\";\n sha256 = \"sha256-f30raalLd9KoZKZSxeTN71PG6BczXRIiP6g7EZeH09U=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n assertthat\n glue\n magrittr\n pkgconfig\n R6\n Rcpp\n rlang\n tibble\n tidyselect\n BH\n plogr;\n };\n }),\n" ) }) - testthat::test_that("Test fetchpkgs works", { testthat::skip_on_cran() testthat::expect_equal( @@ -119,6 +118,20 @@ testthat::test_that("Test fetchpkgs works", { ), archive_pkgs = c("AER@1.2-8", "dplyr@0.8.0") ), - "\n (pkgs.rPackages.buildRPackage {\n name = \"fusen\";\n src = pkgs.fetchgit {\n url = \"https://github.com/ThinkR-open/fusen\";\n rev = \"d617172447d2947efb20ad6a4463742b8a5d79dc\";\n sha256 = \"sha256-TOHA1ymLUSgZMYIA1a2yvuv0799svaDOl3zOhNRxcmw=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n attachment\n cli\n desc\n devtools\n glue\n here\n magrittr\n parsermd\n roxygen2\n stringi\n tibble\n tidyr\n usethis\n yaml;\n };\n })\n\n\n (pkgs.rPackages.buildRPackage {\n name = \"housing\";\n src = pkgs.fetchgit {\n url = \"https://github.com/rap4all/housing/\";\n rev = \"1c860959310b80e67c41f7bbdc3e84cef00df18e\";\n sha256 = \"sha256-s4KGtfKQ7hL0sfDhGb4BpBpspfefBN6hf+XlslqyEn4=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n dplyr\n ggplot2\n janitor\n purrr\n readxl\n rlang\n rvest\n stringr\n tidyr;\n };\n })\n \n (pkgs.rPackages.buildRPackage {\n name = \"AER\";\n src = pkgs.fetchzip {\n url = \"https://cran.r-project.org/src/contrib/Archive/AER/AER_1.2-8.tar.gz\";\n sha256 = \"sha256-OqxXcnUX/2C6wfD5fuNayc8OU+mstI3tt4eBVGQZ2S0=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n car\n lmtest\n sandwich\n survival\n zoo\n Formula;\n };\n })\n\n\n (pkgs.rPackages.buildRPackage {\n name = \"dplyr\";\n src = pkgs.fetchzip {\n url = \"https://cran.r-project.org/src/contrib/Archive/dplyr/dplyr_0.8.0.tar.gz\";\n sha256 = \"sha256-f30raalLd9KoZKZSxeTN71PG6BczXRIiP6g7EZeH09U=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n assertthat\n glue\n magrittr\n pkgconfig\n R6\n Rcpp\n rlang\n tibble\n tidyselect\n BH\n plogr;\n };\n })\n" + "\n fusen = (pkgs.rPackages.buildRPackage {\n name = \"fusen\";\n src = pkgs.fetchgit {\n url = \"https://github.com/ThinkR-open/fusen\";\n rev = \"d617172447d2947efb20ad6a4463742b8a5d79dc\";\n sha256 = \"sha256-TOHA1ymLUSgZMYIA1a2yvuv0799svaDOl3zOhNRxcmw=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n attachment\n cli\n desc\n devtools\n glue\n here\n magrittr\n parsermd\n roxygen2\n stringi\n tibble\n tidyr\n usethis\n yaml;\n };\n });\n\n\n housing = (pkgs.rPackages.buildRPackage {\n name = \"housing\";\n src = pkgs.fetchgit {\n url = \"https://github.com/rap4all/housing/\";\n rev = \"1c860959310b80e67c41f7bbdc3e84cef00df18e\";\n sha256 = \"sha256-s4KGtfKQ7hL0sfDhGb4BpBpspfefBN6hf+XlslqyEn4=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n dplyr\n ggplot2\n janitor\n purrr\n readxl\n rlang\n rvest\n stringr\n tidyr;\n };\n });\n \n AER = (pkgs.rPackages.buildRPackage {\n name = \"AER\";\n src = pkgs.fetchzip {\n url = \"https://cran.r-project.org/src/contrib/Archive/AER/AER_1.2-8.tar.gz\";\n sha256 = \"sha256-OqxXcnUX/2C6wfD5fuNayc8OU+mstI3tt4eBVGQZ2S0=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n car\n lmtest\n sandwich\n survival\n zoo\n Formula;\n };\n }),\n\n\n dplyr = (pkgs.rPackages.buildRPackage {\n name = \"dplyr\";\n src = pkgs.fetchzip {\n url = \"https://cran.r-project.org/src/contrib/Archive/dplyr/dplyr_0.8.0.tar.gz\";\n sha256 = \"sha256-f30raalLd9KoZKZSxeTN71PG6BczXRIiP6g7EZeH09U=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n assertthat\n glue\n magrittr\n pkgconfig\n R6\n Rcpp\n rlang\n tibble\n tidyselect\n BH\n plogr;\n };\n }),\n" + ) +}) + +testthat::test_that("Test fetchgit gets a package with several remote deps and commits", { + testthat::skip_on_cran() + testthat::expect_equal( + fetchgit( + list( + package_name = "lookup", + repo_url = "https://github.com/b-rodrigues/lookup/", + commit = "ee5505c817b19b59d37236ed35a81a65aa376124" + ) + ), + "\n httr2 = (pkgs.rPackages.buildRPackage {\n name = \"httr2\";\n src = pkgs.fetchgit {\n url = \"https://github.com/b-rodrigues/httr2\";\n rev = \"HEAD\";\n sha256 = \"sha256-ny4J2WqUL4LPLWRKS8rgVqwvgMOQ2Rm/lbBWtF+99PE=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n cli\n curl\n glue\n lifecycle\n magrittr\n openssl\n R6\n rappdirs\n rlang\n vctrs\n withr;\n };\n });\n\n gh = (pkgs.rPackages.buildRPackage {\n name = \"gh\";\n src = pkgs.fetchgit {\n url = \"https://github.com/b-rodrigues/gh\";\n rev = \"HEAD\";\n sha256 = \"sha256-POXEMZv8kqHokAxK8LoWkS0qYrcIcVdQi5xyGD992KU=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n cli\n gitcreds\n glue\n ini\n jsonlite\n lifecycle\n rlang;\n } ++ [ httr2 ];\n });\n\n\n highlite = (pkgs.rPackages.buildRPackage {\n name = \"highlite\";\n src = pkgs.fetchgit {\n url = \"https://github.com/jimhester/highlite\";\n rev = \"HEAD\";\n sha256 = \"sha256-lkWMlAi75MYxiBUYnLwxLK9ApXkWanA4Mt7g4qtLpxM=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n Rcpp\n BH;\n };\n });\n\n\n memoise = (pkgs.rPackages.buildRPackage {\n name = \"memoise\";\n src = pkgs.fetchgit {\n url = \"https://github.com/b-rodrigues/memoise\";\n rev = \"74d62c8\";\n sha256 = \"sha256-fsdop66VglkOIYrJ0LKZKikIZmzQ2gqEATLy9tTJ/B8=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n digest;\n };\n });\n\n lookup = (pkgs.rPackages.buildRPackage {\n name = \"lookup\";\n src = pkgs.fetchgit {\n url = \"https://github.com/b-rodrigues/lookup/\";\n rev = \"ee5505c817b19b59d37236ed35a81a65aa376124\";\n sha256 = \"sha256-jiSBuC1vzJbN6OckgVX0E+XuMCeZS5LKsldIVL7DNgo=\";\n };\n propagatedBuildInputs = builtins.attrValues {\n inherit (pkgs.rPackages) \n Rcpp\n codetools\n crayon\n rex\n jsonlite\n rstudioapi\n withr\n httr;\n } ++ [ highlite gh memoise ];\n });\n" ) }) diff --git a/tests/testthat/test-get_sri_hash_deps.R b/tests/testthat/test-get_sri_hash_deps.R index 07b9575e..7cbfe692 100644 --- a/tests/testthat/test-get_sri_hash_deps.R +++ b/tests/testthat/test-get_sri_hash_deps.R @@ -6,7 +6,14 @@ testthat::test_that("get_sri_hash_deps returns correct sri hash and dependencies ), list( "sri_hash" = "sha256-s4KGtfKQ7hL0sfDhGb4BpBpspfefBN6hf+XlslqyEn4=", - "deps" = "dplyr ggplot2 janitor purrr readxl rlang rvest stringr tidyr" + "deps" = list( + "package" = "housing", + "imports" = c( + "dplyr", "ggplot2", "janitor", "purrr", + "readxl", "rlang", "rvest", "stringr", "tidyr" + ), + "remotes" = NULL + ) ) ) }) diff --git a/tests/testthat/test-renv_helpers.R b/tests/testthat/test-renv_helpers.R index f686a717..19ef6c44 100644 --- a/tests/testthat/test-renv_helpers.R +++ b/tests/testthat/test-renv_helpers.R @@ -222,6 +222,18 @@ testthat::test_that("testing renv_helpers", { name = "default_v1-0-7.nix" ) + # This should not get datathin twice in the generated + # default.nix + testthat::expect_snapshot_file( + path = save_renv2nix_test( + "testdata/renv-samples/renv_datathin.lock", + path_env_nix, + "/default_datathin.nix", + override_r_ver = "4.4.2", + ), + name = "default_datathin.nix" + ) + on.exit(unlink(path_env_nix)) }) }) diff --git a/tests/testthat/test-rix.R b/tests/testthat/test-rix.R index d22d2d77..a7469e74 100644 --- a/tests/testthat/test-rix.R +++ b/tests/testthat/test-rix.R @@ -464,9 +464,9 @@ testthat::test_that("rix(), only one Github package", { r_pkgs = NULL, system_pkgs = NULL, git_pkgs = list( - package_name = "lookup", - repo_url = "https://github.com/jimhester/lookup/", - commit = "eba63db477dd2f20153b75e2949eb333a36cccfc" + package_name = "housing", + repo_url = "https://github.com/rap4all/housing/", + commit = "1c860959310b80e67c41f7bbdc3e84cef00df18e" ), ide = "other", project_path = path_default_nix, diff --git a/tests/testthat/testdata/renv-samples/renv_datathin.lock b/tests/testthat/testdata/renv-samples/renv_datathin.lock new file mode 100644 index 00000000..f591b597 --- /dev/null +++ b/tests/testthat/testdata/renv-samples/renv_datathin.lock @@ -0,0 +1,5013 @@ +{ + "R": { + "Version": "4.3.1", + "Repositories": [ + { + "Name": "BioCsoft", + "URL": "https://bioconductor.org/packages/3.18/bioc" + }, + { + "Name": "BioCann", + "URL": "https://bioconductor.org/packages/3.18/data/annotation" + }, + { + "Name": "BioCexp", + "URL": "https://bioconductor.org/packages/3.18/data/experiment" + }, + { + "Name": "BioCworkflows", + "URL": "https://bioconductor.org/packages/3.18/workflows" + }, + { + "Name": "BioCbooks", + "URL": "https://bioconductor.org/packages/3.18/books" + }, + { + "Name": "RSPM", + "URL": "https://packagemanager.rstudio.com/cran/latest" + } + ] + }, + "Bioconductor": { + "Version": "3.18" + }, + "Packages": { + "AsioHeaders": { + "Package": "AsioHeaders", + "Version": "1.22.1-2", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "85bf3bd8fa58da21a22d84fd4f4ef0a8" + }, + "BH": { + "Package": "BH", + "Version": "1.84.0-0", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "a8235afbcd6316e6e91433ea47661013" + }, + "Biobase": { + "Package": "Biobase", + "Version": "2.62.0", + "Source": "Bioconductor", + "Requirements": [ + "BiocGenerics", + "R", + "methods", + "utils" + ], + "Hash": "38252a34e82d3ff6bb46b4e2252d2dce" + }, + "BiocGenerics": { + "Package": "BiocGenerics", + "Version": "0.48.1", + "Source": "Bioconductor", + "Requirements": [ + "R", + "graphics", + "methods", + "stats", + "utils" + ], + "Hash": "e34278c65d7dffcc08f737bf0944ca9a" + }, + "BiocManager": { + "Package": "BiocManager", + "Version": "1.30.25", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "utils" + ], + "Hash": "3aec5928ca10897d7a0a1205aae64627" + }, + "BiocVersion": { + "Package": "BiocVersion", + "Version": "3.18.1", + "Source": "Bioconductor", + "Requirements": [ + "R" + ], + "Hash": "2ecaed86684f5fae76ed5530f9d29c4a" + }, + "CSFAtlasTools": { + "Package": "CSFAtlasTools", + "Version": "2.0.0", + "Source": "GitHub", + "RemoteType": "github", + "RemoteHost": "api.github.com", + "RemoteUsername": "mihem", + "RemoteRepo": "CSFAtlasTools", + "RemoteRef": "main", + "RemoteSha": "02d485896d383e2a876f0f3bbae7265c017e7e92", + "Remotes": "anna-neufeld/datathin", + "Requirements": [ + "RColorBrewer", + "Seurat", + "WRS2", + "abind", + "bestNormalize", + "broom", + "datathin", + "dplyr", + "ggplot2", + "ggsignif", + "glue", + "grDevices", + "mclust", + "pheatmap", + "readr", + "recipes", + "tibble", + "tidyr", + "tune", + "viridis", + "yardstick" + ], + "Hash": "d74d190be1df5c93cda976ef7cf55c55" + }, + "DBI": { + "Package": "DBI", + "Version": "1.2.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "methods" + ], + "Hash": "164809cd72e1d5160b4cb3aa57f510fe" + }, + "DT": { + "Package": "DT", + "Version": "0.33", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "crosstalk", + "htmltools", + "htmlwidgets", + "httpuv", + "jquerylib", + "jsonlite", + "magrittr", + "promises" + ], + "Hash": "64ff3427f559ce3f2597a4fe13255cb6" + }, + "DiceDesign": { + "Package": "DiceDesign", + "Version": "1.10", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "ac8b12951882c375d1a14f64c93e78f1" + }, + "FNN": { + "Package": "FNN", + "Version": "1.1.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "eaabdc7938aa3632a28273f53a0d226d" + }, + "GPfit": { + "Package": "GPfit", + "Version": "1.0-8", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "lattice", + "lhs" + ], + "Hash": "29a7dccade1fd037c8262c2a239775eb" + }, + "ICD10gm": { + "Package": "ICD10gm", + "Version": "1.2.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "dplyr", + "magrittr", + "purrr", + "rlang", + "stringi", + "tibble", + "tidyr", + "tidyselect" + ], + "Hash": "b67aa387ec85d5b165f4678dda88fcd6" + }, + "KMsurv": { + "Package": "KMsurv", + "Version": "0.1-5", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "aee647d15e5541ad44d157f7b78fda01" + }, + "KernSmooth": { + "Package": "KernSmooth", + "Version": "2.23-22", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "stats" + ], + "Hash": "2fecebc3047322fa5930f74fae5de70f" + }, + "LambertW": { + "Package": "LambertW", + "Version": "0.6.9-1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "RColorBrewer", + "Rcpp", + "ggplot2", + "grDevices", + "graphics", + "lamW", + "methods", + "reshape2", + "stats" + ], + "Hash": "af46ea546f675fb5348a3704f05d7a6d" + }, + "MASS": { + "Package": "MASS", + "Version": "7.3-60.0.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics", + "methods", + "stats", + "utils" + ], + "Hash": "b765b28387acc8ec9e9c1530713cb19c" + }, + "Matrix": { + "Package": "Matrix", + "Version": "1.6-5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics", + "grid", + "lattice", + "methods", + "stats", + "utils" + ], + "Hash": "8c7115cd3a0e048bda2a7cd110549f7a" + }, + "MatrixModels": { + "Package": "MatrixModels", + "Version": "0.5-3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "methods", + "stats" + ], + "Hash": "0776bf7526869e0286b0463cb72fb211" + }, + "Polychrome": { + "Package": "Polychrome", + "Version": "1.5.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "colorspace", + "grDevices", + "graphics", + "methods", + "scatterplot3d", + "stats", + "utils" + ], + "Hash": "466f3a16617d769c773ca1f1ea878055" + }, + "R.cache": { + "Package": "R.cache", + "Version": "0.16.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R.methodsS3", + "R.oo", + "R.utils", + "digest", + "utils" + ], + "Hash": "fe539ca3f8efb7410c3ae2cf5fe6c0f8" + }, + "R.methodsS3": { + "Package": "R.methodsS3", + "Version": "1.8.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "utils" + ], + "Hash": "278c286fd6e9e75d0c2e8f731ea445c8" + }, + "R.oo": { + "Package": "R.oo", + "Version": "1.26.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R.methodsS3", + "methods", + "utils" + ], + "Hash": "4fed809e53ddb5407b3da3d0f572e591" + }, + "R.utils": { + "Package": "R.utils", + "Version": "2.12.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R.methodsS3", + "R.oo", + "methods", + "tools", + "utils" + ], + "Hash": "3dc2829b790254bfba21e60965787651" + }, + "R6": { + "Package": "R6", + "Version": "2.5.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "470851b6d5d0ac559e9d01bb352b4021" + }, + "RANN": { + "Package": "RANN", + "Version": "2.6.1", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "d128ea05a972d3e67c6f39de52c72bd7" + }, + "RApiSerialize": { + "Package": "RApiSerialize", + "Version": "0.1.2", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "d8a79c95f553670ceffbd190815bbfce" + }, + "RColorBrewer": { + "Package": "RColorBrewer", + "Version": "1.1-3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "45f0398006e83a5b10b72a90663d8d8c" + }, + "ROCR": { + "Package": "ROCR", + "Version": "1.0-11", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "gplots", + "grDevices", + "graphics", + "methods", + "stats" + ], + "Hash": "cc151930e20e16427bc3d0daec62b4a9" + }, + "RProtoBufLib": { + "Package": "RProtoBufLib", + "Version": "2.14.1", + "Source": "Bioconductor", + "Repository": "Bioconductor 3.18", + "Hash": "0243b2cfde99364e02fc4c67e7bb5ea2" + }, + "RSpectra": { + "Package": "RSpectra", + "Version": "0.16-1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "Rcpp", + "RcppEigen" + ], + "Hash": "6b5ab997fd5ff6d46a5f1d9f8b76961c" + }, + "Rcpp": { + "Package": "Rcpp", + "Version": "1.0.12", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "methods", + "utils" + ], + "Hash": "5ea2700d21e038ace58269ecdbeb9ec0" + }, + "RcppAnnoy": { + "Package": "RcppAnnoy", + "Version": "0.0.22", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp", + "methods" + ], + "Hash": "f6baa1e06fb6c3724f601a764266cb0d" + }, + "RcppArmadillo": { + "Package": "RcppArmadillo", + "Version": "0.12.8.2.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp", + "methods", + "stats", + "utils" + ], + "Hash": "d5448fb24fb114c4da1275a37a571f37" + }, + "RcppEigen": { + "Package": "RcppEigen", + "Version": "0.3.4.0.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp", + "stats", + "utils" + ], + "Hash": "df49e3306f232ec28f1604e36a202847" + }, + "RcppHNSW": { + "Package": "RcppHNSW", + "Version": "0.6.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Rcpp", + "methods" + ], + "Hash": "1f2dc32c27746a35196aaf95adb357be" + }, + "RcppParallel": { + "Package": "RcppParallel", + "Version": "5.1.7", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "a45594a00f5dbb073d5ec9f48592a08a" + }, + "RcppProgress": { + "Package": "RcppProgress", + "Version": "0.4.2", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "1c0aa18b97e6aaa17f93b8b866c0ace5" + }, + "RcppTOML": { + "Package": "RcppTOML", + "Version": "0.2.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp" + ], + "Hash": "c232938949fcd8126034419cc529333a" + }, + "Rhdf5lib": { + "Package": "Rhdf5lib", + "Version": "1.24.2", + "Source": "Bioconductor", + "Repository": "Bioconductor 3.18", + "Requirements": [ + "R" + ], + "Hash": "3cf103db29d75af0221d71946509a30c" + }, + "Rtsne": { + "Package": "Rtsne", + "Version": "0.17", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Rcpp", + "stats" + ], + "Hash": "f81f7764a3c3e310b1d40e1a8acee19e" + }, + "S4Vectors": { + "Package": "S4Vectors", + "Version": "0.40.2", + "Source": "Bioconductor", + "Repository": "Bioconductor 3.18", + "Requirements": [ + "BiocGenerics", + "R", + "methods", + "stats", + "stats4", + "utils" + ], + "Hash": "1716e201f81ced0f456dd5ec85fe20f8" + }, + "SQUAREM": { + "Package": "SQUAREM", + "Version": "2021.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "0cf10dab0d023d5b46a5a14387556891" + }, + "Seurat": { + "Package": "Seurat", + "Version": "5.0.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "KernSmooth", + "MASS", + "Matrix", + "R", + "RANN", + "RColorBrewer", + "ROCR", + "RSpectra", + "Rcpp", + "RcppAnnoy", + "RcppEigen", + "RcppHNSW", + "RcppProgress", + "Rtsne", + "SeuratObject", + "cluster", + "cowplot", + "fastDummies", + "fitdistrplus", + "future", + "future.apply", + "generics", + "ggplot2", + "ggrepel", + "ggridges", + "grDevices", + "graphics", + "grid", + "httr", + "ica", + "igraph", + "irlba", + "jsonlite", + "leiden", + "lifecycle", + "lmtest", + "matrixStats", + "methods", + "miniUI", + "patchwork", + "pbapply", + "plotly", + "png", + "progressr", + "purrr", + "reticulate", + "rlang", + "scales", + "scattermore", + "sctransform", + "shiny", + "spatstat.explore", + "spatstat.geom", + "stats", + "tibble", + "tools", + "utils", + "uwot" + ], + "Hash": "f5325a968489ef65254a51d74dc0c520" + }, + "SeuratObject": { + "Package": "SeuratObject", + "Version": "5.0.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "Rcpp", + "RcppEigen", + "future", + "future.apply", + "generics", + "grDevices", + "grid", + "lifecycle", + "methods", + "progressr", + "rlang", + "sp", + "spam", + "stats", + "tools", + "utils" + ], + "Hash": "424c2b9e50b053c86fc38f17e09917da" + }, + "SoupX": { + "Package": "SoupX", + "Version": "1.6.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "Seurat", + "ggplot2", + "methods" + ], + "Hash": "6fc80c34fe3ded25ba2d9e2b53e8da4f" + }, + "SparseM": { + "Package": "SparseM", + "Version": "1.81", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "graphics", + "methods", + "stats", + "utils" + ], + "Hash": "2042cd9759cc89a453c4aefef0ce9aae" + }, + "VGAM": { + "Package": "VGAM", + "Version": "1.1-11", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "methods", + "splines", + "stats", + "stats4" + ], + "Hash": "0a347b0c06e87ad505699b7a6290abd2" + }, + "WRS2": { + "Package": "WRS2", + "Version": "1.1-6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "R", + "grDevices", + "graphics", + "plyr", + "reshape", + "stats", + "utils" + ], + "Hash": "3648bc27fea147478025db1ebaec8b95" + }, + "abind": { + "Package": "abind", + "Version": "1.4-5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "methods", + "utils" + ], + "Hash": "4f57884290cc75ab22f4af9e9d4ca862" + }, + "askpass": { + "Package": "askpass", + "Version": "1.2.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "sys" + ], + "Hash": "cad6cf7f1d5f6e906700b9d3e718c796" + }, + "backports": { + "Package": "backports", + "Version": "1.4.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "c39fbec8a30d23e721980b8afb31984c" + }, + "base64enc": { + "Package": "base64enc", + "Version": "0.1-3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "543776ae6848fde2f48ff3816d0628bc" + }, + "bestNormalize": { + "Package": "bestNormalize", + "Version": "1.9.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "LambertW", + "R", + "butcher", + "doParallel", + "doRNG", + "dplyr", + "foreach", + "generics", + "methods", + "nortest", + "purrr", + "recipes", + "tibble" + ], + "Hash": "f1d5b9ec47911d8a0c15d35245a8f38e" + }, + "bit": { + "Package": "bit", + "Version": "4.0.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "d242abec29412ce988848d0294b208fd" + }, + "bit64": { + "Package": "bit64", + "Version": "4.0.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "bit", + "methods", + "stats", + "utils" + ], + "Hash": "9fe98599ca456d6552421db0d6772d8f" + }, + "bitops": { + "Package": "bitops", + "Version": "1.0-7", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "b7d8d8ee39869c18d8846a184dd8a1af" + }, + "blob": { + "Package": "blob", + "Version": "1.2.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "methods", + "rlang", + "vctrs" + ], + "Hash": "40415719b5a479b87949f3aa0aee737c" + }, + "boot": { + "Package": "boot", + "Version": "1.3-30", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "graphics", + "stats" + ], + "Hash": "96abeed416a286d4a0f52e550b612343" + }, + "brew": { + "Package": "brew", + "Version": "1.0-10", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "8f4a384e19dccd8c65356dc096847b76" + }, + "brio": { + "Package": "brio", + "Version": "1.1.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "68bd2b066e1fe780bbf62fc8bcc36de3" + }, + "broom": { + "Package": "broom", + "Version": "1.0.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "backports", + "dplyr", + "ellipsis", + "generics", + "glue", + "lifecycle", + "purrr", + "rlang", + "stringr", + "tibble", + "tidyr" + ], + "Hash": "fd25391c3c4f6ecf0fa95f1e6d15378c" + }, + "bslib": { + "Package": "bslib", + "Version": "0.7.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "base64enc", + "cachem", + "fastmap", + "grDevices", + "htmltools", + "jquerylib", + "jsonlite", + "lifecycle", + "memoise", + "mime", + "rlang", + "sass" + ], + "Hash": "8644cc53f43828f19133548195d7e59e" + }, + "butcher": { + "Package": "butcher", + "Version": "0.3.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "lobstr", + "methods", + "purrr", + "rlang", + "tibble", + "utils", + "vctrs" + ], + "Hash": "951e96dd017c1cbf446bbd7d94d5fb6f" + }, + "caTools": { + "Package": "caTools", + "Version": "1.18.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "bitops" + ], + "Hash": "34d90fa5845004236b9eacafc51d07b2" + }, + "cachem": { + "Package": "cachem", + "Version": "1.0.8", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "fastmap", + "rlang" + ], + "Hash": "c35768291560ce302c0a6589f92e837d" + }, + "callr": { + "Package": "callr", + "Version": "3.7.6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "processx", + "utils" + ], + "Hash": "d7e13f49c19103ece9e58ad2d83a7354" + }, + "car": { + "Package": "car", + "Version": "3.1-2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "R", + "abind", + "carData", + "grDevices", + "graphics", + "lme4", + "mgcv", + "nlme", + "nnet", + "pbkrtest", + "quantreg", + "scales", + "stats", + "utils" + ], + "Hash": "839b351f31d56e0147439eb22c00a66a" + }, + "carData": { + "Package": "carData", + "Version": "3.0-5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "ac6cdb8552c61bd36b0e54d07cf2aab7" + }, + "cellranger": { + "Package": "cellranger", + "Version": "1.1.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "rematch", + "tibble" + ], + "Hash": "f61dbaec772ccd2e17705c1e872e9e7c" + }, + "class": { + "Package": "class", + "Version": "7.3-22", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "R", + "stats", + "utils" + ], + "Hash": "f91f6b29f38b8c280f2b9477787d4bb2" + }, + "cli": { + "Package": "cli", + "Version": "3.6.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "utils" + ], + "Hash": "1216ac65ac55ec0058a6f75d7ca0fd52" + }, + "clipr": { + "Package": "clipr", + "Version": "0.8.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "utils" + ], + "Hash": "3f038e5ac7f41d4ac41ce658c85e3042" + }, + "clock": { + "Package": "clock", + "Version": "0.7.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "cpp11", + "lifecycle", + "rlang", + "tzdb", + "vctrs" + ], + "Hash": "3d8a84cdf9f6f8564531c49b70f3833d" + }, + "cluster": { + "Package": "cluster", + "Version": "2.1.6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics", + "stats", + "utils" + ], + "Hash": "0aaa05204035dc43ea0004b9c76611dd" + }, + "codetools": { + "Package": "codetools", + "Version": "0.2-20", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "61e097f35917d342622f21cdc79c256e" + }, + "collections": { + "Package": "collections", + "Version": "0.3.7", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "90a0eda114ab0bef170ddbf5ef0cd93f" + }, + "colorspace": { + "Package": "colorspace", + "Version": "2.1-0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics", + "methods", + "stats" + ], + "Hash": "f20c47fd52fae58b4e377c37bb8c335b" + }, + "commonmark": { + "Package": "commonmark", + "Version": "1.9.1", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "5d8225445acb167abf7797de48b2ee3c" + }, + "conflicted": { + "Package": "conflicted", + "Version": "1.2.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "memoise", + "rlang" + ], + "Hash": "bb097fccb22d156624fd07cd2894ddb6" + }, + "corrplot": { + "Package": "corrplot", + "Version": "0.92", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "fcf11a91936fd5047b2ee9bc00595e36" + }, + "cowplot": { + "Package": "cowplot", + "Version": "1.1.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "ggplot2", + "grDevices", + "grid", + "gtable", + "methods", + "rlang", + "scales" + ], + "Hash": "8ef2084dd7d28847b374e55440e4f8cb" + }, + "cpp11": { + "Package": "cpp11", + "Version": "0.4.7", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "5a295d7d963cc5035284dcdbaf334f4e" + }, + "crayon": { + "Package": "crayon", + "Version": "1.5.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "grDevices", + "methods", + "utils" + ], + "Hash": "e8a1e41acf02548751f45c718d55aa6a" + }, + "crosstalk": { + "Package": "crosstalk", + "Version": "1.2.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R6", + "htmltools", + "jsonlite", + "lazyeval" + ], + "Hash": "ab12c7b080a57475248a30f4db6298c0" + }, + "curl": { + "Package": "curl", + "Version": "5.2.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "411ca2c03b1ce5f548345d2fc2685f7a" + }, + "cyclocomp": { + "Package": "cyclocomp", + "Version": "1.1.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "callr", + "crayon", + "desc", + "remotes", + "withr" + ], + "Hash": "cdc4a473222b0112d4df0bcfbed12d44" + }, + "cytolib": { + "Package": "cytolib", + "Version": "2.14.1", + "Source": "Bioconductor", + "Repository": "Bioconductor 3.18", + "Requirements": [ + "BH", + "R", + "RProtoBufLib", + "Rhdf5lib" + ], + "Hash": "62071794414abc3661aac7a7986ebb4e" + }, + "data.table": { + "Package": "data.table", + "Version": "1.15.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "methods" + ], + "Hash": "8ee9ac56ef633d0c7cab8b2ca87d683e" + }, + "datathin": { + "Package": "datathin", + "Version": "1.0", + "Source": "GitHub", + "RemoteType": "github", + "RemoteHost": "api.github.com", + "RemoteUsername": "anna-neufeld", + "RemoteRepo": "datathin", + "RemoteRef": "main", + "RemoteSha": "58eb154609365fa7301ea0fa397fbf04dd8c28ed", + "Requirements": [ + "R", + "VGAM", + "extraDistr", + "knitr", + "mvtnorm" + ], + "Hash": "176531b6bf79daada66910cacb6a9be9" + }, + "datawizard": { + "Package": "datawizard", + "Version": "0.10.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "insight", + "stats", + "utils" + ], + "Hash": "62d6ec10346d3302a1299e1c54641d83" + }, + "dbplyr": { + "Package": "dbplyr", + "Version": "2.5.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "DBI", + "R", + "R6", + "blob", + "cli", + "dplyr", + "glue", + "lifecycle", + "magrittr", + "methods", + "pillar", + "purrr", + "rlang", + "tibble", + "tidyr", + "tidyselect", + "utils", + "vctrs", + "withr" + ], + "Hash": "39b2e002522bfd258039ee4e889e0fd1" + }, + "deldir": { + "Package": "deldir", + "Version": "2.0-4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics" + ], + "Hash": "24754fce82729ff85317dd195b6646a8" + }, + "desc": { + "Package": "desc", + "Version": "1.4.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "cli", + "utils" + ], + "Hash": "99b79fcbd6c4d1ce087f5c5c758b384f" + }, + "diagram": { + "Package": "diagram", + "Version": "1.6.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "graphics", + "shape", + "stats" + ], + "Hash": "c7f527c59edc72c4bce63519b8d38752" + }, + "dials": { + "Package": "dials", + "Version": "1.2.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "DiceDesign", + "R", + "cli", + "dplyr", + "glue", + "hardhat", + "lifecycle", + "pillar", + "purrr", + "rlang", + "scales", + "tibble", + "utils", + "vctrs", + "withr" + ], + "Hash": "999e5fa12058a2bb3a8c204e637e4707" + }, + "dichromat": { + "Package": "dichromat", + "Version": "2.0-0.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "stats" + ], + "Hash": "16e66f2a483e124af5fc6582d26005f7" + }, + "diffobj": { + "Package": "diffobj", + "Version": "0.3.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "crayon", + "methods", + "stats", + "tools", + "utils" + ], + "Hash": "bcaa8b95f8d7d01a5dedfd959ce88ab8" + }, + "digest": { + "Package": "digest", + "Version": "0.6.35", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "utils" + ], + "Hash": "698ece7ba5a4fa4559e3d537e7ec3d31" + }, + "doFuture": { + "Package": "doFuture", + "Version": "1.0.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "foreach", + "future", + "future.apply", + "globals", + "iterators", + "parallel", + "utils" + ], + "Hash": "bd269daa182b205fa471c89ee9dcc8df" + }, + "doMC": { + "Package": "doMC", + "Version": "1.3.8", + "Source": "Repository", + "Repository": "RSPM", + "OS_type": "unix", + "Requirements": [ + "R", + "foreach", + "iterators", + "parallel", + "utils" + ], + "Hash": "daafe209e13c4fd20f2190a94f2f2103" + }, + "doParallel": { + "Package": "doParallel", + "Version": "1.0.17", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "foreach", + "iterators", + "parallel", + "utils" + ], + "Hash": "451e5edf411987991ab6a5410c45011f" + }, + "doRNG": { + "Package": "doRNG", + "Version": "1.8.6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "foreach", + "iterators", + "rngtools", + "stats", + "utils" + ], + "Hash": "e207fea8a4991e49c7244001746e3232" + }, + "dotCall64": { + "Package": "dotCall64", + "Version": "1.1-1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "80f374ef8500fcdc5d84a0345b837227" + }, + "dplyr": { + "Package": "dplyr", + "Version": "1.1.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "cli", + "generics", + "glue", + "lifecycle", + "magrittr", + "methods", + "pillar", + "rlang", + "tibble", + "tidyselect", + "utils", + "vctrs" + ], + "Hash": "fedd9d00c2944ff00a0e2696ccf048ec" + }, + "dqrng": { + "Package": "dqrng", + "Version": "0.3.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "BH", + "R", + "Rcpp", + "sitmo" + ], + "Hash": "824df2aeba88d701df5e79018b35b815" + }, + "dtplyr": { + "Package": "dtplyr", + "Version": "1.3.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "data.table", + "dplyr", + "glue", + "lifecycle", + "rlang", + "tibble", + "tidyselect", + "vctrs" + ], + "Hash": "54ed3ea01b11e81a86544faaecfef8e2" + }, + "ellipsis": { + "Package": "ellipsis", + "Version": "0.3.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "rlang" + ], + "Hash": "bb0eec2fe32e88d9e2836c2f73ea2077" + }, + "emmeans": { + "Package": "emmeans", + "Version": "1.10.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "estimability", + "graphics", + "methods", + "mvtnorm", + "numDeriv", + "stats", + "utils" + ], + "Hash": "4445298c65c50bcb7d33b687e69bb0bd" + }, + "estimability": { + "Package": "estimability", + "Version": "1.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "stats" + ], + "Hash": "0d5f495f1edc281fca2510d8dabcba0f" + }, + "evaluate": { + "Package": "evaluate", + "Version": "0.23", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "methods" + ], + "Hash": "daf4a1246be12c1fa8c7705a0935c1a0" + }, + "exactRankTests": { + "Package": "exactRankTests", + "Version": "0.8-35", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "stats", + "utils" + ], + "Hash": "790c46974d99ff51442f4d134b2d70eb" + }, + "extraDistr": { + "Package": "extraDistr", + "Version": "1.10.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp" + ], + "Hash": "49235792aad38657fffef40802f614c5" + }, + "fansi": { + "Package": "fansi", + "Version": "1.0.6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "utils" + ], + "Hash": "962174cf2aeb5b9eea581522286a911f" + }, + "farver": { + "Package": "farver", + "Version": "2.1.1", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "8106d78941f34855c440ddb946b8f7a5" + }, + "fastDummies": { + "Package": "fastDummies", + "Version": "1.7.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "data.table", + "stringr", + "tibble" + ], + "Hash": "e0f9c0c051e0e8d89996d7f0c400539f" + }, + "fastmap": { + "Package": "fastmap", + "Version": "1.1.1", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "f7736a18de97dea803bde0a2daaafb27" + }, + "finetune": { + "Package": "finetune", + "Version": "1.2.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "dials", + "dplyr", + "ggplot2", + "parsnip", + "purrr", + "rlang", + "tibble", + "tidyr", + "tidyselect", + "tune", + "utils", + "vctrs", + "workflows" + ], + "Hash": "3abf52a3d5cfd55269f5d765b340a794" + }, + "fitdistrplus": { + "Package": "fitdistrplus", + "Version": "1.1-11", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "R", + "grDevices", + "methods", + "stats", + "survival" + ], + "Hash": "f40ef9686e85681a1ccbf33d9236aeb9" + }, + "flowCore": { + "Package": "flowCore", + "Version": "2.14.2", + "Source": "Bioconductor", + "Repository": "Bioconductor 3.18", + "Requirements": [ + "BH", + "Biobase", + "BiocGenerics", + "R", + "RProtoBufLib", + "Rcpp", + "S4Vectors", + "cpp11", + "cytolib", + "grDevices", + "graphics", + "matrixStats", + "methods", + "stats", + "stats4", + "utils" + ], + "Hash": "f90ca1dae2bc4bbfd38c826a7ddff0d1" + }, + "fontawesome": { + "Package": "fontawesome", + "Version": "0.5.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "htmltools", + "rlang" + ], + "Hash": "c2efdd5f0bcd1ea861c2d4e2a883a67d" + }, + "forcats": { + "Package": "forcats", + "Version": "1.0.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "glue", + "lifecycle", + "magrittr", + "rlang", + "tibble" + ], + "Hash": "1a0a9a3d5083d0d573c4214576f1e690" + }, + "foreach": { + "Package": "foreach", + "Version": "1.5.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "codetools", + "iterators", + "utils" + ], + "Hash": "618609b42c9406731ead03adf5379850" + }, + "fs": { + "Package": "fs", + "Version": "1.6.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "methods" + ], + "Hash": "47b5f30c720c23999b913a1a635cf0bb" + }, + "furrr": { + "Package": "furrr", + "Version": "0.3.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "future", + "globals", + "lifecycle", + "purrr", + "rlang", + "vctrs" + ], + "Hash": "da7a4c32196cb2262a41dd5a25d486ff" + }, + "future": { + "Package": "future", + "Version": "1.33.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "digest", + "globals", + "listenv", + "parallel", + "parallelly", + "utils" + ], + "Hash": "fd7b1d69d16d0d114e4fa82db68f184c" + }, + "future.apply": { + "Package": "future.apply", + "Version": "1.11.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "future", + "globals", + "parallel", + "utils" + ], + "Hash": "afe1507511629f44572e6c53b9baeb7c" + }, + "fuzzyjoin": { + "Package": "fuzzyjoin", + "Version": "0.1.6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "dplyr", + "geosphere", + "purrr", + "stringdist", + "stringr", + "tibble", + "tidyr" + ], + "Hash": "24af5fc67dbeaac6d776a8e6630aacd9" + }, + "gargle": { + "Package": "gargle", + "Version": "1.5.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "fs", + "glue", + "httr", + "jsonlite", + "lifecycle", + "openssl", + "rappdirs", + "rlang", + "stats", + "utils", + "withr" + ], + "Hash": "fc0b272e5847c58cd5da9b20eedbd026" + }, + "generics": { + "Package": "generics", + "Version": "0.1.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "methods" + ], + "Hash": "15e9634c0fcd294799e9b2e929ed1b86" + }, + "geosphere": { + "Package": "geosphere", + "Version": "1.5-18", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp", + "sp" + ], + "Hash": "45aa4def70a402e7d20efde490c13ecb" + }, + "ggplot2": { + "Package": "ggplot2", + "Version": "3.5.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "R", + "cli", + "glue", + "grDevices", + "grid", + "gtable", + "isoband", + "lifecycle", + "mgcv", + "rlang", + "scales", + "stats", + "tibble", + "vctrs", + "withr" + ], + "Hash": "44c6a2f8202d5b7e878ea274b1092426" + }, + "ggpubr": { + "Package": "ggpubr", + "Version": "0.6.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cowplot", + "dplyr", + "ggplot2", + "ggrepel", + "ggsci", + "ggsignif", + "glue", + "grid", + "gridExtra", + "magrittr", + "polynom", + "purrr", + "rlang", + "rstatix", + "scales", + "stats", + "tibble", + "tidyr", + "utils" + ], + "Hash": "c957612b8bb1ee9ab7b2450d26663e7e" + }, + "ggrepel": { + "Package": "ggrepel", + "Version": "0.9.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp", + "ggplot2", + "grid", + "rlang", + "scales", + "withr" + ], + "Hash": "cc3361e234c4a5050e29697d675764aa" + }, + "ggridges": { + "Package": "ggridges", + "Version": "0.5.6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "ggplot2", + "grid", + "scales", + "withr" + ], + "Hash": "66488692cb8621bc78df1b9b819497a6" + }, + "ggsci": { + "Package": "ggsci", + "Version": "3.2.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "ggplot2", + "grDevices", + "scales" + ], + "Hash": "0c3268cddf4d3a3ce4e7e6330f8e92c8" + }, + "ggsignif": { + "Package": "ggsignif", + "Version": "0.6.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "ggplot2" + ], + "Hash": "a57f0f5dbcfd0d77ad4ff33032f5dc79" + }, + "ggtext": { + "Package": "ggtext", + "Version": "0.1.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "ggplot2", + "grid", + "gridtext", + "rlang", + "scales" + ], + "Hash": "c5ba8f5056487403a299b91984be86ca" + }, + "glmnet": { + "Package": "glmnet", + "Version": "4.1-8", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "Rcpp", + "RcppEigen", + "foreach", + "methods", + "shape", + "survival", + "utils" + ], + "Hash": "eb6fc70e561aae41d5911a6726188f71" + }, + "globals": { + "Package": "globals", + "Version": "0.16.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "codetools" + ], + "Hash": "2580567908cafd4f187c1e5a91e98b7f" + }, + "glue": { + "Package": "glue", + "Version": "1.7.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "methods" + ], + "Hash": "e0b3a53876554bd45879e596cdb10a52" + }, + "goftest": { + "Package": "goftest", + "Version": "1.2-3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "stats" + ], + "Hash": "dbe0201f91eeb15918dd3fbf01ee689a" + }, + "googledrive": { + "Package": "googledrive", + "Version": "2.1.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "gargle", + "glue", + "httr", + "jsonlite", + "lifecycle", + "magrittr", + "pillar", + "purrr", + "rlang", + "tibble", + "utils", + "uuid", + "vctrs", + "withr" + ], + "Hash": "e99641edef03e2a5e87f0a0b1fcc97f4" + }, + "googlesheets4": { + "Package": "googlesheets4", + "Version": "1.1.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cellranger", + "cli", + "curl", + "gargle", + "glue", + "googledrive", + "httr", + "ids", + "lifecycle", + "magrittr", + "methods", + "purrr", + "rematch2", + "rlang", + "tibble", + "utils", + "vctrs", + "withr" + ], + "Hash": "d6db1667059d027da730decdc214b959" + }, + "gower": { + "Package": "gower", + "Version": "1.0.1", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "7a0051eef852c301b5efe2f7913dd45f" + }, + "gplots": { + "Package": "gplots", + "Version": "3.1.3.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "KernSmooth", + "R", + "caTools", + "gtools", + "methods", + "stats" + ], + "Hash": "f72b5d1ed587f8905e38ee7295e88d80" + }, + "gridExtra": { + "Package": "gridExtra", + "Version": "2.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "grDevices", + "graphics", + "grid", + "gtable", + "utils" + ], + "Hash": "7d7f283939f563670a697165b2cf5560" + }, + "gridtext": { + "Package": "gridtext", + "Version": "0.1.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp", + "curl", + "grDevices", + "grid", + "jpeg", + "markdown", + "png", + "rlang", + "stringr", + "xml2" + ], + "Hash": "05e4f5fffb1eecfeaac9ea0b7f255fef" + }, + "gtable": { + "Package": "gtable", + "Version": "0.3.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "glue", + "grid", + "lifecycle", + "rlang" + ], + "Hash": "e18861963cbc65a27736e02b3cd3c4a0" + }, + "gtools": { + "Package": "gtools", + "Version": "3.9.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "methods", + "stats", + "utils" + ], + "Hash": "588d091c35389f1f4a9d533c8d709b35" + }, + "hardhat": { + "Package": "hardhat", + "Version": "1.3.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "glue", + "rlang", + "tibble", + "vctrs" + ], + "Hash": "921fd010cd788de75a9c71c2c3aee1f2" + }, + "haven": { + "Package": "haven", + "Version": "2.5.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "cpp11", + "forcats", + "hms", + "lifecycle", + "methods", + "readr", + "rlang", + "tibble", + "tidyselect", + "vctrs" + ], + "Hash": "9171f898db9d9c4c1b2c745adc2c1ef1" + }, + "here": { + "Package": "here", + "Version": "1.0.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "rprojroot" + ], + "Hash": "24b224366f9c2e7534d2344d10d59211" + }, + "highr": { + "Package": "highr", + "Version": "0.10", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "xfun" + ], + "Hash": "06230136b2d2b9ba5805e1963fa6e890" + }, + "hms": { + "Package": "hms", + "Version": "1.1.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "lifecycle", + "methods", + "pkgconfig", + "rlang", + "vctrs" + ], + "Hash": "b59377caa7ed00fa41808342002138f9" + }, + "htmltools": { + "Package": "htmltools", + "Version": "0.5.8.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "base64enc", + "digest", + "fastmap", + "grDevices", + "rlang", + "utils" + ], + "Hash": "81d371a9cc60640e74e4ab6ac46dcedc" + }, + "htmlwidgets": { + "Package": "htmlwidgets", + "Version": "1.6.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "grDevices", + "htmltools", + "jsonlite", + "knitr", + "rmarkdown", + "yaml" + ], + "Hash": "04291cc45198225444a397606810ac37" + }, + "httpgd": { + "Package": "httpgd", + "Version": "2.0.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "AsioHeaders", + "R", + "cpp11", + "unigd" + ], + "Hash": "c30fb41ccc97f7797735633dccb9fcae" + }, + "httpuv": { + "Package": "httpuv", + "Version": "1.6.15", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "Rcpp", + "later", + "promises", + "utils" + ], + "Hash": "d55aa087c47a63ead0f6fc10f8fa1ee0" + }, + "httr": { + "Package": "httr", + "Version": "1.4.7", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "curl", + "jsonlite", + "mime", + "openssl" + ], + "Hash": "ac107251d9d9fd72f0ca8049988f1d7f" + }, + "ica": { + "Package": "ica", + "Version": "1.0-3", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "d9b52ced14e24a0e69e228c20eb5eb27" + }, + "ids": { + "Package": "ids", + "Version": "1.0.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "openssl", + "uuid" + ], + "Hash": "99df65cfef20e525ed38c3d2577f7190" + }, + "igraph": { + "Package": "igraph", + "Version": "2.0.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "cli", + "cpp11", + "grDevices", + "graphics", + "lifecycle", + "magrittr", + "methods", + "pkgconfig", + "rlang", + "stats", + "utils", + "vctrs" + ], + "Hash": "c3b7d801d722e26e4cd888e042bf9af5" + }, + "infer": { + "Package": "infer", + "Version": "1.0.7", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "broom", + "cli", + "dplyr", + "generics", + "ggplot2", + "glue", + "grDevices", + "lifecycle", + "magrittr", + "methods", + "patchwork", + "purrr", + "rlang", + "tibble", + "tidyr", + "vctrs" + ], + "Hash": "8d30ac9c5e21efd8575f934bdb5c3029" + }, + "insight": { + "Package": "insight", + "Version": "0.19.10", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "methods", + "stats", + "utils" + ], + "Hash": "c15a38c9655cba66f5f5537a14c1bef4" + }, + "ipred": { + "Package": "ipred", + "Version": "0.9-14", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "R", + "class", + "nnet", + "prodlim", + "rpart", + "survival" + ], + "Hash": "b25a108cbf4834be7c1b1f46ff30f888" + }, + "irlba": { + "Package": "irlba", + "Version": "2.3.5.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "methods", + "stats" + ], + "Hash": "acb06a47b732c6251afd16e19c3201ff" + }, + "isoband": { + "Package": "isoband", + "Version": "0.2.7", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "grid", + "utils" + ], + "Hash": "0080607b4a1a7b28979aecef976d8bc2" + }, + "iterators": { + "Package": "iterators", + "Version": "1.0.14", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "utils" + ], + "Hash": "8954069286b4b2b0d023d1b288dce978" + }, + "janitor": { + "Package": "janitor", + "Version": "2.2.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "dplyr", + "hms", + "lifecycle", + "lubridate", + "magrittr", + "purrr", + "rlang", + "snakecase", + "stringi", + "stringr", + "tidyr", + "tidyselect" + ], + "Hash": "5baae149f1082f466df9d1442ba7aa65" + }, + "jomo": { + "Package": "jomo", + "Version": "2.7-6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "lme4", + "ordinal", + "stats", + "survival", + "tibble" + ], + "Hash": "74c00eaba35b9631d1656e84585bb6aa" + }, + "jpeg": { + "Package": "jpeg", + "Version": "0.1-10", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "031a0b683d001a7519202f0628fc0358" + }, + "jquerylib": { + "Package": "jquerylib", + "Version": "0.1.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "htmltools" + ], + "Hash": "5aab57a3bd297eee1c1d862735972182" + }, + "jsonlite": { + "Package": "jsonlite", + "Version": "1.8.8", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "methods" + ], + "Hash": "e1b9c55281c5adc4dd113652d9e26768" + }, + "km.ci": { + "Package": "km.ci", + "Version": "0.5-6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "stats", + "survival" + ], + "Hash": "41d857f78edf8f5db59608b6a42b6005" + }, + "knitr": { + "Package": "knitr", + "Version": "1.46", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "evaluate", + "highr", + "methods", + "tools", + "xfun", + "yaml" + ], + "Hash": "6e008ab1d696a5283c79765fa7b56b47" + }, + "labeling": { + "Package": "labeling", + "Version": "0.4.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "graphics", + "stats" + ], + "Hash": "b64ec208ac5bc1852b285f665d6368b3" + }, + "lamW": { + "Package": "lamW", + "Version": "2.2.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Rcpp", + "RcppParallel" + ], + "Hash": "98e671a8a8832e8a3e48f87b41142765" + }, + "languageserver": { + "Package": "languageserver", + "Version": "0.3.16", + "Source": "Repository", + "Repository": "https://reditorsupport.r-universe.dev", + "Requirements": [ + "R", + "R6", + "callr", + "collections", + "fs", + "jsonlite", + "lintr", + "parallel", + "roxygen2", + "stringi", + "styler", + "tools", + "utils", + "xml2", + "xmlparsedata" + ], + "Hash": "f8901f44aedb6d7e7d03b5533986bd97" + }, + "later": { + "Package": "later", + "Version": "1.3.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Rcpp", + "rlang" + ], + "Hash": "a3e051d405326b8b0012377434c62b37" + }, + "lattice": { + "Package": "lattice", + "Version": "0.22-6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics", + "grid", + "stats", + "utils" + ], + "Hash": "cc5ac1ba4c238c7ca9fa6a87ca11a7e2" + }, + "lava": { + "Package": "lava", + "Version": "1.8.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "SQUAREM", + "cli", + "future.apply", + "grDevices", + "graphics", + "methods", + "numDeriv", + "progressr", + "stats", + "survival", + "utils" + ], + "Hash": "579303ca1e817d94cea694b319803380" + }, + "lazyeval": { + "Package": "lazyeval", + "Version": "0.2.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "d908914ae53b04d4c0c0fd72ecc35370" + }, + "leiden": { + "Package": "leiden", + "Version": "0.4.3.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "igraph", + "methods", + "reticulate" + ], + "Hash": "b21c4ae2bb7935504c42bcdf749c04e6" + }, + "lhs": { + "Package": "lhs", + "Version": "1.1.6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp" + ], + "Hash": "a007ff66aa9d478e220bf0493a7b1d95" + }, + "lifecycle": { + "Package": "lifecycle", + "Version": "1.0.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "glue", + "rlang" + ], + "Hash": "b8552d117e1b808b09a832f589b79035" + }, + "lintr": { + "Package": "lintr", + "Version": "3.1.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "backports", + "codetools", + "cyclocomp", + "digest", + "glue", + "knitr", + "rex", + "stats", + "utils", + "xml2", + "xmlparsedata" + ], + "Hash": "08cff46381a242d44c0d8dd0aabd9f71" + }, + "listenv": { + "Package": "listenv", + "Version": "0.9.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "e2fca3e12e4db979dccc6e519b10a7ee" + }, + "lme4": { + "Package": "lme4", + "Version": "1.1-35.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "Matrix", + "R", + "Rcpp", + "RcppEigen", + "boot", + "graphics", + "grid", + "lattice", + "methods", + "minqa", + "nlme", + "nloptr", + "parallel", + "splines", + "stats", + "utils" + ], + "Hash": "862f9d995f528f3051f524791955b20c" + }, + "lmtest": { + "Package": "lmtest", + "Version": "0.9-40", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "graphics", + "stats", + "zoo" + ], + "Hash": "c6fafa6cccb1e1dfe7f7d122efd6e6a7" + }, + "lobstr": { + "Package": "lobstr", + "Version": "1.1.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cpp11", + "crayon", + "methods", + "prettyunits", + "rlang" + ], + "Hash": "f2a94f8fc9db382a642e965339635ad6" + }, + "lubridate": { + "Package": "lubridate", + "Version": "1.9.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "generics", + "methods", + "timechange" + ], + "Hash": "680ad542fbcf801442c83a6ac5a2126c" + }, + "magrittr": { + "Package": "magrittr", + "Version": "2.0.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "7ce2733a9826b3aeb1775d56fd305472" + }, + "mapproj": { + "Package": "mapproj", + "Version": "1.2.11", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "graphics", + "maps", + "stats" + ], + "Hash": "37090866afbdb09e6437ba0b25c307a2" + }, + "maps": { + "Package": "maps", + "Version": "3.4.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "graphics", + "utils" + ], + "Hash": "5f7886e53a3b39d4a110c7bd7fce9164" + }, + "markdown": { + "Package": "markdown", + "Version": "1.13", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "commonmark", + "utils", + "xfun" + ], + "Hash": "074efab766a9d6360865ad39512f2a7e" + }, + "matrixStats": { + "Package": "matrixStats", + "Version": "1.3.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "4b3ea27a19d669c0405b38134d89a9d1" + }, + "maxstat": { + "Package": "maxstat", + "Version": "0.7-25", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "exactRankTests", + "graphics", + "mvtnorm", + "stats" + ], + "Hash": "c166f04bd2bbd830ab34b7329104c019" + }, + "mclust": { + "Package": "mclust", + "Version": "6.1.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics", + "stats", + "utils" + ], + "Hash": "aa9cfd45e2c3297213e270d000d80655" + }, + "memoise": { + "Package": "memoise", + "Version": "2.0.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "cachem", + "rlang" + ], + "Hash": "e2817ccf4a065c5d9d7f2cfbe7c1d78c" + }, + "mgcv": { + "Package": "mgcv", + "Version": "1.9-1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "graphics", + "methods", + "nlme", + "splines", + "stats", + "utils" + ], + "Hash": "110ee9d83b496279960e162ac97764ce" + }, + "mice": { + "Package": "mice", + "Version": "3.16.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp", + "broom", + "cpp11", + "dplyr", + "generics", + "glmnet", + "grDevices", + "graphics", + "lattice", + "methods", + "mitml", + "nnet", + "rlang", + "rpart", + "stats", + "tidyr", + "utils" + ], + "Hash": "da3b0891ad90d22484190996c4100f5e" + }, + "mime": { + "Package": "mime", + "Version": "0.12", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "tools" + ], + "Hash": "18e9c28c1d3ca1560ce30658b22ce104" + }, + "miniUI": { + "Package": "miniUI", + "Version": "0.1.1.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "htmltools", + "shiny", + "utils" + ], + "Hash": "fec5f52652d60615fdb3957b3d74324a" + }, + "minqa": { + "Package": "minqa", + "Version": "1.2.6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Rcpp" + ], + "Hash": "f48238f8d4740426ca12f53f27d004dd" + }, + "mitml": { + "Package": "mitml", + "Version": "0.4-5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "grDevices", + "graphics", + "haven", + "jomo", + "methods", + "pan", + "stats", + "utils" + ], + "Hash": "7664664bb3addc9fd13355952532ec59" + }, + "modeldata": { + "Package": "modeldata", + "Version": "1.3.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "R", + "dplyr", + "purrr", + "rlang", + "tibble" + ], + "Hash": "6ac8ee87ffebd14b29586fce684c14cc" + }, + "modelenv": { + "Package": "modelenv", + "Version": "0.1.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "glue", + "rlang", + "tibble", + "vctrs" + ], + "Hash": "fc2e59a68030885555c7be34ee7765a1" + }, + "modelr": { + "Package": "modelr", + "Version": "0.1.11", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "broom", + "magrittr", + "purrr", + "rlang", + "tibble", + "tidyr", + "tidyselect", + "vctrs" + ], + "Hash": "4f50122dc256b1b6996a4703fecea821" + }, + "munsell": { + "Package": "munsell", + "Version": "0.5.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "colorspace", + "methods" + ], + "Hash": "4fd8900853b746af55b81fda99da7695" + }, + "mvtnorm": { + "Package": "mvtnorm", + "Version": "1.2-5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "stats" + ], + "Hash": "4d1891e59ac7a12b4e7e8a69349125f1" + }, + "nlme": { + "Package": "nlme", + "Version": "3.1-164", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "graphics", + "lattice", + "stats", + "utils" + ], + "Hash": "a623a2239e642806158bc4dc3f51565d" + }, + "nloptr": { + "Package": "nloptr", + "Version": "2.0.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "testthat" + ], + "Hash": "277c67a08f358f42b6a77826e4492f79" + }, + "nnet": { + "Package": "nnet", + "Version": "7.3-19", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "stats", + "utils" + ], + "Hash": "2c797b46eea7fb58ede195bc0b1f1138" + }, + "nortest": { + "Package": "nortest", + "Version": "1.0-4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "stats" + ], + "Hash": "e587e7a30c737ad415590976481332e4" + }, + "numDeriv": { + "Package": "numDeriv", + "Version": "2016.8-1.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "df58958f293b166e4ab885ebcad90e02" + }, + "openssl": { + "Package": "openssl", + "Version": "2.1.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "askpass" + ], + "Hash": "ea2475b073243d9d338aa8f086ce973e" + }, + "ordinal": { + "Package": "ordinal", + "Version": "2023.12-4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "Matrix", + "R", + "methods", + "nlme", + "numDeriv", + "stats", + "ucminf" + ], + "Hash": "4ab0f16b08887630a9c96b8c33ed7b7d" + }, + "pals": { + "Package": "pals", + "Version": "1.8", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "colorspace", + "dichromat", + "grDevices", + "graphics", + "mapproj", + "maps", + "methods", + "stats" + ], + "Hash": "ee8ea3d5a65b3c00a2329e9c36115f13" + }, + "pan": { + "Package": "pan", + "Version": "1.9", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "495d032ad6bfc725f37ce89e3d6dadb2" + }, + "parallelly": { + "Package": "parallelly", + "Version": "1.37.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "parallel", + "tools", + "utils" + ], + "Hash": "5410df8d22bd36e616f2a2343dbb328c" + }, + "parsnip": { + "Package": "parsnip", + "Version": "1.2.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "dplyr", + "generics", + "ggplot2", + "globals", + "glue", + "hardhat", + "lifecycle", + "magrittr", + "pillar", + "prettyunits", + "purrr", + "rlang", + "stats", + "tibble", + "tidyr", + "utils", + "vctrs", + "withr" + ], + "Hash": "ace928adf616e06ece817d970faa2d03" + }, + "patchwork": { + "Package": "patchwork", + "Version": "1.2.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "cli", + "ggplot2", + "grDevices", + "graphics", + "grid", + "gtable", + "rlang", + "stats", + "utils" + ], + "Hash": "9c8ab14c00ac07e9e04d1664c0b74486" + }, + "pbapply": { + "Package": "pbapply", + "Version": "1.7-2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "parallel" + ], + "Hash": "68a2d681e10cf72f0afa1d84d45380e5" + }, + "pbkrtest": { + "Package": "pbkrtest", + "Version": "0.5.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "Matrix", + "R", + "broom", + "dplyr", + "lme4", + "methods", + "numDeriv", + "parallel" + ], + "Hash": "3b5b99f4d3f067bb9c1d59317d071370" + }, + "pheatmap": { + "Package": "pheatmap", + "Version": "1.0.12", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "RColorBrewer", + "grDevices", + "graphics", + "grid", + "gtable", + "scales", + "stats" + ], + "Hash": "db1fb0021811b6693741325bbe916e58" + }, + "pillar": { + "Package": "pillar", + "Version": "1.9.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "cli", + "fansi", + "glue", + "lifecycle", + "rlang", + "utf8", + "utils", + "vctrs" + ], + "Hash": "15da5a8412f317beeee6175fbc76f4bb" + }, + "pkgbuild": { + "Package": "pkgbuild", + "Version": "1.4.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "callr", + "cli", + "desc", + "processx" + ], + "Hash": "a29e8e134a460a01e0ca67a4763c595b" + }, + "pkgconfig": { + "Package": "pkgconfig", + "Version": "2.0.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "utils" + ], + "Hash": "01f28d4278f15c76cddbea05899c5d6f" + }, + "pkgload": { + "Package": "pkgload", + "Version": "1.3.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "crayon", + "desc", + "fs", + "glue", + "methods", + "pkgbuild", + "rlang", + "rprojroot", + "utils", + "withr" + ], + "Hash": "876c618df5ae610be84356d5d7a5d124" + }, + "plotly": { + "Package": "plotly", + "Version": "4.10.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "RColorBrewer", + "base64enc", + "crosstalk", + "data.table", + "digest", + "dplyr", + "ggplot2", + "htmltools", + "htmlwidgets", + "httr", + "jsonlite", + "lazyeval", + "magrittr", + "promises", + "purrr", + "rlang", + "scales", + "tibble", + "tidyr", + "tools", + "vctrs", + "viridisLite" + ], + "Hash": "a1ac5c03ad5ad12b9d1597e00e23c3dd" + }, + "plyr": { + "Package": "plyr", + "Version": "1.8.9", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp" + ], + "Hash": "6b8177fd19982f0020743fadbfdbd933" + }, + "png": { + "Package": "png", + "Version": "0.1-8", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "bd54ba8a0a5faded999a7aab6e46b374" + }, + "polyclip": { + "Package": "polyclip", + "Version": "1.10-6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "436542aadb70675e361cf359285af7c7" + }, + "polynom": { + "Package": "polynom", + "Version": "1.4-1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "graphics", + "stats" + ], + "Hash": "ceb5c2a59ba33d42d051285a3e8a5118" + }, + "praise": { + "Package": "praise", + "Version": "1.0.0", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "a555924add98c99d2f411e37e7d25e9f" + }, + "prettyunits": { + "Package": "prettyunits", + "Version": "1.2.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "6b01fc98b1e86c4f705ce9dcfd2f57c7" + }, + "processx": { + "Package": "processx", + "Version": "3.8.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "ps", + "utils" + ], + "Hash": "0c90a7d71988856bad2a2a45dd871bb9" + }, + "prodlim": { + "Package": "prodlim", + "Version": "2023.08.28", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "KernSmooth", + "R", + "Rcpp", + "data.table", + "diagram", + "grDevices", + "graphics", + "lava", + "stats", + "survival" + ], + "Hash": "c73e09a2039a0f75ac0a1e5454b39993" + }, + "progress": { + "Package": "progress", + "Version": "1.2.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "crayon", + "hms", + "prettyunits" + ], + "Hash": "f4625e061cb2865f111b47ff163a5ca6" + }, + "progressr": { + "Package": "progressr", + "Version": "0.14.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "digest", + "utils" + ], + "Hash": "ac50c4ffa8f6a46580dd4d7813add3c4" + }, + "promises": { + "Package": "promises", + "Version": "1.3.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R6", + "Rcpp", + "fastmap", + "later", + "magrittr", + "rlang", + "stats" + ], + "Hash": "434cd5388a3979e74be5c219bcd6e77d" + }, + "ps": { + "Package": "ps", + "Version": "1.7.6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "utils" + ], + "Hash": "dd2b9319ee0656c8acf45c7f40c59de7" + }, + "purrr": { + "Package": "purrr", + "Version": "1.0.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "lifecycle", + "magrittr", + "rlang", + "vctrs" + ], + "Hash": "1cba04a4e9414bdefc9dcaa99649a8dc" + }, + "qs": { + "Package": "qs", + "Version": "0.26.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "BH", + "R", + "RApiSerialize", + "Rcpp", + "stringfish" + ], + "Hash": "c0626a04f3021a24f05ab211280209ab" + }, + "quantreg": { + "Package": "quantreg", + "Version": "5.97", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "Matrix", + "MatrixModels", + "R", + "SparseM", + "graphics", + "methods", + "stats", + "survival" + ], + "Hash": "1bbc97f7d637ab3917c514a69047b2c1" + }, + "ragg": { + "Package": "ragg", + "Version": "1.3.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "systemfonts", + "textshaping" + ], + "Hash": "082e1a198e3329d571f4448ef0ede4bc" + }, + "rappdirs": { + "Package": "rappdirs", + "Version": "0.3.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "5e3c5dc0b071b21fa128676560dbe94d" + }, + "readr": { + "Package": "readr", + "Version": "2.1.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "cli", + "clipr", + "cpp11", + "crayon", + "hms", + "lifecycle", + "methods", + "rlang", + "tibble", + "tzdb", + "utils", + "vroom" + ], + "Hash": "9de96463d2117f6ac49980577939dfb3" + }, + "readxl": { + "Package": "readxl", + "Version": "1.4.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cellranger", + "cpp11", + "progress", + "tibble", + "utils" + ], + "Hash": "8cf9c239b96df1bbb133b74aef77ad0a" + }, + "recipes": { + "Package": "recipes", + "Version": "1.0.10", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "cli", + "clock", + "dplyr", + "ellipsis", + "generics", + "glue", + "gower", + "hardhat", + "ipred", + "lifecycle", + "lubridate", + "magrittr", + "purrr", + "rlang", + "stats", + "tibble", + "tidyr", + "tidyselect", + "timeDate", + "utils", + "vctrs", + "withr" + ], + "Hash": "69783cdd607c58fffb21c5c26c6ededf" + }, + "rematch": { + "Package": "rematch", + "Version": "2.0.0", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "cbff1b666c6fa6d21202f07e2318d4f1" + }, + "rematch2": { + "Package": "rematch2", + "Version": "2.1.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "tibble" + ], + "Hash": "76c9e04c712a05848ae7a23d2f170a40" + }, + "remotes": { + "Package": "remotes", + "Version": "2.5.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "methods", + "stats", + "tools", + "utils" + ], + "Hash": "3ee025083e66f18db6cf27b56e23e141" + }, + "renv": { + "Package": "renv", + "Version": "1.0.7", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "utils" + ], + "Hash": "397b7b2a265bc5a7a06852524dabae20" + }, + "repr": { + "Package": "repr", + "Version": "1.1.7", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "base64enc", + "grDevices", + "htmltools", + "jsonlite", + "pillar", + "utils" + ], + "Hash": "1393acc49816f4fe143d87fb33e75631" + }, + "reprex": { + "Package": "reprex", + "Version": "2.1.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "callr", + "cli", + "clipr", + "fs", + "glue", + "knitr", + "lifecycle", + "rlang", + "rmarkdown", + "rstudioapi", + "utils", + "withr" + ], + "Hash": "1425f91b4d5d9a8f25352c44a3d914ed" + }, + "reshape": { + "Package": "reshape", + "Version": "0.8.9", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "plyr" + ], + "Hash": "603d56041d7d4fa3ceb1864b3f6ee6b1" + }, + "reshape2": { + "Package": "reshape2", + "Version": "1.4.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp", + "plyr", + "stringr" + ], + "Hash": "bb5996d0bd962d214a11140d77589917" + }, + "reticulate": { + "Package": "reticulate", + "Version": "1.36.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "Rcpp", + "RcppTOML", + "graphics", + "here", + "jsonlite", + "methods", + "png", + "rappdirs", + "rlang", + "utils", + "withr" + ], + "Hash": "e037fb5dc364efdaf616eb6bc05aaca2" + }, + "rex": { + "Package": "rex", + "Version": "1.2.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "lazyeval" + ], + "Hash": "ae34cd56890607370665bee5bd17812f" + }, + "rlang": { + "Package": "rlang", + "Version": "1.1.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "utils" + ], + "Hash": "42548638fae05fd9a9b5f3f437fbbbe2" + }, + "rmarkdown": { + "Package": "rmarkdown", + "Version": "2.26", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "bslib", + "evaluate", + "fontawesome", + "htmltools", + "jquerylib", + "jsonlite", + "knitr", + "methods", + "tinytex", + "tools", + "utils", + "xfun", + "yaml" + ], + "Hash": "9b148e7f95d33aac01f31282d49e4f44" + }, + "rngtools": { + "Package": "rngtools", + "Version": "1.5.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "digest", + "methods", + "parallel", + "stats", + "utils" + ], + "Hash": "367a915f939520767660671efa0e32bd" + }, + "roxygen2": { + "Package": "roxygen2", + "Version": "7.3.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "brew", + "cli", + "commonmark", + "cpp11", + "desc", + "knitr", + "methods", + "pkgload", + "purrr", + "rlang", + "stringi", + "stringr", + "utils", + "withr", + "xml2" + ], + "Hash": "6ee25f9054a70f44d615300ed531ba8d" + }, + "rpart": { + "Package": "rpart", + "Version": "4.1.23", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics", + "stats" + ], + "Hash": "b3d390424f41d04174cccf84d49676c2" + }, + "rprojroot": { + "Package": "rprojroot", + "Version": "2.0.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "4c8415e0ec1e29f3f4f6fc108bef0144" + }, + "rsample": { + "Package": "rsample", + "Version": "1.2.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "dplyr", + "furrr", + "generics", + "glue", + "lifecycle", + "methods", + "pillar", + "purrr", + "rlang", + "slider", + "tibble", + "tidyr", + "tidyselect", + "vctrs" + ], + "Hash": "95e0f11d79a7494919c14aa4d8e9e177" + }, + "rstatix": { + "Package": "rstatix", + "Version": "0.7.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "broom", + "car", + "corrplot", + "dplyr", + "generics", + "magrittr", + "purrr", + "rlang", + "stats", + "tibble", + "tidyr", + "tidyselect", + "utils" + ], + "Hash": "5045fbb71b143878d8c51975d1d7d56d" + }, + "rstudioapi": { + "Package": "rstudioapi", + "Version": "0.16.0", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "96710351d642b70e8f02ddeb237c46a7" + }, + "rvest": { + "Package": "rvest", + "Version": "1.0.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "glue", + "httr", + "lifecycle", + "magrittr", + "rlang", + "selectr", + "tibble", + "xml2" + ], + "Hash": "0bcf0c6f274e90ea314b812a6d19a519" + }, + "sass": { + "Package": "sass", + "Version": "0.4.9", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R6", + "fs", + "htmltools", + "rappdirs", + "rlang" + ], + "Hash": "d53dbfddf695303ea4ad66f86e99b95d" + }, + "scales": { + "Package": "scales", + "Version": "1.3.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "RColorBrewer", + "cli", + "farver", + "glue", + "labeling", + "lifecycle", + "munsell", + "rlang", + "viridisLite" + ], + "Hash": "c19df082ba346b0ffa6f833e92de34d1" + }, + "scattermore": { + "Package": "scattermore", + "Version": "1.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "ggplot2", + "grDevices", + "graphics", + "grid", + "scales" + ], + "Hash": "d316e4abb854dd1677f7bd3ad08bc4e8" + }, + "scatterplot3d": { + "Package": "scatterplot3d", + "Version": "0.3-44", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics", + "stats" + ], + "Hash": "10ee4b91ec812690bd55d9bf51edccee" + }, + "sctransform": { + "Package": "sctransform", + "Version": "0.4.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "MASS", + "Matrix", + "R", + "Rcpp", + "RcppArmadillo", + "dplyr", + "future", + "future.apply", + "ggplot2", + "gridExtra", + "magrittr", + "matrixStats", + "methods", + "reshape2", + "rlang" + ], + "Hash": "0242402f321be0246fb67cf8c63b3572" + }, + "selectr": { + "Package": "selectr", + "Version": "0.4-2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "methods", + "stringr" + ], + "Hash": "3838071b66e0c566d55cc26bd6e27bf4" + }, + "shape": { + "Package": "shape", + "Version": "1.4.6.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics", + "stats" + ], + "Hash": "5c47e84dc0a3ca761ae1d307889e796d" + }, + "shiny": { + "Package": "shiny", + "Version": "1.8.1.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "bslib", + "cachem", + "commonmark", + "crayon", + "fastmap", + "fontawesome", + "glue", + "grDevices", + "htmltools", + "httpuv", + "jsonlite", + "later", + "lifecycle", + "methods", + "mime", + "promises", + "rlang", + "sourcetools", + "tools", + "utils", + "withr", + "xtable" + ], + "Hash": "54b26646816af9960a4c64d8ceec75d6" + }, + "sitmo": { + "Package": "sitmo", + "Version": "2.0.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp" + ], + "Hash": "c956d93f6768a9789edbc13072b70c78" + }, + "skimr": { + "Package": "skimr", + "Version": "2.1.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "dplyr", + "knitr", + "magrittr", + "pillar", + "purrr", + "repr", + "rlang", + "stats", + "stringr", + "tibble", + "tidyr", + "tidyselect", + "vctrs" + ], + "Hash": "8f138ff2c8fbea9e0a523f6c399c0386" + }, + "slider": { + "Package": "slider", + "Version": "0.3.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "rlang", + "vctrs", + "warp" + ], + "Hash": "a584625e2b9e4fad4be135c8ea5c99aa" + }, + "snakecase": { + "Package": "snakecase", + "Version": "0.11.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "stringi", + "stringr" + ], + "Hash": "58767e44739b76965332e8a4fe3f91f1" + }, + "sourcetools": { + "Package": "sourcetools", + "Version": "0.1.7-1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "5f5a7629f956619d519205ec475fe647" + }, + "sp": { + "Package": "sp", + "Version": "2.1-3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics", + "grid", + "lattice", + "methods", + "stats", + "utils" + ], + "Hash": "1a0cc0cec2915700e63fd0921085cf6a" + }, + "spam": { + "Package": "spam", + "Version": "2.10-0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp", + "dotCall64", + "grid", + "methods" + ], + "Hash": "ffe1f9e95a4375530747b268f82b5086" + }, + "spatstat.data": { + "Package": "spatstat.data", + "Version": "3.0-4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "spatstat.utils" + ], + "Hash": "114a35341cb4955e1b8d30e28ec356c6" + }, + "spatstat.explore": { + "Package": "spatstat.explore", + "Version": "3.2-7", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "abind", + "goftest", + "grDevices", + "graphics", + "methods", + "nlme", + "spatstat.data", + "spatstat.geom", + "spatstat.random", + "spatstat.sparse", + "spatstat.utils", + "stats", + "utils" + ], + "Hash": "b590c5d278d0606d53278afac666ad60" + }, + "spatstat.geom": { + "Package": "spatstat.geom", + "Version": "3.2-9", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "deldir", + "grDevices", + "graphics", + "methods", + "polyclip", + "spatstat.data", + "spatstat.utils", + "stats", + "utils" + ], + "Hash": "96b9f23da42d16660aa6d136ad99cf5f" + }, + "spatstat.random": { + "Package": "spatstat.random", + "Version": "3.2-3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "methods", + "spatstat.data", + "spatstat.geom", + "spatstat.utils", + "stats", + "utils" + ], + "Hash": "01aff260c49550e820a47d97e566af6a" + }, + "spatstat.sparse": { + "Package": "spatstat.sparse", + "Version": "3.0-3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "abind", + "methods", + "spatstat.utils", + "stats", + "tensor", + "utils" + ], + "Hash": "1daaecefd754bb259a5ad5ce95a2cdcc" + }, + "spatstat.utils": { + "Package": "spatstat.utils", + "Version": "3.0-4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics", + "methods", + "stats", + "utils" + ], + "Hash": "81d929f43f8532c1f8180a105449d414" + }, + "stringdist": { + "Package": "stringdist", + "Version": "0.9.12", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "parallel" + ], + "Hash": "f360720fa3feb7db9d4133b31ebb067f" + }, + "stringfish": { + "Package": "stringfish", + "Version": "0.16.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "Rcpp", + "RcppParallel" + ], + "Hash": "b7eb79470319ae71d4b5ed9cd7bf7294" + }, + "stringi": { + "Package": "stringi", + "Version": "1.8.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "stats", + "tools", + "utils" + ], + "Hash": "058aebddea264f4c99401515182e656a" + }, + "stringr": { + "Package": "stringr", + "Version": "1.5.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "glue", + "lifecycle", + "magrittr", + "rlang", + "stringi", + "vctrs" + ], + "Hash": "960e2ae9e09656611e0b8214ad543207" + }, + "styler": { + "Package": "styler", + "Version": "1.10.3", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R.cache", + "cli", + "magrittr", + "purrr", + "rlang", + "rprojroot", + "tools", + "vctrs", + "withr" + ], + "Hash": "93a2b1beac2437bdcc4724f8bf867e2c" + }, + "survMisc": { + "Package": "survMisc", + "Version": "0.5.6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "KMsurv", + "data.table", + "ggplot2", + "grDevices", + "graphics", + "grid", + "gridExtra", + "km.ci", + "knitr", + "stats", + "survival", + "utils", + "xtable", + "zoo" + ], + "Hash": "2367feed5d6f99ee1e380da3eac55ab6" + }, + "survival": { + "Package": "survival", + "Version": "3.5-8", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "graphics", + "methods", + "splines", + "stats", + "utils" + ], + "Hash": "184d7799bca4ba8c3be72ea396f4b9a3" + }, + "survminer": { + "Package": "survminer", + "Version": "0.4.9", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "broom", + "dplyr", + "ggplot2", + "ggpubr", + "ggtext", + "grid", + "gridExtra", + "magrittr", + "maxstat", + "methods", + "purrr", + "rlang", + "scales", + "stats", + "survMisc", + "survival", + "tibble", + "tidyr" + ], + "Hash": "3f29f006a8eb499eff91d8b72325756e" + }, + "sys": { + "Package": "sys", + "Version": "3.4.2", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "3a1be13d68d47a8cd0bfd74739ca1555" + }, + "systemfonts": { + "Package": "systemfonts", + "Version": "1.0.6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cpp11" + ], + "Hash": "6d538cff441f0f1f36db2209ac7495ac" + }, + "tensor": { + "Package": "tensor", + "Version": "1.5", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "25cfab6cf405c15bccf7e69ec39df090" + }, + "testthat": { + "Package": "testthat", + "Version": "3.2.1.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "R6", + "brio", + "callr", + "cli", + "desc", + "digest", + "evaluate", + "jsonlite", + "lifecycle", + "magrittr", + "methods", + "pkgload", + "praise", + "processx", + "ps", + "rlang", + "utils", + "waldo", + "withr" + ], + "Hash": "3f6e7e5e2220856ff865e4834766bf2b" + }, + "textshaping": { + "Package": "textshaping", + "Version": "0.3.7", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cpp11", + "systemfonts" + ], + "Hash": "997aac9ad649e0ef3b97f96cddd5622b" + }, + "tibble": { + "Package": "tibble", + "Version": "3.2.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "fansi", + "lifecycle", + "magrittr", + "methods", + "pillar", + "pkgconfig", + "rlang", + "utils", + "vctrs" + ], + "Hash": "a84e2cc86d07289b3b6f5069df7a004c" + }, + "tidymodels": { + "Package": "tidymodels", + "Version": "1.2.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "broom", + "cli", + "conflicted", + "dials", + "dplyr", + "ggplot2", + "hardhat", + "infer", + "modeldata", + "parsnip", + "purrr", + "recipes", + "rlang", + "rsample", + "rstudioapi", + "tibble", + "tidyr", + "tune", + "workflows", + "workflowsets", + "yardstick" + ], + "Hash": "c3296bbe8389a31fafc1ee07e69889a7" + }, + "tidyr": { + "Package": "tidyr", + "Version": "1.3.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "cpp11", + "dplyr", + "glue", + "lifecycle", + "magrittr", + "purrr", + "rlang", + "stringr", + "tibble", + "tidyselect", + "utils", + "vctrs" + ], + "Hash": "915fb7ce036c22a6a33b5a8adb712eb1" + }, + "tidyselect": { + "Package": "tidyselect", + "Version": "1.2.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "glue", + "lifecycle", + "rlang", + "vctrs", + "withr" + ], + "Hash": "829f27b9c4919c16b593794a6344d6c0" + }, + "tidyverse": { + "Package": "tidyverse", + "Version": "2.0.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "broom", + "cli", + "conflicted", + "dbplyr", + "dplyr", + "dtplyr", + "forcats", + "ggplot2", + "googledrive", + "googlesheets4", + "haven", + "hms", + "httr", + "jsonlite", + "lubridate", + "magrittr", + "modelr", + "pillar", + "purrr", + "ragg", + "readr", + "readxl", + "reprex", + "rlang", + "rstudioapi", + "rvest", + "stringr", + "tibble", + "tidyr", + "xml2" + ], + "Hash": "c328568cd14ea89a83bd4ca7f54ae07e" + }, + "timeDate": { + "Package": "timeDate", + "Version": "4032.109", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "graphics", + "methods", + "stats", + "utils" + ], + "Hash": "fa276a2ec2555d74b4eabf56fba3d209" + }, + "timechange": { + "Package": "timechange", + "Version": "0.3.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cpp11" + ], + "Hash": "c5f3c201b931cd6474d17d8700ccb1c8" + }, + "tinytex": { + "Package": "tinytex", + "Version": "0.50", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "xfun" + ], + "Hash": "be7a76845222ad20adb761f462eed3ea" + }, + "tune": { + "Package": "tune", + "Version": "1.2.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "GPfit", + "R", + "cli", + "dials", + "doFuture", + "dplyr", + "foreach", + "future", + "generics", + "ggplot2", + "glue", + "hardhat", + "lifecycle", + "parsnip", + "purrr", + "recipes", + "rlang", + "rsample", + "tibble", + "tidyr", + "tidyselect", + "vctrs", + "withr", + "workflows", + "yardstick" + ], + "Hash": "7fbdbcd58e7a63957b23ddb751b346af" + }, + "tzdb": { + "Package": "tzdb", + "Version": "0.4.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cpp11" + ], + "Hash": "f561504ec2897f4d46f0c7657e488ae1" + }, + "ucminf": { + "Package": "ucminf", + "Version": "1.2.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "48f2c17a0f91a1669cffdc8593aa62b2" + }, + "unigd": { + "Package": "unigd", + "Version": "0.1.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cpp11", + "systemfonts" + ], + "Hash": "9ed4b1941002ff508006885c66b5e473" + }, + "utf8": { + "Package": "utf8", + "Version": "1.2.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "62b65c52671e6665f803ff02954446e9" + }, + "uuid": { + "Package": "uuid", + "Version": "1.2-0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "303c19bfd970bece872f93a824e323d9" + }, + "uwot": { + "Package": "uwot", + "Version": "0.2.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "FNN", + "Matrix", + "RSpectra", + "Rcpp", + "RcppAnnoy", + "RcppProgress", + "dqrng", + "irlba", + "methods" + ], + "Hash": "f693a0ca6d34b02eb432326388021805" + }, + "vctrs": { + "Package": "vctrs", + "Version": "0.6.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "glue", + "lifecycle", + "rlang" + ], + "Hash": "c03fa420630029418f7e6da3667aac4a" + }, + "vip": { + "Package": "vip", + "Version": "0.4.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "foreach", + "ggplot2", + "stats", + "tibble", + "utils", + "yardstick" + ], + "Hash": "4bfee1f7181f71d552a4b63485f8fc25" + }, + "viridis": { + "Package": "viridis", + "Version": "0.6.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "ggplot2", + "gridExtra", + "viridisLite" + ], + "Hash": "acd96d9fa70adeea4a5a1150609b9745" + }, + "viridisLite": { + "Package": "viridisLite", + "Version": "0.4.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "c826c7c4241b6fc89ff55aaea3fa7491" + }, + "vroom": { + "Package": "vroom", + "Version": "1.6.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "bit64", + "cli", + "cpp11", + "crayon", + "glue", + "hms", + "lifecycle", + "methods", + "progress", + "rlang", + "stats", + "tibble", + "tidyselect", + "tzdb", + "vctrs", + "withr" + ], + "Hash": "390f9315bc0025be03012054103d227c" + }, + "waldo": { + "Package": "waldo", + "Version": "0.5.2", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "diffobj", + "fansi", + "glue", + "methods", + "rematch2", + "rlang", + "tibble" + ], + "Hash": "c7d3fd6d29ab077cbac8f0e2751449e6" + }, + "warp": { + "Package": "warp", + "Version": "0.2.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "fea474d578b1cbcb696ae6ac8bdcc439" + }, + "withr": { + "Package": "withr", + "Version": "3.0.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics" + ], + "Hash": "d31b6c62c10dcf11ec530ca6b0dd5d35" + }, + "workflows": { + "Package": "workflows", + "Version": "1.1.4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "generics", + "glue", + "hardhat", + "lifecycle", + "modelenv", + "parsnip", + "rlang", + "tidyselect", + "vctrs" + ], + "Hash": "f2c2cefdf6babfed4594b33479d19fc3" + }, + "workflowsets": { + "Package": "workflowsets", + "Version": "1.1.0", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "dplyr", + "generics", + "ggplot2", + "glue", + "hardhat", + "lifecycle", + "parsnip", + "pillar", + "prettyunits", + "purrr", + "rlang", + "rsample", + "stats", + "tibble", + "tidyr", + "tune", + "vctrs", + "withr", + "workflows" + ], + "Hash": "ff4540bb4cccc1dd2447d58a97158820" + }, + "writexl": { + "Package": "writexl", + "Version": "1.5.0", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "856a075aec895ea1bea3055fa54e356c" + }, + "xfun": { + "Package": "xfun", + "Version": "0.43", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "grDevices", + "stats", + "tools" + ], + "Hash": "ab6371d8653ce5f2f9290f4ec7b42a8e" + }, + "xgboost": { + "Package": "xgboost", + "Version": "1.7.7.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "Matrix", + "R", + "data.table", + "jsonlite", + "methods" + ], + "Hash": "6303e61eac62aef7bd2b396ef7e24386" + }, + "xml2": { + "Package": "xml2", + "Version": "1.3.6", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "methods", + "rlang" + ], + "Hash": "1d0336142f4cd25d8d23cd3ba7a8fb61" + }, + "xmlparsedata": { + "Package": "xmlparsedata", + "Version": "1.0.5", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R" + ], + "Hash": "45e4bf3c46476896e821fc0a408fb4fc" + }, + "xtable": { + "Package": "xtable", + "Version": "1.8-4", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "stats", + "utils" + ], + "Hash": "b8acdf8af494d9ec19ccb2481a9b11c2" + }, + "yaml": { + "Package": "yaml", + "Version": "2.3.8", + "Source": "Repository", + "Repository": "RSPM", + "Hash": "29240487a071f535f5e5d5a323b7afbd" + }, + "yardstick": { + "Package": "yardstick", + "Version": "1.3.1", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "cli", + "dplyr", + "generics", + "hardhat", + "lifecycle", + "rlang", + "tibble", + "tidyselect", + "utils", + "vctrs", + "withr" + ], + "Hash": "9ce4117141b326c4fffc7c42e56e0f88" + }, + "zoo": { + "Package": "zoo", + "Version": "1.8-12", + "Source": "Repository", + "Repository": "RSPM", + "Requirements": [ + "R", + "grDevices", + "graphics", + "lattice", + "stats", + "utils" + ], + "Hash": "5c715954112b45499fb1dadc6ee6ee3e" + } + } +} diff --git a/vignettes/z-advanced-topic-handling-packages-with-remote-dependencies.Rmd b/vignettes/z-advanced-topic-handling-packages-with-remote-dependencies.Rmd index 645dc1b4..377c123b 100644 --- a/vignettes/z-advanced-topic-handling-packages-with-remote-dependencies.Rmd +++ b/vignettes/z-advanced-topic-handling-packages-with-remote-dependencies.Rmd @@ -21,15 +21,14 @@ library(rix) ## Introduction Packages published on CRAN must have their dependencies on either CRAN or -BioConductor, but not on GitHub. However, there are many packages available on +Bioconductor, but not on GitHub. However, there are many packages available on GitHub that never get published on CRAN, and some of these packages may even depend on other packages that are also only available on GitHub. `{rix}` makes -it possible to install packages from GitHub, but in case one of the package's -dependencies has also only been released on GitHub, building the Nix environment -will fail. This is because Nix will be looking for these packages on `nixpkgs`, -but only packages released on CRAN and Bioconductor are available through -`nixpkgs`. This vignette explains how to install such a packages that have -dependencies only available on GitHub. +it possible to install packages from GitHub and if these packages have +dependencies that are also on Github, these also get correctly added to the +generated `default.nix`. + +There are however certain caveats you should be aware of. ## The {lookup} package @@ -62,17 +61,130 @@ rix( ) ``` -Trying to build this environment will fail with following error message: +This will generate the following `default.nix`: ``` -error: attribute 'highlite' missing -``` +let + pkgs = import (fetchTarball "https://github.com/NixOS/nixpkgs/archive/6a25f33c843a45b8d67ba782b6782973a7265774.tar.gz") {}; + + httr2 = (pkgs.rPackages.buildRPackage { + name = "httr2"; + src = pkgs.fetchgit { + url = "https://github.com/r-lib/httr2"; + rev = "HEAD"; + sha256 = "sha256-UgJCFPO47mgUt3esRRPhXjr0oNDRrR9XAAIxMhZYbFc="; + }; + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + cli + curl + glue + lifecycle + magrittr + openssl + R6 + rappdirs + rlang + vctrs + withr; + }; + }); + + gh = (pkgs.rPackages.buildRPackage { + name = "gh"; + src = pkgs.fetchgit { + url = "https://github.com/gaborcsardi/gh"; + rev = "HEAD"; + sha256 = "sha256-VpxFIfUEk0PudytQ3boMhEJhT0AnelWkSU++WD/HAyo="; + }; + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + cli + gitcreds + glue + ini + jsonlite + lifecycle + rlang; + } ++ [ httr2 ]; + }); + + + highlite = (pkgs.rPackages.buildRPackage { + name = "highlite"; + src = pkgs.fetchgit { + url = "https://github.com/jimhester/highlite"; + rev = "HEAD"; + sha256 = "sha256-lkWMlAi75MYxiBUYnLwxLK9ApXkWanA4Mt7g4qtLpxM="; + }; + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + Rcpp + BH; + }; + }); + + + memoise = (pkgs.rPackages.buildRPackage { + name = "memoise"; + src = pkgs.fetchgit { + url = "https://github.com/hadley/memoise"; + rev = "HEAD"; + sha256 = "sha256-FDMNgrgctzkN8dXKRoWsOKe3tXxmm8Cqdu/Sh6WKx/Q="; + }; + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + rlang + cachem; + }; + }); + + lookup = (pkgs.rPackages.buildRPackage { + name = "lookup"; + src = pkgs.fetchgit { + url = "https://github.com/jimhester/lookup/"; + rev = "eba63db477dd2f20153b75e2949eb333a36cccfc"; + sha256 = "sha256-arl7LVxL8xGUW3LhuDCSUjcfswX0rdofL/7v8Klw8FM="; + }; + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + Rcpp + codetools + crayon + rex + jsonlite + rstudioapi + withr + httr; + } ++ [ highlite gh memoise ]; + }); + + system_packages = builtins.attrValues { + inherit (pkgs) + glibcLocales + nix + R; + }; -## Building remote dependencies +in -`{highlite}` is a dependency of [{lookup}](https://github.com/jimhester/lookup) -that is only available on GitHub. This can be checked by looking at the -`DESCRIPTION` file of [{lookup}](https://github.com/jimhester/lookup): +pkgs.mkShell { + LOCALE_ARCHIVE = if pkgs.system == "x86_64-linux" then "${pkgs.glibcLocales}/lib/locale/locale-archive" else ""; + LANG = "en_US.UTF-8"; + LC_ALL = "en_US.UTF-8"; + LC_TIME = "en_US.UTF-8"; + LC_MONETARY = "en_US.UTF-8"; + LC_PAPER = "en_US.UTF-8"; + LC_MEASUREMENT = "en_US.UTF-8"; + + buildInputs = [ lookup system_packages ]; + +} +``` + +as you can see, several other packages hosted on Github were added +automatically. This is because these were listed as remote dependencies in +`{lookup}`'s `DESCRIPTION` file: ``` Remotes: @@ -81,131 +193,210 @@ Remotes: hadley/memoise ``` -We see that there are actually three packages that come from GitHub: but `{gh}` -and `{memoise}` have in the meantime been released on CRAN, which means that -they are also available through `nixpkgs`. We have to deal with `{highlite}` -however, because it never got released on CRAN. Doing so is fairly easy: first, -create a new expression using `{rix}` to install `{highlite}`: - -```{r, eval = F} -path_default_nix <- tempdir() - -rix( - r_ver = "latest-upstream", - r_pkgs = NULL, - system_pkgs = NULL, - git_pkgs = list( - package_name = "highlite", - repo_url = "https://github.com/jimhester/highlite/", - commit = "767b122ef47a60a01e1707e4093cf3635a99c86b" - ), - ide = "other", - project_path = path_default_nix, - overwrite = FALSE, - print = TRUE -) -``` +## Caveats -(you don't need to overwrite the previous expression, simply printing this -one on screen will do). Copy the following lines: +`{highlite}` is a dependency of [{lookup}](https://github.com/jimhester/lookup) +that is only available on GitHub. `{gh}` and `{memoise}` are also listed as +remote dependencies, however, they are also available on CRAN. What likely +happened here was that `{gh}` and `{memoise}` were not yet available on CRAN at +the time when `{lookup}` was written (which was more than 6 years ago as of +2025). Because they are listed as remote dependencies, they will also be built +from GitHub instead of CRAN. Here, it is up to you to decide if you want to keep +the GitHub version of these packages, or if you should instead include the +released CRAN version. Depending on what you want to do, going for the CRAN +release of the packages might be advisable. For example in this case, trying to +build this expression will not work. + +This is because `{httr2}` is a package that needs to be compiled from source and +which needs some Nix-specific fixes applied to its source code for it to build +successfully. Installing the version provided by `nixpkgs`, which builds upon +the released CRAN version will succeed however. To do so, change the +`default.nix` manually to this (essentially remove the definition of `{httr2}` +and put it as a `propagatedBuildInput` to `{gh}`): ``` -git_archive_pkgs = [(pkgs.rPackages.buildRPackage { - name = "highlite"; - src = pkgs.fetchgit { - url = "https://github.com/jimhester/highlite/"; - rev = "767b122ef47a60a01e1707e4093cf3635a99c86b"; - sha256 = "sha256-lkWMlAi75MYxiBUYnLwxLK9ApXkWanA4Mt7g4qtLpxM="; - }; - propagatedBuildInputs = builtins.attrValues { - inherit (pkgs.rPackages) Rcpp BH; +let + pkgs = import (fetchTarball "https://github.com/NixOS/nixpkgs/archive/6a25f33c843a45b8d67ba782b6782973a7265774.tar.gz") {}; + + gh = (pkgs.rPackages.buildRPackage { + name = "gh"; + src = pkgs.fetchgit { + url = "https://github.com/gaborcsardi/gh"; + rev = "HEAD"; + sha256 = "sha256-VpxFIfUEk0PudytQ3boMhEJhT0AnelWkSU++WD/HAyo="; + }; + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + cli + gitcreds + glue + httr2 # <- httr2 is now declared here, so it's the CRAN version + ini + jsonlite + lifecycle + rlang; + }; + }); + + highlite = (pkgs.rPackages.buildRPackage { + name = "highlite"; + src = pkgs.fetchgit { + url = "https://github.com/jimhester/highlite"; + rev = "HEAD"; + sha256 = "sha256-lkWMlAi75MYxiBUYnLwxLK9ApXkWanA4Mt7g4qtLpxM="; + }; + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + Rcpp + BH; + }; + }); + + memoise = (pkgs.rPackages.buildRPackage { + name = "memoise"; + src = pkgs.fetchgit { + url = "https://github.com/hadley/memoise"; + rev = "HEAD"; + sha256 = "sha256-FDMNgrgctzkN8dXKRoWsOKe3tXxmm8Cqdu/Sh6WKx/Q="; + }; + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + rlang + cachem; + }; + }); + + lookup = (pkgs.rPackages.buildRPackage { + name = "lookup"; + src = pkgs.fetchgit { + url = "https://github.com/jimhester/lookup/"; + rev = "eba63db477dd2f20153b75e2949eb333a36cccfc"; + sha256 = "sha256-arl7LVxL8xGUW3LhuDCSUjcfswX0rdofL/7v8Klw8FM="; + }; + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + Rcpp + codetools + crayon + rex + jsonlite + rstudioapi + withr + httr; + } ++ [ highlite gh memoise ]; + }); + + system_packages = builtins.attrValues { + inherit (pkgs) + glibcLocales + nix + R; }; -}) ]; -``` -into the previous expression (and change `git_archive_pkgs` into `highlite`). -The file should look like this now: +in -``` -let - pkgs = import (fetchTarball "https://github.com/NixOS/nixpkgs/archive/b200e0df08f80c32974a6108ce431d8a8a5e6547.tar.gz") {}; +pkgs.mkShell { + LOCALE_ARCHIVE = if pkgs.system == "x86_64-linux" then "${pkgs.glibcLocales}/lib/locale/locale-archive" else ""; + LANG = "en_US.UTF-8"; + LC_ALL = "en_US.UTF-8"; + LC_TIME = "en_US.UTF-8"; + LC_MONETARY = "en_US.UTF-8"; + LC_PAPER = "en_US.UTF-8"; + LC_MEASUREMENT = "en_US.UTF-8"; - highlite = [(pkgs.rPackages.buildRPackage { - name = "highlite"; - src = pkgs.fetchgit { - url = "https://github.com/jimhester/highlite/"; - rev = "767b122ef47a60a01e1707e4093cf3635a99c86b"; - sha256 = "sha256-lkWMlAi75MYxiBUYnLwxLK9ApXkWanA4Mt7g4qtLpxM="; - }; - propagatedBuildInputs = builtins.attrValues { - inherit (pkgs.rPackages) Rcpp BH; - }; - }) ]; - git_archive_pkgs = [(pkgs.rPackages.buildRPackage { - name = "lookup"; - src = pkgs.fetchgit { - url = "https://github.com/jimhester/lookup/"; - rev = "eba63db477dd2f20153b75e2949eb333a36cccfc"; - sha256 = "sha256-arl7LVxL8xGUW3LhuDCSUjcfswX0rdofL/7v8Klw8FM="; - }; - propagatedBuildInputs = builtins.attrValues { - inherit (pkgs.rPackages) gh memoise Rcpp codetools crayon rex highlite jsonlite rstudioapi withr httr; - }; - }) ]; - system_packages = builtins.attrValues { - inherit (pkgs) R ; -}; - in - pkgs.mkShell { - buildInputs = [ git_archive_pkgs system_packages ]; - shellHook = '' -R --vanilla -''; - } + buildInputs = [ lookup system_packages ]; +} ``` -The only thing that we need to change is this line: +In this manually edited expression, `{httr2}` will now build successfully +because Nix is instructed to build the CRAN version by applying [this +fix](https://github.com/NixOS/nixpkgs/blob/7b87fced8bc525d466c7258a042bd12ea336a3c6/pkgs/development/r-modules/default.nix#L1817) +which was added there by packagers and maintainers of the R programming language +for `nixpkgs` (it is exactly the same if you tried to install `{httr2}` from +GitHub on Windows: you would need to build it from source and thus make sure +that you have the required system-level dependencies to build it. Instead, it is +easier to install a pre-compiled binary from CRAN). + +Another important point to address is that if remote dependencies are listed in +a `DESCRIPTION` file like this: ``` -propagatedBuildInputs = builtins.attrValues { - inherit (pkgs.rPackages) gh memoise Rcpp codetools crayon rex highlite jsonlite rstudioapi withr httr; - }; +Remotes: + jimhester/highlite, + gaborcsardi/gh, + hadley/memoise ``` -into: +`{rix}` will automatically use the latest commit from these repositories as the +revision. This also means that if these repositories are being actively worked on, +rebuilding these environments will actually pull another version of these packages. +Instead, it is advisable to edit the `default.nix` yet again, and replace mentions +of `HEAD` with an actual commit. For example, edit this: ``` -propagatedBuildInputs = builtins.attrValues { - inherit (pkgs.rPackages) gh memoise Rcpp codetools crayon rex jsonlite rstudioapi withr httr; - } ++ [highlite]; - + gh = (pkgs.rPackages.buildRPackage { + name = "gh"; + src = pkgs.fetchgit { + url = "https://github.com/gaborcsardi/gh"; + rev = "HEAD"; + sha256 = "sha256-VpxFIfUEk0PudytQ3boMhEJhT0AnelWkSU++WD/HAyo="; + }; + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + cli + gitcreds + glue + ini + jsonlite + lifecycle + rlang; + } ++ [ httr2 ]; + }); ``` -and this line: +to this: ``` -buildInputs = [ git_archive_pkgs system_packages ]; + gh = (pkgs.rPackages.buildRPackage { + name = "gh"; + src = pkgs.fetchgit { + url = "https://github.com/gaborcsardi/gh"; + rev = "27db16cf363dc"; + sha256 = ""; # <- You will need to try to build the expression once, and then + }; # <- put the sha256 that nix-build returns + propagatedBuildInputs = builtins.attrValues { + inherit (pkgs.rPackages) + cli + gitcreds + glue + ini + jsonlite + lifecycle + rlang; + } ++ [ httr2 ]; + }); ``` -into: + +However, if instead the remotes are listed like this: ``` -buildInputs = [ git_archive_pkgs system_packages highlite ]; +Remotes: + jimhester/highlite@abc123, + gaborcsardi/gh@def123, + hadley/memoise@ghi123 ``` -Building the expression now succeeds. - -We know that this is quite tedious, but at the moment there are no plans to make -`{rix}` handle remote dependencies automatically. This is for mainly three -reasons: +then the listed commits will be used, which will make sure that the build +process is reproducible. Only commits can be used, anything else listed there +(such as pull request numbers or release tags) will not work with `{rix}`. -- packages with remote dependencies are rare, and never on CRAN on Bioconductor; -- packages may have remote dependencies, but these dependencies may later be available on CRAN (such as with `{memoise}` and `{gh}` for [{lookup}](https://github.com/jimhester/lookup)); -- `{rix}` cannot decide for the user which commit to use for a remote dependency (or whether to use the released version of that dependency from CRAN). +In conclusion, `{rix}` makes it easier to build packages from GitHub which +have themselves dependencies hosted on GitHub, you should however make sure +that the expression that is generated uses fixed commits instead of `HEAD` +for the packages being built from GitHub, and you should also decide if you +want to use the version of a packages hosted on GitHub instead of the CRAN +release. These are decisions that `{rix}` cannot take for you. -Because of these reasons, we believe that it is safer for users that really need -to use such packages to manually edit their Nix expressions. Don't hesitate to -[open an issue](https://github.com/ropensci/rix/issues) if you require -assistance.