Skip to content

Commit

Permalink
initial chart directory
Browse files Browse the repository at this point in the history
  • Loading branch information
Edouard-Legoupil committed Feb 8, 2024
1 parent fa7ea1a commit a2dae97
Show file tree
Hide file tree
Showing 72 changed files with 2,429 additions and 474 deletions.
5 changes: 4 additions & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -16,14 +16,17 @@ BugReports: https://github.com/unhcr-americas/iati/issues
Imports:
dplyr,
ggplot2,
glue,
knitr,
magrittr,
scales,
showtext,
stringr,
sysfonts,
systemfonts,
tidyr,
unhcrthemes
Suggests:
knitr,
rmarkdown,
testthat
VignetteBuilder:
Expand Down
1 change: 0 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@ export("%>%")
export(show_donors)
export(show_earmarking)
export(show_expenditure)
export(show_implementers)
export(show_indicators)
export(show_partnership)
export(show_sectors)
Expand Down
35 changes: 35 additions & 0 deletions R/data.R
Original file line number Diff line number Diff line change
Expand Up @@ -133,6 +133,8 @@
#' \item{\code{result_indicator_target_value_1}}{character COLUMN_DESCRIPTION}
#' \item{\code{result_indicator_target_dimension_2}}{character COLUMN_DESCRIPTION}
#' \item{\code{result_indicator_target_value_2}}{character COLUMN_DESCRIPTION}
#' \item{\code{result_type_name}}{character COLUMN_DESCRIPTION}
#' \item{\code{result_type_description}}{character COLUMN_DESCRIPTION}
#'}
#' @source \url{https://iatistandard.org/en/iati-standard/203/}
#' @examples
Expand All @@ -153,6 +155,8 @@
#' \item{\code{sector_code}}{character COLUMN_DESCRIPTION}
#' \item{\code{sector_pct}}{character COLUMN_DESCRIPTION}
#' \item{\code{sector_desc}}{character COLUMN_DESCRIPTION}
#' \item{\code{sector_vocabulary_name}}{character COLUMN_DESCRIPTION}
#' \item{\code{sector_vocabulary_description}}{character COLUMN_DESCRIPTION}
#'}
#' @source \url{https://iatistandard.org/en/iati-standard/203/}
#' @examples
Expand Down Expand Up @@ -309,6 +313,10 @@
#' \item{\code{participating_org_role}}{double An IATI code describing the organisation’s role in the activity (donor, agency, etc.). see codeOrganisationRole}
#' \item{\code{participating_org_activity_id}}{logical A valid activity identifier published by the participating organisation which points to the activity that it has published to IATI that describes its role in this activity.}
#' \item{\code{participating_org_crs_channel_code}}{logical Under CRS++ Reporting Directives this code identifies the implementing agency. Codes ending in ‘00’ are generic and are similar to the OrganisationType code.}
#' \item{\code{participating_org_type_name}}{character COLUMN_DESCRIPTION}
#' \item{\code{participating_org_type_description}}{character COLUMN_DESCRIPTION}
#' \item{\code{participating_org_role_name}}{character COLUMN_DESCRIPTION}
#' \item{\code{participating_org_role_description}}{character COLUMN_DESCRIPTION}
#'}
#' @source \url{https://iatistandard.org/en/iati-standard/203/}
#' @examples
Expand Down Expand Up @@ -339,7 +347,34 @@
#### All code list doc ############


#' @title codeBudgetType
#' @description This is a Core codelist.
#' @format A data frame with 2 rows and 6 variables:
#' \describe{
#' \item{\code{code}}{double COLUMN_DESCRIPTION}
#' \item{\code{name}}{character COLUMN_DESCRIPTION}
#' \item{\code{description}}{character COLUMN_DESCRIPTION}
#' \item{\code{category}}{logical COLUMN_DESCRIPTION}
#' \item{\code{url}}{logical COLUMN_DESCRIPTION}
#' \item{\code{status}}{character COLUMN_DESCRIPTION}
#'}
#' @source \url{https://iatistandard.org/en/iati-standard/203/codelists/budgettype/}
"codeBudgetType"


