diff --git a/NAMESPACE b/NAMESPACE
index 0540f000a..d59028eb4 100644
--- a/NAMESPACE
+++ b/NAMESPACE
@@ -35,6 +35,8 @@ export(TADA_FlagMeasureQualifierCode)
export(TADA_FlagMethod)
export(TADA_FlagResultUnit)
export(TADA_FlagSpeciation)
+export(TADA_FlaggedSitesMap)
+export(TADA_FormatDelimitedString)
export(TADA_GetATTAINS)
export(TADA_GetActivityTypeRef)
export(TADA_GetCharacteristicRef)
@@ -47,6 +49,7 @@ export(TADA_GetNutrientSummationRef)
export(TADA_GetSynonymRef)
export(TADA_GetTemplate)
export(TADA_GetUSGSSynonymRef)
+export(TADA_GetUniqueNearbySites)
export(TADA_GetWQXCharValRef)
export(TADA_HarmonizeSynonyms)
export(TADA_Histogram)
diff --git a/R/Figures.R b/R/Figures.R
index d5ef10fef..7015fb2fd 100644
--- a/R/Figures.R
+++ b/R/Figures.R
@@ -560,6 +560,93 @@ TADA_OverviewMap <- function(.data) {
}))
}
+#' Create Flagged Sites Map
+#'
+#' @param .data TADA data frame containing the data downloaded from the WQP, where
+#' each row represents a unique data record. Data frame must include the columns
+#' 'MonitoringLocationIdentifier','MonitoringLocationName','TADA.LatitudeMeasure',
+#' and 'TADA.LongitudeMeasure' to run this function.
+#'
+#' @return A leaflet map that shows all sites in the data frame that contain
+#' flagged data in the form of:
+#' 1) imprecise coordinates - latitudes and/or longitudes that contain fewer
+#' then 3 decimal places.
+#' 2) outside USA - coordinates that fall outside the bounds of the USA.
+#' 3) near other sites - groups of sites that are spatially located within
+#' a threshhold distance (defaulting to 100 m) from each other.
+#'
+#' @export
+#'
+#' @examples
+#' \dontrun{
+#' # Load example data frame:
+#' data(Data_Nutrients_UT)
+#' data(Data_NCTCShepherdstown_HUC12)
+#' data(Data_6Tribes_5y_Harmonized)
+#'
+#' # Create maps:
+#' TADA_FlaggedSitesMap(Data_Nutrients_UT)
+#' TADA_FlaggedSitesMap(Data_NCTCShepherdstown_HUC12)
+#' TADA_FlaggedSitesMap(Data_6Tribes_5y_Harmonized)
+#' }
+#'
+#'
+TADA_FlaggedSitesMap <- function(.data) {
+ invalid <- TADA_FlagCoordinates(.data, flaggedonly = TRUE)
+ lowres <- invalid[invalid$TADA.InvalidCoordinates.Flag == "Imprecise_lessthan3decimaldigits",]
+ outsideusa <- invalid[invalid$TADA.InvalidCoordinates.Flag %in% c("LAT_OutsideUSA", "LONG_OutsideUSA"),]
+ nearby <- TADA_FindNearbySites(.data)
+ print(colnames(nearby))
+ nearby <- TADA_GetUniqueNearbySites(nearby)
+
+ lowresIcon <- leaflet::makeAwesomeIcon(icon = "circle", library = "fa", iconColor = "#ffffff", markerColor = "green")
+ outsideIcon <- leaflet::makeAwesomeIcon(icon = "circle", library = "fa", iconColor = "#ffffff", markerColor = "darkblue")
+ nearbyIcon <- leaflet::makeAwesomeIcon(icon = "circle", library = "fa", iconColor = "#ffffff", markerColor = "pink")
+
+ map <- leaflet::leaflet() %>%
+ leaflet::addProviderTiles("Esri.WorldTopoMap", group = "World topo", options = leaflet::providerTileOptions(updateWhenZooming = FALSE, updateWhenIdle = TRUE)) %>%
+ leaflet.extras::addResetMapButton() # button to reset to initial zoom and lat/long
+ if (nrow(outsideusa) > 0) {
+ map <- map %>% leaflet::addAwesomeMarkers(~TADA.LongitudeMeasure,
+ ~TADA.LatitudeMeasure,
+ icon = outsideIcon,
+ # label = ~as.character(MonitoringLocationIdentifier),
+ popup = paste0(
+ "Site ID: ", outsideusa$MonitoringLocationIdentifier,
+ "
Site Name: ", outsideusa$MonitoringLocationName,
+ "
Latitude: ", outsideusa$TADA.LatitudeMeasure,
+ "
Longitude: ", outsideusa$TADA.LongitudeMeasure),
+ data = outsideusa)
+ }
+ if (nrow(lowres) > 0) {
+ map <- map %>% leaflet::addAwesomeMarkers(~TADA.LongitudeMeasure,
+ ~TADA.LatitudeMeasure,
+ icon = lowresIcon,
+ # label = ~as.character(MonitoringLocationIdentifier),
+ popup = paste0(
+ "Site ID: ", lowres$MonitoringLocationIdentifier,
+ "
Site Name: ", lowres$MonitoringLocationName,
+ "
Latitude: ", lowres$TADA.LatitudeMeasure,
+ "
Longitude: ", lowres$TADA.LongitudeMeasure),
+ data = lowres)
+ }
+ if (nrow(nearby) > 0) {
+ map <- map %>% leaflet::addAwesomeMarkers(~TADA.LongitudeMeasure,
+ ~TADA.LatitudeMeasure,
+ icon = nearbyIcon,
+ # label = ~as.character(TADA.MonitoringLocationIdentifier),
+ popup = paste0(
+ "Nearby Group Name: ", nearby$TADA.MonitoringLocationIdentifier,
+ "
Site ID: ", nearby$MonitoringLocationIdentifier,
+ "
Site Name: ", nearby$MonitoringLocationName,
+ "
Latitude: ", nearby$TADA.LatitudeMeasure,
+ "
Longitude: ", nearby$TADA.LongitudeMeasure),
+ data = nearby)
+ }
+
+ return(map)
+}
+
#' Field Values Pie Chart
#'
#' Function creates a ggplot2 pie chart showing the relative proportions of values in a given field in a TADA dataset.
diff --git a/R/RequiredCols.R b/R/RequiredCols.R
index 9994a9bd4..0877d6cfa 100644
--- a/R/RequiredCols.R
+++ b/R/RequiredCols.R
@@ -179,7 +179,7 @@ require.cols <- c(
"TADA.InvalidCoordinates.Flag", # generated
"HUCEightDigitCode",
"MonitoringLocationIdentifier", # required
- "TADA.NearbySiteGroups",
+ "TADA.MonitoringLocationIdentifier",
# Groundwater fields
"AquiferName", # filter, groundwater
diff --git a/R/ResultFlagsIndependent.R b/R/ResultFlagsIndependent.R
index 0fbc28951..e95d3f0b1 100644
--- a/R/ResultFlagsIndependent.R
+++ b/R/ResultFlagsIndependent.R
@@ -1182,9 +1182,9 @@ TADA_FlagCoordinates <- function(.data,
#' issues in the data analysis.
#'
#' This function runs TADA_FindNearbySites within it which adds the
-#' TADA.NearbySiteGroups field. Duplicates are only flagged as duplicates if
+#' TADA.MonitoringLocationIdentifier field. Duplicates are only flagged as duplicates if
#' the distance between sites is less than the function input dist_buffer
-#' (default is 100m). Each group in the TADA.NearbySiteGroups field indicates
+#' (default is 100m). Each group in the TADA.MonitoringLocationIdentifier field indicates
#' that the sites within each group are within the specified distance from each other.
#'
#' We recommend running TADA_FindPotentialDuplicatesMultipleOrgs after running
@@ -1208,7 +1208,7 @@ TADA_FlagCoordinates <- function(.data,
#' containing a number unique to results that may represent duplicated
#' measurement events, a TADA.ResultSelectedMultipleOrgs column indicating
#' which rows are selected to keep (Y) and remove (N) based on the
-#' org hierarchy, and a TADA.NearbySiteGroups column indicating which
+#' org hierarchy, and a TADA.MonitoringLocationIdentifier column indicating which
#' monitoring locations are within the distance buffer from each other.
#'
#' @export
@@ -1225,29 +1225,29 @@ TADA_FlagCoordinates <- function(.data,
#'
TADA_FindPotentialDuplicatesMultipleOrgs <- function(.data, dist_buffer = 100, org_hierarchy = "none") {
# from those datapoints, determine which are in adjacent sites
- if (!"TADA.NearbySiteGroups" %in% names(.data)) {
+ if (!"TADA.MonitoringLocationIdentifier" %in% names(.data)) {
.data <- TADA_FindNearbySites(.data, dist_buffer = dist_buffer)
}
- dupsites <- unique(.data[, c("MonitoringLocationIdentifier", "TADA.LatitudeMeasure", "TADA.LongitudeMeasure", "TADA.NearbySiteGroups")])
+ dupsites <- unique(.data[, c("MonitoringLocationIdentifier", "TADA.LatitudeMeasure", "TADA.LongitudeMeasure", "TADA.MonitoringLocationIdentifier")])
# get rid of results with no site group added - not duplicated spatially
- dupsites <- subset(dupsites, !dupsites$TADA.NearbySiteGroups %in% c("No nearby sites")) %>%
- tidyr::separate_rows(TADA.NearbySiteGroups, sep = ",")
+ dupsites <- subset(dupsites, !dupsites$TADA.MonitoringLocationIdentifier %in% c("No nearby sites")) %>%
+ tidyr::separate_rows(TADA.MonitoringLocationIdentifier, sep = ",")
# remove results with no nearby sites get all data that are not NA and round to 2 digits
dupsprep <- .data %>%
dplyr::filter(MonitoringLocationIdentifier %in% dupsites$MonitoringLocationIdentifier) %>%
dplyr::select(
OrganizationIdentifier, ResultIdentifier, ActivityStartDate, ActivityStartTime.Time,
- TADA.CharacteristicName, ActivityTypeCode, TADA.ResultMeasureValue, TADA.NearbySiteGroups
+ TADA.CharacteristicName, ActivityTypeCode, TADA.ResultMeasureValue, TADA.MonitoringLocationIdentifier
) %>%
dplyr::filter(!is.na(TADA.ResultMeasureValue)) %>%
dplyr::mutate(roundRV = round(TADA.ResultMeasureValue, digits = 2))
# group by date, time, characteristic, and rounded result value and determine the number of organizations that have those same row values, and filter to those summary rows with more than one organization
dups_sum <- dupsprep %>%
- dplyr::group_by(ActivityStartDate, ActivityStartTime.Time, TADA.CharacteristicName, ActivityTypeCode, roundRV, TADA.NearbySiteGroups) %>%
+ dplyr::group_by(ActivityStartDate, ActivityStartTime.Time, TADA.CharacteristicName, ActivityTypeCode, roundRV, TADA.MonitoringLocationIdentifier) %>%
dplyr::mutate(numorgs = length(unique(OrganizationIdentifier))) %>%
dplyr::filter(numorgs > 1) %>%
# group duplicates
@@ -1264,7 +1264,7 @@ TADA_FindPotentialDuplicatesMultipleOrgs <- function(.data, dist_buffer = 100, o
"OrganizationIdentifier",
"ResultIdentifier",
"TADA.ResultMeasureValue",
- "TADA.NearbySiteGroups"
+ "TADA.MonitoringLocationIdentifier"
)) %>%
dplyr::mutate(TADA.MultipleOrgDuplicate = ifelse(is.na(TADA.MultipleOrgDupGroupID), "N", "Y")) %>%
# remove results that are listed twice (as part of two groups)
@@ -1305,9 +1305,9 @@ TADA_FindPotentialDuplicatesMultipleOrgs <- function(.data, dist_buffer = 100, o
dplyr::slice_sample(n = 1)
dupsdat <- dupsdat %>%
- dplyr::rename(SingleNearbyGroup = TADA.NearbySiteGroups) %>%
+ dplyr::rename(SingleNearbyGroup = TADA.MonitoringLocationIdentifier) %>%
dplyr::mutate(
- TADA.NearbySiteGroups = paste(SingleNearbyGroup, sep = ","),
+ TADA.MonitoringLocationIdentifier = paste(SingleNearbyGroup, sep = ","),
TADA.ResultSelectedMultipleOrgs = ifelse(ResultIdentifier %in% duppicks$ResultIdentifier, "Y", "N")
) %>%
dplyr::select(-SingleNearbyGroup)
diff --git a/R/Utilities.R b/R/Utilities.R
index f391a47bb..ff1076969 100644
--- a/R/Utilities.R
+++ b/R/Utilities.R
@@ -84,7 +84,8 @@ utils::globalVariables(c(
"TADA.ResultDepthHeightMeasure.MeasureUnitCode", "TADA.ResultDepthHeightMeasure.MeasureValue",
"YAxis.DepthUnit", "TADA.CharacteristicsForDepthProfile", "TADA.ConsolidatedDepth",
"TADA.ConsolidatedDepth.Bottom", "TADA.ConsolidatedDepth.Unit", "col2rgb",
- "palette.colors", "rect", "rgb", "text", "CodeNoSpeciation", "ResultMeasure.MeasureUnitCode.Upper"
+ "palette.colors", "rect", "rgb", "text", "CodeNoSpeciation", "ResultMeasure.MeasureUnitCode.Upper",
+ "TADA.MonitoringLocationIdentifier", "StringA", "StringB"
))
# global variables for tribal feature layers used in TADA_OverviewMap in Utilities.R
@@ -719,6 +720,29 @@ TADA_CreateComparableID <- function(.data) {
return(.data)
}
+#' Convert a delimited string to the format used by WQX 3.0 profiles for one-to-manys
+#'
+#' This utility function takes a delimited string of entities, and a delimiter (which defaults to a comma)
+#' and returns a new string in the WQX 3.0 format of c("StringA","StringB")
+#'
+#' @param delimited_string Character argument. Should be a string delimited by the character
+#' passed in the delimiter parameter.
+#'
+#' @param delimiter Character argument The character used to delimit the string passed in
+#' delimited_string. Defaults to a comma.
+#'
+#' @return String.
+#'
+#' @export
+#'
+TADA_FormatDelimitedString <- function(delimited_string, delimiter = ",") {
+ esc_chars = c("|", "^", "&", ".", "!", "?", "\\", "*", "-", "+", ">", "<")
+ if (delimiter %in% esc_chars) {
+ delimiter <- paste0("\\", delimiter)
+ }
+ return(paste0('["', gsub(delimiter, '","', delimited_string), '"]'))
+}
+
#' Identify and group nearby monitoring locations (UNDER ACTIVE DEVELOPMENT)
#'
@@ -731,7 +755,7 @@ TADA_CreateComparableID <- function(.data) {
#' @param dist_buffer Numeric. The maximum distance (in meters) two sites can be
#' from one another to be considered "nearby" and grouped together.
#'
-#' @return Input dataframe with a TADA.NearbySiteGroups column that indicates
+#' @return Input dataframe with a TADA.MonitoringLocationIdentifier column that indicates
#' the nearby site groups each monitoring location belongs to.
#'
#' @export
@@ -739,26 +763,26 @@ TADA_CreateComparableID <- function(.data) {
TADA_FindNearbySites <- function(.data, dist_buffer = 100) {
# check .data is data.frame
TADA_CheckType(.data, "data.frame", "Input object")
-
+
# .data required columns
required_cols <- c("MonitoringLocationIdentifier", "TADA.LongitudeMeasure", "TADA.LatitudeMeasure")
# check .data has required columns
TADA_CheckColumns(.data, required_cols)
-
+
# create spatial dataset based on sites
data_sf <- unique(.data[, c("MonitoringLocationIdentifier", "TADA.LongitudeMeasure", "TADA.LatitudeMeasure")])
# convert to sf object
data_sf <- sf::st_as_sf(data_sf,
- coords = c("TADA.LongitudeMeasure", "TADA.LatitudeMeasure"),
- # Change to your CRS
- crs = "+proj=longlat +ellps=WGS84 +datum=WGS84 +no_defs"
+ coords = c("TADA.LongitudeMeasure", "TADA.LatitudeMeasure"),
+ # Change to your CRS
+ crs = "+proj=longlat +ellps=WGS84 +datum=WGS84 +no_defs"
)
# create a distance matrix in meters
dist.mat <- data.frame(sf::st_distance(data_sf)) # Great Circle distance since in lat/lon
-
+
row.names(dist.mat) <- data_sf$MonitoringLocationIdentifier
colnames(dist.mat) <- data_sf$MonitoringLocationIdentifier
-
+
# convert distances to those within buffer (1) and beyond buffer (0)
dist.mat1 <- apply(dist.mat, c(1, 2), function(x) {
if (x <= dist_buffer) {
@@ -767,10 +791,10 @@ TADA_FindNearbySites <- function(.data, dist_buffer = 100) {
x <- 0
}
})
-
+
# create empty dataframe for groups
groups <- data.frame()
-
+
# loop through distance matrix and extract site groups that are within the buffer distance from one another
for (i in 1:dim(dist.mat1)[1]) {
fsite <- rownames(dist.mat1)[i] # focal site
@@ -779,51 +803,88 @@ TADA_FindNearbySites <- function(.data, dist_buffer = 100) {
sites <- dat$MonitoringLocationIdentifier[dat$Count == 1] # filter to sites within buffer
sites1 <- sites[!sites %in% fsite] # get site list within buffer that does not include focal site
if (length(sites1) > 0) { # if this list is greater than 0, combine sites within buffer into data frame
- df <- data.frame(MonitoringLocationIdentifier = sites, TADA.SiteGroup = paste0(sites, collapse = ", "))
+ df <- data.frame(MonitoringLocationIdentifier = sites, TADA.MonitoringLocationIdentifier = paste0(sites, collapse = ","))
+ df[c("TADA.MonitoringLocationIdentifier")] <- lapply(df[c("TADA.MonitoringLocationIdentifier")], TADA_FormatDelimitedString)
groups <- plyr::rbind.fill(groups, df)
}
}
-
+
# get unique groups (since represented multiple times for each site looped through, above)
groups <- unique(groups)
-
+
if (dim(groups)[1] > 0) { # if there are groups of nearby sites...
# create group ID's for easier understanding
- grp <- data.frame(TADA.SiteGroup = unique(groups$TADA.SiteGroup), TADA.SiteGroupID = paste0("Group_", 1:length(unique(groups$TADA.SiteGroup))))
- groups <- merge(groups, grp, all.x = TRUE)
- groups <- unique(groups[, !names(groups) %in% c("TADA.SiteGroup")])
-
+ # grp <- data.frame(TADA.SiteGroup = unique(groups$TADA.SiteGroup), TADA.SiteGroupID = paste0("Group_", 1:length(unique(groups$TADA.SiteGroup))))
+ # groups <- merge(groups, grp, all.x = TRUE)
+ # groups <- unique(groups[, !names(groups) %in% c("TADA.SiteGroup")])
+
# find any sites within multiple groups
summ_sites <- groups %>%
dplyr::group_by(MonitoringLocationIdentifier) %>%
dplyr::mutate(GroupCount = 1:length(MonitoringLocationIdentifier))
-
+
# pivot wider if a site belongs to multiple groups
groups_wide <- merge(groups, summ_sites, all.x = TRUE)
- groups_wide <- tidyr::pivot_wider(groups_wide, id_cols = "MonitoringLocationIdentifier", names_from = "GroupCount", names_prefix = "TADA.SiteGroup", values_from = "TADA.SiteGroupID")
+ groups_wide <- tidyr::pivot_wider(groups_wide, id_cols = "MonitoringLocationIdentifier", names_from = "GroupCount", names_prefix = "TADA.MonitoringLocationIdentifier", values_from = "TADA.MonitoringLocationIdentifier")
# merge data to site groupings
.data <- merge(.data, groups_wide, all.x = TRUE)
-
+
# concatenate and move site id cols to right place
- grpcols <- names(.data)[grepl("TADA.SiteGroup", names(.data))]
-
- .data <- .data %>% tidyr::unite(col = TADA.NearbySiteGroups, dplyr::all_of(grpcols), sep = ", ", na.rm = TRUE)
- .data$TADA.NearbySiteGroups[.data$TADA.NearbySiteGroups == ""] <- "No nearby sites"
+ grpcols <- names(.data)[grepl("TADA.MonitoringLocationIdentifier", names(.data))]
+
+ .data <- .data %>% tidyr::unite(col = TADA.MonitoringLocationIdentifier, dplyr::all_of(grpcols), sep = ", ", na.rm = TRUE)
}
-
- if (dim(groups)[1] == 0) { # if no groups, give a TADA.NearbySiteGroups column filled with NA
- .data$TADA.NearbySiteGroups <- "No nearby sites"
+
+ if (!"TADA.MonitoringLocationIdentifier" %in% colnames(.data)) {
+ .data$TADA.MonitoringLocationIdentifier <- NA
+ }
+
+ .data <- .data %>%
+ dplyr::mutate(TADA.MonitoringLocationIdentifier = ifelse(TADA.MonitoringLocationIdentifier == "", MonitoringLocationIdentifier, TADA.MonitoringLocationIdentifier))
+
+ if (dim(groups)[1] == 0) { # #if no groups, give a TADA.MonitoringLocationIdentifier column filled with NA
print("No nearby sites detected using input buffer distance.")
}
-
+
# order columns
if ("ResultIdentifier" %in% names(.data)) {
.data <- TADA_OrderCols(.data)
}
+
+ return(.data)
+}
+
+#' Get grouped monitoring stations that are near each other
+#'
+#' This function takes a TADA dataset that contains grouped nearby monitoring stations
+#' and returns a unique dataset of the original MonitoringLocationIdentifier, the grouped
+#' TADA.MonitoringLocationIdentifier, TADA.LongitudeMeasure, and TADA.LatitudeMeasure,
+#' filtered for only those stations that have a nearby station.
+#'
+#' @param .data TADA dataframe
+#'
+#' @return New dataframe with unique values for MonitoringLocationIdentifier,
+#' TADA.MonitoringLocationIdentifier, TADA.LongitudeMeasure, and TADA.LatitudeMeasure
+#'
+#' @export
+#'
+TADA_GetUniqueNearbySites <- function(.data) {
+ # check .data is data.frame
+ TADA_CheckType(.data, "data.frame", "Input object")
+
+ # .data required columns
+ required_cols <- c("MonitoringLocationIdentifier", "TADA.MonitoringLocationIdentifier", "TADA.LongitudeMeasure", "TADA.LatitudeMeasure")
+ # check .data has required columns
+ TADA_CheckColumns(.data, required_cols)
+
+ .data <- .data[c("MonitoringLocationIdentifier", "MonitoringLocationName", "MonitoringLocationTypeName", "MonitoringLocationDescriptionText", "TADA.MonitoringLocationIdentifier", "TADA.LongitudeMeasure", "TADA.LatitudeMeasure")]
+ .data <- unique(dplyr::filter(.data, grepl(",", TADA.MonitoringLocationIdentifier)))
+
return(.data)
}
+
#' Generate a random WQP dataset
#'
#' Retrieves data for a period of time in the past 20 years using
diff --git a/data/Data_6Tribes_5y.rda b/data/Data_6Tribes_5y.rda
index 3d4c3b142..884fe1f6e 100644
Binary files a/data/Data_6Tribes_5y.rda and b/data/Data_6Tribes_5y.rda differ
diff --git a/data/Data_6Tribes_5y_Harmonized.rda b/data/Data_6Tribes_5y_Harmonized.rda
index beee1d7fb..b22842b54 100644
Binary files a/data/Data_6Tribes_5y_Harmonized.rda and b/data/Data_6Tribes_5y_Harmonized.rda differ
diff --git a/data/Data_NCTCShepherdstown_HUC12.rda b/data/Data_NCTCShepherdstown_HUC12.rda
index 8d7cea9f8..0ec1accc7 100644
Binary files a/data/Data_NCTCShepherdstown_HUC12.rda and b/data/Data_NCTCShepherdstown_HUC12.rda differ
diff --git a/data/Data_Nutrients_UT.rda b/data/Data_Nutrients_UT.rda
index 6e2b8a294..b3216f22d 100644
Binary files a/data/Data_Nutrients_UT.rda and b/data/Data_Nutrients_UT.rda differ
diff --git a/data/Data_R5_TADAPackageDemo.rda b/data/Data_R5_TADAPackageDemo.rda
index b77678b52..1d9e7f974 100644
Binary files a/data/Data_R5_TADAPackageDemo.rda and b/data/Data_R5_TADAPackageDemo.rda differ
diff --git a/inst/extdata/AKAllotments.dbf b/inst/extdata/AKAllotments.dbf
index 1e9c408a8..bb127befa 100644
Binary files a/inst/extdata/AKAllotments.dbf and b/inst/extdata/AKAllotments.dbf differ
diff --git a/inst/extdata/AKVillages.dbf b/inst/extdata/AKVillages.dbf
index 214cf27c5..e3358f15b 100644
Binary files a/inst/extdata/AKVillages.dbf and b/inst/extdata/AKVillages.dbf differ
diff --git a/inst/extdata/AmericanIndian.dbf b/inst/extdata/AmericanIndian.dbf
index b796dceb2..3007c8b96 100644
Binary files a/inst/extdata/AmericanIndian.dbf and b/inst/extdata/AmericanIndian.dbf differ
diff --git a/inst/extdata/OKTribe.dbf b/inst/extdata/OKTribe.dbf
index 4c617f1f9..efaad9d88 100644
Binary files a/inst/extdata/OKTribe.dbf and b/inst/extdata/OKTribe.dbf differ
diff --git a/inst/extdata/OffReservation.dbf b/inst/extdata/OffReservation.dbf
index c5fa7e7ae..ae2718675 100644
Binary files a/inst/extdata/OffReservation.dbf and b/inst/extdata/OffReservation.dbf differ
diff --git a/inst/extdata/VATribe.dbf b/inst/extdata/VATribe.dbf
index e8fac566d..6ee52d31e 100644
Binary files a/inst/extdata/VATribe.dbf and b/inst/extdata/VATribe.dbf differ
diff --git a/inst/extdata/WQXCharacteristicRef.csv b/inst/extdata/WQXCharacteristicRef.csv
index 8a2d17965..620be61d8 100644
--- a/inst/extdata/WQXCharacteristicRef.csv
+++ b/inst/extdata/WQXCharacteristicRef.csv
@@ -14566,6 +14566,7 @@ d","Deprecated","SULFLURAMID"
"Ibuprofen***retired***use Benzeneacetic acid, .alpha.-methyl-4-(2-methylpropyl)-","Deprecated","BENZENEACETIC ACID, .ALPHA.-METHYL-4-(2-METHYLPROPYL)-"
"Ibuprofen-13C3","Accepted",""
"Ibuprofen-d3","Accepted",""
+"Ice cover duration","Accepted",""
"Ice cover, floating or solid - severity (choice list)","Accepted",""
"Ice cover, floating or solid, as % area estimate","Accepted",""
"Ice thickness","Accepted",""
diff --git a/man/TADA_FindNearbySites.Rd b/man/TADA_FindNearbySites.Rd
index a32b26fd3..ff7d785b6 100644
--- a/man/TADA_FindNearbySites.Rd
+++ b/man/TADA_FindNearbySites.Rd
@@ -13,7 +13,7 @@ TADA_FindNearbySites(.data, dist_buffer = 100)
from one another to be considered "nearby" and grouped together.}
}
\value{
-Input dataframe with a TADA.NearbySiteGroups column that indicates
+Input dataframe with a TADA.MonitoringLocationIdentifier column that indicates
the nearby site groups each monitoring location belongs to.
}
\description{
diff --git a/man/TADA_FindPotentialDuplicatesMultipleOrgs.Rd b/man/TADA_FindPotentialDuplicatesMultipleOrgs.Rd
index 794f16068..8130dcc1d 100644
--- a/man/TADA_FindPotentialDuplicatesMultipleOrgs.Rd
+++ b/man/TADA_FindPotentialDuplicatesMultipleOrgs.Rd
@@ -30,7 +30,7 @@ or more different organizations, a TADA.MultipleOrgDupGroupID column
containing a number unique to results that may represent duplicated
measurement events, a TADA.ResultSelectedMultipleOrgs column indicating
which rows are selected to keep (Y) and remove (N) based on the
-org hierarchy, and a TADA.NearbySiteGroups column indicating which
+org hierarchy, and a TADA.MonitoringLocationIdentifier column indicating which
monitoring locations are within the distance buffer from each other.
}
\description{
@@ -42,9 +42,9 @@ issues in the data analysis.
}
\details{
This function runs TADA_FindNearbySites within it which adds the
-TADA.NearbySiteGroups field. Duplicates are only flagged as duplicates if
+TADA.MonitoringLocationIdentifier field. Duplicates are only flagged as duplicates if
the distance between sites is less than the function input dist_buffer
-(default is 100m). Each group in the TADA.NearbySiteGroups field indicates
+(default is 100m). Each group in the TADA.MonitoringLocationIdentifier field indicates
that the sites within each group are within the specified distance from each other.
We recommend running TADA_FindPotentialDuplicatesMultipleOrgs after running
diff --git a/man/TADA_FlaggedSitesMap.Rd b/man/TADA_FlaggedSitesMap.Rd
new file mode 100644
index 000000000..300ffac9a
--- /dev/null
+++ b/man/TADA_FlaggedSitesMap.Rd
@@ -0,0 +1,43 @@
+% Generated by roxygen2: do not edit by hand
+% Please edit documentation in R/Figures.R
+\name{TADA_FlaggedSitesMap}
+\alias{TADA_FlaggedSitesMap}
+\title{Create Flagged Sites Map}
+\usage{
+TADA_FlaggedSitesMap(.data)
+}
+\arguments{
+\item{.data}{TADA data frame containing the data downloaded from the WQP, where
+each row represents a unique data record. Data frame must include the columns
+'MonitoringLocationIdentifier','MonitoringLocationName','TADA.LatitudeMeasure',
+and 'TADA.LongitudeMeasure' to run this function.}
+}
+\value{
+A leaflet map that shows all sites in the data frame that contain
+flagged data in the form of:
+\enumerate{
+\item imprecise coordinates - latitudes and/or longitudes that contain fewer
+then 3 decimal places.
+\item outside USA - coordinates that fall outside the bounds of the USA.
+\item near other sites - groups of sites that are spatially located within
+a threshhold distance (defaulting to 100 m) from each other.
+}
+}
+\description{
+Create Flagged Sites Map
+}
+\examples{
+\dontrun{
+# Load example data frame:
+data(Data_Nutrients_UT)
+data(Data_NCTCShepherdstown_HUC12)
+data(Data_6Tribes_5y_Harmonized)
+
+# Create maps:
+TADA_FlaggedSitesMap(Data_Nutrients_UT)
+TADA_FlaggedSitesMap(Data_NCTCShepherdstown_HUC12)
+TADA_FlaggedSitesMap(Data_6Tribes_5y_Harmonized)
+}
+
+
+}
diff --git a/man/TADA_FormatDelimitedString.Rd b/man/TADA_FormatDelimitedString.Rd
new file mode 100644
index 000000000..3bc84d7ff
--- /dev/null
+++ b/man/TADA_FormatDelimitedString.Rd
@@ -0,0 +1,22 @@
+% Generated by roxygen2: do not edit by hand
+% Please edit documentation in R/Utilities.R
+\name{TADA_FormatDelimitedString}
+\alias{TADA_FormatDelimitedString}
+\title{Convert a delimited string to the format used by WQX 3.0 profiles for one-to-manys}
+\usage{
+TADA_FormatDelimitedString(delimited_string, delimiter = ",")
+}
+\arguments{
+\item{delimited_string}{Character argument. Should be a string delimited by the character
+passed in the delimiter parameter.}
+
+\item{delimiter}{Character argument The character used to delimit the string passed in
+delimited_string. Defaults to a comma.}
+}
+\value{
+String.
+}
+\description{
+This utility function takes a delimited string of entities, and a delimiter (which defaults to a comma)
+and returns a new string in the WQX 3.0 format of c("StringA","StringB")
+}
diff --git a/man/TADA_GetUniqueNearbySites.Rd b/man/TADA_GetUniqueNearbySites.Rd
new file mode 100644
index 000000000..0432ddd58
--- /dev/null
+++ b/man/TADA_GetUniqueNearbySites.Rd
@@ -0,0 +1,21 @@
+% Generated by roxygen2: do not edit by hand
+% Please edit documentation in R/Utilities.R
+\name{TADA_GetUniqueNearbySites}
+\alias{TADA_GetUniqueNearbySites}
+\title{Get grouped monitoring stations that are near each other}
+\usage{
+TADA_GetUniqueNearbySites(.data)
+}
+\arguments{
+\item{.data}{TADA dataframe}
+}
+\value{
+New dataframe with unique values for MonitoringLocationIdentifier,
+TADA.MonitoringLocationIdentifier, TADA.LongitudeMeasure, and TADA.LatitudeMeasure
+}
+\description{
+This function takes a TADA dataset that contains grouped nearby monitoring stations
+and returns a unique dataset of the original MonitoringLocationIdentifier, the grouped
+TADA.MonitoringLocationIdentifier, TADA.LongitudeMeasure, and TADA.LatitudeMeasure,
+filtered for only those stations that have a nearby station.
+}
diff --git a/tests/testthat/test-ResultFlagsIndependent.R b/tests/testthat/test-ResultFlagsIndependent.R
index d4d45e97d..b74b916a0 100644
--- a/tests/testthat/test-ResultFlagsIndependent.R
+++ b/tests/testthat/test-ResultFlagsIndependent.R
@@ -90,9 +90,9 @@ test_that("TADA_FindPotentialDuplicatsMultipleOrgs labels nearby site and multip
testdat <- TADA_FindPotentialDuplicatesMultipleOrgs(testdat)
testdat1 <- testdat %>%
- dplyr::select(TADA.NearbySiteGroups) %>%
- dplyr::filter(TADA.NearbySiteGroups != "No nearby sites") %>%
- tidyr::separate_rows(TADA.NearbySiteGroups, sep = ", ") %>%
+ dplyr::select(TADA.MonitoringLocationIdentifier) %>%
+ dplyr::filter(TADA.MonitoringLocationIdentifier != "No nearby sites") %>%
+ tidyr::separate_rows(TADA.MonitoringLocationIdentifier, sep = ", ") %>%
dplyr::pull() %>%
stringr::str_remove_all("Group_") %>%
unique() %>%
@@ -118,6 +118,6 @@ test_that("TADA_FindPotentialDuplicatsMultipleOrgs has non-NA values for each ro
expect_false(any(is.na(testdat$TADA.MultipleOrgDupGroupID)))
expect_false(any(is.na(testdat$TADA.MultipleOrgDuplicate)))
- expect_false(any(is.na(testdat$TADA.NearbySiteGroups)))
+ expect_false(any(is.na(testdat$TADA.MonitoringLocationIdentifier)))
expect_false(any(is.na(testdat$TADA.ResultSelectedMultipleOrgs)))
})
diff --git a/tests/testthat/test_TADAWaterSciConWorkshopDemo.Rmd b/tests/testthat/test_TADAWaterSciConWorkshopDemo.Rmd
new file mode 100644
index 000000000..6ee5e9d31
--- /dev/null
+++ b/tests/testthat/test_TADAWaterSciConWorkshopDemo.Rmd
@@ -0,0 +1,7 @@
+context("TADAWaterSciConWorkshopDemo")
+
+
+test_that("TADAWaterSciConWorkshopDemo works as expected", {
+
+
+})