From 564cafd2d13fa5f7632d2d180b206cc89bcd1b7b Mon Sep 17 00:00:00 2001 From: dgkf <18220321+dgkf@users.noreply.github.com> Date: Fri, 1 Mar 2024 18:50:37 -0500 Subject: [PATCH 1/8] updating pkgdepends gitlab url parsing; fix authed ls-remotes --- R/git-protocol.R | 29 +++++++++++++++++++++++++++-- R/type-gitlab.R | 26 ++++++++++++++++++++------ 2 files changed, 47 insertions(+), 8 deletions(-) diff --git a/R/git-protocol.R b/R/git-protocol.R index 0f41cb7a..fef62632 100644 --- a/R/git-protocol.R +++ b/R/git-protocol.R @@ -788,10 +788,22 @@ async_git_send_message_v2 <- function( "git-protocol" = "version=2", "content-length" = as.character(length(msg)) ) + + options <- list() + tryCatch( + { + creds <- gitcreds_get(url) + options$username <- creds$username + options$password <- creds$password + }, + error = function(e) NULL + ) + http_post( url2, data = msg, - headers = headers + headers = headers, + options = options )$then(http_stop_for_status)$ then(function(res) git_parse_message(res$content)) } @@ -1006,11 +1018,24 @@ async_git_list_refs_v2 <- function(url, prefixes = character()) { url; prefixes url1 <- paste0(url, "/info/refs?service=git-upload-pack") + headers <- c( "User-Agent" = git_ua(), "git-protocol" = "version=2" ) - http_get(url1, headers = headers)$ + + # headers from tracing action with GIT_CURL_VERBOSE=1 GIT_TRACE=1 + options <- list() + tryCatch( + { + creds <- gitcreds_get(url) + options$username <- creds$username + options$password <- creds$password + }, + error = function(e) NULL + ) + + http_get(url1, headers = headers, options = options)$ then(http_stop_for_status)$ then(function(res) async_git_list_refs_v2_process_1(res, url, prefixes)) } diff --git a/R/type-gitlab.R b/R/type-gitlab.R index 52bd7f56..bf085354 100644 --- a/R/type-gitlab.R +++ b/R/type-gitlab.R @@ -1,11 +1,10 @@ parse_remote_gitlab <- function(specs, config, ...) { - pds <- re_match(specs, gitlab_rx()) pds$ref <- pds$.text pds$protocol[pds$protocol == ""] <- "https" pds$host[pds$host == ""] <- "gitlab.com" - pds$path <- paste0("/", pds$username, "/") + pds$path <- paste0("/", pds$projectpath, "/", pds$project) pds$dotgit <- "" pds$commitish[pds$commitish == ""] <- "HEAD" pds$url <- paste0(pds$protocol, "://", pds$host, pds$path, pds$repo, ".git") @@ -55,16 +54,31 @@ installedok_remote_gitlab <- function(installed, solution, config, ...) { installedok_remote_git(installed, solution, config, ...) } +# source: https://docs.gitlab.com/ee/user/reserved_names.html#limitations-on-usernames-project-and-group-names +gitlab_slug_rx <- function() { + "[a-zA-Z0-9][-._a-zA-Z0-9]*[a-zA-Z0-9]" +} + +gitlab_project_rx <- function() { + paste0("(?", gitlab_slug_rx(), ")") +} + +gitlab_project_path_rx <- function() { + paste0("(?", gitlab_slug_rx(), "(?:/", gitlab_slug_rx(), ")*)") +} + gitlab_rx <- function() { paste0( "^", ## Optional package name "(?:(?", package_name_rx(), ")=)?", "gitlab::", - "(?:(?[^/]*)://(?[^/]+))?", - github_username_rx(), "/", - github_repo_rx(), - github_subdir_rx(), "?", + ## Optional protocol::host + "(?:(?[^/]*)://(?[^/]+)/)?", + gitlab_project_path_rx(), "/", + gitlab_project_rx(), + ## Optional subdirectory, prefixed with /-, ie project/-/sub/dir + "(?:/-", github_subdir_rx(), ")?", "(?:", github_commitish_rx(), ")?", "$" ) From 20994a892a89a8a71e15e4f0f5b0e4ecfa450670 Mon Sep 17 00:00:00 2001 From: dgkf <18220321+dgkf@users.noreply.github.com> Date: Mon, 4 Mar 2024 18:48:31 -0500 Subject: [PATCH 2/8] cleaning up tests --- R/errors.R | 26 +- R/install-plan.R | 4 +- R/type-gitlab.R | 8 +- tests/testthat/_snaps/parse-remotes.md | 561 ++++++++++++++++++++++--- tests/testthat/_snaps/type-gitlab.md | 2 +- tests/testthat/helper-install.R | 2 +- tests/testthat/test-parse-remotes.R | 27 +- tests/testthat/test-type-gitlab.R | 4 +- 8 files changed, 543 insertions(+), 91 deletions(-) diff --git a/R/errors.R b/R/errors.R index 3f10eda8..ed61bd2e 100644 --- a/R/errors.R +++ b/R/errors.R @@ -239,7 +239,7 @@ err <- local({ cond <- process_call(cond) if (!is.null(parent)) { - cond$parent <- process_call(parent) + cond$parents <- process_call(parent) } # We can set an option to always add the trace to the thrown @@ -723,23 +723,23 @@ err <- local({ c( paste0(if (add_exp) exp, msg), - if (inherits(cond$parent, "condition")) { - msg <- if (full && inherits(cond$parent, "rlib_error_3_0")) { - format(cond$parent, + if (inherits(cond$parents, "condition")) { + msg <- if (full && inherits(cond$parents, "rlib_error_3_0")) { + format(cond$parents, trace = FALSE, full = TRUE, class = FALSE, header = FALSE, advice = FALSE ) - } else if (inherits(cond$parent, "interrupt")) { + } else if (inherits(cond$parents, "interrupt")) { "interrupt" } else { - conditionMessage(cond$parent) + conditionMessage(cond$parents) } add_exp <- substr(cli::ansi_strip(msg[1]), 1, 1) != "!" if (add_exp) msg[1] <- paste0(exp, msg[1]) - c(format_header_line_cli(cond$parent, prefix = "Caused by error"), + c(format_header_line_cli(cond$parents, prefix = "Caused by error"), msg ) } @@ -753,25 +753,25 @@ err <- local({ add_exp <- is.null(names(cond$message)) c( paste0(if (add_exp) exp, cnd_message_robust(cond)), - if (inherits(cond$parent, "condition")) { - msg <- if (full && inherits(cond$parent, "rlib_error_3_0")) { - format(cond$parent, + if (inherits(cond$parents, "condition")) { + msg <- if (full && inherits(cond$parents, "rlib_error_3_0")) { + format(cond$parents, trace = FALSE, full = TRUE, class = FALSE, header = FALSE, advice = FALSE ) - } else if (inherits(cond$parent, "interrupt")) { + } else if (inherits(cond$parents, "interrupt")) { "interrupt" } else { - conditionMessage(cond$parent) + conditionMessage(cond$parents) } add_exp <- substr(msg[1], 1, 1) != "!" if (add_exp) { msg[1] <- paste0(exp, msg[1]) } - c(format_header_line_plain(cond$parent, prefix = "Caused by error"), + c(format_header_line_plain(cond$parents, prefix = "Caused by error"), msg ) } diff --git a/R/install-plan.R b/R/install-plan.R index fa5d104d..73e6fb92 100644 --- a/R/install-plan.R +++ b/R/install-plan.R @@ -667,7 +667,7 @@ stop_task_package_build <- function(state, worker) { state$cache$add(state$plan$file[pkgidx], state$plan$target[pkgidx], package = pkg, version = version, built = TRUE, sha256 = state$plan$extra[[pkgidx]]$remotesha, - vignettes = state$plan$vignette[pkgidx], + vignettes = state$plan$vignettes[pkgidx], platform = "source"), error = function(err) { alert("warning", "Failed to add {.pkg {pkg}} \\ @@ -744,7 +744,7 @@ stop_task_build <- function(state, worker) { state$cache$add(state$plan$file[pkgidx], target, package = pkg, version = version, built = TRUE, sha256 = state$plan$extra[[pkgidx]]$remotesha, - vignettes = state$plan$vignette[pkgidx], + vignettes = state$plan$vignettes[pkgidx], platform = ptfm, rversion = rv), error = function(err) { alert("warning", "Failed to add {.pkg {pkg}} \\ diff --git a/R/type-gitlab.R b/R/type-gitlab.R index bf085354..bf0346e5 100644 --- a/R/type-gitlab.R +++ b/R/type-gitlab.R @@ -7,11 +7,11 @@ parse_remote_gitlab <- function(specs, config, ...) { pds$path <- paste0("/", pds$projectpath, "/", pds$project) pds$dotgit <- "" pds$commitish[pds$commitish == ""] <- "HEAD" - pds$url <- paste0(pds$protocol, "://", pds$host, pds$path, pds$repo, ".git") + pds$url <- paste0(pds$protocol, "://", pds$host, pds$path, ".git") cn <- setdiff(colnames(pds), c(".match", ".text")) pds <- pds[, cn] pds$type <- "gitlab" - pds$package <- ifelse(nzchar(pds$package), pds$package, pds$repo) + pds$package <- ifelse(nzchar(pds$package), pds$package, pds$project) lapply( seq_len(nrow(pds)), function(i) as.list(pds[i,]) @@ -23,8 +23,8 @@ resolve_remote_gitlab <- function(remote, direct, config, cache, resolve_remote_git(remote, direct, config, cache, dependencies, ...)$ then(function(res) { res$metadata["RemoteHost"] <- remote$host - res$metadata["RemoteRepo"] <- remote$repo - res$metadata["RemoteUsername"] <- remote$username + res$metadata["RemoteRepo"] <- remote$project + res$metadata["RemoteUsername"] <- remote$projectpath res$metadata["RemoteType"] <- "gitlab" if (!is.null(remote$subdir) && remote$subdir != "") { res$metadata["RemoteSubdir"] <- remote$subdir diff --git a/tests/testthat/_snaps/parse-remotes.md b/tests/testthat/_snaps/parse-remotes.md index f0ba8ece..bcda31d0 100644 --- a/tests/testthat/_snaps/parse-remotes.md +++ b/tests/testthat/_snaps/parse-remotes.md @@ -261,10 +261,10 @@ # gitlab Code - parse_pkg_ref("gitlab::user/repo") + parse_pkg_ref("gitlab::user/project") Output $package - [1] "repo" + [1] "project" $protocol [1] "https" @@ -272,11 +272,11 @@ $host [1] "gitlab.com" - $username + $projectpath [1] "user" - $repo - [1] "repo" + $project + [1] "project" $subdir [1] "" @@ -285,16 +285,16 @@ [1] "HEAD" $ref - [1] "gitlab::user/repo" + [1] "gitlab::user/project" $path - [1] "/user/" + [1] "/user/project" $dotgit [1] "" $url - [1] "https://gitlab.com/user/repo.git" + [1] "https://gitlab.com/user/project.git" $type [1] "gitlab" @@ -305,10 +305,10 @@ attr(,"class") [1] "remote_ref_gitlab" "remote_ref" "list" Code - parse_pkg_ref("gitlab::user/repo@ref") + parse_pkg_ref("gitlab::user/project@ref") Output $package - [1] "repo" + [1] "project" $protocol [1] "https" @@ -316,11 +316,11 @@ $host [1] "gitlab.com" - $username + $projectpath [1] "user" - $repo - [1] "repo" + $project + [1] "project" $subdir [1] "" @@ -329,16 +329,16 @@ [1] "ref" $ref - [1] "gitlab::user/repo@ref" + [1] "gitlab::user/project@ref" $path - [1] "/user/" + [1] "/user/project" $dotgit [1] "" $url - [1] "https://gitlab.com/user/repo.git" + [1] "https://gitlab.com/user/project.git" $type [1] "gitlab" @@ -349,10 +349,10 @@ attr(,"class") [1] "remote_ref_gitlab" "remote_ref" "list" Code - parse_pkg_ref("gitlab::user/repo/sub/dir") + parse_pkg_ref("gitlab::user/project/-/sub/dir") Output $package - [1] "repo" + [1] "project" $protocol [1] "https" @@ -360,11 +360,11 @@ $host [1] "gitlab.com" - $username + $projectpath [1] "user" - $repo - [1] "repo" + $project + [1] "project" $subdir [1] "sub/dir" @@ -373,16 +373,16 @@ [1] "HEAD" $ref - [1] "gitlab::user/repo/sub/dir" + [1] "gitlab::user/project/-/sub/dir" $path - [1] "/user/" + [1] "/user/project" $dotgit [1] "" $url - [1] "https://gitlab.com/user/repo.git" + [1] "https://gitlab.com/user/project.git" $type [1] "gitlab" @@ -393,10 +393,10 @@ attr(,"class") [1] "remote_ref_gitlab" "remote_ref" "list" Code - parse_pkg_ref("gitlab::user/repo/sub/dir@ref") + parse_pkg_ref("gitlab::user/project/-/sub/dir@ref") Output $package - [1] "repo" + [1] "project" $protocol [1] "https" @@ -404,11 +404,11 @@ $host [1] "gitlab.com" - $username + $projectpath [1] "user" - $repo - [1] "repo" + $project + [1] "project" $subdir [1] "sub/dir" @@ -417,16 +417,16 @@ [1] "ref" $ref - [1] "gitlab::user/repo/sub/dir@ref" + [1] "gitlab::user/project/-/sub/dir@ref" $path - [1] "/user/" + [1] "/user/project" $dotgit [1] "" $url - [1] "https://gitlab.com/user/repo.git" + [1] "https://gitlab.com/user/project.git" $type [1] "gitlab" @@ -437,7 +437,227 @@ attr(,"class") [1] "remote_ref_gitlab" "remote_ref" "list" Code - parse_pkg_ref("pkg=gitlab::user/repo") + parse_pkg_ref("gitlab::group/subgroup/project") + Output + $package + [1] "project" + + $protocol + [1] "https" + + $host + [1] "gitlab.com" + + $projectpath + [1] "group/subgroup" + + $project + [1] "project" + + $subdir + [1] "" + + $commitish + [1] "HEAD" + + $ref + [1] "gitlab::group/subgroup/project" + + $path + [1] "/group/subgroup/project" + + $dotgit + [1] "" + + $url + [1] "https://gitlab.com/group/subgroup/project.git" + + $type + [1] "gitlab" + + $params + character(0) + + attr(,"class") + [1] "remote_ref_gitlab" "remote_ref" "list" + Code + parse_pkg_ref("gitlab::group/subgroup/project@ref") + Output + $package + [1] "project" + + $protocol + [1] "https" + + $host + [1] "gitlab.com" + + $projectpath + [1] "group/subgroup" + + $project + [1] "project" + + $subdir + [1] "" + + $commitish + [1] "ref" + + $ref + [1] "gitlab::group/subgroup/project@ref" + + $path + [1] "/group/subgroup/project" + + $dotgit + [1] "" + + $url + [1] "https://gitlab.com/group/subgroup/project.git" + + $type + [1] "gitlab" + + $params + character(0) + + attr(,"class") + [1] "remote_ref_gitlab" "remote_ref" "list" + Code + parse_pkg_ref("gitlab::group/subgroup/project/-/sub/dir") + Output + $package + [1] "project" + + $protocol + [1] "https" + + $host + [1] "gitlab.com" + + $projectpath + [1] "group/subgroup" + + $project + [1] "project" + + $subdir + [1] "sub/dir" + + $commitish + [1] "HEAD" + + $ref + [1] "gitlab::group/subgroup/project/-/sub/dir" + + $path + [1] "/group/subgroup/project" + + $dotgit + [1] "" + + $url + [1] "https://gitlab.com/group/subgroup/project.git" + + $type + [1] "gitlab" + + $params + character(0) + + attr(,"class") + [1] "remote_ref_gitlab" "remote_ref" "list" + Code + parse_pkg_ref("gitlab::group/subgroup/project/-/sub/dir@ref") + Output + $package + [1] "project" + + $protocol + [1] "https" + + $host + [1] "gitlab.com" + + $projectpath + [1] "group/subgroup" + + $project + [1] "project" + + $subdir + [1] "sub/dir" + + $commitish + [1] "ref" + + $ref + [1] "gitlab::group/subgroup/project/-/sub/dir@ref" + + $path + [1] "/group/subgroup/project" + + $dotgit + [1] "" + + $url + [1] "https://gitlab.com/group/subgroup/project.git" + + $type + [1] "gitlab" + + $params + character(0) + + attr(,"class") + [1] "remote_ref_gitlab" "remote_ref" "list" + Code + parse_pkg_ref("gitlab::https://acme.co/group/subgroup/project/-/sub/dir@ref") + Output + $package + [1] "project" + + $protocol + [1] "https" + + $host + [1] "acme.co" + + $projectpath + [1] "group/subgroup" + + $project + [1] "project" + + $subdir + [1] "sub/dir" + + $commitish + [1] "ref" + + $ref + [1] "gitlab::https://acme.co/group/subgroup/project/-/sub/dir@ref" + + $path + [1] "/group/subgroup/project" + + $dotgit + [1] "" + + $url + [1] "https://acme.co/group/subgroup/project.git" + + $type + [1] "gitlab" + + $params + character(0) + + attr(,"class") + [1] "remote_ref_gitlab" "remote_ref" "list" + Code + parse_pkg_ref("pkg=gitlab::user/project") Output $package [1] "pkg" @@ -448,11 +668,11 @@ $host [1] "gitlab.com" - $username + $projectpath [1] "user" - $repo - [1] "repo" + $project + [1] "project" $subdir [1] "" @@ -461,16 +681,16 @@ [1] "HEAD" $ref - [1] "pkg=gitlab::user/repo" + [1] "pkg=gitlab::user/project" $path - [1] "/user/" + [1] "/user/project" $dotgit [1] "" $url - [1] "https://gitlab.com/user/repo.git" + [1] "https://gitlab.com/user/project.git" $type [1] "gitlab" @@ -481,7 +701,7 @@ attr(,"class") [1] "remote_ref_gitlab" "remote_ref" "list" Code - parse_pkg_ref("pkg=gitlab::user/repo@ref") + parse_pkg_ref("pkg=gitlab::user/project@ref") Output $package [1] "pkg" @@ -492,11 +712,11 @@ $host [1] "gitlab.com" - $username + $projectpath [1] "user" - $repo - [1] "repo" + $project + [1] "project" $subdir [1] "" @@ -505,16 +725,16 @@ [1] "ref" $ref - [1] "pkg=gitlab::user/repo@ref" + [1] "pkg=gitlab::user/project@ref" $path - [1] "/user/" + [1] "/user/project" $dotgit [1] "" $url - [1] "https://gitlab.com/user/repo.git" + [1] "https://gitlab.com/user/project.git" $type [1] "gitlab" @@ -525,7 +745,7 @@ attr(,"class") [1] "remote_ref_gitlab" "remote_ref" "list" Code - parse_pkg_ref("pkg=gitlab::user/repo/sub/dir") + parse_pkg_ref("pkg=gitlab::user/project/-/sub/dir") Output $package [1] "pkg" @@ -536,11 +756,11 @@ $host [1] "gitlab.com" - $username + $projectpath [1] "user" - $repo - [1] "repo" + $project + [1] "project" $subdir [1] "sub/dir" @@ -549,16 +769,16 @@ [1] "HEAD" $ref - [1] "pkg=gitlab::user/repo/sub/dir" + [1] "pkg=gitlab::user/project/-/sub/dir" $path - [1] "/user/" + [1] "/user/project" $dotgit [1] "" $url - [1] "https://gitlab.com/user/repo.git" + [1] "https://gitlab.com/user/project.git" $type [1] "gitlab" @@ -569,7 +789,7 @@ attr(,"class") [1] "remote_ref_gitlab" "remote_ref" "list" Code - parse_pkg_ref("pkg=gitlab::user/repo/sub/dir@ref") + parse_pkg_ref("pkg=gitlab::user/project/-/sub/dir@ref") Output $package [1] "pkg" @@ -580,11 +800,232 @@ $host [1] "gitlab.com" - $username + $projectpath [1] "user" - $repo - [1] "repo" + $project + [1] "project" + + $subdir + [1] "sub/dir" + + $commitish + [1] "ref" + + $ref + [1] "pkg=gitlab::user/project/-/sub/dir@ref" + + $path + [1] "/user/project" + + $dotgit + [1] "" + + $url + [1] "https://gitlab.com/user/project.git" + + $type + [1] "gitlab" + + $params + character(0) + + attr(,"class") + [1] "remote_ref_gitlab" "remote_ref" "list" + Code + parse_pkg_ref("pkg=gitlab::group/subgroup/project") + Output + $package + [1] "pkg" + + $protocol + [1] "https" + + $host + [1] "gitlab.com" + + $projectpath + [1] "group/subgroup" + + $project + [1] "project" + + $subdir + [1] "" + + $commitish + [1] "HEAD" + + $ref + [1] "pkg=gitlab::group/subgroup/project" + + $path + [1] "/group/subgroup/project" + + $dotgit + [1] "" + + $url + [1] "https://gitlab.com/group/subgroup/project.git" + + $type + [1] "gitlab" + + $params + character(0) + + attr(,"class") + [1] "remote_ref_gitlab" "remote_ref" "list" + Code + parse_pkg_ref("pkg=gitlab::group/subgroup/project@ref") + Output + $package + [1] "pkg" + + $protocol + [1] "https" + + $host + [1] "gitlab.com" + + $projectpath + [1] "group/subgroup" + + $project + [1] "project" + + $subdir + [1] "" + + $commitish + [1] "ref" + + $ref + [1] "pkg=gitlab::group/subgroup/project@ref" + + $path + [1] "/group/subgroup/project" + + $dotgit + [1] "" + + $url + [1] "https://gitlab.com/group/subgroup/project.git" + + $type + [1] "gitlab" + + $params + character(0) + + attr(,"class") + [1] "remote_ref_gitlab" "remote_ref" "list" + Code + parse_pkg_ref("pkg=gitlab::group/subgroup/project/-/sub/dir") + Output + $package + [1] "pkg" + + $protocol + [1] "https" + + $host + [1] "gitlab.com" + + $projectpath + [1] "group/subgroup" + + $project + [1] "project" + + $subdir + [1] "sub/dir" + + $commitish + [1] "HEAD" + + $ref + [1] "pkg=gitlab::group/subgroup/project/-/sub/dir" + + $path + [1] "/group/subgroup/project" + + $dotgit + [1] "" + + $url + [1] "https://gitlab.com/group/subgroup/project.git" + + $type + [1] "gitlab" + + $params + character(0) + + attr(,"class") + [1] "remote_ref_gitlab" "remote_ref" "list" + Code + parse_pkg_ref("pkg=gitlab::group/subgroup/project/-/sub/dir@ref") + Output + $package + [1] "pkg" + + $protocol + [1] "https" + + $host + [1] "gitlab.com" + + $projectpath + [1] "group/subgroup" + + $project + [1] "project" + + $subdir + [1] "sub/dir" + + $commitish + [1] "ref" + + $ref + [1] "pkg=gitlab::group/subgroup/project/-/sub/dir@ref" + + $path + [1] "/group/subgroup/project" + + $dotgit + [1] "" + + $url + [1] "https://gitlab.com/group/subgroup/project.git" + + $type + [1] "gitlab" + + $params + character(0) + + attr(,"class") + [1] "remote_ref_gitlab" "remote_ref" "list" + Code + parse_pkg_ref( + "pkg=gitlab::https://acme.co/group/subgroup/project/-/sub/dir@ref") + Output + $package + [1] "pkg" + + $protocol + [1] "https" + + $host + [1] "acme.co" + + $projectpath + [1] "group/subgroup" + + $project + [1] "project" $subdir [1] "sub/dir" @@ -593,16 +1034,16 @@ [1] "ref" $ref - [1] "pkg=gitlab::user/repo/sub/dir@ref" + [1] "pkg=gitlab::https://acme.co/group/subgroup/project/-/sub/dir@ref" $path - [1] "/user/" + [1] "/group/subgroup/project" $dotgit [1] "" $url - [1] "https://gitlab.com/user/repo.git" + [1] "https://acme.co/group/subgroup/project.git" $type [1] "gitlab" diff --git a/tests/testthat/_snaps/type-gitlab.md b/tests/testthat/_snaps/type-gitlab.md index 9fe80373..f7847769 100644 --- a/tests/testthat/_snaps/type-gitlab.md +++ b/tests/testthat/_snaps/type-gitlab.md @@ -130,7 +130,7 @@ RemoteUrl "https://gitlab.com/gaborcsardi/feather.git" RemotePkgRef - "gitlab::gaborcsardi/feather/R" + "gitlab::gaborcsardi/feather/-/R" RemoteRef "HEAD" RemoteSha diff --git a/tests/testthat/helper-install.R b/tests/testthat/helper-install.R index 3f622fd2..e2f6bcb2 100644 --- a/tests/testthat/helper-install.R +++ b/tests/testthat/helper-install.R @@ -115,7 +115,7 @@ make_dummy_worker_process <- function(n_iter = 10, sleep = 1, status = 0) { } make_install_plan <- function(ref, lib = .libPaths()[1]) { - r <- pkg_plan$new(ref, lib = lib) + r <- pkg_plan$new(ref, library = lib) r$resolve() r$solve() r$download_solution() diff --git a/tests/testthat/test-parse-remotes.R b/tests/testthat/test-parse-remotes.R index 5caef05f..0b1e727b 100644 --- a/tests/testthat/test-parse-remotes.R +++ b/tests/testthat/test-parse-remotes.R @@ -300,13 +300,24 @@ test_that("explicit package names", { test_that("gitlab", { expect_snapshot({ - parse_pkg_ref("gitlab::user/repo") - parse_pkg_ref("gitlab::user/repo@ref") - parse_pkg_ref("gitlab::user/repo/sub/dir") - parse_pkg_ref("gitlab::user/repo/sub/dir@ref") - parse_pkg_ref("pkg=gitlab::user/repo") - parse_pkg_ref("pkg=gitlab::user/repo@ref") - parse_pkg_ref("pkg=gitlab::user/repo/sub/dir") - parse_pkg_ref("pkg=gitlab::user/repo/sub/dir@ref") + parse_pkg_ref("gitlab::user/project") + parse_pkg_ref("gitlab::user/project@ref") + parse_pkg_ref("gitlab::user/project/-/sub/dir") + parse_pkg_ref("gitlab::user/project/-/sub/dir@ref") + parse_pkg_ref("gitlab::group/subgroup/project") + parse_pkg_ref("gitlab::group/subgroup/project@ref") + parse_pkg_ref("gitlab::group/subgroup/project/-/sub/dir") + parse_pkg_ref("gitlab::group/subgroup/project/-/sub/dir@ref") + parse_pkg_ref("gitlab::https://acme.co/group/subgroup/project/-/sub/dir@ref") + + parse_pkg_ref("pkg=gitlab::user/project") + parse_pkg_ref("pkg=gitlab::user/project@ref") + parse_pkg_ref("pkg=gitlab::user/project/-/sub/dir") + parse_pkg_ref("pkg=gitlab::user/project/-/sub/dir@ref") + parse_pkg_ref("pkg=gitlab::group/subgroup/project") + parse_pkg_ref("pkg=gitlab::group/subgroup/project@ref") + parse_pkg_ref("pkg=gitlab::group/subgroup/project/-/sub/dir") + parse_pkg_ref("pkg=gitlab::group/subgroup/project/-/sub/dir@ref") + parse_pkg_ref("pkg=gitlab::https://acme.co/group/subgroup/project/-/sub/dir@ref") }) }) diff --git a/tests/testthat/test-type-gitlab.R b/tests/testthat/test-type-gitlab.R index ba4b257e..ccc070c5 100644 --- a/tests/testthat/test-type-gitlab.R +++ b/tests/testthat/test-type-gitlab.R @@ -47,7 +47,7 @@ test_that("resolve", { # subdirectory p <- suppressMessages(new_pkg_installation_proposal( - "gitlab::gaborcsardi/feather/R", + "gitlab::gaborcsardi/feather/-/R", config = list(library = tmp, dependencies = FALSE) )) suppressMessages(p$resolve()) @@ -67,7 +67,7 @@ test_that("download", { # subdirectory p <- suppressMessages(new_pkg_installation_proposal( - "gitlab::gaborcsardi/feather/R", + "gitlab::gaborcsardi/feather/-/R", config = list(library = tmp, dependencies = FALSE) )) suppressMessages(p$resolve()) From 3e63f3b57e84f5a152dec502a62a633ee91b7229 Mon Sep 17 00:00:00 2001 From: dgkf <18220321+dgkf@users.noreply.github.com> Date: Mon, 4 Mar 2024 19:05:21 -0500 Subject: [PATCH 3/8] revert fix to partial match on cond$parent --- R/errors.R | 26 +++++++++++++------------- 1 file changed, 13 insertions(+), 13 deletions(-) diff --git a/R/errors.R b/R/errors.R index ed61bd2e..3f10eda8 100644 --- a/R/errors.R +++ b/R/errors.R @@ -239,7 +239,7 @@ err <- local({ cond <- process_call(cond) if (!is.null(parent)) { - cond$parents <- process_call(parent) + cond$parent <- process_call(parent) } # We can set an option to always add the trace to the thrown @@ -723,23 +723,23 @@ err <- local({ c( paste0(if (add_exp) exp, msg), - if (inherits(cond$parents, "condition")) { - msg <- if (full && inherits(cond$parents, "rlib_error_3_0")) { - format(cond$parents, + if (inherits(cond$parent, "condition")) { + msg <- if (full && inherits(cond$parent, "rlib_error_3_0")) { + format(cond$parent, trace = FALSE, full = TRUE, class = FALSE, header = FALSE, advice = FALSE ) - } else if (inherits(cond$parents, "interrupt")) { + } else if (inherits(cond$parent, "interrupt")) { "interrupt" } else { - conditionMessage(cond$parents) + conditionMessage(cond$parent) } add_exp <- substr(cli::ansi_strip(msg[1]), 1, 1) != "!" if (add_exp) msg[1] <- paste0(exp, msg[1]) - c(format_header_line_cli(cond$parents, prefix = "Caused by error"), + c(format_header_line_cli(cond$parent, prefix = "Caused by error"), msg ) } @@ -753,25 +753,25 @@ err <- local({ add_exp <- is.null(names(cond$message)) c( paste0(if (add_exp) exp, cnd_message_robust(cond)), - if (inherits(cond$parents, "condition")) { - msg <- if (full && inherits(cond$parents, "rlib_error_3_0")) { - format(cond$parents, + if (inherits(cond$parent, "condition")) { + msg <- if (full && inherits(cond$parent, "rlib_error_3_0")) { + format(cond$parent, trace = FALSE, full = TRUE, class = FALSE, header = FALSE, advice = FALSE ) - } else if (inherits(cond$parents, "interrupt")) { + } else if (inherits(cond$parent, "interrupt")) { "interrupt" } else { - conditionMessage(cond$parents) + conditionMessage(cond$parent) } add_exp <- substr(msg[1], 1, 1) != "!" if (add_exp) { msg[1] <- paste0(exp, msg[1]) } - c(format_header_line_plain(cond$parents, prefix = "Caused by error"), + c(format_header_line_plain(cond$parent, prefix = "Caused by error"), msg ) } From ebf8759c78a7543fda087523a3c87426e66ae956 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?G=C3=A1bor=20Cs=C3=A1rdi?= Date: Thu, 4 Apr 2024 12:31:39 +0200 Subject: [PATCH 4/8] Remove auth from type-git We push it down to the git protocol functions. --- R/type-git.R | 26 ++++---------------------- tests/testthat/test-type-git.R | 21 --------------------- 2 files changed, 4 insertions(+), 43 deletions(-) diff --git a/R/type-git.R b/R/type-git.R index 15ff687e..1ddb6aa6 100644 --- a/R/type-git.R +++ b/R/type-git.R @@ -88,7 +88,7 @@ download_remote_git <- function(resolution, target, target_tree, ## 4. Need to download the repo - url <- type_git_auth_url(resolution$remote[[1]]) + url <- resolution$remote[[1]]$url sha <- resolution$metadata[[1]][["RemoteSha"]] pkgdir <- file.path(target_tree, resolution$package) mkdirp(pkgdir) @@ -168,36 +168,18 @@ git_rx <- function() { ) } -type_git_auth_url <- function(remote) { - url <- remote$url - auth <- tryCatch(gitcreds_get(url), error = function(err) NULL) - if (is.null(auth)) { - url - } else { - paste0( - remote$protocol, - "://", - auth$username, - ":", - auth$password, - "@", - sub(paste0("^", remote$protocol, "://"), "", remote$url) - ) - } -} - type_git_get_data <- function(remote) { remote + url <- remote$url sha <- NULL dsc <- NULL - auth_url <- type_git_auth_url(remote) desc_path <- if (is.null(remote$subdir) || remote$subdir == "") { "DESCRIPTION" } else { paste0(remote$subdir, "/", "DESCRIPTION") } - async_git_list_files(auth_url, remote$commitish)$ + async_git_list_files(url, remote$commitish)$ catch(error = function(err) { throw(pkg_error( "Failed to download {.path {desc_path}} from git repo at {.url {remote$url}}." @@ -219,7 +201,7 @@ type_git_get_data <- function(remote) { files$files$hash[desc_idx] })$ then(function(desc_hash) { - async_git_download_file(auth_url, desc_hash, output = NULL)$ + async_git_download_file(url, desc_hash, output = NULL)$ catch(error = function(err) { throw(pkg_error( "Failed to download {.path {desc_path}} from git repo at {.url {remote$url}}." diff --git a/tests/testthat/test-type-git.R b/tests/testthat/test-type-git.R index e1f6595f..c3ac71f9 100644 --- a/tests/testthat/test-type-git.R +++ b/tests/testthat/test-type-git.R @@ -167,27 +167,6 @@ test_that("installedok_remote_git", { ) }) -test_that("type_git_auth_url", { - mockery::stub(type_git_auth_url, "gitcreds_get", function(...) stop("oops")) - expect_equal( - type_git_auth_url(list(url = "https://github.com/r-lib/cli.git")), - "https://github.com/r-lib/cli.git" - ) - - mockery::stub( - type_git_auth_url, - "gitcreds_get", - list(username = "user", password = "secret") - ) - expect_equal( - type_git_auth_url(list( - protocol = "https", - url = "https://github.com/r-lib/cli.git" - )), - "https://user:secret@github.com/r-lib/cli.git" - ) -}) - test_that("type_git_get_data", { # TODO expect_true(TRUE) From a63559433afac536425d2c6ce2e4ef34b86fa863 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?G=C3=A1bor=20Cs=C3=A1rdi?= Date: Thu, 4 Apr 2024 12:33:59 +0200 Subject: [PATCH 5/8] Remove git auth from submodule code Will be pushed down to the git protocol. --- R/git-submodules.R | 24 +----------------------- tests/testthat/_snaps/git-submodules.md | 21 --------------------- tests/testthat/test-git-submodules.R | 11 ----------- 3 files changed, 1 insertion(+), 55 deletions(-) diff --git a/R/git-submodules.R b/R/git-submodules.R index 5d0fcf0a..217955f0 100644 --- a/R/git-submodules.R +++ b/R/git-submodules.R @@ -122,7 +122,7 @@ async_update_submodule <- function(url, path, branch) { if (is.null(branch) || is.na(branch)) branch <- "HEAD" # message("getting ", path) async_git_download_repo( - git_auth_url(url), + url, ref = branch, output = path, submodules = TRUE @@ -130,28 +130,6 @@ async_update_submodule <- function(url, path, branch) { } } -git_auth_url <- function(url) { - parsed <- parse_url(url) - auth <- tryCatch(gitcreds_get(url), error = function(err) NULL) - if (is.null(auth)) { - url - } else { - paste0( - parsed$protocol, - "://", - auth$username, - ":", - auth$password, - "@", - sub(paste0("^", parsed$protocol, "://"), "", parsed$url), - # gitlab needs .git suffix - if (parsed$host == "gitlab.com" && !endsWith(parsed$url, ".git")) { - ".git" - } - ) - } -} - update_git_submodules_r <- function(path, subdir) { synchronize(async_update_git_submodules_r(path, subdir)) # nocov } diff --git a/tests/testthat/_snaps/git-submodules.md b/tests/testthat/_snaps/git-submodules.md index ba32ad5f..6991ddb7 100644 --- a/tests/testthat/_snaps/git-submodules.md +++ b/tests/testthat/_snaps/git-submodules.md @@ -143,27 +143,6 @@ [9] "v1/README.md" [10] "v1/wipe.R" -# git_auth_url - - Code - git_auth_url("https://github.com/r-lib/pak") - Output - [1] "https://github.com/r-lib/pak" - ---- - - Code - git_auth_url("https://github.com/r-lib/pak") - Output - [1] "https://user:pass@github.com/r-lib/pak" - ---- - - Code - git_auth_url("https://gitlab.com/gaborcsardi/vli") - Output - [1] "https://user:pass@gitlab.com/gaborcsardi/vli.git" - # directories Code diff --git a/tests/testthat/test-git-submodules.R b/tests/testthat/test-git-submodules.R index 6f6def98..914835ae 100644 --- a/tests/testthat/test-git-submodules.R +++ b/tests/testthat/test-git-submodules.R @@ -133,17 +133,6 @@ test_that("git_download_repo R package with ignored submodule", { expect_snapshot(dir(tmp, recursive = TRUE, all.files = TRUE, no.. = TRUE)) }) -test_that("git_auth_url", { - mockery::stub(git_auth_url, "gitcreds_get", function(...) stop("no")) - expect_snapshot(git_auth_url("https://github.com/r-lib/pak")) - - mockery::stub(git_auth_url, "gitcreds_get", function(...) { - list(username = "user", password = "pass") - }) - expect_snapshot(git_auth_url("https://github.com/r-lib/pak")) - expect_snapshot(git_auth_url("https://gitlab.com/gaborcsardi/vli")) -}) - test_that("directories", { dir.create(tmp <- tempfile()) on.exit(unlink(tmp, recursive = TRUE), add = TRUE) From 9e33037a860619abf86369e81250245858ca561b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?G=C3=A1bor=20Cs=C3=A1rdi?= Date: Thu, 4 Apr 2024 13:10:52 +0200 Subject: [PATCH 6/8] Add auth to all git HTTP queries --- R/git-protocol.R | 60 ++++++++++++++++++++++-------------------------- 1 file changed, 27 insertions(+), 33 deletions(-) diff --git a/R/git-protocol.R b/R/git-protocol.R index 263b8af7..2771799b 100644 --- a/R/git-protocol.R +++ b/R/git-protocol.R @@ -1,4 +1,3 @@ - #' git protocol notes, for developers #' #' Assumptions, they might be relaxed or checked for later: @@ -39,6 +38,23 @@ NULL # ------------------------------------------------------------------------- +git_creds_for_url <- function(url) { + tryCatch( + gitcreds_get(url)[c("username", "password")], + error = function(e) NULL + ) +} + +git_http_get <- function(url, options = list(), ...) { + options <- c(options, git_creds_for_url(url)) + http_get(url, options = options, ...) +} + +git_http_post <- function(url, options = list(), ...) { + options <- c(options, git_creds_for_url(url)) + http_post( url, options = options, ...) +} + #' List references in a remote git repository #' #' @details @@ -803,21 +819,10 @@ async_git_send_message_v2 <- function( "content-length" = as.character(length(msg)) ) - options <- list() - tryCatch( - { - creds <- gitcreds_get(url) - options$username <- creds$username - options$password <- creds$password - }, - error = function(e) NULL - ) - - http_post( + git_http_post( url2, data = msg, - headers = headers, - options = options + headers = headers )$then(http_stop_for_status)$ then(function(res) git_parse_message(res$content)) } @@ -833,7 +838,7 @@ async_git_send_message_v1 <- function(url, args, caps) { "accept" = "application/x-git-upload-pack-result", "content-length" = as.character(length(msg)) ) - http_post( + git_http_post( url2, data = msg, headers = headers @@ -906,7 +911,7 @@ git_list_refs_v1 <- function(url) { async_git_list_refs_v1 <- function(url) { url url1 <- paste0(url, "/info/refs?service=git-upload-pack") - http_get(url1, headers = c("User-Agent" = git_ua()))$ + git_http_get(url1, headers = c("User-Agent" = git_ua()))$ then(http_stop_for_status)$ then(function(response) git_list_refs_v1_process(response, url)) } @@ -1038,18 +1043,7 @@ async_git_list_refs_v2 <- function(url, prefixes = character()) { "git-protocol" = "version=2" ) - # headers from tracing action with GIT_CURL_VERBOSE=1 GIT_TRACE=1 - options <- list() - tryCatch( - { - creds <- gitcreds_get(url) - options$username <- creds$username - options$password <- creds$password - }, - error = function(e) NULL - ) - - http_get(url1, headers = headers, options = options)$ + git_http_get(url1, headers = headers)$ then(http_stop_for_status)$ then(function(res) async_git_list_refs_v2_process_1(res, url, prefixes)) } @@ -1695,9 +1689,9 @@ async_git_dumb_list_refs <- function(url) { "User-Agent" = git_ua() ) when_all( - http_get(url1, headers = headers)$ + git_http_get(url1, headers = headers)$ then(http_stop_for_status), - http_get(url2, headers = headers)$ + git_http_get(url2, headers = headers)$ then(http_stop_for_status) )$ then(function(res) async_git_dumb_list_refs_process(res, url)) @@ -1777,7 +1771,7 @@ async_git_dumb_get_commit <- function(url, sha) { "User-Agent" = git_ua(), "accept-encoding" = "deflate, gzip" ) - http_get(url = url1, headers = headers)$ + git_http_get(url = url1, headers = headers)$ then(http_stop_for_status)$ then(function(res) { cmt <- zip::inflate(res$content)$output @@ -1806,7 +1800,7 @@ async_git_dumb_get_tree <- function(url, sha) { "User-Agent" = git_ua(), "accept-encoding" = "deflate, gzip" ) - http_get(url = url1, headers = headers)$ + git_http_get(url = url1, headers = headers)$ then(http_stop_for_status)$ then(function(res) { cmt <- zip::inflate(res$content)$output @@ -1835,7 +1829,7 @@ async_git_dumb_get_blob <- function(url, sha) { "User-Agent" = git_ua(), "accept-encoding" = "deflate, gzip" ) - http_get(url = url1, headers = headers)$ + git_http_get(url = url1, headers = headers)$ then(http_stop_for_status)$ then(function(res) { cmt <- zip::inflate(res$content)$output From e5e84fde15bb1432c4bea884c7a2a1250d812f00 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?G=C3=A1bor=20Cs=C3=A1rdi?= Date: Thu, 4 Apr 2024 14:33:19 +0200 Subject: [PATCH 7/8] Cache git credential lookup failure --- R/git-protocol.R | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/R/git-protocol.R b/R/git-protocol.R index 2771799b..c7306a6b 100644 --- a/R/git-protocol.R +++ b/R/git-protocol.R @@ -39,10 +39,17 @@ NULL # ------------------------------------------------------------------------- git_creds_for_url <- function(url) { - tryCatch( + creds <- tryCatch( gitcreds_get(url)[c("username", "password")], error = function(e) NULL ) + if (is.null(creds)) { + do.call( + Sys.setenv, + structure(list("FAIL"), names = gitcreds_cache_envvar(url)) + ) + } + creds } git_http_get <- function(url, options = list(), ...) { @@ -52,7 +59,7 @@ git_http_get <- function(url, options = list(), ...) { git_http_post <- function(url, options = list(), ...) { options <- c(options, git_creds_for_url(url)) - http_post( url, options = options, ...) + http_post(url, options = options, ...) } #' List references in a remote git repository From 019393c9c8d155e386595c70298608cc87a739e0 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?G=C3=A1bor=20Cs=C3=A1rdi?= Date: Thu, 4 Apr 2024 16:03:02 +0200 Subject: [PATCH 8/8] Document changes in gitlab:: package sources --- NEWS.md | 3 +++ inst/docs/pkg-refs.rds | Bin 5202 -> 5366 bytes man/pkg_refs.Rd | 18 ++++++++++++++---- tools/doc/pkg-refs.Rmd | 18 ++++++++++++++---- tools/doc/pkg-refs.md | 18 ++++++++++++++---- 5 files changed, 45 insertions(+), 12 deletions(-) diff --git a/NEWS.md b/NEWS.md index 416c5187..39646d17 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # pkgdepends (development version) +* pkgdepends now supports `gitlab::` package sources better, by adding + explicit syntax to specify subdirectories (#353, @dgkf). + # pkgdepends 0.7.2 * pkgdepends now supports the `*` wildcard for parameter specifications, diff --git a/inst/docs/pkg-refs.rds b/inst/docs/pkg-refs.rds index b774acf7c761181083ccc3fc043a8932f67616c8..ba139340e52a971207f52d4ff6463738fef31f84 100644 GIT binary patch delta 5028 zcmV;V6I<-kDE29TABzY80000000Y%rd2`%Gc30N>Px`NXgf6;jmrM;Yl2);m2}x6H zX;-TFDoI<8OH{dffS#ESF~BSiQey@Biup=;M_<5zqz>9icJ1;2=;QV4cl_S#*ZdE0 z=gytq-TD1zpWXT0XYljRKf%BMaOd}T{_)P8r~iFc>$EX{W%2e0m7c4mmX%)UN*AfF zySL(7Rcz(ve3|KuF0xvxB9j|+E*EVv|Q>!S0Y?n#AB3YMhmBNVPWhv{8PR(K)&Bk9R zvW3-{rl#3xW8?-VHg6{K(ljf0WS-7uov8IjRjNUMc0_xYR;rlI)>~kBC)ZjP%w+y( zU%N>cRk@a5KY#QcQ1z&{aA|OAB2(qNEWnkiMw;~|H>qjztzD7PwZPfZvRIg9Tj`93 z-#^UFxjumYo3b`Qv0f@)KAMhn;JM?JBQMKy6e~&ZL3{;jkrl|nQfMW;g(TwHLT<}eW+szG*+~6nz!lhM7;n6{ z+}F5wxVctc$_**%{vI{kJLnEbjtU|b#DkfFqtOEXY)T+8Yf~7nH?o*-L3tLc%^MUt za?wayDD7)n_&1xnOx3wUS1~R z%rts!e$j9FS0sj(+?l6Bf z&C_7P*ZNE{wZF>!YOG?7aD+$R{3FH;Q|hT~+DITnu<<&9lx>1EhZ%XE@sIjwHn!V#C(@0|^Ed=pvI6tZB2|XkLLz zQ@v^Got*{can|95);)3aj;d1YD~2y+x>5xUwkj`W2`i~0mkAt#m6ex8UaCxI0_gV) zNhHp;_XCct8(r0VZt6~))$QCl;ukA_P#c&cLkCROU0u+!OtGA>WhluosQglG!L(~& zHoA*8k4(g_Efgd>JGM6wKf#bIoTJuY7Up_^PL4S^Fyg^JugI4Slt>JX?^E<-ibg}r z2i;-evTAeoyI>beRR=T3Ce=%p00FyE{(&r;NbNe z@Vqr37Ej%Xeq#^ooI&N*mWm_W?hrNNN>+F zp7n5eM3!F{nI7;Q4(ALptWXSthsp=o9J|lamB6fPQ-B>L3m?xQp3Dqm9f6E&R#kaf z(@a%`C>N-U?d}hejUdzeqmwfQJ{YdoWdo~``)F;=+T^M_0N1MXtlmXffAN!v1(g9$ zlOF~xf4k{rS)JEJ#t0FBsecs`mdj0EHusNde8-(MFWW4s4mVZ#pJ33EvRY2-DxE?U z(^O_YO_HQTlec5^oY6*$x0?f!Yqezy&2c0Fbk}7fRR$l}e!x#PH7c!Sc7xj3MU`f*UK+Nx~?H=C-}9rs8`ob(%o zf6!U5Uu!PQ*qt&<1A3al2Ajp(RkO~!w`YKP-X3Mc=o9Y2~(I8{K;--HnK-K|zh|#adNULi?5272+K85LFt}Dcjofkw*z+J7@K4FLA zNJcHs(Q8{BLH=)U>^l)`Y692`#>OHYe?U3crK30p=a3G4CQv{0T|P4x++-Nv1wK86 zf$f@?7m+^)s0Wc7qBJxOmx|*BP%Hu!wkL<-(NY6wNQ8)FWD+Gzr8N{xoi#d@c3&|q znC8ZNi3o=vC285_8RZXyWZD5^AP*xPf8_`D5t0Zd1ec1wrlEECG$*cTND>SNf8hQC zvF8GT6zWS3>&>=N7(Fy$Uyr7oBC|H0NCGW{IJaXUkMf4j^$4^r{Ha1hN;}Yj$rI7<{Y1&c1Q1@-!VkNbV&ddNiHo8V@S%*j`9tdfis9e z`g|LCl5y%MJ#0Q1Mp2Vte+V@ZeVjVkU3%gUeL* zVj4`mdR9|wN;YO3-Gt<(+{ZTa*5u8Bn`gg15MXS^XYR?vhci{&$kY+}xq*j-hp)&3 zSf%7c3GySc(}_+WYQTFj-3N$W!ueM?6_bByft&TVXw;jJhiR{Pf11}G)4V!;b#nar z$Qr#9`CszX9>d^I4Dw!IgUW`^v5%L!s}ie8zrCA$;5jJy>K;%L4e%cbBPafZAxr)7 ztU%9@!uo{!ar!WM7#>cJ@sZiJ+cfVzS&m)JDDfT0&5WQ+IOGCj=T6YvDtlREY|w~( zje!dU(ir|ytmJafe+Ls#peE$P__%fl;*1?+d8xC?GbVL$KX%$Ie8Xe_8pEDMPayWh z!xQ>K+RPF9#|te}c}qe&V9yJy@H?!DECI3SB?VB32YgFy$nSY2MUjo!#^`Sm6j$8H zJ2}d`Pf+-}Q z=~0;SD){&X&Ow z_C@E8LWYYPN>e7f6S-gEw^PMd^S3M89$spd@$Ev z+`s!}|1Hzid-wT+d;K<+Dc87K3~ImvU+BWnS&>zdkm~bwS#wPch|{P_^n9SLz>uHL zps_?WtqXOe5}(UQRsv_@`leH?Jew|8ifiboC&=vkb-TC^@#{V6!xD01H*Pk4xR|H& ze|hjwfB)&;7u3Bc=Qj<4ji+C7MO$H ztTV(imy|LwID}>8I<*>3FF8bD{v5~63oe`5~xEx-n9QGc|@bg6%7$wObqbO=7d zE%S2u+xb=b9fhly$3iJ*N+!Go>z3Vw7VZRw$(bJdqK4rqw5c1|u@*cYM)xGiSFvo& z^M0VC{q^16@Mzj57-}LDR<w>$X5|F)tDde71WE_LzVc;DMG5Vl?= zq3KyZXZCL0riDY@ufTO2txCXC|GQRe{2bhlPxS3n0`))Qe{6|0)c`juH^`t=Q@+4c z#v#`Qp9Fj9Bp(IRyFjJFlc0?e>Ld9+NHUGWqdmDo{3vP&%dFj|KC*e@j8V8 zq`t8c?)-Z<3=sUidsuirY!CK^+7HYWQFDDl%+?C4b6XKg>EJ_aSzrj@G3Syo#RX=l zsmfycwkVsNj!mvbUoyzweWCu3nIiM+eo_ zRPjsidFm98d^P~abHu(e=8BWOjHml!BSwU_U@iJ;Uo zL?E!27d+&!Dbbb0wVBBo{I8?iD`>KEJnm>*HOF4E*Bzii0)E#f(-nuEh^_{u>rU2e zN*RlUaMq}j{T6JFW$1KKmeaX{0F5XA8G2iG5=GGc*TILLK3 zCThWp1K_sN6+}1Js`&xwe>nn@O4k_jI>|w-01I@3^942@nMz@=9W?QFQm_e>SP%_r z7+0)TZ86dpPu1i2g{l|bEuiQ`E%;>%WLS#gdXeN8v+2mxLA(*U5aJ-h8(auz7hSrD z&wl4RRk#PZ2uH4n4>0?7ly(Qi`-1Pk#YK3D{E?9e5Wi9z_)t^Xf9|Gj>fM2yGUG8O zh!bADkc+mWQv)|WQBEih>%pjYnq8EuLUJP_@~Lh`{XeMq?-5HO`gHuauj0LtBJj|d zY>S9dPdO7)O|39bpFVl?829l*RDW;(2OWquKz!46TT=5nc z|JcM-gLw+X4Rorvf0MalHO|5Q-->&Vs5-J)Ar}mNL=@$6Fa*#I0L7|bk%|lU3~I_@ zE@v2p_0NjKY45Ep_ucgQ^iRnb4q1O-?M-!!x_GV!W>KFPf^vUZ7;AaGdjGO@Pn;v;+QTs9rq;*GZ;WFxkMQ#>Jtdg$v{*c zB?6YVE;)*+e-vJK!BT~qi>(AA5rBM{LnLs)DN0wKhQ!(dDbIq>JuQJvy3l#K!NQN> z)IKYqs6J?63hf86&wfrp$Lu2ms0QMK@BbZ>oh27bf`@Jp;Y5vbL<&L?V6d_wtl=@p zS2Y+y5+|7{fg@1~&r2WCun>hpS4Kco$^n~;cAg*xe@3xDKH3Y+V>`M&&$c)!NE0}OHhtwnE(;R(F?qW4am?+oD;ZEO1EFD?SU&- z_c#HkhRDkyHSfp=fAYbGQ$%RTvIiy>7KYNK9Cq9bRS(>9f?>U)_>C`T=O%69sBb_> zBEPq{e@O|e;SJMUW;IE`2lAV4jNnCAXYWx?Ks;G7N${M|_KHB~Ta@6DOKYKkb>W>E z)nGbrwsSczpr65DFMZ<7-y5T=VmQjPxTHBoX7-{s9ma*Y$7KQVCJ5cQuJp3aRTWp6 zXL><*_IlOQkNGc+bgl;V*_r|h|NNp|E>Q%de@m243fNoxdnJM|wxJBoHOfif{({&P zWpP*!s)bykAKpdDGQKjldtH$-H3R0@1fowrdDl+GlaX)lfnT&_KB*DPpbVwj6TH!+R%_-t&EU ze|{yCB$3x7{G;fQu0|k>*+`Rnb`_~U8ZNPvJRIol$Qw%s@E4EZx7zc-q1}8-e zC7c!KYrj1-7&~Y(K_SKdvD~x-&d4$d&)YD^L`eGtAzXEOaW{E@ug-JKV*;Y7r&al8 zyVS+!_a592jom$-)AWlk@7{a3P!Im~M$79C=U=|p-w1JknZTw2BBnSYWEG`2I>uQj u%J@ePR^;=kh5b7On7%g+S^X_KQCA@koowkIZ}^&vdH)C9`QfhZNB{uaLZyuW delta 4864 zcmV+b6aVb?Dbgr^ABzY80000000Zq@>2ushc2|=9lKzyB`PfBQ?UJb>M$#&_G9f7{ zl6I|%50#`X$0e#2U%-H*4sNAf65|U-Q4j zojZ5_{?70I0saer@7(z(`1^Nves|{|@7($GKcCe)ZA@8zynmt6bG6j6(hFVbBGq;G zUVN{Lt=yb1GriG8R!dc6a-+`WqAjRbEgN;N;T88S)LKI$_){(0wJw@E5zmrkBG1w? z)9<0@YzCwKVv4#^dA@(pQGXa^~(){X5`Yrj01szR!~E_sUAZeU{bZXz#Dvw}zF>1@`CT5nXP8e~U*v}b9hirH+v1%`KWtyRHH=8yKZ zn{-i?Yx(5m;~#*k$GwG1gHsckD&J)Ru1q!3tT(wyO_Oi!ij1xW&X$(N!YtcLXEgl& zVQ$X#0rcOLwE>C^OWhcI_J4xzAU*KW#H52r6`88CZrI~Myej+4gMRw2t+`M+NHlIt ze+18e9j6?5S)QXURUKz&^uxL7_u# zT88Gv>yAv@3U-ueZ8w{;YIHVWFf0(Z>^&DD6@@6>MFUPIuLlJN3MLh=%%ox0FZVFr_H32ewrrPJMRZAG05`Ind9u`+Id zN(1&A#XZcfs&r*820XOpS!bvL(m#ze9Bp<-lHv`qVQc+~1cM56kx2>GwApSnuRx`# z-Zb^j&Vuqd>+nkJp165ORjKtA!EGKLkN-_*8zf@Z=?HZVk z?xM{j6R~Rx1MbiUbb0M9d4@fzrmm-Wwo5vRXT+z zrm4()nj}ewCU3{+IirmhZ#M@d*J{fan&U_U=&s8|sti!BR10_l8~E2&*Vss`Rdt?- zr)ELJG*K5qgErFuJ?9w9O10j=C)A&PR*2tse+P)NE0sbYh~b^>gXM3X8AHw?1poH+ z>lf(mZ7K?AfHq-5@QxxZl9mHjd6BE7Q+`*S_8OPlLMe{|;od`78ZdQpdwN={)ZZ=h`JMNK?IO%r^ zf1$Hrzt&uqu{&j!2J|$84K|DSt7e^d@6Q19yg$m!g-k)&>*GB(SWjS@y_2pxL&XD7 zpc>c=o9Y2~(I8_Uans)yAnO1<#OT*!q}4T{2hj~@pThJo*A-&N&I=+Y;I39{pRhx5 zB%_w+=(VkmApbWv_MHeeH394eV`GsHf1sS}(ovj)b4Z6i6R02hE}xkTZZeGT0-v73 zz;?~ci^!h?)Pu+kQ5u?tOU3a5C>DVV+mplaXsH1-Btk?oGKmtV(i#e;&KjLcyRVoQ zOmpMCM1(_-lC*5|jPi#;GVOpdkcSbDANfIjgd~Cq!KI?FX=oij&50`-k_3YRf4ILu z?72W7h5C}idb4d5Mh{KclhKq@WY)$LNuY%g=XMO_(H?|OpqfSyAhFujmC>muPeAa?!*)OvoPCV*^!-IKe(ni5Y>xd&ZM(}e(hnIm= z&LhAI0XR@huZj>&AbX*`X7^@+!S@R6>^sLQPt);(e+fzcAtVP$ zM<{<$i#{<{*ML{cCHY|(<1dG_lA0mf#0=AJx!I#b1sOdXM*8+b@~_=-G$ zRZ2dTAU_g2o#^zT2D}&3eSp{{oPUK=G5Mz!xLI$DM!oxdnD&OJe|hUM&70FVC&zD( ztkFA>|07TBF%15QLEhVIP}$Hq_VH48Rbn;iw|A2dJO?FT-2*D30saGFXE}??r7Q7g=`ML;S<(LI9>3;4rVv-;84U3U4V1tJa#j> zP{)A>>biore?@Q(gBZFFhp{N4gOM9S59a#o z`**+Tzh%05@4k9)uiwTp#?7V=7xQ%f zuMZyTe?Q*)n!5Mo{H8&$@$?(+=*0Y{KDJ#wg~c)5cdyy>$HA!(M7QbIovn_m>!@C3 zLY~$pz-Hm-_%x7ZH;~kxXJ}$r~h|>x8eekm9Yz4R%N^SZTr5+ zV|}87`YpH%ryNT)FRQc$cxt9;ZiIVZ9fIIae=(Vmm+ATG8a)3;LsGA5!0TSIo9QX1 z)682}yKwIK2&~)Dssxw+f2&^ON40i*qHm{IrT-ECXRCmzOto3LK?c=?@)aJ04Y@A( zu+k^B$&7*mEl_^(uw-J>a1>opnKZC=X)a(HUycoD;uZkjZ$zoa54;E1?8Zj8KOfyN ze_*+f?qPA>usvu#wI3J-qUQR{iY+=-=eD$v@`{I6|6vG_dQM7Wt^|xlQ#6Vk+ zMnk-mPriRjud|NJB1Ld&G#1thfD%R(v$q6kEcHi7_Q?&ne_rVe(`>m?0>NL28W^md zFYRy_8BD)MM-@WN>8y*Zl_uvVgs0uRB1q0sO8_rYnwLuvlzR1MOtZ<|eV) z1ZRy(qHn?GScXm)WjUQIK>9rSFM!tJUs!3f{8j8UI$yeXiI_TuPmw$01AO3bxCv9_ zyhx^wr}RZ6*T}`73~PiVw8t}lXn`s~${m(O3ke*WVR?(&1+G8~91#)@!8 zPxx!Dag1sN_k=ylA80T|sQdA$18MEgR-Vze^o}H8cG6<}feTqs8L`qToCvzo`&#hg zHdVRNRldDm%@0V=5jIr1#@NY84tjK0pc|ZTLh;B{Q+e&6iMNx2O`ycee_Bw(xb(4V zi;=!~JR5^-DuZ*^Nur|}cTiM2xWQ5s7aki?)ZrY~a9mpv&o`-=rVGX}r zv=ybF-Sk8`VJ$2yq9R;&e^IWS#f^ygq`DRL|D-Ci$1H{D)A4U##d{+~;Gr?u7IB@P za!6lItuRl&efIb%?&GJZ{@^YLReFDt0T8}=@o!}So)7Q9cyr(ZM>vsiRX|)tVlx~K z2EvFN=y+%+1;T2agZ;l1_Z(5hE_&)imd}WFpuZ1v05w*s>X$a+e}X-OnliZ|R_Y%* zhGWB9S?-7F%jqAJuN|`f#Q3yd2yM3*Z#cQ#{mWIm3PvJCKjQ`E?L4(11eG&G<%7pi&cg% zGcd;z`Eyi0Xxj^{?~AhF6MnEIG91(8rsKY3VFm-pCD*zFMSTLnIT?t3qi}s`3tXd^ zO5wc;JoB!(YDXXv0mz3}A_!b?9?jJ`A+dHq%7)-`PfK8ve=c-hZm@!2IJJ-66&0E+ zOriZC_Sw%V=)87h0M$TT@Z*1CVP45qci^ELL^x4n9Fc-h1Q@Jr2y1u@@>LCnkiMf0vWJgM(`{m!KTWG65orqZfFe7m%TqI45wSCTqV|+XGkk>~R844Uv~a zYTl6#es_Qkr-;ywWe-d&EDWVdIqbL>j?cN}1jBko@f+Xr%}v_GQQv@&ME+>6B@$M{ ztBSYGYLb9Y)lDTj^z+t12#6&h&yVfAz|4 zpYpG)=v*=5^ECw&{`pnAT%rg@xAC48u($Y&F9hF^LK&KCl#{;w1+gj0;;_c9rs*Xt>0hBZgT0lqrVF^>s|rk+;iyX{gJU)_6f zKQwk1LQd1Kzqxzw;X*z5w{NaH<$e88zih%?akpuJh$&78Sw$(1j&T->GTxS7k}}\preformatted{[=][github::]/[/][] +\if{html}{\out{
}}\preformatted{[=][github::]/[/-/][] }\if{html}{\out{
}} \itemize{ \item \verb{} is the name of the package. If this is missing, then the name of the repository is used. -\item \verb{} is a GitLab username or group name. -\item \verb{} is the name of the repository. +\item \verb{} is a typically the GitLab username or group name, but +it may contain subgroups. +\item \verb{} is the name of the repository, or the project in GitLab +terminology. \item \verb{} optional subdirectory, if the package is within a -subdirectory in the repository. +subdirectory in the repository. Note that for GitLab, this must come +after a \verb{/-} prefix, to be able to distinguish it from subgroups. \item \verb{} may specify a git branch, tag or (prefix of) a commit hash. } If \verb{} is missing, then the latest commit of the \emph{default} branch is used. +\verb{gitlab::} supports git submodules, see the \code{git-submodules} configuration +entry. + Examples: \if{html}{\out{
}}\preformatted{gitlab::gaborcsardi/cli gitlab::r-hub/filelock@main +gitlab::group/subgroup/subsubgroup/project/-/subdir@ref }\if{html}{\out{
}} } @@ -306,6 +313,9 @@ a git branch, tag or (prefix of) a commit hash: \verb{@}. If \verb{} is missing, then the latest commit of the \emph{default} branch is used. +\verb{git::} supports git submodules, see the \code{git-submodules} configuration +entry. + Examples: \if{html}{\out{
}}\preformatted{git::https://github.com/r-lib/crayon diff --git a/tools/doc/pkg-refs.Rmd b/tools/doc/pkg-refs.Rmd index fb81738f..afe52451 100644 --- a/tools/doc/pkg-refs.Rmd +++ b/tools/doc/pkg-refs.Rmd @@ -260,24 +260,31 @@ A GitHub remote string can also be used instead of an URL, for example: Packages from a GitLab repository. Full syntax: ``` -[=][github::]/[/][] +[=][github::]/[/-/][] ``` - `` is the name of the package. If this is missing, then the name of the repository is used. -- `` is a GitLab username or group name. -- `` is the name of the repository. +- `` is a typically the GitLab username or group name, but + it may contain subgroups. +- `` is the name of the repository, or the project in GitLab + terminology. - `` optional subdirectory, if the package is within a - subdirectory in the repository. + subdirectory in the repository. Note that for GitLab, this must come + after a `/-` prefix, to be able to distinguish it from subgroups. - `` may specify a git branch, tag or (prefix of) a commit hash. If `` is missing, then the latest commit of the _default_ branch is used. +`gitlab::` supports git submodules, see the `git-submodules` configuration +entry. + Examples: ``` gitlab::gaborcsardi/cli gitlab::r-hub/filelock@main +gitlab::group/subgroup/subsubgroup/project/-/subdir@ref ``` ### Packages in git repositories (`git::`) @@ -298,6 +305,9 @@ Full syntax: If `` is missing, then the latest commit of the _default_ branch is used. +`git::` supports git submodules, see the `git-submodules` configuration +entry. + Examples: ``` git::https://github.com/r-lib/crayon diff --git a/tools/doc/pkg-refs.md b/tools/doc/pkg-refs.md index 90e703e1..3ea75778 100644 --- a/tools/doc/pkg-refs.md +++ b/tools/doc/pkg-refs.md @@ -256,25 +256,32 @@ A GitHub remote string can also be used instead of an URL, for example: Packages from a GitLab repository. Full syntax: -\if{html}{\out{
}}\preformatted{[=][github::]/[/][] +\if{html}{\out{
}}\preformatted{[=][github::]/[/-/][] }\if{html}{\out{
}} \itemize{ \item \verb{} is the name of the package. If this is missing, then the name of the repository is used. -\item \verb{} is a GitLab username or group name. -\item \verb{} is the name of the repository. +\item \verb{} is a typically the GitLab username or group name, but +it may contain subgroups. +\item \verb{} is the name of the repository, or the project in GitLab +terminology. \item \verb{} optional subdirectory, if the package is within a -subdirectory in the repository. +subdirectory in the repository. Note that for GitLab, this must come +after a \verb{/-} prefix, to be able to distinguish it from subgroups. \item \verb{} may specify a git branch, tag or (prefix of) a commit hash. } If \verb{} is missing, then the latest commit of the \emph{default} branch is used. +\verb{gitlab::} supports git submodules, see the \code{git-submodules} configuration +entry. + Examples: \if{html}{\out{
}}\preformatted{gitlab::gaborcsardi/cli gitlab::r-hub/filelock@main +gitlab::group/subgroup/subsubgroup/project/-/subdir@ref }\if{html}{\out{
}} } @@ -296,6 +303,9 @@ a git branch, tag or (prefix of) a commit hash: \verb{@}. If \verb{} is missing, then the latest commit of the \emph{default} branch is used. +\verb{git::} supports git submodules, see the \code{git-submodules} configuration +entry. + Examples: \if{html}{\out{
}}\preformatted{git::https://github.com/r-lib/crayon