Skip to content

Commit

Permalink
fix rcmdcheck issues (#122)
Browse files Browse the repository at this point in the history
  • Loading branch information
dfalster authored Nov 10, 2023
1 parent 791c8a5 commit 906713c
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 14 deletions.
20 changes: 10 additions & 10 deletions R/process.R
Original file line number Diff line number Diff line change
Expand Up @@ -208,14 +208,14 @@ dataset_process <- function(filename_data_raw,
metadata[["exclude_observations"]] %>%
traits.build::util_list_to_df2() %>%
dplyr::mutate(
find = stringr::str_split(find, ", ")
find = stringr::str_split(.data$find, ", ")
) %>%
tidyr::unnest_longer(find) %>%
dplyr::filter(variable == "taxon_name")
tidyr::unnest_longer(.data$find) %>%
dplyr::filter(.data$variable == "taxon_name")

taxonomic_updates <-
taxonomic_updates %>%
dplyr::filter(!aligned_name %in% taxa_to_exclude$find)
dplyr::filter(!.data$aligned_name %in% taxa_to_exclude$find)
}

## A temporary dataframe created to generate and bind `method_id`,
Expand Down Expand Up @@ -263,7 +263,7 @@ dataset_process <- function(filename_data_raw,
dplyr::select(dplyr::all_of(c("error")), everything()) %>%
dplyr::select(-dplyr::all_of(c("unit_in"))),
taxonomic_updates = taxonomic_updates %>%
dplyr::filter(aligned_name %in% traits$taxon_name),
dplyr::filter(.data$aligned_name %in% traits$taxon_name),
taxa = taxonomic_updates %>%
dplyr::select(dplyr::all_of(c(taxon_name = "aligned_name"))) %>%
dplyr::distinct(),
Expand Down Expand Up @@ -1903,20 +1903,20 @@ build_update_taxonomy <- function(austraits_raw, taxa) {
taxa$taxon_rank[match(.data$taxon_name, taxa$aligned_name)],
.data$taxonomic_resolution),
taxon_rank = .data$taxonomic_resolution,
name_to_match_to = taxon_name,
name_to_match_to = .data$taxon_name,
# Create variable `name_to_match_to` which specifies the part of the taxon name to which matches can be made.
# This step requires taxon_rank.
name_to_match_to = stringr::str_replace(taxon_name, " \\[.+",""),
name_to_match_to = ifelse(!taxon_rank %in% c("species", "subspecies", "series", "variety", "form"),
stringr::word(taxon_name,1), name_to_match_to)
name_to_match_to = stringr::str_replace(.data$taxon_name, " \\[.+",""),
name_to_match_to = ifelse(!.data$taxon_rank %in% c("species", "subspecies", "series", "variety", "form"),
stringr::word(.data$taxon_name,1), .data$name_to_match_to)
) %>%
# Remove taxon_rank, as it is about to be merged back in, but matches will now be possible to more rows.
select(-dplyr::any_of(c("taxon_rank", "taxonomic_resolution"))) %>%
util_df_convert_character() %>%
# Merge in all data from taxa.
dplyr::left_join(by = c("taxon_name"),
taxa %>% dplyr::select(-dplyr::any_of(dplyr::contains("align"))) %>%
dplyr::distinct(taxon_name, .keep_all = TRUE) %>%
dplyr::distinct(.data$taxon_name, .keep_all = TRUE) %>%
util_df_convert_character()
) %>%
dplyr::arrange(.data$taxon_name) %>%
Expand Down
7 changes: 3 additions & 4 deletions R/setup.R
Original file line number Diff line number Diff line change
Expand Up @@ -899,14 +899,14 @@ metadata_add_taxonomic_change <- function(dataset_id, find, replace, reason, tax
} else {
message(sprintf(red("Existing substitution will be overwritten for ") %+% green("'%s'"), find))
data <- data %>%
filter(find != to_add$find) %>%
filter(.data$find != to_add$find) %>%
dplyr::bind_rows(to_add) %>%
filter(!find == replace) %>%
filter(!.data$find == replace) %>%
arrange(.data$find)
}
} else {
data <- dplyr::bind_rows(data, to_add) %>%
filter(!find == replace) %>%
filter(!.data$find == replace) %>%
arrange(.data$find)
}
}
Expand Down Expand Up @@ -971,7 +971,6 @@ metadata_add_taxonomic_changes_list <- function(dataset_id, taxonomic_updates) {

# Read in dataframe of taxonomic changes, split into single-row lists, and add to metadata file
metadata$taxonomic_updates <- taxonomic_updates %>% dplyr::filter(!.data$find == .data$replace)

}

# Write metadata
Expand Down

0 comments on commit 906713c

Please sign in to comment.