Skip to content

Commit

Permalink
Merge pull request #4 from pepfar-datim/v0.3.0
Browse files Browse the repository at this point in the history
Update to v0.3.0
  • Loading branch information
cnemarich authored Nov 24, 2021
2 parents b185d50 + 29109f2 commit f1a030d
Show file tree
Hide file tree
Showing 18 changed files with 258 additions and 108 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: daa.analytics
Title: Utilities for Compiling and Analyzing PEPFAR Data Alignment Activity Data
Version: 0.2.0
Version: 0.3.0
Date: 2021-06-17
Authors@R:
person(given = "Chris",
Expand Down
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ export(get_pvls_emr_table)
export(get_upload_timestamps)
export(weighted_concordance)
export(weighted_discordance)
export(weighting_levels)
importFrom(magrittr,"%<>%")
importFrom(magrittr,"%>%")
importFrom(rlang,.data)
23 changes: 23 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
# daa.analytics v0.3.0

## Breaking changes
* `adorn_daa_data` now no longer exports columns `county_of_matched_sites`,
`pepfar_sum_at_matched_sites`, `weighting`, `weighted_discordance`,
or `weighted_concordance`.
- `count_of_matched_sites` and `pepfar_sum_at_matched_sites` will now no
longer be supported.
- `weighting`, `weighted_discordance`, and `weighted_concordance` will be
replaced by weights and metrics calculated at each level of the organisation
hierarchy going forward and will be calculated using the `weighting_levels`
function.

## Experimental features
* `weighting_levels` is a new function that calculates weightings as well as
concordance and discordance metrics for DAA indicators at all levels of the
organisation hierarchy.

## Minor improvements and fixes
* Adds UIDs for each organisation hierarchy level to `ou_hierarchy` dataset
* Documentation updates
* Adds `NEWS.md` file

18 changes: 14 additions & 4 deletions R/combine-data.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,4 @@
#' @export
#' @importFrom magrittr %>% %<>%
#' @importFrom rlang .data
#' @title Combine DAA datasets together.
#'
#' @description
Expand Down Expand Up @@ -29,15 +27,27 @@ combine_data <- function(daa_indicator_data,
keep = FALSE)

ou_hierarchy %<>%
dplyr::select(-.data$organisationunitid) %>%
dplyr::select(.data$facilityuid, .data$namelevel3, .data$namelevel4,
.data$namelevel5, .data$namelevel6, .data$namelevel7) %>%
unique()

df <- daa_indicator_data %>%
# Joins DAA Indicator data to OU hierarchy metadata
dplyr::left_join(ou_hierarchy, by = c("facilityuid")) %>%

# Joins PVLS and EMR datasets
dplyr::left_join(pvls_emr, by = c("facilityuid", "period", "indicator")) %>%

# Joins site attribute data
dplyr::left_join(attribute_data %>%
dplyr::filter(!is.na(.data$moh_id)),
by = c("facilityuid")) %>%
dplyr::select(-.data$name, -.data$organisationunitid)

# Selects rows for export
dplyr::select(.data$facilityuid, dplyr::starts_with("namelevel"),
.data$indicator, .data$period, .data$moh, .data$pepfar,
.data$reported_by, dplyr::starts_with("level"),
dplyr::everything(), -.data$name, -.data$organisationunitid)

return(df)
}
9 changes: 9 additions & 0 deletions R/daa.analytics-package.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
#' @keywords internal
"_PACKAGE"

