diff --git a/NAMESPACE b/NAMESPACE index 9624d11d0..64223f47b 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -42,6 +42,7 @@ export(scaffold) export(settings) export(snapshot) export(status) +export(sysreqs) export(update) export(upgrade) export(use) diff --git a/NEWS.md b/NEWS.md index 377b888d3..cfad16936 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,6 +1,15 @@ # renv (development version) +* `renv` gains the `sysreqs()` function, which can be used to query the system + packages required by a set of R packages. Functionality is currently available + for Debian-based distributions, as well as Red Hat distributions. + +* On Linux, `renv` now uses the database from + when determining if + an R package's required system libraries are installed, and notifies + the user which packages (if any) are missing during install / restore. + * Fixed an issue where `renv` could fail to retrieve credentials registered for 'github.com' when querying URLs at 'api.github.com'. diff --git a/R/abi.R b/R/abi.R index 8b7031c73..b458215e8 100644 --- a/R/abi.R +++ b/R/abi.R @@ -45,7 +45,7 @@ renv_abi_check <- function(packages = NULL, reasons <- unique(tbl$reason) if ("Rcpp_precious_list" %in% reasons) { packages <- sort(unique(tbl$package[tbl$reason == "Rcpp_precious_list"])) - caution_bullets( + bulletin( "The following packages were built against a newer version of Rcpp than is currently available:", packages, c( @@ -61,7 +61,7 @@ renv_abi_check <- function(packages = NULL, if ("missing" %in% reasons) { missing <- tbl[tbl$reason == "missing", ] - caution_bullets( + bulletin( "The following required system libraries are unavailable:", unique(missing$dependency), c( diff --git a/R/aliases.R b/R/aliases.R index 1578d88b7..610c04350 100644 --- a/R/aliases.R +++ b/R/aliases.R @@ -1,6 +1,6 @@ # aliases used primarily for nicer / normalized text output -the$aliases <- list( +the$aliases <- c( bioc = "Bioconductor", bioconductor = "Bioconductor", bitbucket = "Bitbucket", @@ -16,6 +16,8 @@ the$aliases <- list( xgit = "Git" ) -alias <- function(text) { - the$aliases[[text]] %||% text +alias <- function(text, aliases = the$aliases) { + matches <- text %in% names(aliases) + text[matches] <- aliases[text[matches]] + text } diff --git a/R/available-packages.R b/R/available-packages.R index 80fc12111..afd6d2572 100644 --- a/R/available-packages.R +++ b/R/available-packages.R @@ -95,7 +95,7 @@ renv_available_packages_query <- function(type, repos, quiet = FALSE) { paste(c(header(url), msgs, ""), collapse = "\n") }) - caution_bullets(header, msgs) + bulletin(header, msgs) filter(dbs, Negate(is.null)) } diff --git a/R/cache.R b/R/cache.R index c6db9334c..a56d1719c 100644 --- a/R/cache.R +++ b/R/cache.R @@ -275,7 +275,7 @@ renv_cache_diagnose_corrupt_metadata <- function(paths, problems, verbose) { # nocov start if (verbose) { - caution_bullets( + bulletin( "The following package(s) are missing 'Meta/package.rds':", renv_cache_format_path(bad), "These packages should be purged and reinstalled." @@ -304,7 +304,7 @@ renv_cache_diagnose_corrupt_metadata <- function(paths, problems, verbose) { # nocov start if (verbose) { - caution_bullets( + bulletin( "The following package(s) have corrupt 'Meta/package.rds' files:", renv_cache_format_path(bad), "These packages should be purged and reinstalled." @@ -335,7 +335,7 @@ renv_cache_diagnose_missing_descriptions <- function(paths, problems, verbose) { # nocov start if (verbose) { - caution_bullets( + bulletin( "The following packages are missing DESCRIPTION files in the cache:", renv_cache_format_path(bad), "These packages should be purged and reinstalled." @@ -369,7 +369,7 @@ renv_cache_diagnose_bad_hash <- function(paths, problems, verbose) { fmt <- "%s %s [Hash: %s != %s]" entries <- sprintf(fmt, lhs$Package, lhs$Version, lhs$Hash, rhs$Hash) - caution_bullets( + bulletin( "The following packages have incorrect hashes:", entries, "Consider using `renv::rehash()` to re-hash these packages." @@ -412,7 +412,7 @@ renv_cache_diagnose_wrong_built_version <- function(paths, problems, verbose) { # nocov start if (verbose) { - caution_bullets( + bulletin( "The following packages have no 'Built' field recorded in their DESCRIPTION file:", paths[isna], "renv is unable to validate the version of R this package was built for." @@ -450,7 +450,7 @@ renv_cache_diagnose_wrong_built_version <- function(paths, problems, verbose) { # nocov start if (verbose) { - caution_bullets( + bulletin( "The following packages in the cache were built for a different version of R:", renv_cache_format_path(paths[wrong]), "These packages will need to be purged and reinstalled." diff --git a/R/caution.R b/R/caution.R index 4b8960c23..a9776a625 100644 --- a/R/caution.R +++ b/R/caution.R @@ -5,12 +5,12 @@ caution <- function(fmt = "", ..., con = stdout()) { writeLines(sprintf(fmt, ...), con = con) } -caution_bullets <- function(preamble = NULL, - values = NULL, - postamble = NULL, - ..., - bullets = TRUE, - emitter = NULL) +bulletin <- function(preamble = NULL, + values = NULL, + postamble = NULL, + ..., + bullets = TRUE, + emitter = NULL) { if (empty(values)) return(invisible()) @@ -18,7 +18,7 @@ caution_bullets <- function(preamble = NULL, renv_dots_check(...) lines <- c( - if (length(preamble)) paste(preamble, collapse = "\n"), + if (length(preamble)) paste(preamble, collapse = "\n"), if (bullets) paste("-", values, collapse = "\n") else diff --git a/R/clean.R b/R/clean.R index 8861c3369..f8c389c2d 100644 --- a/R/clean.R +++ b/R/clean.R @@ -131,7 +131,7 @@ renv_clean_library_tempdirs <- function(project, prompt) { # nocov start if (prompt || renv_verbose()) { - caution_bullets("The following directories will be removed:", bad) + bulletin("The following directories will be removed:", bad) if (prompt && !proceed()) cancel() @@ -177,7 +177,7 @@ renv_clean_system_library <- function(project, prompt) { # nocov start if (prompt || renv_verbose()) { - caution_bullets( + bulletin( "The following non-system packages are installed in the system library:", packages, c( @@ -227,7 +227,7 @@ renv_clean_unused_packages <- function(project, prompt) { # nocov start if (prompt || renv_verbose()) { - caution_bullets( + bulletin( c( "The following packages are installed in the project library,", "but appear to be no longer used in your project." @@ -272,7 +272,7 @@ renv_clean_package_locks <- function(project, prompt) { # nocov start if (prompt || renv_verbose()) { - caution_bullets( + bulletin( "The following stale package locks were discovered in your library:", basename(old), "These locks will be removed." @@ -306,7 +306,7 @@ renv_clean_cache <- function(project, prompt) { missing <- !file.exists(projlist) if (any(missing)) { - caution_bullets( + bulletin( "The following projects are monitored by renv, but no longer exist:", projlist[missing], "These projects will be removed from renv's project list." @@ -342,7 +342,7 @@ renv_clean_cache <- function(project, prompt) { if (prompt || renv_verbose()) { - caution_bullets( + bulletin( "The following packages are installed in the cache but no longer used:", renv_cache_format_path(diff), "These packages will be removed." diff --git a/R/config-defaults.R b/R/config-defaults.R index adb9af51b..17d807291 100644 --- a/R/config-defaults.R +++ b/R/config-defaults.R @@ -339,6 +339,15 @@ config <- list( ) }, + sysreqs.check = function(..., default = TRUE) { + renv_config_get( + name = "sysreqs.check", + type = "logical[1]", + default = default, + args = list(...) + ) + }, + updates.check = function(..., default = FALSE) { renv_config_get( name = "updates.check", diff --git a/R/dependencies.R b/R/dependencies.R index 407484ade..8ee428bfc 100644 --- a/R/dependencies.R +++ b/R/dependencies.R @@ -1883,7 +1883,7 @@ renv_dependencies_report <- function(errors) { paste(c(header(file), messages, ""), collapse = "\n") }) - caution_bullets( + bulletin( "WARNING: One or more problems were discovered while enumerating dependencies.", c("", lines), "Please see `?renv::dependencies` for more information.", diff --git a/R/diagnostics.R b/R/diagnostics.R index fcbc48844..7b251f982 100644 --- a/R/diagnostics.R +++ b/R/diagnostics.R @@ -29,6 +29,7 @@ diagnostics <- function(project = NULL) { renv_diagnostics_project, renv_diagnostics_status, renv_diagnostics_packages, + renv_diagnostics_sysreqs, renv_diagnostics_abi, renv_diagnostics_profile, renv_diagnostics_settings, @@ -145,6 +146,21 @@ renv_diagnostics_packages <- function(project) { } +renv_diagnostics_sysreqs <- function(project) { + + if (!renv_platform_linux()) + return() + + writef(header("R System Requirements")) + + lockfile <- renv_lockfile_create(project) + records <- renv_lockfile_records(lockfile) + sysreqs <- map(records, `[[`, "SystemRequirements") + ok <- renv_sysreqs_check(sysreqs, prompt = FALSE) + invisible(ok) + +} + renv_diagnostics_packages_version <- function(lockfile, all) { data <- rep.int(NA_character_, length(all)) diff --git a/R/equip-macos.R b/R/equip-macos.R index 1e6a4f4b6..33d665e19 100644 --- a/R/equip-macos.R +++ b/R/equip-macos.R @@ -80,7 +80,7 @@ renv_equip_macos_toolchain <- function() { return(TRUE) command <- paste("sudo /usr/sbin/installer -pkg", shQuote(destfile), "-target /") - caution_bullets( + bulletin( "The R LLVM toolchain has been successfully downloaded. Please execute:", command, "in a separate terminal to complete installation." @@ -123,7 +123,7 @@ renv_equip_macos_rstudio <- function(spec, destfile) { if (!installed) return(FALSE) - caution_bullets( + bulletin( "The R LLVM toolchain has been downloaded and installed to:", spec$dst, "This toolchain will be used by renv when installing packages from source." diff --git a/R/extsoft.R b/R/extsoft.R index e92756bca..49942be40 100644 --- a/R/extsoft.R +++ b/R/extsoft.R @@ -31,7 +31,7 @@ renv_extsoft_install <- function(quiet = FALSE) { if (interactive()) { - caution_bullets( + bulletin( "The following external software tools will be installed:", files, sprintf("Tools will be installed into %s.", renv_path_pretty(extsoft)) @@ -135,7 +135,7 @@ renv_extsoft_use <- function(quiet = FALSE) { if (interactive()) { - caution_bullets( + bulletin( "The following entries will be added to ~/.R/Makevars:", c(localsoft, libxml, localcpp, locallibs), "These tools will be used when compiling R packages from source." diff --git a/R/hydrate.R b/R/hydrate.R index 651b59cb5..3eb8a7930 100644 --- a/R/hydrate.R +++ b/R/hydrate.R @@ -366,7 +366,7 @@ renv_hydrate_resolve_missing <- function(project, library, remotes, missing) { sprintf("[%s]: %s", package, short) }) - caution_bullets( + bulletin( "The following package(s) were not installed successfully:", text, "You may need to manually download and install these packages." @@ -416,7 +416,7 @@ renv_hydrate_report <- function(packages, na, linkable) { } if (length(na)) { - caution_bullets( + bulletin( "The following packages are used in this project, but not available locally:", csort(names(na)), "renv will attempt to download and install these packages." diff --git a/R/install.R b/R/install.R index 3756852f7..ad2263a96 100644 --- a/R/install.R +++ b/R/install.R @@ -227,6 +227,14 @@ install <- function(packages = NULL, cancel_if(prompt && !proceed()) } + # check for installed dependencies + if (config$sysreqs.check(default = renv_platform_linux())) { + paths <- map(records, `[[`, "Path") + sysreqs <- map(paths, renv_sysreqs_read) + renv_sysreqs_check(sysreqs, prompt = prompt) + } + + # install retrieved records before <- Sys.time() renv_install_impl(records) @@ -766,7 +774,7 @@ renv_install_preflight_requirements <- function(records) { fmt <- "Package '%s' requires '%s', but '%s' will be installed" text <- sprintf(fmt, format(package), format(requires), format(actual)) if (renv_verbose()) { - caution_bullets( + bulletin( "The following issues were discovered while preparing for installation:", text, "Installation of these packages may not succeed." @@ -789,7 +797,7 @@ renv_install_postamble <- function(packages) { installed <- map_chr(packages, renv_package_version) loaded <- map_chr(packages, renv_namespace_version) - caution_bullets( + bulletin( c("", "The following loaded package(s) have been updated:"), packages[installed != loaded], "Restart your R session to use the new versions." @@ -826,7 +834,7 @@ renv_install_preflight_permissions <- function(library) { postamble <- sprintf(fmt, info$effective_user %||% info$user) # print it - caution_bullets( + bulletin( preamble = preamble, values = library, postamble = postamble diff --git a/R/library.R b/R/library.R index ab03e573e..68adcd502 100644 --- a/R/library.R +++ b/R/library.R @@ -22,7 +22,7 @@ renv_library_diagnose <- function(project, libpath) { # if only some symlinks are broken, report to user if (any(missing)) { - caution_bullets( + bulletin( "The following package(s) are missing entries in the cache:", basename(children[missing]), "These packages will need to be reinstalled." diff --git a/R/load.R b/R/load.R index 79426778b..5396539ec 100644 --- a/R/load.R +++ b/R/load.R @@ -766,7 +766,7 @@ renv_load_check_description <- function(project) { values <- sprintf("[line %i is blank]", bad) - caution_bullets( + bulletin( sprintf("%s contains blank lines:", renv_path_pretty(descpath)), values, c( diff --git a/R/lockfile-read.R b/R/lockfile-read.R index 469961e87..f5cd9a85a 100644 --- a/R/lockfile-read.R +++ b/R/lockfile-read.R @@ -76,7 +76,7 @@ renv_lockfile_read_preflight <- function(contents) { all <- unlist(parts, recursive = TRUE, use.names = FALSE) - caution_bullets( + bulletin( "The lockfile contains one or more merge conflict markers:", head(all, n = -1L), "You will need to resolve these merge conflicts before the file can be read." diff --git a/R/migrate.R b/R/migrate.R index 5b6748401..bab34071c 100644 --- a/R/migrate.R +++ b/R/migrate.R @@ -321,7 +321,7 @@ renv_migrate_packrat_cache_impl <- function(targets) { if (nrow(bad) == 0) return(TRUE) - caution_bullets( + bulletin( "The following packages could not be copied from the Packrat cache:", with(bad, sprintf("%s [%s]", format(source), reason)), "These packages may need to be reinstalled and re-cached." diff --git a/R/platform.R b/R/platform.R index 63623949f..553a7a919 100644 --- a/R/platform.R +++ b/R/platform.R @@ -1,8 +1,31 @@ -the$sysinfo <- NULL +the$distro <- NULL +the$os <- NULL +the$platform <- NULL +the$sysinfo <- NULL renv_platform_init <- function() { - the$sysinfo <- Sys.info() + + the$sysinfo <- as.list(Sys.info()) + + the$platform <- if (file.exists("/etc/os-release")) { + renv_properties_read( + path = "/etc/os-release", + delimiter = "=", + dequote = TRUE, + trim = TRUE + ) + } + + the$os <- tolower(the$sysinfo$sysname) + + # NOTE: This is chosen to be compatible with the distribution field + # used within r-system-requirements. + if (the$os == "linux") { + aliases <- list(rhel = "redhat") + the$distro <- alias(the$platform$ID, aliases) + } + } renv_platform_unix <- function() { diff --git a/R/properties.R b/R/properties.R index 439666d4a..6a5fc0f17 100644 --- a/R/properties.R +++ b/R/properties.R @@ -18,6 +18,12 @@ renv_properties_read <- function(path = NULL, # split into key / value pairs index <- regexpr(delimiter, parts, fixed = TRUE) + + # if we couldn't match a delimiter, treat the whole thing as a key + missed <- index == -1 + index[missed] <- nchar(parts)[missed] + 1L + + # perform the subsetting keys <- substring(parts, 1L, index - 1L) vals <- substring(parts, index + 1L) diff --git a/R/purge.R b/R/purge.R index 9e8a691c3..f8ad959dd 100644 --- a/R/purge.R +++ b/R/purge.R @@ -88,7 +88,7 @@ renv_purge_impl <- function(package, missing <- !file.exists(paths) if (any(missing)) { - caution_bullets( + bulletin( "The following entries were not found in the cache:", paths[missing], "They will be ignored." @@ -101,7 +101,7 @@ renv_purge_impl <- function(package, # nocov start if (prompt || renv_verbose()) { - caution_bullets( + bulletin( "The following packages will be purged from the cache:", renv_cache_format_path(paths) ) diff --git a/R/python-virtualenv.R b/R/python-virtualenv.R index e2cdc6405..4841d3eb0 100644 --- a/R/python-virtualenv.R +++ b/R/python-virtualenv.R @@ -95,7 +95,7 @@ renv_python_virtualenv_snapshot <- function(project, prompt, python) { return(FALSE) } - caution_bullets("The following will be written to requirements.txt:", after) + bulletin("The following will be written to requirements.txt:", after) cancel_if(prompt && !proceed()) @@ -123,7 +123,7 @@ renv_python_virtualenv_restore <- function(project, prompt, python) { return(FALSE) } - caution_bullets("The following Python packages will be restored:", diff) + bulletin("The following Python packages will be restored:", diff) cancel_if(prompt && !proceed()) pip_install_requirements(saved, python = python, stream = TRUE) diff --git a/R/rehash.R b/R/rehash.R index 36eefa242..2c6fb2044 100644 --- a/R/rehash.R +++ b/R/rehash.R @@ -54,7 +54,7 @@ renv_rehash_cache <- function(cache, prompt, action, label) { packages <- basename(old)[changed] oldhash <- renv_path_component(old[changed], 2L) newhash <- renv_path_component(new[changed], 2L) - caution_bullets( + bulletin( "The following packages will be re-cached:", sprintf(fmt, format(packages), format(oldhash), format(newhash)), sprintf("Packages will be %s to their new locations in the cache.", label) diff --git a/R/repair.R b/R/repair.R index b09b102b2..0b76380d7 100644 --- a/R/repair.R +++ b/R/repair.R @@ -92,7 +92,7 @@ renv_repair_sources <- function(library, lockfile, project) { # ask used renv_scope_options(renv.verbose = TRUE) - caution_bullets( + bulletin( c( "The following package(s) do not have an explicitly-declared remote source.", "However, renv was available to infer remote sources from their DESCRIPTION file." diff --git a/R/restore.R b/R/restore.R index 11c5655f6..b366e4d7b 100644 --- a/R/restore.R +++ b/R/restore.R @@ -106,6 +106,13 @@ restore <- function(project = NULL, # repair potential issues in the lockfile lockfile <- renv_lockfile_repair(lockfile) + # check for system requirements from these packages + if (config$sysreqs.check(default = renv_platform_linux())) { + records <- renv_lockfile_records(lockfile) + sysreqs <- map(records, `[[`, "SystemRequirements") + renv_sysreqs_check(sysreqs, prompt = prompt) + } + # override repositories if requested repos <- repos %||% config$repos.override() %||% lockfile$R$Repositories diff --git a/R/retrieve.R b/R/retrieve.R index 2a3a46905..e3960efb1 100644 --- a/R/retrieve.R +++ b/R/retrieve.R @@ -772,7 +772,7 @@ renv_retrieve_repos_error_report <- function(record, errors) { fmt <- "The following error(s) occurred while retrieving '%s':" preamble <- sprintf(fmt, record$Package) - caution_bullets( + bulletin( preamble = preamble, values = paste("-", messages) ) @@ -1453,7 +1453,7 @@ renv_retrieve_incompatible_report <- function(package, record, replacement, comp postamble <- with(replacement, sprintf(fmt, Package, Version)) if (!renv_tests_running()) { - caution_bullets( + bulletin( preamble = preamble, values = values, postamble = postamble diff --git a/R/snapshot.R b/R/snapshot.R index 6433ea119..3646daf21 100644 --- a/R/snapshot.R +++ b/R/snapshot.R @@ -430,7 +430,7 @@ renv_snapshot_validate_bioconductor <- function(project, lockfile, libpaths) { fmt <- "%s [installed %s != latest %s]" msg <- sprintf(fmt, format(bad$Package), format(bad$Version), bad$Latest) - caution_bullets( + bulletin( "The following Bioconductor packages appear to be from a separate Bioconductor release:", msg, c( @@ -488,7 +488,7 @@ renv_snapshot_validate_dependencies_available <- function(project, lockfile, lib }) - caution_bullets( + bulletin( "The following required packages are not installed:", sprintf("%s [required by %s]", format(missing), usedby), "Consider reinstalling these packages before snapshotting the lockfile." @@ -552,7 +552,7 @@ renv_snapshot_validate_dependencies_compatible <- function(project, lockfile, li fmt <- "%s requires %s, but version %s is installed" txt <- sprintf(fmt, format(package), format(requires), format(request)) - caution_bullets( + bulletin( "The following package(s) have unsatisfied dependencies:", txt, "Consider updating the required dependencies as appropriate." @@ -633,7 +633,7 @@ renv_snapshot_library <- function(library = NULL, messages <- map_chr(broken, conditionMessage) text <- sprintf("'%s': %s", names(broken), messages) - caution_bullets( + bulletin( "renv was unable to snapshot the following packages:", text, "These packages will likely need to be repaired and / or reinstalled." @@ -665,7 +665,7 @@ renv_snapshot_check_broken_link <- function(paths) { if (!any(broken)) return(paths) - caution_bullets( + bulletin( "The following package(s) have broken symlinks into the cache:", basename(paths)[broken], "Use `renv::repair()` to try and reinstall these packages." @@ -682,7 +682,7 @@ renv_snapshot_check_tempfile <- function(paths) { if (!any(missing)) return(paths) - caution_bullets( + bulletin( "The following folder(s) appear to be left-over temporary directories:", map_chr(paths[missing], renv_path_pretty), "Consider removing these folders from your R library." @@ -699,7 +699,7 @@ renv_snapshot_check_missing_description <- function(paths) { if (!any(missing)) return(paths) - caution_bullets( + bulletin( "The following package(s) are missing their DESCRIPTION files:", sprintf("%s [%s]", format(basename(paths[missing])), paths[missing]), c( @@ -1207,7 +1207,7 @@ renv_snapshot_report_missing <- function(missing, type) { "Use `renv::dependencies()` to see where this package is used in your project." ) - caution_bullets( + bulletin( preamble = preamble, values = sort(unique(missing)), postamble = postamble diff --git a/R/status.R b/R/status.R index 0d8e5be50..b44528557 100644 --- a/R/status.R +++ b/R/status.R @@ -237,7 +237,7 @@ renv_status_check_consistent <- function(lockfile, library, used) { missing <- issues$used & !issues$installed if (all(missing)) { - caution_bullets( + bulletin( preamble = "The following package(s) are used in this project, but are not installed:", values = issues$package[missing] ) diff --git a/R/sysreqs.R b/R/sysreqs.R new file mode 100644 index 000000000..034a9cc9f --- /dev/null +++ b/R/sysreqs.R @@ -0,0 +1,379 @@ + +the$sysreqs <- NULL + +#' R System Requirements +#' +#' Compute the system requirements (system libraries; operating system packages) +#' required by a set of \R packages. +#' +#' This function relies on the database of package system requirements +#' maintained by Posit at , +#' as well as the "meta-CRAN" service at . This +#' service primarily exists to map the (free-form) `SystemRequirements` field +#' used by \R packages to the system packages made available by a particular +#' operating system. +#' +#' As an example, the `curl` R package depends on the `libcurl` system library, +#' and declares this with a `SystemRequirements` field of the form: +#' +#' - libcurl (>= 7.62): libcurl-devel (rpm) or libcurl4-openssl-dev (deb) +#' +#' This dependency can be satisfied with the following command line invocations +#' on different systems: +#' +#' - Debian: `sudo apt install libcurl4-openssl-dev` +#' - Redhat: `sudo dnf install libcurl-devel` +#' +#' and so `sysreqs("curl")` would help provide the name of the package +#' whose installation would satisfy the `libcurl` dependency. +#' +#' +#' @inheritParams renv-params +#' +#' @param packages A vector of \R package names. When `NULL` +#' (the default), the project's package dependencies as reported via +#' [renv::dependencies()] are used. +#' +#' @param local Boolean; should `renv` rely on locally-installed copies of +#' packages when resolving system requirements? When `FALSE`, `renv` will +#' use to resolve the system requirements +#' for these packages. +#' +#' @param check Boolean; should `renv` also check whether the requires system +#' packages appear to be installed on the current system? +#' +#' @param report Boolean; should `renv` also report the commands which could be +#' used to install all of the requisite package dependencies? +#' +#' @param collapse Boolean; when reporting which packages need to be installed, +#' should the report be collapsed into a single installation command? When +#' `FALSE` (the default), a separate installation line is printed for each +#' required system package. +#' +#' @param distro The name of the Linux distribution for which system requirements +#' should be checked -- typical values are "ubuntu", "debian", and "redhat". +#' These should match the distribution names used by the R system requirements +#' database. +#' +#' @examples +#' +#' \dontrun{ +#' +#' # report the required system packages for this system +#' sysreqs() +#' +#' # report the required system packages for a specific OS +#' sysreqs(platform = "ubuntu") +#' +#' } +#' +#' @export +sysreqs <- function(packages = NULL, + ..., + local = FALSE, + check = NULL, + report = TRUE, + distro = NULL, + collapse = FALSE, + project = NULL) +{ + # allow user to provide additional package names as part of '...' + if (!missing(...)) { + dots <- list(...) + names(dots) <- names(dots) %||% rep.int("", length(dots)) + packages <- c(packages, dots[!nzchar(names(dots))]) + } + + # resolve packages + packages <- packages %||% { + project <- renv_project_resolve(project) + deps <- dependencies(project, dev = TRUE) + sort(unique(deps$Package)) + } + + # remove 'base' packages + base <- installed_packages(priority = "base") + packages <- setdiff(packages, base$Package) + names(packages) <- packages + + # set up distro + distro <- distro %||% the$distro + check <- check %||% identical(distro, the$distro) + renv_scope_binding(the, "os", "linux") + renv_scope_binding(the, "distro", distro) + + # compute package records + if (local) { + lockfile <- renv_lockfile_create(project, dev = TRUE) + records <- renv_lockfile_records(lockfile) + } else { + callback <- renv_progress_callback(renv_sysreqs_crandb, length(packages)) + records <- map(packages, callback) + } + + # extract and resolve the system requirements + sysreqs <- map(records, `[[`, "SystemRequirements") + syspkgs <- map(sysreqs, renv_sysreqs_resolve) + + # check the package status if possible + if (check && renv_platform_linux()) + renv_sysreqs_check(sysreqs, prompt = FALSE) + + # report installation commands if requested + if (report) { + + all <- sort(unique(unlist(syspkgs))) + installer <- renv_sysreqs_installer(distro) + body <- if (collapse) paste(all, collapse = " ") else all + message <- paste("sudo", installer, "-y", body) + + if (interactive()) { + preamble <- "The requisite system packages can be installed with:" + bulletin(preamble, message) + } else { + writeLines(message) + } + + } + + # return result + invisible(syspkgs) + +} + +renv_sysreqs_crandb <- function(package) { + tryCatch( + renv_sysreqs_crandb_impl(package), + error = warnify + ) +} + +renv_sysreqs_crandb_impl <- function(package) { + memoize( + key = package, + value = renv_sysreqs_crandb_impl_one(package), + scope = "sysreqs" + ) +} + +renv_sysreqs_crandb_impl_one <- function(package) { + url <- paste("https://crandb.r-pkg.org", package, sep = "/") + destfile <- tempfile("renv-crandb-", fileext = ".json") + download(url, destfile = destfile, quiet = TRUE) + renv_json_read(destfile) +} + +renv_sysreqs_resolve <- function(sysreqs, rules = renv_sysreqs_rules()) { + matches <- map(sysreqs, renv_sysreqs_match, rules) + unlist(matches, use.names = FALSE) +} + +renv_sysreqs_read <- function(package) { + desc <- renv_description_read(package) + desc[["SystemRequirements"]] %||% "" +} + +renv_sysreqs_rules <- function() { + the$sysreqs <- the$sysreqs %||% renv_sysreqs_rules_impl() +} + +renv_sysreqs_rules_impl <- function() { + rules <- system.file("sysreqs/sysreqs.json", package = "renv") + renv_json_read(rules) +} + +renv_sysreqs_match <- function(sysreq, rules = renv_sysreqs_rules()) { + map(rules, renv_sysreqs_match_impl, sysreq = sysreq) +} + +renv_sysreqs_match_impl <- function(sysreq, rule) { + + # check for a match in the declared system requirements + pattern <- paste(rule$patterns, collapse = "|") + matches <- grepl(pattern, sysreq, ignore.case = TRUE, perl = TRUE) + + # if we got a match, pull out the dependent packages + if (matches) { + for (dependency in rule$dependencies) { + for (constraint in dependency$constraints) { + if (constraint$os == the$os) { + if (constraint$distribution == the$distro) { + return(dependency$packages) + } + } + } + } + } + +} + +renv_sysreqs_aliases <- function(type, syspkgs) { + case( + type == "deb" ~ renv_sysreqs_aliases_deb(syspkgs), + type == "rpm" ~ renv_sysreqs_aliases_rpm(syspkgs) + ) +} + +renv_sysreqs_aliases_deb <- function(pkgs) { + + # https://www.debian.org/doc/debian-policy/ch-relationships.html#s-virtual + # + # > A virtual package is one which appears in the Provides control field of + # > another package. The effect is as if the package(s) which provide a + # > particular virtual package name had been listed by name everywhere the + # > virtual package name appears. (See also Virtual packages) + # + # read the package database, look which packages 'provide' others, + # and then reverse that map to map virtual packages to the concrete + # package which provides them + # + command <- "dpkg-query -W -f '${Package}=${Provides}\n'" + output <- system(command, intern = TRUE) + result <- renv_properties_read(text = output, delimiter = "=") + + # keep only packages which provide other packages + aliases <- result[nzchar(result)] + + # a package might provide multiple other packages, so split those + splat <- lapply(aliases, function(alias) { + parts <- strsplit(alias, ",\\s*", perl = TRUE)[[1L]] + names(renv_properties_read(text = parts, delimiter = " ")) + }) + + # reverse the map, so that we can map virtual packages to the + # concrete packages which they refer to + envir <- new.env(parent = emptyenv()) + enumerate(splat, function(package, virtuals) { + for (virtual in virtuals) { + envir[[virtual]] <<- c(envir[[virtual]], package) + } + }) + + # convert to intermediate list + result <- as.list(envir, all.names = TRUE) + + # return as named character vector + convert(result, type = "character") + +} + +renv_sysreqs_aliases_rpm <- function(pkgs) { + + # for each package, check if there's another package that 'provides' it + fmt <- "rpm --query --whatprovides %s --queryformat '%%{Name}\n'" + args <- paste(renv_shell_quote(pkgs), collapse = " ") + command <- sprintf(fmt, args) + result <- suppressWarnings(system(command, intern = TRUE)) + + # return as named vector, mapping virtual packages to 'real' packages + matches <- grep("no package provides", result, fixed = TRUE, invert = TRUE) + aliases <- result[matches] + names(aliases) <- pkgs[matches] + + convert(aliases, type = "character") + +} + +renv_sysreqs_check <- function(sysreqs, prompt) { + + type <- case( + nzchar(Sys.which("dpkg")) ~ "deb", + nzchar(Sys.which("rpm")) ~ "rpm", + ~ stop("don't know how to check sysreqs on this system") + ) + + # figure out which system packages are required + syspkgs <- map(sysreqs, renv_sysreqs_resolve) + + # collect list of all packages discovered + allsyspkgs <- sort(unique(unlist(syspkgs, use.names = FALSE))) + + # some packages might be virtual packages, and won't be reported as installed + # when queried. try to resolve those to the actual underlying packages. + # some examples follows: + # + # Fedora 41: zlib-devel => zlib-ng-compat-devel + # Ubuntu 24.04: libfreetype6-dev => libfreetype-dev + # + aliases <- renv_sysreqs_aliases(type, allsyspkgs) + resolvedpkgs <- alias(allsyspkgs, aliases) + + # list all currently-installed packages + installedpkgs <- case( + type == "deb" ~ system("dpkg-query -W -f '${Package}\n'", intern = TRUE), + type == "rpm" ~ system("rpm --query --all --queryformat='%{Name}\n'", intern = TRUE) + ) + + # check for matches + misspkgs <- setdiff(resolvedpkgs, installedpkgs) + if (empty(misspkgs)) + return(TRUE) + + # notify the user + preamble <- "The following required system packages are not installed:" + postamble <- "The R packages depending on these system packages may fail to install." + parts <- map(misspkgs, function(misspkg) { + needs <- map_lgl(syspkgs, function(syspkg) misspkg %in% syspkg) + list(misspkg, names(syspkgs)[needs]) + }) + + lhs <- extract_chr(parts, 1L) + rhs <- map_chr(extract(parts, 2L), paste, collapse = ", ") + messages <- sprintf("%s [required by %s]", format(lhs), rhs) + bulletin(preamble, messages, postamble) + + installer <- case( + nzchar(Sys.which("apt")) ~ "apt install", + nzchar(Sys.which("dnf")) ~ "dnf install", + nzchar(Sys.which("pacman")) ~ "pacman -S", + nzchar(Sys.which("yum")) ~ "yum install", + nzchar(Sys.which("zypper")) ~ "zypper install", + ) + + preamble <- "An administrator can install these packages with:" + command <- paste("sudo", installer, paste(misspkgs, collapse = " ")) + bulletin(preamble, command) + + cancel_if(prompt && !proceed()) + +} + +renv_sysreqs_installer <- function(distro) { + case( + distro == "debian" ~ "apt install", + distro == "redhat" ~ "dnf install", + distro == "ubuntu" ~ "apt install", + ~ "" + ) +} + +renv_sysreqs_update <- function() { + + # save path to sysreqs folder + dest <- renv_path_normalize("inst/sysreqs/sysreqs.json") + + # move to temporary directory + renv_scope_tempdir() + + # clone the system requirements repository + args <- c("clone", "--depth", "1", "https://github.com/rstudio/r-system-requirements") + renv_system_exec("git", args, action = "cloing rstudio/r-system-requirements") + + # read all of the rules from the requirements repository + files <- list.files( + path = "r-system-requirements/rules", + pattern = "[.]json$", + full.names = TRUE + ) + + contents <- map(files, renv_json_read) + + # give names without extensions for these files + names <- basename(files) + idx <- map_int(gregexpr(".", names, fixed = TRUE), tail, n = 1L) + names(contents) <- substr(names, 1L, idx - 1L) + + # write to sysreqs.json + renv_json_write(contents, file = dest) + +} diff --git a/R/tests.R b/R/tests.R index 4f960e9c2..cd36f9563 100644 --- a/R/tests.R +++ b/R/tests.R @@ -64,26 +64,26 @@ renv_test_retrieve <- function(record) { renv_tests_diagnostics <- function() { # print library paths - caution_bullets( + bulletin( "The following R libraries are set:", paste("-", .libPaths()) ) # print repositories repos <- getOption("repos") - caution_bullets( + bulletin( "The following repositories are set:", paste(names(repos), repos, sep = ": ") ) # print renv root - caution_bullets( + bulletin( "The following renv root directory is being used:", paste("-", paths$root()) ) # print cache root - caution_bullets( + bulletin( "The following renv cache directory is being used:", paste("-", paths$cache()) ) @@ -102,7 +102,7 @@ renv_tests_diagnostics <- function() { path <- Sys.getenv("PATH") splat <- strsplit(path, .Platform$path.sep, fixed = TRUE)[[1]] - caution_bullets( + bulletin( "The following PATH is set:", paste("-", splat) ) @@ -120,7 +120,7 @@ renv_tests_diagnostics <- function() { vals <- Sys.getenv(envvars, unset = "") vals[vals != ""] <- renv_json_quote(vals[vals != ""]) - caution_bullets( + bulletin( "The following environment variables of interest are set:", paste(keys, vals, sep = " : ") ) diff --git a/R/update.R b/R/update.R index 1e80cb933..41e4cb359 100644 --- a/R/update.R +++ b/R/update.R @@ -306,7 +306,7 @@ update <- function(packages = NULL, if (!empty(missing)) { if (prompt || renv_verbose()) { - caution_bullets( + bulletin( "The following package(s) are not currently installed:", missing, "The latest available versions of these packages will be installed instead." @@ -457,7 +457,7 @@ renv_update_errors_emit_impl <- function(key, preamble, postamble) { sprintf("%s: %s", format(package), errmsg) }) - caution_bullets( + bulletin( preamble = preamble, values = messages, postamble = postamble diff --git a/R/zzz.R b/R/zzz.R index 387bd8cb8..a2d770b05 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -3,10 +3,10 @@ # NOTE: needs to be visible to embedded instances of renv as well the$envir_self <<- renv_envir_self() - + # load extensions if available renv_ext_onload(libname, pkgname) - + # make sure renv (and packages using renv!!!) use tempdir for storage # when running tests, or R CMD check if (checking() || testing()) { @@ -14,7 +14,7 @@ # set root directory root <- Sys.getenv("RENV_PATHS_ROOT", unset = tempfile("renv-root-")) Sys.setenv(RENV_PATHS_ROOT = root) - + # unset on exit reg.finalizer(renv_envir_self(), function(envir) { if (identical(root, Sys.getenv("RENV_PATHS_ROOT", unset = NA))) @@ -29,14 +29,12 @@ } } - + # don't lock sandbox while testing / checking if (testing() || checking() || devmode()) { options(renv.sandbox.locking_enabled = FALSE) Sys.setenv(RENV_SANDBOX_LOCKING_ENABLED = FALSE) } - - renv_defer_init() renv_metadata_init() @@ -53,7 +51,7 @@ renv_sdkroot_init() renv_watchdog_init() renv_tempdir_init() - + if (!renv_metadata_embedded()) { # TODO: It's not clear if these callbacks are safe to use when renv is diff --git a/_pkgdown.yml b/_pkgdown.yml index a6c5c1cf0..e8a0edf1d 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -69,6 +69,7 @@ reference: - consent - diagnostics - run + - sysreqs - title: internal contents: @@ -77,7 +78,6 @@ reference: - renv-package - retrieve - sandbox - - sandbox articles: diff --git a/inst/config.yml b/inst/config.yml index ff80ce934..c6439bff4 100644 --- a/inst/config.yml +++ b/inst/config.yml @@ -321,6 +321,14 @@ description: > Check that the project library is synchronized with the lockfile on load? +- name: "sysreqs.check" + type: "logical[1]" + default: true + description: > + Check whether the requisite system packages are installed during package + installation and restore? This feature uses the R System Requirements + database maintained at . + - name: "updates.check" type: "logical[1]" default: false diff --git a/inst/sysreqs/sysreqs.json b/inst/sysreqs/sysreqs.json new file mode 100644 index 000000000..6303cd330 --- /dev/null +++ b/inst/sysreqs/sysreqs.json @@ -0,0 +1,13727 @@ +{ + "apparmor": { + "patterns": [ + "\\bapparmor\\b", + "\\blibapparmor\\b" + ], + "dependencies": [ + { + "packages": [ + "libapparmor-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libapparmor-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "libapparmor-dev", + "libapparmor" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "atk": { + "patterns": [ + "\\batk\\b" + ], + "dependencies": [ + { + "packages": [ + "libatk1.0-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "atk-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libatk-1_0-0" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "15.6" + ] + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "15.6" + ] + } + ] + }, + { + "packages": [ + "atk-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "15.3", + "15.4", + "15.5" + ] + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "15.3", + "15.4", + "15.5" + ] + } + ] + }, + { + "packages": [ + "atk-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine", + "versions": [ + "3.15", + "3.16" + ] + } + ] + }, + { + "packages": [ + "atkmm2.36-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine", + "versions": [ + "edge" + ] + } + ] + }, + { + "packages": [ + "atkmm-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine", + "versions": [ + "3.17", + "3.18", + "3.19", + "3.20" + ] + } + ] + } + ] + }, + "automake": { + "patterns": [ + "\\bautomake\\b" + ], + "dependencies": [ + { + "packages": [ + "automake" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "automake" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "automake" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "automake" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "berkeleydb": { + "patterns": [ + "\\bberkeley db\\b", + "\\blibdb\\b" + ], + "dependencies": [ + { + "packages": [ + "libdb-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libdb-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libdb-4_8-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "db-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "blender": { + "patterns": [ + "\\bblender\\b" + ], + "dependencies": [ + { + "packages": [ + "blender" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "blender" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "blender" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "12.3", + "15.0", + "15.2" + ] + } + ] + }, + { + "packages": [ + "blender" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine", + "versions": [ + "3.16", + "3.17", + "3.18", + "3.19", + "3.20", + "edge" + ] + } + ] + } + ] + }, + "boost": { + "patterns": [ + "\\Boost\\b" + ], + "dependencies": [ + { + "packages": [ + "libboost-all-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "boost-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + } + ] + }, + { + "packages": [ + "boost-gnu-hpc-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "boost-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "bowtie2": { + "patterns": [ + "\\bbowtie2\\b" + ], + "dependencies": [ + { + "packages": [ + "bowtie2" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "bowtie2" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + } + ] + }, + "bwidget": { + "patterns": [ + "\\bbwidget\\b" + ], + "dependencies": [ + { + "packages": [ + "bwidget" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "bwidget" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "bwidget" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "12.3" + ] + } + ] + } + ] + }, + "cairo": { + "patterns": [ + "\\bcairo\\b" + ], + "dependencies": [ + { + "packages": [ + "libcairo2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "cairo-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "cairo-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "cairo-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-cairo", + "mingw-w64-i686-cairo" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "chrome": { + "patterns": [ + "\\bchrome\\b", + "\\bchromium\\b" + ], + "dependencies": [ + { + "pre_install": [ + { + "command": "apt-get install -y software-properties-common" + }, + { + "command": "add-apt-repository -y ppa:xtradeb/apps" + }, + { + "command": "apt-get update" + } + ], + "packages": [ + "chromium" + ], + "post_install": [], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu", + "versions": [ + "22.04", + "24.04" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "[ $(which google-chrome) ] || apt-get install -y gnupg curl" + }, + { + "command": "[ $(which google-chrome) ] || curl -fsSL -o /tmp/google-chrome.deb https://dl.google.com/linux/direct/google-chrome-stable_current_amd64.deb" + }, + { + "command": "[ $(which google-chrome) ] || DEBIAN_FRONTEND='noninteractive' apt-get install -y /tmp/google-chrome.deb" + } + ], + "packages": [], + "post_install": [ + { + "command": "rm -f /tmp/google-chrome.deb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu", + "versions": [ + "20.04" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + }, + { + "command": "dnf install -y epel-release" + } + ], + "packages": [ + "chromium" + ], + "post_install": [], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + }, + { + "command": "dnf install -y epel-release" + } + ], + "packages": [ + "chromium" + ], + "post_install": [], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "packages": [ + "chromium" + ], + "post_install": [], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "packages": [ + "chromium" + ], + "post_install": [], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "pre_install": [], + "packages": [ + "chromium" + ], + "post_install": [], + "constraints": [ + { + "os": "linux", + "distribution": "debian" + }, + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "pre_install": [ + { + "command": "yum install -y which" + }, + { + "command": "[ $(which google-chrome) ] || curl -fsSL -o /tmp/google-chrome.rpm https://dl.google.com/linux/chrome/rpm/stable/x86_64/google-chrome-stable-125.0.6422.141-1.x86_64.rpm" + }, + { + "command": "[ $(which google-chrome) ] || yum install -y /tmp/google-chrome.rpm" + } + ], + "packages": [], + "post_install": [ + { + "command": "rm -f /tmp/google-chrome.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7", + "8" + ] + } + ] + } + ] + }, + "cmake": { + "patterns": [ + "\\bcmake\\b" + ], + "dependencies": [ + { + "packages": [ + "cmake" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "cmake" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8", + "9" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "cmake", + "cmake3" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "cmake", + "cmake3" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "cmake" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "cmake" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "coin-or-clp": { + "patterns": [ + "\\bcoin-or clp\\b" + ], + "dependencies": [ + { + "packages": [ + "coinor-libclp-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "coin-or-Clp-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-coinor-cbc", + "mingw-w64-i686-coinor-cbc" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "coinor-symphony": { + "patterns": [ + "\\bsymphony\\b", + "\\blibsymphony\\b" + ], + "dependencies": [ + { + "packages": [ + "coinor-symphony", + "coinor-libsymphony-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "coin-or-SYMPHONY", + "coin-or-SYMPHONY-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + } + ] + }, + "cuda": { + "patterns": [ + "\\bnvcc\\b", + "\\bcuda\\b" + ], + "dependencies": [ + { + "packages": [ + "nvidia-cuda-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + } + ] + } + ] + }, + "dcraw": { + "patterns": [ + "\\bdcraw\\b" + ], + "dependencies": [ + { + "packages": [ + "dcraw" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "dcraw" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "dcraw" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "12.3" + ] + } + ] + } + ] + }, + "eigen": { + "patterns": [ + "\\beigen3?\\b" + ], + "dependencies": [ + { + "packages": [ + "libeigen3-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "eigen3-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "eigen3-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "eigen3-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "eigen3-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "eigen3-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "eigen3-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "eigen3-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "eigen-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "exiftool": { + "patterns": [ + "\\bexiftool\\b" + ], + "dependencies": [ + { + "packages": [ + "libimage-exiftool-perl" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "perl-Image-ExifTool" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "perl-Image-ExifTool" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "perl-Image-ExifTool" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "perl-Image-ExifTool" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "perl-Image-ExifTool" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "perl-Image-ExifTool" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "perl-Image-ExifTool" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "perl-image-exiftool" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "fftw3": { + "patterns": [ + "\\bfftw\\b", + "\\bfftw3\\b", + "\\blibfftw3\\b" + ], + "dependencies": [ + { + "packages": [ + "libfftw3-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "fftw-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "fftw3-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "fftw-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-fftw", + "mingw-w64-i686-fftw" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "flint": { + "patterns": [ + "\\bflint\\b" + ], + "dependencies": [ + { + "packages": [ + "libflint-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "flint-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + } + ] + }, + "fluidsynth": { + "patterns": [ + "\\bfluidsynth\\b" + ], + "dependencies": [ + { + "packages": [ + "libfluidsynth-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "fluidsynth-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "fluidsynth-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + } + ] + }, + { + "packages": [ + "fluidsynth-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "fontconfig": { + "patterns": [ + "\\bfontconfig\\b" + ], + "dependencies": [ + { + "packages": [ + "libfontconfig1-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "fontconfig-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "sle" + }, + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "fontconfig-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "freetype": { + "patterns": [ + "\\bfreetype\\b", + "\\bfreetype2\\b" + ], + "dependencies": [ + { + "packages": [ + "libfreetype6-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "freetype-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "freetype2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "freetype-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-freetype", + "mingw-w64-i686-freetype" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "fribidi": { + "patterns": [ + "\\bfribidi\\b" + ], + "dependencies": [ + { + "packages": [ + "libfribidi-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "fribidi-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "fribidi-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "gdal": { + "patterns": [ + "\\bgdal\\b", + "\\blibgdal\\b" + ], + "dependencies": [ + { + "packages": [ + "libgdal-dev", + "gdal-bin" + ], + "pre_install": [ + { + "command": "apt-get install -y software-properties-common" + }, + { + "command": "add-apt-repository -y ppa:ubuntugis/ppa" + }, + { + "command": "apt-get update" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu", + "versions": [ + "14.04", + "16.04" + ] + } + ] + }, + { + "packages": [ + "libgdal-dev", + "gdal-bin" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "gdal-devel", + "gdal" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "gdal-devel", + "gdal" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "packages": [ + "gdal-devel", + "gdal" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + }, + { + "command": "dnf install -y epel-release" + } + ], + "packages": [ + "gdal-devel", + "gdal", + "sqlite-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "packages": [ + "gdal-devel", + "gdal", + "sqlite-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "gdal-devel", + "gdal" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + }, + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "gdal-devel", + "gdal" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "gdal-devel", + "gdal" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "gdal-devel", + "gdal" + ], + "pre_install": [ + { + "command": "zypper repos openSUSE_Backports_SLE-12 || zypper addrepo https://download.opensuse.org/repositories/openSUSE:/Backports:/SLE-12/standard/openSUSE:Backports:SLE-12.repo" + }, + { + "command": "zypper --gpg-auto-import-keys refresh" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "sle", + "versions": [ + "12.3" + ] + } + ] + }, + { + "packages": [ + "gdal-dev", + "gdal-tools" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "geos": { + "patterns": [ + "\\bgeos\\b" + ], + "dependencies": [ + { + "packages": [ + "libgeos-dev" + ], + "pre_install": [ + { + "command": "apt-get install -y software-properties-common" + }, + { + "command": "add-apt-repository -y ppa:ubuntugis/ppa" + }, + { + "command": "apt-get update" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu", + "versions": [ + "14.04", + "16.04" + ] + } + ] + }, + { + "packages": [ + "libgeos-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "geos-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "geos-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "geos-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "geos-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "packages": [ + "geos-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "geos-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "geos-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "geos-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-geos", + "mingw-w64-i686-geos" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "ggobi": { + "patterns": [ + "\\bggobi\\b" + ], + "dependencies": [ + { + "packages": [ + "ggobi" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "ggobi-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "ggobi-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + } + ] + }, + "git": { + "patterns": [ + "\\bgit\\b" + ], + "dependencies": [ + { + "packages": [ + "git" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "git" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "git" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "git" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "glib": { + "patterns": [ + "\\bglib\\b" + ], + "dependencies": [ + { + "packages": [ + "libglib2.0-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "glib2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "glib2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "glib-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "glpk": { + "patterns": [ + "\\bglpk\\b" + ], + "dependencies": [ + { + "packages": [ + "libglpk-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "glpk-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "packages": [ + "glpk-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "glpk-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "glpk-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "glpk-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "glpk-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "glpk-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-glpk", + "mingw-w64-i686-glpk" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "glu": { + "patterns": [ + "\\bglu\\b" + ], + "dependencies": [ + { + "packages": [ + "libglu1-mesa-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "mesa-libGLU-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "glu-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "glu-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "gmp": { + "patterns": [ + "\\bgmp\\b" + ], + "dependencies": [ + { + "packages": [ + "libgmp3-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "gmp-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "gmp-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "gmp-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-gmp", + "mingw-w64-i686-gmp" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "gnumake": { + "patterns": [ + "\\bgnu make\\b", + "\\bgmake\\b" + ], + "dependencies": [ + { + "packages": [ + "make" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "make" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "make" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "make" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "gpgme": { + "patterns": [ + "\\bgpgme\\b" + ], + "dependencies": [ + { + "packages": [ + "libgpgme11-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "gpgme-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "gpgme-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "gpgme-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "gpgme" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7", + "8" + ] + } + ] + }, + { + "packages": [ + "gpgme-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libgpgme-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "gpgme-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "grpcpp": { + "patterns": [ + "\\blibgrpc\\+\\+" + ], + "dependencies": [ + { + "packages": [ + "libgrpc++-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "grpc-devel", + "pkgconf" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "pre_install": [ + { + "command": "yum install -y epel-release" + }, + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "packages": [ + "grpc-devel", + "pkgconf" + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "grpc-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "grpc-devel", + "pkgconf" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "grpc-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "gsl": { + "patterns": [ + "\\blibgsl\\b", + "\\bgsl\\b", + "\\bgnu scientific library\\b" + ], + "dependencies": [ + { + "packages": [ + "libgsl0-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "gsl-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7", + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8", + "9" + ] + } + ] + }, + { + "packages": [ + "gsl-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "gsl-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "gsl-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-gsl", + "mingw-w64-i686-gsl" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "gtk": { + "patterns": [ + "\\bgtk\\b" + ], + "dependencies": [ + { + "packages": [ + "libgtk2.0-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "gtk2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "gtk2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "gtk+2.0-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "harfbuzz": { + "patterns": [ + "\\bharfbuzz\\b" + ], + "dependencies": [ + { + "packages": [ + "libharfbuzz-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "harfbuzz-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "harfbuzz-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "haveged": { + "patterns": [ + "\\bhaveged\\b" + ], + "dependencies": [ + { + "packages": [ + "haveged" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "haveged-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "haveged-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "haveged-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "haveged-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "haveged-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "haveged-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "haveged-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "haveged" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "haveged-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "hdf5": { + "patterns": [ + "\\bhdf5\\b", + "\\blibhdf5\\b" + ], + "dependencies": [ + { + "packages": [ + "libhdf5-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "hdf5-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "hdf5-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "hdf5-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + }, + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "packages": [ + "hdf5-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "hdf5-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "hdf5-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "hdf5-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "hdf5-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "hdf5-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "12.3" + ] + } + ] + }, + { + "packages": [ + "hdf5-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-hdf5", + "mingw-w64-i686-hdf5" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "hiredis": { + "patterns": [ + "\\bhiredis\\b" + ], + "dependencies": [ + { + "packages": [ + "libhiredis-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "hiredis-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "hiredis-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "hiredis-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "hiredis-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "hiredis-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "hiredis-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "hiredis-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "hiredis-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "imagej": { + "patterns": [ + "\\bimagej\\b" + ], + "dependencies": [ + { + "packages": [ + "imagej" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "imagej" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + } + ] + }, + "imagemagick": { + "patterns": [ + "\\bimagemagick\\b", + "\\bimage magick\\b" + ], + "dependencies": [ + { + "packages": [ + "libmagick++-dev", + "gsfonts" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "ImageMagick-devel", + "ImageMagick-c++-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "ImageMagick-devel", + "ImageMagick-c++-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + }, + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "ImageMagick-devel", + "ImageMagick-c++-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "ImageMagick-c++-devel", + "ImageMagick-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "ImageMagick-c++-devel", + "ImageMagick-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "ImageMagick-c++-devel", + "ImageMagick-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "ImageMagick-devel", + "libMagick++-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "imagemagick-dev", + "imagemagick-c++" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "jags": { + "patterns": [ + "\\bjags\\b" + ], + "dependencies": [ + { + "packages": [ + "jags" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + } + ] + }, + "java": { + "patterns": [ + "\\bjava\\b" + ], + "dependencies": [ + { + "post_install": [ + { + "command": "R CMD javareconf" + } + ], + "packages": [ + "default-jdk" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "post_install": [ + { + "command": "R CMD javareconf" + } + ], + "packages": [ + "java-1.8.0-openjdk-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7", + "8" + ] + } + ] + }, + { + "post_install": [ + { + "command": "R CMD javareconf" + } + ], + "packages": [ + "java-11-openjdk-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "post_install": [ + { + "command": "R CMD javareconf" + } + ], + "packages": [ + "java-1_8_0-openjdk-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "15.3" + ] + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "15.3" + ] + } + ] + }, + { + "post_install": [ + { + "command": "R CMD javareconf" + } + ], + "packages": [ + "java-11-openjdk-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "15.4", + "15.5", + "15.6" + ] + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "15.4", + "15.5", + "15.6" + ] + } + ] + }, + { + "packages": [ + "java-jdk" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "latex": { + "patterns": [ + "\\blatex\\b" + ], + "dependencies": [ + { + "packages": [ + "texlive" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "texlive" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "texlive" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "texlive" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "leptonica": { + "patterns": [ + "\\bleptonica\\b" + ], + "dependencies": [ + { + "packages": [ + "libleptonica-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "leptonica-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "leptonica-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "leptonica-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "leptonica-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "leptonica-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "leptonica-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "leptonica-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "leptonica-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-leptonica", + "mingw-w64-i686-leptonica" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "libarchive": { + "patterns": [ + "\\blibarchive\\b" + ], + "dependencies": [ + { + "packages": [ + "libarchive-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libarchive-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libarchive-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "libarchive-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libarchive" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7", + "8" + ] + } + ] + }, + { + "packages": [ + "libarchive-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "libarchive-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libarchive3-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "libarchive-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "libarchive-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-libarchive", + "mingw-w64-i686-libarchive" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "libavfilter": { + "patterns": [ + "\\blibavfilter\\b" + ], + "dependencies": [ + { + "packages": [ + "libavfilter-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libavfilter-free-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libavfilter-free-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + }, + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libavfilter-free-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "ffmpeg-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + }, + { + "command": "yum install -y --nogpgcheck https://mirrors.rpmfusion.org/free/el/rpmfusion-free-release-$(rpm -E %rhel).noarch.rpm https://mirrors.rpmfusion.org/nonfree/el/rpmfusion-nonfree-release-$(rpm -E %rhel).noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "ffmpeg-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + }, + { + "command": "yum install -y --nogpgcheck https://mirrors.rpmfusion.org/free/el/rpmfusion-free-release-$(rpm -E %rhel).noarch.rpm https://mirrors.rpmfusion.org/nonfree/el/rpmfusion-nonfree-release-$(rpm -E %rhel).noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "ffmpeg-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + }, + { + "command": "dnf install -y epel-release" + }, + { + "command": "dnf install -y --nogpgcheck https://mirrors.rpmfusion.org/free/el/rpmfusion-free-release-$(rpm -E %rhel).noarch.rpm https://mirrors.rpmfusion.org/nonfree/el/rpmfusion-nonfree-release-$(rpm -E %rhel).noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + }, + { + "command": "dnf install -y --nogpgcheck https://mirrors.rpmfusion.org/free/el/rpmfusion-free-release-$(rpm -E %rhel).noarch.rpm https://mirrors.rpmfusion.org/nonfree/el/rpmfusion-nonfree-release-$(rpm -E %rhel).noarch.rpm" + } + ], + "packages": [ + "ffmpeg-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "ffmpeg-4-libavfilter-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "ffmpeg-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libbsd": { + "patterns": [ + "\\blibbsd\\b" + ], + "dependencies": [ + { + "packages": [ + "libbsd-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libbsd-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libbsd-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "libbsd-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "libbsd-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "libbsd-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "libbsd-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "libbsd-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libbsd-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "libbsd-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libbz2": { + "patterns": [ + "\\blibbz2\\b" + ], + "dependencies": [ + { + "packages": [ + "libbz2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "bzip2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libbz2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "bzip2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libcurl": { + "patterns": [ + "\\blibcurl\\b" + ], + "dependencies": [ + { + "packages": [ + "libcurl4-openssl-dev" + ], + "apt_satisfy": [ + "libcurl4-openssl-dev | libcurl4-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libcurl-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libcurl-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "curl-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-curl", + "mingw-w64-i686-curl" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "libgit2": { + "patterns": [ + "\\blibgit2\\b" + ], + "dependencies": [ + { + "packages": [ + "libgit2-dev" + ], + "pre_install": [ + { + "command": "apt-get install -y software-properties-common" + }, + { + "command": "add-apt-repository -y ppa:cran/libgit2" + }, + { + "command": "apt-get update" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu", + "versions": [ + "16.04", + "18.04" + ] + } + ] + }, + { + "packages": [ + "libgit2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu", + "versions": [ + "20.04", + "22.04", + "24.04" + ] + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libgit2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libgit2-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "libgit2-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "libgit2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "libgit2_1.7-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "libgit2-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libgit2_1.7-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "libgit2-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libgit2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "15.0", + "15.2", + "15.3", + "15.4", + "15.5", + "15.6" + ] + } + ] + }, + { + "packages": [ + "libgit2-24" + ], + "constraints": [ + { + "os": "linux", + "distribution": "sle", + "versions": [ + "12.3" + ] + } + ] + }, + { + "packages": [ + "libgit2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libicu": { + "patterns": [ + "\\bicu4c\\b" + ], + "dependencies": [ + { + "packages": [ + "libicu-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libicu-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libicu" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "libicu-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "42.3", + "15.0", + "15.2" + ] + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "12.3", + "15.0", + "15.2" + ] + } + ] + }, + { + "packages": [ + "icu.691-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "15.3", + "15.4", + "15.5" + ] + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "15.3", + "15.4", + "15.5" + ] + } + ] + }, + { + "packages": [ + "libicu73_2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "15.6" + ] + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "15.6" + ] + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-icu", + "mingw-w64-i686-icu" + ], + "constraints": [ + { + "os": "windows" + } + ] + }, + { + "packages": [ + "icu-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libjpeg": { + "patterns": [ + "\\blibjpeg\\b", + "\\bjpeg\\b" + ], + "dependencies": [ + { + "packages": [ + "libjpeg-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libjpeg-turbo-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libjpeg8-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "jpeg-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-libjpeg", + "mingw-w64-i686-libjpeg" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "libjq": { + "patterns": [ + "\\blibjq\\b" + ], + "dependencies": [ + { + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "packages": [ + "jq-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "jq-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "jq-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "jq-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "packages": [ + "jq-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "jq-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "jq-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libjq-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libjq-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "sle" + }, + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "jq-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "liblzma": { + "patterns": [ + "\\bliblzma\\b" + ], + "dependencies": [ + { + "packages": [ + "liblzma-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "xz-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "xz-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "xz-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libmagic": { + "patterns": [ + "\\blibmagic\\b" + ], + "dependencies": [ + { + "packages": [ + "libmagic-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "file-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "file-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "file-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "file-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "file-libs" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7", + "8" + ] + } + ] + }, + { + "packages": [ + "file-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "file-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "file-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libmecab": { + "patterns": [ + "\\blibmecab\\b", + "\\bmecab\\b" + ], + "dependencies": [ + { + "packages": [ + "libmecab-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "packages": [ + "mecab-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "mecab-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "mecab-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "packages": [ + "mecab-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "packages": [ + "mecab-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + } + ] + }, + "libmysqlclient": { + "patterns": [ + "\\blibmysqlclient\\b" + ], + "dependencies": [ + { + "packages": [ + "libmysqlclient-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + } + ] + }, + { + "packages": [ + "libmariadb-dev-compat", + "libmariadb-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "mysql-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "mariadb-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7", + "8" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7", + "8" + ] + }, + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "mariadb-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "mariadb-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libmysqlclient-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "42.3" + ] + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "12.3" + ] + } + ] + }, + { + "packages": [ + "libmariadb-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "15.0", + "15.2", + "15.3", + "15.4", + "15.5", + "15.6" + ] + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "15.0", + "15.2", + "15.3", + "15.4", + "15.5", + "15.6" + ] + } + ] + }, + { + "packages": [ + "mariadb-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libpng": { + "patterns": [ + "\\blibpng\\b" + ], + "dependencies": [ + { + "packages": [ + "libpng-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libpng-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libpng16-compat-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-libpng", + "mingw-w64-i686-libpng" + ], + "constraints": [ + { + "os": "windows" + } + ] + }, + { + "packages": [ + "libpng-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libprotobuf": { + "patterns": [ + "\\blibprotobuf\\b" + ], + "dependencies": [ + { + "packages": [ + "libprotobuf-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "protobuf-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "protobuf-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "packages": [ + "protobuf-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "protobuf-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "protobuf-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "protobuf" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + } + ], + "packages": [ + "protobuf-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "protobuf-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "protobuf-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "protobuf-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-protobuf", + "mingw-w64-i686-protobuf" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "librsvg2": { + "patterns": [ + "\\blibrsvg2\\b" + ], + "dependencies": [ + { + "packages": [ + "librsvg2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "librsvg2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "librsvg-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "librsvg-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libsecret": { + "patterns": [ + "\\blibsecret\\b" + ], + "dependencies": [ + { + "packages": [ + "libsecret-1-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libsecret-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libsecret-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "libsecret-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libsndfile": { + "patterns": [ + "\\blibsndfile\\b" + ], + "dependencies": [ + { + "packages": [ + "libsndfile1-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libsndfile-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libsndfile-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "libsndfile-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "libsndfile-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libsndfile" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7", + "8" + ] + } + ] + }, + { + "packages": [ + "libsndfile-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libsndfile-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "libsndfile-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libsodium": { + "patterns": [ + "\\blibsodium\\b" + ], + "dependencies": [ + { + "packages": [ + "libsodium-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libsodium-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libsodium-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "libsodium-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "libsodium-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "libsodium-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "libsodium-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "libsodium-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libsodium-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "libsodium-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libssh": { + "patterns": [ + "\\blibssh\\b" + ], + "dependencies": [ + { + "packages": [ + "libssh-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libssh-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libssh-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "libssh-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "libssh" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7", + "8" + ] + } + ] + }, + { + "packages": [ + "libssh-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libssh-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "libssh-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-libssh", + "mingw-w64-i686-libssh" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "libssh2": { + "patterns": [ + "\\blibssh2\\b" + ], + "dependencies": [ + { + "packages": [ + "libssh2-1-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libssh2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libssh2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "libssh2-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "libssh2" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7", + "8" + ] + } + ] + }, + { + "packages": [ + "libssh2-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libopenssl-devel", + "libssh2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "libssh2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-libssh2", + "mingw-w64-i686-libssh2" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "libtiff": { + "patterns": [ + "\\blibtiff\\b", + "\\btiff\\b" + ], + "dependencies": [ + { + "packages": [ + "libtiff-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libtiff-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libtiff-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "tiff-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-libtiff", + "mingw-w64-i686-libtiff" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "libtool": { + "patterns": [ + "\\blibtool\\b" + ], + "dependencies": [ + { + "packages": [ + "libtool" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libtool" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libtool" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "libtool" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libwebp": { + "patterns": [ + "\\blibwebp\\b" + ], + "dependencies": [ + { + "packages": [ + "libwebp-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libwebp-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libwebp-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "libwebp-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7", + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "libwebp-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "libwebp" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "libwebp-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8", + "9" + ] + } + ] + }, + { + "packages": [ + "libwebp-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "libwebp-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libxml2": { + "patterns": [ + "\\blibxml2\\b" + ], + "dependencies": [ + { + "packages": [ + "libxml2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libxml2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libxml2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "libxml2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-libxml2", + "mingw-w64-i686-libxml2" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "libxslt": { + "patterns": [ + "\\blibxslt\\b" + ], + "dependencies": [ + { + "packages": [ + "libxslt-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libxslt-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libxslt-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "libxslt-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "libzstd": { + "patterns": [ + "\\blibzstd\\b" + ], + "dependencies": [ + { + "packages": [ + "libzstd-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y epel-release" + } + ], + "packages": [ + "libzstd-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "libzstd-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "libzstd-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8", + "9" + ] + }, + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "zstd-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "mongodb": { + "patterns": [ + "\\bmongodb\\b", + "\\bmongo\\b" + ], + "dependencies": [ + { + "packages": [ + "mongodb" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu", + "versions": [ + "18.04", + "20.04" + ] + } + ] + }, + { + "packages": [ + "mongodb" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "mongodb" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "mongodb" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "42.3" + ] + } + ] + }, + { + "packages": [ + "mongodb-tools" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "mpfr": { + "patterns": [ + "\\bmpfr\\b" + ], + "dependencies": [ + { + "packages": [ + "libmpfr-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "mpfr-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "mpfr-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "mpfr-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "mysql": { + "patterns": [ + "\\bmysql.*server\\b" + ], + "dependencies": [ + { + "packages": [ + "mysql-server" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + } + ] + }, + { + "packages": [ + "mariadb-server" + ], + "constraints": [ + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "mysql" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "mariadb" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7", + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7", + "8", + "9" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "mariadb" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "mariadb" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "netcdf4": { + "patterns": [ + "\\bnetcdf\\b", + "\\bnetcdf4\\b" + ], + "dependencies": [ + { + "packages": [ + "libnetcdf-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "netcdf-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "netcdf-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "netcdf-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + }, + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "netcdf-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "netcdf-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "netcdf-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "netcdf-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "netcdf-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "netcdf-gnu-hpc-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "sle", + "versions": [ + "12.3" + ] + } + ] + }, + { + "packages": [ + "netcdf-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "nlopt": { + "patterns": [ + "\\bnlopt\\b" + ], + "dependencies": [ + { + "packages": [ + "mingw-w64-x86_64-nlopt", + "mingw-w64-i686-nlopt" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "odbc": { + "patterns": [ + "\\bodbc\\b", + "\\bodbc3\\b" + ], + "dependencies": [ + { + "packages": [ + "unixodbc-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "unixODBC-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7", + "8" + ] + }, + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "unixODBC-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "unixODBC-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "unixODBC-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "unixodbc-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "openbabel": { + "patterns": [ + "\\bopenbabel\\b" + ], + "dependencies": [ + { + "packages": [ + "libopenbabel-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "openbabel-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "openbabel-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "openbabel-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "openbabel-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "openbabel-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "openbabel-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + } + ] + }, + "opencl": { + "patterns": [ + "\\bopencl\\b" + ], + "dependencies": [ + { + "packages": [ + "ocl-icd-opencl-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "ocl-icd", + "opencl-headers" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "ocl-icd", + "opencl-headers" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "ocl-icd", + "opencl-headers" + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "ocl-icd", + "opencl-headers" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "ocl-icd", + "opencl-headers" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "ocl-icd" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8", + "9" + ] + } + ] + }, + { + "packages": [ + "libOpenCL1", + "opencl-headers" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "opencl-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine", + "versions": [ + "3.16", + "3.17", + "3.18", + "3.19", + "3.20", + "edge" + ] + } + ] + } + ] + }, + "opencv": { + "patterns": [ + "\\bopencv\\b" + ], + "dependencies": [ + { + "packages": [ + "libopencv-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "opencv-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "sle" + }, + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "opencv-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "opencv-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "opencv-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "packages": [ + "opencv-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "opencv-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + }, + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "opencv-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + }, + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "opencv-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "opengl": { + "patterns": [ + "\\bopengl\\b" + ], + "dependencies": [ + { + "packages": [ + "libgl1-mesa-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "mesa-libGL-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "Mesa-libGL-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "mesa-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "openmpi": { + "patterns": [ + "\\bopenmpi\\b", + "\\bmpi\\b" + ], + "dependencies": [ + { + "packages": [ + "libopenmpi-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "openmpi-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7", + "8", + "9" + ] + }, + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7", + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "openmpi-1.10-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + }, + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "openmpi-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "openmpi-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "openmpt": { + "patterns": [ + "\\bopenmpt\\b" + ], + "dependencies": [ + { + "packages": [ + "libopenmpt-dev", + "portaudio19-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libopenmpt-devel", + "portaudio-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libopenmpt-devel", + "portaudio-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + } + ] + }, + { + "packages": [ + "libopenmpt-dev", + "portaudio-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine", + "versions": [ + "3.18", + "3.19", + "3.20", + "edge" + ] + } + ] + } + ] + }, + "openssl": { + "patterns": [ + "\\bopenssl\\b" + ], + "dependencies": [ + { + "packages": [ + "libssl-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "openssl-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libopenssl-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "openssl-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-openssl", + "mingw-w64-i686-openssl" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "osmium-tool": { + "patterns": [ + "\\bosmium-tool\\b" + ], + "dependencies": [ + { + "packages": [ + "osmium-tool" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + } + ] + }, + "pandoc-citeproc": { + "patterns": [ + "\\bpandoc-citeproc\\b" + ], + "dependencies": [ + { + "packages": [ + "pandoc-citeproc" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu", + "versions": [ + "14.04", + "16.04", + "18.04", + "20.04", + "22.04" + ] + }, + { + "os": "linux", + "distribution": "debian", + "versions": [ + "10", + "11" + ] + } + ] + }, + { + "packages": [ + "pandoc-citeproc" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "pandoc-citeproc" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + } + ] + }, + "pandoc": { + "patterns": [ + "\\bpandoc\\b" + ], + "dependencies": [ + { + "packages": [ + "pandoc" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "pandoc" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "pandoc" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "pandoc" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "pandoc" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "pandoc" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "pandoc" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "pandoc" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine", + "versions": [ + "3.17" + ] + } + ] + }, + { + "packages": [ + "pandoc-cli" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine", + "versions": [ + "3.18" + ] + } + ] + } + ] + }, + "pango": { + "patterns": [ + "\\bpango\\b" + ], + "dependencies": [ + { + "packages": [ + "libpango1.0-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "pango-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "pango-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "pango-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "pari-gp": { + "patterns": [ + "\\bpari/gp\\b", + "\\bpari-gp\\b" + ], + "dependencies": [ + { + "packages": [ + "pari-gp" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "pari-gp" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "pari-gp" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "pari-gp" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "pari-gp" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + } + ] + }, + "patch": { + "patterns": [ + "\\bpatch\\b" + ], + "dependencies": [ + { + "packages": [ + "patch" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + }, + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "perl": { + "patterns": [ + "\\bperl\\b" + ], + "dependencies": [ + { + "packages": [ + "perl" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "perl" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "perl" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "perl" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "pkg-config": { + "patterns": [ + "\\bpkg-config\\b", + "\\bpkgconfig\\b" + ], + "dependencies": [ + { + "packages": [ + "pkg-config" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "pkgconfig" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "pkgconf-pkg-config" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8", + "9" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "pkg-config" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "pkgconf" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "poppler-glib": { + "patterns": [ + "\\bPoppler glib\\b" + ], + "dependencies": [ + { + "packages": [ + "libpoppler-glib-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "poppler-glib-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "poppler-glib-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "poppler-glib-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "poppler-glib-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "poppler-glib-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libpoppler-glib-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "poppler-glib" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "poppler": { + "patterns": [ + "\\bPoppler C\\+\\+" + ], + "dependencies": [ + { + "packages": [ + "libpoppler-cpp-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "poppler-cpp-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "poppler-cpp-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "poppler-cpp-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "poppler-cpp-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "poppler-cpp-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libpoppler-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "poppler-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "postgresql": { + "patterns": [ + "\\bpostgresql\\b", + "\\blibpq-dev\\b", + "\\bpostgresql-devel\\b" + ], + "dependencies": [ + { + "packages": [ + "libpq-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "postgresql-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "libpq-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8", + "9" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "postgresql-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "postgresql10-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "libpq-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-libpq", + "mingw-w64-i686-libpq" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "proj": { + "patterns": [ + "\\bproj\\b", + "\\bproj\\.4\\b" + ], + "dependencies": [ + { + "packages": [ + "libproj-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "proj-devel", + "proj-epsg" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "proj-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "proj-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "proj-devel", + "proj-epsg" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "proj-devel", + "proj-epsg" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "proj-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "proj-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libproj-devel", + "proj" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "42.3", + "15.0" + ] + } + ] + }, + { + "packages": [ + "proj-devel", + "proj" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "15.2", + "15.3", + "15.4", + "15.5", + "15.6" + ] + } + ] + }, + { + "packages": [ + "libproj-devel", + "proj" + ], + "pre_install": [ + { + "command": "zypper repos openSUSE_Backports_SLE-12 || zypper addrepo https://download.opensuse.org/repositories/openSUSE:/Backports:/SLE-12/standard/openSUSE:Backports:SLE-12.repo" + }, + { + "command": "zypper --gpg-auto-import-keys refresh" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "sle", + "versions": [ + "12.3" + ] + } + ] + }, + { + "packages": [ + "proj-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "protobuf-compiler": { + "patterns": [ + "\\bprotobuf-compiler\\b" + ], + "dependencies": [ + { + "packages": [ + "protobuf-compiler", + "libprotoc-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "protobuf-compiler" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "protobuf-compiler" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "protobuf-compiler" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "protobuf-compiler" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "protobuf-compiler" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "protobuf-compiler" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "protobuf-compiler" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "protobuf-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "protobuf-c-compiler" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "protobuf-grpc": { + "patterns": [ + "\\bgrpc/protobuf\\b" + ], + "dependencies": [ + { + "packages": [ + "protobuf-compiler-grpc" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "grpc-plugins" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "pre_install": [ + { + "command": "yum install -y epel-release" + }, + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "packages": [ + "grpc-plugins" + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "grpc-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "grpc-plugins" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "grpc-plugins" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine", + "versions": [ + "3.17", + "3.18", + "3.19", + "3.20", + "edge" + ] + } + ] + }, + { + "packages": [ + "grpc-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine", + "versions": [ + "3.16" + ] + } + ] + } + ] + }, + "python": { + "patterns": [ + "\\bpython\\b" + ], + "dependencies": [ + { + "packages": [ + "python3" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "python" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "python2" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "python3" + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "python" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "python3" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "python3": { + "patterns": [ + "\\bpython3\\b" + ], + "dependencies": [ + { + "packages": [ + "python3" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "python34" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "python36" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "python34" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "python34" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "python3" + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "python3" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "python3" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-python3", + "mingw-w64-i686-python3" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "qgis": { + "patterns": [ + "\\bqgis\\b" + ], + "dependencies": [ + { + "packages": [ + "libqgis-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "qgis-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "qgis-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "qgis-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "qgis-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + } + ] + }, + "QuantLib": { + "patterns": [ + "\\bQuantLib\\b" + ], + "dependencies": [ + { + "packages": [ + "libquantlib0-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "QuantLib-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "QuantLib-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "QuantLib-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "QuantLib-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + } + ] + }, + "redland": { + "patterns": [ + "\\bredland\\b", + "\\blibrdf0\\b" + ], + "dependencies": [ + { + "packages": [ + "librdf0-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "redland-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "redland-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "redland-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "redland" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat" + } + ] + }, + { + "packages": [ + "redland-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "redland-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "libredland-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "12.3" + ] + } + ] + }, + { + "packages": [ + "redland-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-redland", + "mingw-w64-i686-redland" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + }, + "rust": { + "patterns": [ + "\\brust\\b", + "\\brustc\\b", + "\\bcargo\\b" + ], + "dependencies": [ + { + "packages": [ + "rustc", + "cargo" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "rust", + "cargo" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "rust", + "cargo" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "rust", + "cargo" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "rust", + "cargo" + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8", + "9" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "rust", + "cargo" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "rust", + "cargo" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "saga": { + "patterns": [ + "\\bsaga\\b", + "\\bsaga gis\\b" + ], + "dependencies": [ + { + "packages": [ + "saga" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "saga-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora", + "versions": [ + "36", + "37" + ] + } + ] + } + ] + }, + "saint": { + "patterns": [ + "\\bsaint" + ], + "dependencies": [ + { + "packages": [ + "saint" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + } + ] + }, + "sasl": { + "patterns": [ + "\\bsasl\\b", + "\\bcyrus sasl\\b" + ], + "dependencies": [ + { + "packages": [ + "libsasl2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "cyrus-sasl-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "cyrus-sasl-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "cyrus-sasl-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "sdl2": { + "patterns": [ + "\\bsdl2\\b" + ], + "dependencies": [ + { + "packages": [ + "libsdl2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "SDL2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "packages": [ + "SDL2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + }, + { + "command": "dnf install -y epel-release" + } + ], + "packages": [ + "SDL2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "SDL2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "15.6" + ] + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "15.6" + ] + } + ] + }, + { + "packages": [ + "libSDL2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "15.0", + "15.2", + "15.3", + "15.4", + "15.5" + ] + }, + { + "os": "linux", + "distribution": "sle", + "versions": [ + "15.0", + "15.2", + "15.3", + "15.4", + "15.5" + ] + } + ] + }, + { + "packages": [ + "sdl2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "sqlite3": { + "patterns": [ + "\\bsqlite3\\b", + "\\bsqlite\\b" + ], + "dependencies": [ + { + "packages": [ + "libsqlite3-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "sqlite-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "sqlite3-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "sqlite-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "suitesparse": { + "patterns": [ + "\\bsuitesparse\\b" + ], + "dependencies": [ + { + "packages": [ + "libsuitesparse-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "suitesparse-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "7" + ] + }, + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "packages": [ + "suitesparse-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "suitesparse-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + } + ], + "packages": [ + "suitesparse-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "suitesparse-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "suitesparse-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "swftools": { + "patterns": [ + "\\bswftools\\b", + "\\bswf tools\\b" + ], + "dependencies": [ + { + "packages": [ + "swftools" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu", + "versions": [ + "14.04", + "16.04", + "18.04" + ] + } + ] + }, + { + "packages": [ + "swftools" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "42.3" + ] + } + ] + } + ] + }, + "tcltk": { + "patterns": [ + "\\btcl/tk\\b" + ], + "dependencies": [ + { + "packages": [ + "tcl", + "tk" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "tcl", + "tk" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "tcl", + "tk" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "tcl", + "tk" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "tesseract": { + "patterns": [ + "\\btesseract\\b" + ], + "dependencies": [ + { + "packages": [ + "libtesseract-dev", + "tesseract-ocr-eng" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "tesseract-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "tesseract-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled powertools" + } + ], + "packages": [ + "tesseract-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "tesseract-devel" + ], + "pre_install": [ + { + "command": "dnf install -y dnf-plugins-core" + }, + { + "command": "dnf config-manager --set-enabled crb" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "tesseract-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-8-$(arch)-rpms" + } + ], + "packages": [ + "tesseract-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "tesseract-devel" + ], + "pre_install": [ + { + "command": "subscription-manager repos --enable codeready-builder-for-rhel-9-$(arch)-rpms" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "tesseract-ocr-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + }, + { + "packages": [ + "tesseract-ocr-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "tk": { + "patterns": [ + "\\btk\\b" + ], + "dependencies": [ + { + "packages": [ + "tk-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "tk-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "sle" + }, + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "tk-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "tktable": { + "patterns": [ + "\\btktable\\b" + ], + "dependencies": [ + { + "packages": [ + "tk-table" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "tktable" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + } + ] + } + ] + }, + "udunits2": { + "patterns": [ + "\\budunits-2\\b" + ], + "dependencies": [ + { + "packages": [ + "libudunits2-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "udunits2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "udunits2-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "udunits2-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "udunits2-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "udunits2-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "packages": [ + "udunits2-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "udunits2-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + }, + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "udunits-dev" + ], + "pre_install": [ + { + "command": "apk add udunits-dev --repository=https://dl-cdn.alpinelinux.org/alpine/edge/community" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "v8": { + "patterns": [ + "\\bv8\\b" + ], + "dependencies": [ + { + "packages": [ + "libnode-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu", + "versions": [ + "20.04", + "22.04", + "24.04" + ] + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libv8-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu", + "versions": [ + "18.04" + ] + } + ] + }, + { + "packages": [ + "v8-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "v8-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "v8-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "v8-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "nodejs-libs" + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux", + "versions": [ + "9" + ] + }, + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "v8-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse", + "versions": [ + "42.3" + ] + } + ] + } + ] + }, + "wget": { + "patterns": [ + "\\bwget\\b" + ], + "dependencies": [ + { + "packages": [ + "wget" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "wget" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "wget" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "wget" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "x11": { + "patterns": [ + "\\bX11\\b" + ], + "dependencies": [ + { + "packages": [ + "libx11-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + }, + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "libX11-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + } + ] + }, + "xft": { + "patterns": [ + "\\bxft\\b" + ], + "dependencies": [ + { + "packages": [ + "libxft-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "libXft-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "libXft-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "libxft-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "xz": { + "patterns": [ + "\\bxz\\b" + ], + "dependencies": [ + { + "packages": [ + "xz-utils" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "xz" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + }, + { + "os": "linux", + "distribution": "fedora" + }, + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "zeromq": { + "patterns": [ + "\\bzeromq\\b" + ], + "dependencies": [ + { + "packages": [ + "libzmq3-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "zeromq-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "zeromq-devel" + ], + "pre_install": [ + { + "command": "yum install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "6", + "7" + ] + } + ] + }, + { + "packages": [ + "zeromq-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "zeromq-devel" + ], + "pre_install": [ + { + "command": "dnf install -y epel-release" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "rockylinux" + } + ] + }, + { + "packages": [ + "zeromq-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/6/x86_64/epel-release-6-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "6" + ] + } + ] + }, + { + "packages": [ + "zeromq-devel" + ], + "pre_install": [ + { + "command": "rpm -q epel-release || yum install -y https://archives.fedoraproject.org/pub/archive/epel/7/x86_64/Packages/e/epel-release-7-14.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "7" + ] + } + ] + }, + { + "packages": [ + "zeromq-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-8.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "8" + ] + } + ] + }, + { + "packages": [ + "zeromq-devel" + ], + "pre_install": [ + { + "command": "dnf install -y https://dl.fedoraproject.org/pub/epel/epel-release-latest-9.noarch.rpm" + } + ], + "constraints": [ + { + "os": "linux", + "distribution": "redhat", + "versions": [ + "9" + ] + } + ] + }, + { + "packages": [ + "zeromq-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "zeromq-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + } + ] + }, + "zlib": { + "patterns": [ + "\\bzlib\\b" + ], + "dependencies": [ + { + "packages": [ + "zlib1g-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "ubuntu" + }, + { + "os": "linux", + "distribution": "debian" + } + ] + }, + { + "packages": [ + "zlib-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "centos" + }, + { + "os": "linux", + "distribution": "rockylinux" + }, + { + "os": "linux", + "distribution": "redhat" + }, + { + "os": "linux", + "distribution": "fedora" + } + ] + }, + { + "packages": [ + "zlib-devel" + ], + "constraints": [ + { + "os": "linux", + "distribution": "opensuse" + }, + { + "os": "linux", + "distribution": "sle" + } + ] + }, + { + "packages": [ + "zlib-dev" + ], + "constraints": [ + { + "os": "linux", + "distribution": "alpine" + } + ] + }, + { + "packages": [ + "mingw-w64-x86_64-zlib", + "mingw-w64-i686-zlib" + ], + "constraints": [ + { + "os": "windows" + } + ] + } + ] + } +} diff --git a/man/config.Rd b/man/config.Rd index 0aa745022..2b01f17a8 100644 --- a/man/config.Rd +++ b/man/config.Rd @@ -124,6 +124,8 @@ Defaults to \code{TRUE}.} Defaults to \code{NULL}.} \subsection{renv.config.synchronized.check}{Check that the project library is synchronized with the lockfile on load? Defaults to \code{TRUE}.} +\subsection{renv.config.sysreqs.check}{Check whether the requisite system packages are installed during package installation and restore? This feature uses the R System Requirements database maintained at \url{https://github.com/rstudio/r-system-requirements}. +Defaults to \code{TRUE}.} \subsection{renv.config.updates.check}{Check for package updates when the session is initialized? This can be useful if you'd like to ensure that your project lockfile remains up-to-date with packages as they are released on CRAN. Defaults to \code{FALSE}.} \subsection{renv.config.updates.parallel}{Check for package updates in parallel? This can be useful when a large number of packages installed from non-CRAN remotes are installed, as these packages can then be checked for updates in parallel. diff --git a/man/sysreqs.Rd b/man/sysreqs.Rd new file mode 100644 index 000000000..6d96773ef --- /dev/null +++ b/man/sysreqs.Rd @@ -0,0 +1,91 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/sysreqs.R +\name{sysreqs} +\alias{sysreqs} +\title{R System Requirements} +\usage{ +sysreqs( + packages = NULL, + ..., + local = FALSE, + check = NULL, + report = TRUE, + distro = NULL, + collapse = FALSE, + project = NULL +) +} +\arguments{ +\item{packages}{A vector of \R package names. When \code{NULL} +(the default), the project's package dependencies as reported via +\code{\link[=dependencies]{dependencies()}} are used.} + +\item{...}{Unused arguments, reserved for future expansion. If any arguments +are matched to \code{...}, renv will signal an error.} + +\item{local}{Boolean; should \code{renv} rely on locally-installed copies of +packages when resolving system requirements? When \code{FALSE}, \code{renv} will +use \url{https://crandb.r-pkg.org} to resolve the system requirements +for these packages.} + +\item{check}{Boolean; should \code{renv} also check whether the requires system +packages appear to be installed on the current system?} + +\item{report}{Boolean; should \code{renv} also report the commands which could be +used to install all of the requisite package dependencies?} + +\item{distro}{The name of the Linux distribution for which system requirements +should be checked -- typical values are "ubuntu", "debian", and "redhat". +These should match the distribution names used by the R system requirements +database.} + +\item{collapse}{Boolean; when reporting which packages need to be installed, +should the report be collapsed into a single installation command? When +\code{FALSE} (the default), a separate installation line is printed for each +required system package.} + +\item{project}{The project directory. If \code{NULL}, then the active project will +be used. If no project is currently active, then the current working +directory is used instead.} +} +\description{ +Compute the system requirements (system libraries; operating system packages) +required by a set of \R packages. +} +\details{ +This function relies on the database of package system requirements +maintained by Posit at \url{https://github.com/rstudio/r-system-requirements}, +as well as the "meta-CRAN" service at \url{https://crandb.r-pkg.org}. This +service primarily exists to map the (free-form) \code{SystemRequirements} field +used by \R packages to the system packages made available by a particular +operating system. + +As an example, the \code{curl} R package depends on the \code{libcurl} system library, +and declares this with a \code{SystemRequirements} field of the form: +\itemize{ +\item libcurl (>= 7.62): libcurl-devel (rpm) or libcurl4-openssl-dev (deb) +} + +This dependency can be satisfied with the following command line invocations +on different systems: +\itemize{ +\item Debian: \verb{sudo apt install libcurl4-openssl-dev} +\item Redhat: \verb{sudo dnf install libcurl-devel} +} + +and so \code{sysreqs("curl")} would help provide the name of the package +whose installation would satisfy the \code{libcurl} dependency. +} +\examples{ + +\dontrun{ + +# report the required system packages for this system +sysreqs() + +# report the required system packages for a specific OS +sysreqs(platform = "ubuntu") + +} + +} diff --git a/tests/testthat/_snaps/caution.md b/tests/testthat/_snaps/caution.md index f77622680..166f098c8 100644 --- a/tests/testthat/_snaps/caution.md +++ b/tests/testthat/_snaps/caution.md @@ -1,7 +1,7 @@ -# caution_bullets() creates bulleted list with optional postamble +# bulletin() creates bulleted list with optional postamble Code - caution_bullets("preamble", letters[1:3]) + bulletin("preamble", letters[1:3]) Output preamble - a @@ -9,7 +9,7 @@ - c Code - caution_bullets("preamble", letters[1:3], postamble = "after") + bulletin("preamble", letters[1:3], postamble = "after") Output preamble - a diff --git a/tests/testthat/test-caution.R b/tests/testthat/test-caution.R index ce71eeb78..07bbabd25 100644 --- a/tests/testthat/test-caution.R +++ b/tests/testthat/test-caution.R @@ -1,13 +1,13 @@ -test_that("caution_bullets() creates bulleted list with optional postamble", { +test_that("bulletin() creates bulleted list with optional postamble", { expect_snapshot({ - caution_bullets("preamble", letters[1:3]) - caution_bullets("preamble", letters[1:3], postamble = "after") + bulletin("preamble", letters[1:3]) + bulletin("preamble", letters[1:3], postamble = "after") }) }) -test_that("caution_bullets() doesn't show pre/post amble if no values", { - expect_silent(caution_bullets("before", character(), "after")) +test_that("bulletin() doesn't show pre/post amble if no values", { + expect_silent(bulletin("before", character(), "after")) }) test_that("options(renv.pretty.print.emitter) is respected", { @@ -22,7 +22,7 @@ test_that("options(renv.pretty.print.emitter) is respected", { renv_scope_options(renv.verbose = TRUE) # regular pretty printer - expect_condition(caution_bullets("preamble", 1), class = cls) + expect_condition(bulletin("preamble", 1), class = cls) # record printer lockfile <- renv_lockfile_create(project = getwd()) diff --git a/tests/testthat/test-init.R b/tests/testthat/test-init.R index 16c8d4ac6..629bda35c 100644 --- a/tests/testthat/test-init.R +++ b/tests/testthat/test-init.R @@ -63,6 +63,7 @@ test_that("attempts to initialize a project with a missing package is okay", { test_that("the remotes field in a DESCRIPTION is honored", { skip_on_cran() + skip_if_no_github_auth() renv_tests_scope("halloween") install("halloween") @@ -272,11 +273,15 @@ test_that("init() respects user-requested snapshot type", { }) test_that("init() respects Remotes in a project DESCRIPTION file", { + skip_on_cran() + skip_if_no_github_auth() + project <- renv_tests_scope("skeleton") writeLines("Depends: skeleton\nRemotes: kevinushey/skeleton", con = "DESCRIPTION") init() expect_true(renv_package_installed("skeleton")) + }) test_that("a project using named remotes can be initialized", { diff --git a/tests/testthat/test-internal.R b/tests/testthat/test-internal.R index 063a883fc..dafd3022e 100644 --- a/tests/testthat/test-internal.R +++ b/tests/testthat/test-internal.R @@ -11,7 +11,7 @@ test_that("R files have balanced covr exclusions", { nocov <- FALSE contents <- catch(readLines(file)) if (inherits(contents, "error")) { - caution_bullets(values = "[%s]: %s", file, conditionMessage(contents)) + bulletin(values = "[%s]: %s", file, conditionMessage(contents)) return() } diff --git a/tests/testthat/test-reload.R b/tests/testthat/test-reload.R index ee4dbd339..8c02f2177 100644 --- a/tests/testthat/test-reload.R +++ b/tests/testthat/test-reload.R @@ -1,8 +1,11 @@ test_that("renv can be reloaded within the same session", { + skip_on_cran() script <- renv_test_code({ + + # load renv tools renv:::summon() # set up temporary library path diff --git a/tests/testthat/test-remotes.R b/tests/testthat/test-remotes.R index e51b1d884..1d70a5585 100644 --- a/tests/testthat/test-remotes.R +++ b/tests/testthat/test-remotes.R @@ -31,6 +31,7 @@ test_that("we can parse a variety of remotes", { test_that("we can parse a variety of remotes", { skip_on_cran() + skip_if_no_github_auth() skip_on_os("windows") renv_tests_scope() diff --git a/tests/testthat/test-snapshot.R b/tests/testthat/test-snapshot.R index 616c6b51d..a0781cf30 100644 --- a/tests/testthat/test-snapshot.R +++ b/tests/testthat/test-snapshot.R @@ -319,6 +319,8 @@ test_that("snapshot() accepts relative library paths", { test_that("snapshot(update = TRUE) preserves old records", { skip_on_cran() + skip_if_no_github_auth() + renv_tests_scope("breakfast") init() diff --git a/tests/testthat/test-sysreqs.R b/tests/testthat/test-sysreqs.R new file mode 100644 index 000000000..e508a9c1f --- /dev/null +++ b/tests/testthat/test-sysreqs.R @@ -0,0 +1,21 @@ + +test_that("system requirements are reported", { + + skip_on_cran() + + renv_tests_scope() + renv_scope_binding(the, "os", "linux") + + local({ + renv_scope_binding(the, "distro", "ubuntu") + syspkg <- renv_sysreqs_resolve("zlib") + expect_equal(syspkg, "zlib1g-dev") + }) + + local({ + renv_scope_binding(the, "distro", "redhat") + syspkg <- renv_sysreqs_resolve("zlib") + expect_equal(syspkg, "zlib-devel") + }) + +})