Skip to content

Commit

Permalink
Merge pull request #353 from r-world-devs/test
Browse files Browse the repository at this point in the history
Release 1.1.0
  • Loading branch information
maciekbanas authored Jan 8, 2024
2 parents 9ae656a + 222cc4c commit e42d640
Show file tree
Hide file tree
Showing 118 changed files with 7,659 additions and 972 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: GitStats
Title: Get Statistics from GitHub and GitLab
Version: 1.0.0
Version: 1.1.0
Authors@R: c(
person(given = "Maciej", family = "Banas", email = "[email protected]", role = c("aut", "cre")),
person(given = "Kamil", family = "Koziej", email = "[email protected]", role = "aut"),
Expand Down
4 changes: 4 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -4,14 +4,18 @@ S3method(gitstats_plot,commits_stats)
S3method(gitstats_plot,repos_stats)
export("%>%")
export(create_gitstats)
export(get_R_package_usage)
export(get_commits)
export(get_commits_stats)
export(get_files)
export(get_orgs)
export(get_repos)
export(get_repos_stats)
export(get_users)
export(gitstats_plot)
export(pull_R_package_usage)
export(pull_commits)
export(pull_files)
export(pull_repos)
export(pull_repos_contributors)
export(pull_users)
Expand Down
19 changes: 19 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,22 @@
# GitStats 1.1.0

## New features:

- `pull_R_package_usage()` with `get_R_package_usage()` functions to pull repositories where package name is found in DESCRIPTION or NAMESPACE files or code blobs with phrases related to using an R package (`library(package)`, `require(package)`) ([#326](https://github.com/r-world-devs/GitStats/issues/326), [#341](https://github.com/r-world-devs/GitStats/issues/341)),
- `pull_files()` with `get_files()` to pull content of text files ([#200](https://github.com/r-world-devs/GitStats/issues/200)).
- possibility to pass specific repositories to `GitStats` with `set_host()` function by using `repos` parameter instead of `orgs` ([#330](https://github.com/r-world-devs/GitStats/issues/330)).

## Bug fixes:

- fixed pulling responses when GitLab groups have private or empty content ([#314](https://github.com/r-world-devs/GitStats/issues/314)),
- fixed pulling users when pulling from multiple hosts ([#312](https://github.com/r-world-devs/GitStats/issues/312)),
- improved search API error handling.

## Minor changes and features:

- rename column names for repository output - `id` to `repo_id` and `name` to `repo_name`,
- added a `default_branch` column to repositories output as a consequence of [#200](https://github.com/r-world-devs/GitStats/issues/200).

# GitStats 1.0.0

## Breaking changes:
Expand Down
60 changes: 47 additions & 13 deletions R/EngineGraphQL.R
Original file line number Diff line number Diff line change
Expand Up @@ -29,11 +29,12 @@ EngineGraphQL <- R6::R6Class("EngineGraphQL",
#' @param vars A list of named variables.
#' @return A list.
gql_response = function(gql_query, vars = "null") {
httr2::request(paste0(self$gql_api_url, "?")) %>%
httr2::req_headers("Authorization" = paste0("Bearer ", private$token)) %>%
httr2::req_body_json(list(query = gql_query, variables = vars)) %>%
httr2::req_perform() %>%
httr2::resp_body_json()
response <- private$perform_request(
gql_query = gql_query,
vars = vars
)
response_list <- httr2::resp_body_json(response)
return(response_list)
},

#' @description Get information on users in the form of table
Expand All @@ -45,6 +46,29 @@ EngineGraphQL <- R6::R6Class("EngineGraphQL",
private$prepare_user_table()
}) %>%
purrr::list_rbind()
},

#' @description A method to retrieve given files from all repositories for
#' an organization in a table format.
#' @param org An organization.
#' @param file_path A file path.
#' @param pulled_repos Optional parameter to pass repository output object.
#' @param settings A list of `GitStats` settings.
#' @return A table.
pull_files = function(org, file_path, pulled_repos = NULL) {
if (!private$scan_all) {
cli::cli_alert_info("[Engine:{cli::col_yellow('GraphQL')}][org:{org}] Pulling {file_path} files...")
}
files_table <- private$pull_file_from_org(
org = org,
file_path = file_path,
pulled_repos = pulled_repos
) %>%
private$prepare_files_table(
org = org,
file_path = file_path
)
return(files_table)
}

),
Expand All @@ -55,19 +79,29 @@ EngineGraphQL <- R6::R6Class("EngineGraphQL",
# @field A boolean.
scan_all = FALSE,

perform_request = function(gql_query, vars) {
response <- httr2::request(paste0(self$gql_api_url, "?")) %>%
httr2::req_headers("Authorization" = paste0("Bearer ", private$token)) %>%
httr2::req_body_json(list(query = gql_query, variables = vars)) %>%
httr2::req_retry(
is_transient = ~ httr2::resp_status(.x) == "400|502",
max_seconds = 60
) %>%
httr2::req_perform()
return(response)
},

# @description A method to pull information on user.
# @param username A login.
# @return A user response.
pull_user = function(username) {
response <- self$gql_response(
gql_query = self$gql_query$user(),
vars = list("user" = username)
)
if (length(response$errors) > 0) {
cli::cli_abort(
response$errors[[1]]$message
response <- NULL
try(
response <- self$gql_response(
gql_query = self$gql_query$user(),
vars = list("user" = username)
)
}
)
return(response)
}
)
Expand Down
141 changes: 118 additions & 23 deletions R/EngineGraphQLGitHub.R
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,7 @@ EngineGraphQLGitHub <- R6::R6Class("EngineGraphQLGitHub",
#' @param settings A list of `GitStats` settings.
#' @return A table.
pull_repos = function(org,
settings) {
settings) {
if (settings$search_param %in% c("org", "team")) {
if (settings$search_param == "org") {
if (!private$scan_all) {
Expand Down Expand Up @@ -89,30 +89,41 @@ EngineGraphQLGitHub <- R6::R6Class("EngineGraphQLGitHub",
#' @param settings A list of `GitStats` settings.
#' @return Nothing.
pull_repos_supportive = function(org,
settings) {
settings) {
NULL
},

#' @description Method to pull all commits from organization, optionally
#' filtered by team members.
#' @param org An organization.
#' @param repos_names A vector of names of repositories.
#' @param date_from A starting date to look commits for.
#' @param date_until An end date to look commits for.
#' @param settings A list of `GitStats` settings.
#' @return A table of commits.
pull_commits = function(org,
date_from,
date_until,
settings) {
repos_table <- self$pull_repos(
org = org,
settings = list(search_param = "org")
)
repos_names <- repos_table$name

if (settings$search_param == "org") {
repos = NULL,
date_from,
date_until,
settings) {
if (is.null(repos)) {
repos_table <- self$pull_repos(
org = org,
settings = list(search_param = "org")
)
repos_names <- repos_table$repo_name
}
if (!is.null(repos)) {
repos_names <- repos
}
if (settings$search_param %in% c("org", "repo")) {
if (!private$scan_all) {
cli::cli_alert_info("[GitHub][Engine:{cli::col_yellow('GraphQL')}][org:{org}] Pulling commits...")
if (settings$search_param == "org") {
cli::cli_alert_info("[GitHub][Engine:{cli::col_yellow('GraphQL')}][org:{org}] Pulling commits...")
}
if (settings$search_param == "repo") {
cli::cli_alert_info("[GitHub][Engine:{cli::col_yellow('GraphQL')}][org:{org}][custom repositories] Pulling commits...")
}
}
repos_list_with_commits <- private$pull_commits_from_repos(
org = org,
Expand Down Expand Up @@ -156,6 +167,7 @@ EngineGraphQLGitHub <- R6::R6Class("EngineGraphQLGitHub",
settings) {
NULL
}

),
private = list(

Expand Down Expand Up @@ -249,16 +261,29 @@ EngineGraphQLGitHub <- R6::R6Class("EngineGraphQLGitHub",
# @param repos_list A list of repositories.
# @return Table of repositories.
prepare_repos_table = function(repos_list) {
repos_table <- purrr::map_dfr(repos_list, function(repo) {
repo$languages <- purrr::map_chr(repo$languages$nodes, ~ .$name) %>%
paste0(collapse = ", ")
repo$created_at <- gts_to_posixt(repo$created_at)
repo$issues_open <- repo$issues_open$totalCount
repo$issues_closed <- repo$issues_closed$totalCount
repo$last_activity_at <- as.POSIXct(repo$last_activity_at)
repo$organization <- repo$organization$login
data.frame(repo)
})
if (length(repos_list) > 0) {
repos_table <- purrr::map_dfr(repos_list, function(repo) {
repo$default_branch <- if(!is.null(repo$default_branch)) {
repo$default_branch$name
} else {
""
}
repo$languages <- purrr::map_chr(repo$languages$nodes, ~ .$name) %>%
paste0(collapse = ", ")
repo$created_at <- gts_to_posixt(repo$created_at)
repo$issues_open <- repo$issues_open$totalCount
repo$issues_closed <- repo$issues_closed$totalCount
repo$last_activity_at <- as.POSIXct(repo$last_activity_at)
repo$organization <- repo$organization$login
repo <- data.frame(repo) %>%
dplyr::relocate(
default_branch,
.after = repo_name
)
})
} else {
repos_table <- NULL
}
return(repos_table)
},

Expand Down Expand Up @@ -446,6 +471,76 @@ EngineGraphQLGitHub <- R6::R6Class("EngineGraphQLGitHub",
user_table <- NULL
}
return(user_table)
},

# @description Pull all given files from all repositories of an
# organization.
# @param org An organization.
# @param file_path Path to a file.
# @param pulled_repos Optional, if not empty, function will make use of the
# argument to iterate over it when pulling files.
# @return A response in a list form.
pull_file_from_org = function(org, file_path, pulled_repos = NULL) {
if (is.null(pulled_repos)) {
repos_list <- private$pull_repos_from_org(
from = "org",
org = org
)
repositories <- purrr::map(repos_list, ~ .$repo_name)
def_branches <- purrr::map(repos_list, ~ .$default_branch$name)
} else {
repos_table <- pulled_repos %>%
dplyr::filter(organization == org)
repositories <- repos_table$repo_name
def_branches <- repos_table$default_branch
}
files_list <- purrr::map(file_path, function(file_path) {
files_list <- purrr::map2(repositories, def_branches, function(repository, def_branch) {
files_query <- self$gql_query$files_by_repo()
files_response <- self$gql_response(
gql_query = files_query,
vars = list(
"org" = org,
"repo" = repository,
"file_path" = paste0(def_branch, ":", file_path)
)
)
}) %>%
purrr::map(~ .$data$repository)
names(files_list) <- repositories
files_list <- purrr::discard(files_list, ~ length(.$object) == 0)
return(files_list)
})
names(files_list) <- file_path
return(files_list)
},

# @description Prepare files table.
# @param files_response A list.
# @param org An organization.
# @return A table with information on files.
prepare_files_table = function(files_response, org, file_path) {
if (!is.null(files_response)) {
files_table <- purrr::map(file_path, function(file) {
purrr::imap(files_response[[file]], function(repository, name) {
data.frame(
"repo_name" = repository$name,
"repo_id" = repository$id,
"organization" = org,
"file_path" = file,
"file_content" = repository$object$text,
"file_size" = repository$object$byteSize,
"repo_url" = repository$url,
"api_url" = self$gql_api_url
)
}) %>%
purrr::list_rbind()
}) %>%
purrr::list_rbind()
} else {
files_table <- NULL
}
return(files_table)
}
)
)
Loading

0 comments on commit e42d640

Please sign in to comment.