## usethis namespace: start
#' @importFrom magrittr %<>%
#' @importFrom magrittr %>%
#' @importFrom rlang .data
## usethis namespace: end
NULL
31 changes: 13 additions & 18 deletions R/data.R
Original file line number Diff line number Diff line change
Expand Up @@ -136,6 +136,19 @@
#' unit in DATIM.}
#' \item{facilityuid}{The alphanumeric UID used to identify the facility in
#' DATIM.}
#' \item{namelevel3uid}{The UID of the parent organisation unit at hierarchy
#' level 3 to the given facility.}
#' \item{namelevel4uid}{The UID of the parent organisation unit at hierarchy
#' level 4 to the given facility.}
#' \item{namelevel5uid}{The UID of the parent organisation unit at hierarchy
#' level 5 to the given facility.}
#' \item{namelevel6uid}{For countries with their facility level at hierarchy
#' level 6, this will represent the UID of the facility. For countries with
#' their facility level at hierarchy level 7, this will represent the parent
#' organisation unit at hierarchy level 6 to the given facility.}
#' \item{namelevel7uid}{For countries with their facility level at hierarchy
#' level 7, this will represent the UID of the facility. For countries with
#' their facility level at hierarchy level 6, this value will be 'NA'.}
#' \item{namelevel3}{The name of the parent organisation unit at hierarchy
#' level 3 to the given facility.}
#' \item{namelevel4}{The name of the parent organisation unit at hierarchy
Expand Down Expand Up @@ -194,24 +207,6 @@
#' \item{reported_by}{A text value indicating whether results were reported
#' by just the MOH, just PEPFAR, or both entities at the given site for the
#' given indicator during the reporting period.}
#' \item{count_of_matched_sites}{The number of facilities in a country for the
#' particular indicator and reporting period for which results were reported
#' by both the MOH and PEPFAR.}
#' \item{pepfar_sum_at_matched_sites}{The total results reported by PEPFAR
#' at all facilities in a country for the particular indicator and reporting
#' period.}
#' \item{weighting}{The PEPFAR results at the particular facility divided by
#' the total results reported by PEPFAR at all facilities for the given
#' indicator and reporting period. This figure provides the weighting value
#' for concordance and discordance metrics.}
#' \item{weighted_discordance}{The weighted discordance between the PEPFAR
#' and MOH reported results at the particular facility. Can be summed across
#' facilities grouped by country, indicator, and period to calculate the
#' weighted average discordance.}
#' \item{weighted_concordance}{The weighted concordance between the PEPFAR
#' and MOH reported results at the particular facility. Can be summed across
#' facilities grouped by country, indicator, and period to calculate the
#' weighted average concordance.}
#' }
#' @source \url{http://www.datim.org/}
"daa_indicator_data"
Expand Down
2 changes: 0 additions & 2 deletions R/get-attributes.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,4 @@
#' @export
#' @importFrom magrittr %>% %<>%
#' @importFrom rlang .data
#' @title Fetch MOH ID and attributes from DATIM
#'
#' @description
Expand Down
152 changes: 123 additions & 29 deletions R/get-daa-data.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,4 @@
#' @export
#' @importFrom magrittr %>% %<>%
#' @importFrom rlang .data
#' @title Get DAA Indicator Data
#'
#' @description
Expand Down Expand Up @@ -67,7 +65,6 @@ get_daa_data <- function(ou_uid, d2_session) {
}

#' @export
#' @importFrom magrittr %>% %<>%
#' @title Adorn DAA Indicator Data
#'
#' @description
Expand Down Expand Up @@ -128,42 +125,139 @@ adorn_daa_data <- function(df) {
ifelse(!is.na(.data$pepfar),
"PEPFAR", "Neither"))) %>%

# Groups rows by indicator and calculates indicator-specific summaries
dplyr::group_by(.data$Data, .data$period) %>%
dplyr::mutate(count_of_matched_sites =
sum(ifelse(.data$reported_by == "Both", 1, 0))) %>%
dplyr::mutate(pepfar_sum_at_matched_sites =
sum(ifelse(.data$reported_by == "Both",
.data$pepfar, 0))) %>%
# Reorganizes table for export
dplyr::select(facilityuid = .data$`Organisation unit`,
indicator = .data$`Data`,
.data$period,
.data$moh,
.data$pepfar,
.data$reported_by)

return(df)
}