#' @title codeBudgetStatus
#' @description Code to denote if the described budget is binding. This is a Core codelist.
#' @format A data frame with 2 rows and 6 variables:
#' \describe{
#' \item{\code{code}}{double COLUMN_DESCRIPTION}
#' \item{\code{name}}{character COLUMN_DESCRIPTION}
#' \item{\code{description}}{character COLUMN_DESCRIPTION}
#' \item{\code{category}}{logical COLUMN_DESCRIPTION}
#' \item{\code{url}}{logical COLUMN_DESCRIPTION}
#' \item{\code{status}}{character COLUMN_DESCRIPTION}
#'}
#' @source \url{https://iatistandard.org/en/iati-standard/203/codelists/budgetstatus/}
"codeBudgetStatus"


#' @title codeCollaborationType
Expand Down
12 changes: 11 additions & 1 deletion R/globals.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,5 +4,15 @@

globalVariables(unique(c(
# show_donors:
"programmme_lab", "reporting_org_type_name", "transaction_type_name", "transaction_value_USD", "year"
"programmme_lab", "reporting_org_type_name", "transaction_type_name", "transaction_value_USD", "year",
# show_earmarking:
"aid_type1_name",
# show_expenditure:
"aid_type1_name",
# show_indicators:
"actual", "gap_actual_target", "gap_color", "indicator_measure_name", "operation", "result_indicator_baseline_dimension_1", "result_indicator_baseline_dimension_2", "result_indicator_baseline_dimension_value_1", "result_indicator_baseline_dimension_value_2", "result_indicator_baseline_location_ref", "result_indicator_baseline_value", "result_indicator_target_value", "result_indicator_title", "result_title", "target",
# show_partnership:
"participating_org_eng", "participating_org_role_name", "participating_org_type_name",
# show_sectors:
"sector_desc", "sector_pct", "sector_vocabulary", "thiprogramme_lab"
)))
122 changes: 81 additions & 41 deletions R/show_donors.R
Original file line number Diff line number Diff line change
@@ -1,11 +1,15 @@
# WARNING - Generated by {fusen} from dev/dev_unhcr_programme.Rmd: do not edit by hand

