Skip to content

Commit

Permalink
Mock some responses.
Browse files Browse the repository at this point in the history
  • Loading branch information
maciekbanas committed Oct 7, 2024
1 parent c9fd7a5 commit 057c64b
Show file tree
Hide file tree
Showing 3 changed files with 38 additions and 12 deletions.
7 changes: 3 additions & 4 deletions R/EngineRestGitLab.R
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,7 @@ EngineRestGitLab <- R6::R6Class(
private$map_search_into_repos(
progress = progress
) %>%
private$pull_repos_languages(
private$get_repos_languages(
progress = progress
)
}
Expand Down Expand Up @@ -87,7 +87,6 @@ EngineRestGitLab <- R6::R6Class(
issues <- purrr::map(repos_table$repo_id, function(repos_id) {
id <- gsub("gid://gitlab/Project/", "", repos_id)
issues_endpoint <- paste0(self$rest_api_url, "/projects/", id, "/issues_statistics")

self$response(
endpoint = issues_endpoint
)[["statistics"]][["counts"]]
Expand Down Expand Up @@ -237,7 +236,7 @@ EngineRestGitLab <- R6::R6Class(
endpoint = repo_endpoint
)
full_repos_list <- repos_response %>%
private$pull_repos_languages(
private$get_repos_languages(
progress = progress
)
return(full_repos_list)
Expand Down Expand Up @@ -301,7 +300,7 @@ EngineRestGitLab <- R6::R6Class(
},

# Pull languages of repositories.
pull_repos_languages = function(repos_list, progress) {
get_repos_languages = function(repos_list, progress) {
repos_list_with_languages <- purrr::map(repos_list, function(repo) {
id <- repo$id
repo$languages <- names(self$response(paste0(private$endpoints[["projects"]], id, "/languages")))
Expand Down
15 changes: 15 additions & 0 deletions tests/testthat/helper-fixtures.R
Original file line number Diff line number Diff line change
Expand Up @@ -735,3 +735,18 @@ test_fixtures$github_issues_response <- list(
test_fixtures$github_open_issue_response,
test_fixtures$github_closed_issue_response
)

test_fixtures$gitlab_issues_response <- list(
"statistics" = list(
"counts" = list(
"all" = 3,
"closed" = 2,
"opened" = 1
)
)
)

test_fixtures$gitlab_languages_response <- list(
"Python" = 100,
"R" = 50
)
28 changes: 20 additions & 8 deletions tests/testthat/test-01-get_repos-GitLab.R
Original file line number Diff line number Diff line change
Expand Up @@ -90,16 +90,20 @@ test_that("`map_search_into_repos()` works", {
test_mocker$cache(gl_search_repos_by_code)
})

test_that("`pull_repos_languages` works", {
test_that("`get_repos_languages` works", {
repos_list <- test_mocker$use("gl_search_repos_by_code")
repos_list[[1]]$id <- "45300912"
suppressMessages(
repos_list_with_languages <- test_rest_gitlab_priv$pull_repos_languages(
repos_list = repos_list,
progress = FALSE
)
mockery::stub(
test_rest_gitlab_priv$get_repos_languages,
"self$response",
test_fixtures$gitlab_languages_response
)
repos_list_with_languages <- test_rest_gitlab_priv$get_repos_languages(
repos_list = repos_list,
progress = FALSE
)
purrr::walk(repos_list_with_languages, ~ expect_list_contains(., "languages"))
expect_equal(repos_list_with_languages[[1]]$languages, c("Python", "R"))
})

test_that("`prepare_repos_table()` prepares repos table", {
Expand All @@ -121,10 +125,8 @@ test_that("GitHost adds `repo_api_url` column to GitLab repos table", {

test_that("`tailor_repos_response()` tailors precisely `repos_list`", {
gl_repos_by_code <- test_mocker$use("gl_search_repos_by_code")

gl_repos_by_code_tailored <-
gitlab_testhost_priv$tailor_repos_response(gl_repos_by_code)

gl_repos_by_code_tailored %>%
expect_type("list") %>%
expect_length(length(gl_repos_by_code))
Expand Down Expand Up @@ -158,6 +160,11 @@ test_that("GitHost prepares table from GitLab repositories response", {
})

test_that("`get_repos_issues()` adds issues to repos table", {
mockery::stub(
test_rest_gitlab$get_repos_issues,
"self$response",
test_fixtures$gitlab_issues_response
)
gl_repos_by_code_table <- test_mocker$use("gl_repos_by_code_table")
gl_repos_by_code_table <- test_rest_gitlab$get_repos_issues(
gl_repos_by_code_table,
Expand All @@ -175,6 +182,11 @@ test_that("`get_repos_issues()` adds issues to repos table", {
})

test_that("`get_repos_contributors()` adds contributors to repos table", {
mockery::stub(
test_rest_gitlab$get_repos_contributors,
"private$get_contributors_from_repo",
"Maciej Banas"
)
gl_repos_table_with_contributors <- test_rest_gitlab$get_repos_contributors(
test_mocker$use("gl_repos_table_with_api_url"),
progress = FALSE
Expand Down

0 comments on commit 057c64b

Please sign in to comment.