Skip to content

Commit

Permalink
change counts colname in conversion and filter by species funs, order…
Browse files Browse the repository at this point in the history
… season in plot_record_by_season
  • Loading branch information
MatGreco90 committed May 13, 2024
1 parent aaa7643 commit 5c2f1a5
Show file tree
Hide file tree
Showing 5 changed files with 24 additions and 15 deletions.
13 changes: 7 additions & 6 deletions R/compute_abundances.R
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,8 @@ compute_abundances <- function(data, aggregate = TRUE) {
.data$subsample_count_type,
.data$subsample_all_shells_present_were_counted,
.data$total_of_forams_counted_ind,
.data$sampling_device_type))
.data$sampling_device_type)) %>%
rename('counts_raw_ab' = 'counts')

conc_data_to_convert <- data %>%
filter(.data$sample_volume_filtered > 0) %>%
Expand All @@ -44,7 +45,7 @@ compute_abundances <- function(data, aggregate = TRUE) {
.data$total_of_forams_counted_ind)) %>%
mutate(new_counts = floor(.data$counts * .data$sample_volume_filtered)) %>%
select(-c(.data$counts, .data$subsample_count_type)) %>%
rename('counts' = 'new_counts') %>%
rename('counts_raw_ab' = 'new_counts') %>%
distinct()

rel_data_to_convert <- data %>%
Expand All @@ -65,7 +66,7 @@ compute_abundances <- function(data, aggregate = TRUE) {
.data$subsample_all_shells_present_were_counted,
.data$total_of_forams_counted_ind,
.data$sampling_device_type)) %>%
rename('counts' = 'new_counts') %>%
rename('counts_raw_ab' = 'new_counts') %>%
distinct()

excluded_samples_volume <- data %>%
Expand Down Expand Up @@ -98,13 +99,13 @@ compute_abundances <- function(data, aggregate = TRUE) {

tot_dat <- tot_dat %>%
group_by(.data$sample_id, .data$taxa) %>%
mutate(new_counts = sum(.data$counts, na.rm = TRUE)) %>%
mutate(new_counts = sum(.data$counts_raw_ab, na.rm = TRUE)) %>%
ungroup() %>%
select(-c(.data$counts, .data$subsample_id,
select(-c(.data$counts_raw_ab, .data$subsample_id,
.data$subsample_size_fraction_min,
.data$subsample_size_fraction_max)) %>%
distinct() %>%
rename('counts' = 'new_counts')
rename('counts_raw_ab' = 'new_counts')
}

tot_dat
Expand Down
13 changes: 7 additions & 6 deletions R/compute_concentrations.R
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,8 @@ compute_concentrations <- function(data, aggregate = TRUE) {
.data$subsample_count_type,
.data$subsample_all_shells_present_were_counted,
.data$total_of_forams_counted_ind,
.data$sampling_device_type))
.data$sampling_device_type))%>%
rename('counts_n_conc' = 'counts')

abs_data_to_convert <- data %>%
filter(.data$sample_volume_filtered > 0) %>%
Expand All @@ -81,7 +82,7 @@ compute_concentrations <- function(data, aggregate = TRUE) {
.data$subsample_all_shells_present_were_counted,
.data$total_of_forams_counted_ind,
.data$sampling_device_type)) %>%
rename('counts' = 'new_counts') %>%
rename('counts_n_conc' = 'new_counts') %>%
distinct()

rel_data_to_convert <- data %>%
Expand All @@ -104,7 +105,7 @@ compute_concentrations <- function(data, aggregate = TRUE) {
.data$subsample_all_shells_present_were_counted,
.data$total_of_forams_counted_ind,
.data$sampling_device_type)) %>%
rename('counts' = 'new_counts') %>%
rename('counts_n_conc' = 'new_counts') %>%
distinct()

excluded_samples_volume <- data %>%
Expand Down Expand Up @@ -140,18 +141,18 @@ compute_concentrations <- function(data, aggregate = TRUE) {
tot_dat <- tot_dat %>%
filter(!is.na(.data$sample_volume_filtered)) %>%
mutate(abs_sub_tot = floor(.data$sample_volume_filtered *
.data$counts)) %>%
.data$counts_n_conc)) %>%
group_by(.data$sample_id, .data$taxa) %>%
mutate(new_counts = sum(.data$abs_sub_tot, na.rm = TRUE)) %>%
ungroup() %>%
select(-c(.data$counts, .data$abs_sub_tot, .data$subsample_id,
select(-c(.data$counts_n_conc, .data$abs_sub_tot, .data$subsample_id,
.data$subsample_size_fraction_min,
.data$subsample_size_fraction_max)) %>%
distinct() %>%
mutate(conc_counts = .data$new_counts / .data$sample_volume_filtered) %>%
select(-.data$new_counts) %>%
distinct() %>%
rename('counts' = 'conc_counts')
rename('counts_n_conc' = 'conc_counts')
}

tot_dat
Expand Down
6 changes: 4 additions & 2 deletions R/compute_frequencies.R
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,8 @@ compute_frequencies <- function(data, aggregate = TRUE) {
mutate(counts = (.data$counts / .data$tot_subsample) * 100) %>%
select(-c(.data$tot_subsample, .data$tot_sample))

tot_dat <- rbind(partial_data, ready_dat)
tot_dat <- rbind(partial_data, ready_dat)%>%
rename('counts_rel_ab' = 'counts')


if (!aggregate) {
Expand All @@ -126,7 +127,8 @@ compute_frequencies <- function(data, aggregate = TRUE) {
select(-c(.data$subsample_id,
.data$subsample_size_fraction_min,
.data$subsample_size_fraction_max)) %>%
distinct()
distinct()%>%
rename('counts_rel_ab' = 'counts')

return(aggregated_dat)
}
Expand Down
5 changes: 4 additions & 1 deletion R/filter_by_species.R
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,10 @@ filter_by_species <- function(data, species, rm_na = FALSE) {
## Remove lines w/ NA counts (if required) ----

if (rm_na) {
data <- data[!is.na(data$"counts"), ]
count_columns <- grepl("counts", names(data))
#data <- data[!is.na(data$"counts"), ]
data <- data[!is.na(data[, count_columns]), ]

}

data
Expand Down
2 changes: 2 additions & 0 deletions R/plot_record_by_season.R
Original file line number Diff line number Diff line change
Expand Up @@ -72,6 +72,8 @@ plot_record_by_season <- function(data) {
select(.data$sample_id, .data$season) %>%
distinct()

data$season <-factor(data$season, levels = c("Fall", "Winter", "Spring", "Summer", "Unknown"))


## Plot ----

Expand Down

0 comments on commit 5c2f1a5

Please sign in to comment.