#' Ploting Donors
#' show_donors
#'
#' @description Who are the main donors by country in terms of number of projects and/or total budget?
#'
#' @param thisyear year to select starting from 2016 - could be one year or a list
#' @param thisprogrammme_lab programme_lab
#' @param thistransaction_type_name Transaction type
#' @param year year to select starting from 2016 - could be one year or a list
#' @param programme_lab A character vector corresponding to the name of the programme.
#' @param iati_identifier_ops A character vector corresponding to the name of the operation.
#' @param ctr_name A character vector corresponding to the name of the country.
#' @param transaction_type_name Transaction type - default is "Incoming Commitment" ,
#' can also be "Disbursement", or "Expenditure"
#'
#' @import ggplot2
#' @import dplyr
Expand All @@ -19,39 +23,77 @@
#'
#' knitr::kable( codeTransactionType |> dplyr::select(name, description) )
#'
#' show_donors(thisyear = 2018,
#' thisprogrammme_lab = "The Americas",
#' thistransaction_type_name = "Incoming Commitment" )
#' show_donors(year = 2018,
#' programme_lab = "The Americas",
#' transaction_type_name = "Incoming Commitment" )
#'
#' show_donors(year = 2018,
#' ctr_name = "Brazil",
#' transaction_type_name = "Incoming Commitment" )
#'
#' show_donors(thisyear = 2018,
#' thisprogrammme_lab = "The Americas",
#' thistransaction_type_name = "Disbursement" )
#'
show_donors <- function(thisyear,
thisprogrammme_lab,
thistransaction_type_name = "Incoming Commitment" ) {
#require(ggplot2)
# require(tidyverse)
# require(scales)
Transaction0 <- iati::dataTransaction |>
dplyr::left_join(iati::dataActivity, by= c("iati_identifier"))

Transaction <- Transaction0 |>
## Add filters
dplyr::filter(year >= as.integer(thisyear)) |>
#dplyr::filter(year >= 2018) |>
dplyr::filter(programmme_lab == as.character(thisprogrammme_lab)) |>
## Add filters transaction type transaction type
# dplyr::filter(TransactionType == "Incoming Commitment") |>
dplyr::filter(transaction_type_name %in% thistransaction_type_name) |>

dplyr::group_by(year, reporting_org_type_name) |>
dplyr::summarise( transaction_value_USD = sum(transaction_value_USD , na.rm = TRUE)) |>
dplyr::mutate(reporting_org_type_name = as.character(reporting_org_type_name) ) |>
dplyr::mutate(reporting_org_type_name = as.factor(reporting_org_type_name) )

p <- Transaction |>
#' show_donors(year = 2018,
#' programme_lab = "The Americas",
#' transaction_type_name = "Disbursement" )
#'
#'
#' show_donors(year = 2018,
#' programme_lab = "The Americas",
#' transaction_type_name = "Expenditure" )
#'
show_donors <- function(year,
programme_lab = NULL,
iati_identifier_ops = NULL,
ctr_name = NULL,
transaction_type_name = "Incoming Commitment" ) {


# Check if only one argument is passed
if (!is.null(programme_lab) && !is.null(iati_identifier_ops)) {
stop("Please pass only one of the arguments programme_lab or iati_identifier_ops.")
} else if (!is.null(programme_lab) && !is.null(ctr_name)) {
stop("Please pass only one of the arguments programme_lab or ctr_name.")
} else if (!is.null(iati_identifier_ops) && !is.null(ctr_name)) {
stop("Please pass only one of the arguments iati_identifier_ops or ctr_name.")
}

df <- iati::dataTransaction |>
dplyr::left_join(iati::dataActivity, by= c("iati_identifier"))

if (!is.null(programme_lab)) {
thisprogramme_lab <- programme_lab
thisyear <- year
thistransaction_type_name <- transaction_type_name
df <- df |>
# levels(as.factor(df$programmme_lab))
dplyr::filter( programmme_lab == thisprogramme_lab &
year >= thisyear &
transaction_type_name == thistransaction_type_name)
} else if (!is.null(iati_identifier_ops)) {
thisiati_identifier_ops <- iati_identifier_ops
thisyear <- year
thistransaction_type_name <- transaction_type_name
df <- df |>
dplyr::filter(iati_identifier_ops == thisiati_identifier_ops &
year >= thisyear &
transaction_type_name == thistransaction_type_name)
} else if (!is.null(ctr_name)) {
thisctr_name <- ctr_name
thisyear <- year
thistransaction_type_name <- transaction_type_name
df <- df |>
dplyr::filter( ctr_name == thisctr_name &
year >= thisyear &
transaction_type_name == thistransaction_type_name)
}

df <- df |>
dplyr::group_by(year, reporting_org_type_name) |>
dplyr::summarise( transaction_value_USD = sum(transaction_value_USD , na.rm = TRUE)) |>
dplyr::mutate(reporting_org_type_name = as.character(reporting_org_type_name) ) |>
dplyr::mutate(reporting_org_type_name = as.factor(reporting_org_type_name) )

p <- df |>
# dplyr::filter(transaction_value_USD <= 1000000 & transaction_value_USD > 1000) |>
ggplot2::ggplot(ggplot2::aes(y = transaction_value_USD ,
x = year,
Expand All @@ -60,18 +102,16 @@ p <- Transaction |>
ggplot2::scale_fill_viridis_d(option = "inferno", na.value = "grey50") +
ggplot2::scale_y_continuous(
expand = ggplot2::expansion(mult = c(0, .1)),
labels = scales::label_number(scale_cut = scales::cut_short_scale())
) +
labels = scales::label_number(scale_cut = scales::cut_short_scale()) ) +
# scale_x_continuous(labels = scales::label_number(scale_cut = cut_short_scale())) +
# ggplot2::facet_wrap(~ trans_year) +
unhcrthemes::theme_unhcr()+
unhcrthemes::theme_unhcr(grid = "Y", axis = "X", axis_title = "X")+
ggplot2::labs(
title = paste0(thistransaction_type_name," received by UNHCR in USD"),
subtitle = paste0("In ", thisprogrammme_lab, " recorded since ", thisyear,""),
title = paste0(transaction_type_name," received by UNHCR in USD"),
subtitle = paste0("In ", programme_lab, ctr_name,iati_identifier_ops, " recorded since ", year,""),
x = "",
y = "",
caption = "Data Source: UNHCR IATI (International Aid Transparency Initiative)"
)
caption = "Data Source: UNHCR IATI (International Aid Transparency Initiative)" )

return(p)
}
83 changes: 79 additions & 4 deletions R/show_earmarking.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,12 @@

#' Title
#'
#' Description
#' @description What’s the breakdown of Earmarking Type (Un-earmarked, Tightly earmarked, etc.) from Donor Funds by Year?
#'
#' @param year A numeric value corresponding to the first year of focus until the most recent year within the dataset.
#' @param programme_lab A character vector corresponding to the name of the programme.
#' @param iati_identifier_ops A character vector corresponding to the name of the operation.
#' @param ctr_name A character vector corresponding to the name of the country.
#'
#' @import ggplot2
#' @import dplyr
Expand All @@ -12,7 +17,77 @@
#' @export
#' @return a graph
#' @examples
#' show_earmarking()
show_earmarking <- function(){

#' show_earmarking(year = 2018,
#' programme_lab = NULL,
#' iati_identifier_ops = NULL,
#' ctr_name = "Brazil")
show_earmarking <- function(year,
programme_lab = NULL,
iati_identifier_ops = NULL,
ctr_name = NULL ) {


# Check if only one argument is passed
if (!is.null(programme_lab) && !is.null(iati_identifier_ops)) {
stop("Please pass only one of the arguments programme_lab or iati_identifier_ops.")
} else if (!is.null(programme_lab) && !is.null(ctr_name)) {
stop("Please pass only one of the arguments programme_lab or ctr_name.")
} else if (!is.null(iati_identifier_ops) && !is.null(ctr_name)) {
stop("Please pass only one of the arguments iati_identifier_ops or ctr_name.")
}

df <- iati::dataTransaction |>
dplyr::left_join(iati::dataActivity, by= c("iati_identifier"))

if (!is.null(programme_lab)) {
thisprogramme_lab <- programme_lab
thisyear <- year
df <- df |>
# levels(as.factor(df$programmme_lab))
dplyr::filter( programmme_lab == thisprogramme_lab &
year >= thisyear &
transaction_type_name == "Incoming Commitment")
} else if (!is.null(iati_identifier_ops)) {
thisiati_identifier_ops <- iati_identifier_ops
thisyear <- year
df <- df |>
dplyr::filter(iati_identifier_ops == thisiati_identifier_ops &
year >= thisyear &
transaction_type_name == "Incoming Commitment")
} else if (!is.null(ctr_name)) {
thisctr_name <- ctr_name
thisyear <- year
df <- df |>
dplyr::filter( ctr_name == thisctr_name &
year >= thisyear &
transaction_type_name == "Incoming Commitment")
}

df <- df |>
dplyr::group_by(year, aid_type1_name) |>
dplyr::summarise( transaction_value_USD = sum(transaction_value_USD , na.rm = TRUE)) |>
dplyr::mutate(aid_type1_name = as.character(aid_type1_name) ) |>
dplyr::mutate(aid_type1_name = as.factor(aid_type1_name) )

p <- df |>
# dplyr::filter(transaction_value_USD <= 1000000 & transaction_value_USD > 1000) |>
ggplot2::ggplot(ggplot2::aes(y = transaction_value_USD ,
x = year,
fill = aid_type1_name)) +
ggplot2::geom_bar(alpha = 0.9, stat = "identity") +
ggplot2::scale_fill_viridis_d(option = "inferno", na.value = "grey50") +
ggplot2::scale_y_continuous(
expand = ggplot2::expansion(mult = c(0, .1)),
labels = scales::label_number(scale_cut = scales::cut_short_scale()) ) +
# scale_x_continuous(labels = scales::label_number(scale_cut = cut_short_scale())) +
# ggplot2::facet_wrap(~ trans_year) +
unhcrthemes::theme_unhcr(grid = "Y", axis = "X", axis_title = "X")+
ggplot2::labs(
title = paste0("Earmarking level in USD"),
subtitle = paste0("In recorded since ", year,""),
x = "",
y = "",
caption = "Data Source: UNHCR IATI (International Aid Transparency Initiative)" )

return(p)
}
Loading

0 comments on commit a2dae97

Please sign in to comment.