#' Adorn DAA Indicator Data with Weighted Metrics for All Levels
#'
#' @param daa_indicator_data Dataframe containing DAA indicator data.
#' @param ou_hierarchy Dataframe containing the Organisational hierarchy.
#'
#' @return A dataframe of DAA Indicator data with weightings and weighted
#' discordance and concordance calculated for levels 3 through 5.
#' @export
#'
weighting_levels <- function(daa_indicator_data = NULL, ou_hierarchy = NULL) {
ou_hierarchy %<>%
dplyr::select(-.data$organisationunitid, -paste0("namelevel", 3:7)) %>%
unique()

df <- daa_indicator_data %>%
# Joins DAA Indicator data to OU hierarchy metadata
dplyr::left_join(ou_hierarchy, by = c("facilityuid")) %>%

# Calculates Level 3 weighted concordance and discordance
dplyr::group_by(.data$indicator,
.data$period,
.data$namelevel3uid) %>%
dplyr::mutate(level3_weighting =
ifelse(.data$reported_by == "Both",
.data$pepfar / sum(
ifelse(.data$reported_by == "Both",
.data$pepfar, 0)),
NA)) %>%
dplyr::rowwise() %>%
dplyr::mutate(level3_discordance =
daa.analytics::weighted_discordance(
moh = .data$moh,
pepfar = .data$pepfar,
weighting = .data$level3_weighting),
level3_concordance =
daa.analytics::weighted_concordance(
moh = .data$moh,
pepfar = .data$pepfar,
weighting = .data$level3_weighting)
) %>%
dplyr::ungroup() %>%

# Calculates weighting variables
dplyr::mutate(weighting =
# Calculates Level 4 weighted concordance and discordance
dplyr::group_by(.data$indicator,
.data$period,
.data$namelevel4uid) %>%
dplyr::mutate(level4_weighting =
ifelse(.data$reported_by == "Both",
.data$pepfar / .data$pepfar_sum_at_matched_sites,
.data$pepfar / sum(
ifelse(.data$reported_by == "Both",
.data$pepfar, 0)),
NA)) %>%
dplyr::rowwise() %>%
dplyr::mutate(weighted_discordance =
daa.analytics::weighted_discordance(.data$moh,
.data$pepfar,
.data$weighting)) %>%
dplyr::mutate(weighted_concordance =
daa.analytics::weighted_concordance(.data$moh,
.data$pepfar,
.data$weighting)) %>%
dplyr::mutate(level4_discordance =
daa.analytics::weighted_discordance(
moh = .data$moh,
pepfar = .data$pepfar,
weighting = .data$level4_weighting),
level4_concordance =
daa.analytics::weighted_concordance(
moh = .data$moh,
pepfar = .data$pepfar,
weighting = .data$level4_weighting)
)%>%
dplyr::ungroup() %>%

# Reorganizes table for export
dplyr::select(facilityuid = .data$`Organisation unit`,
indicator = .data$`Data`,
.data$period,
.data$moh, .data$pepfar, .data$reported_by,
.data$count_of_matched_sites,
.data$pepfar_sum_at_matched_sites, .data$weighting,
.data$weighted_discordance, .data$weighted_concordance)
# Calculates Level 5 weighted concordance and discordance
dplyr::group_by(.data$indicator,
.data$period,
.data$namelevel5uid) %>%
dplyr::mutate(level5_weighting =
ifelse(.data$reported_by == "Both",
.data$pepfar / sum(
ifelse(.data$reported_by == "Both",
.data$pepfar, 0)),
NA)) %>%
dplyr::rowwise() %>%
dplyr::mutate(level5_discordance =
daa.analytics::weighted_discordance(
moh = .data$moh,
pepfar = .data$pepfar,
weighting = .data$level5_weighting),
level5_concordance =
daa.analytics::weighted_concordance(
moh = .data$moh,
pepfar = .data$pepfar,
weighting = .data$level5_weighting)
) %>%
dplyr::ungroup() %>%

# # Calculates Level 6 weighted concordance and discordance
# dplyr::group_by(.data$indicator,
# .data$period,
# .data$namelevel6uid) %>%
# dplyr::mutate(level6_weighting =
# ifelse(.data$reported_by == "Both",
# .data$pepfar / sum(
# ifelse(.data$reported_by == "Both",
# .data$pepfar, 0)),
# NA)) %>%
# dplyr::rowwise() %>%
# dplyr::mutate(level6_discordance = ifelse(is.na(namelevel7), NA_real_,
# daa.analytics::weighted_discordance(
# moh = .data$moh,
# pepfar = .data$pepfar,
# weighting = .data$level6_weighting)),
# level6_concordance = ifelse(is.na(namelevel7), NA_real_,
# daa.analytics::weighted_concordance(
# moh = .data$moh,
# pepfar = .data$pepfar,
# weighting = .data$level6_weighting))
# ) %>%
# dplyr::ungroup() %>%

# Selects rows for export
dplyr::select(-dplyr::starts_with("namelevel"))

return(df)
}


# Helper functions ------------------------------------------
#' @title Get Indicator Name
#'
Expand Down
6 changes: 0 additions & 6 deletions R/get-geoalign-data.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,4 @@
#' @export
#' @importFrom magrittr %>% %<>%
#' @importFrom rlang .data
#' @title Fetch List of Participating Countries from GeoAlign
#'
#' @description
Expand Down Expand Up @@ -34,8 +32,6 @@ get_daa_countries <- function(geo_session) {
}

#' @export
#' @importFrom magrittr %>% %<>%
#' @importFrom rlang .data
#' @title Fetch Indicator Mapping and Data Availability from GeoAlign
#'
#' @description
Expand Down Expand Up @@ -104,8 +100,6 @@ get_data_availability <- function(geo_session = geo_session) {
}

#' @export
#' @importFrom magrittr %>% %<>%
#' @importFrom rlang .data
#' @title Fetch Import Timestamps from GeoAlign
#'
#' @description
Expand Down
Loading

0 comments on commit f1a030d

Please sign in to comment.