Skip to content

Commit

Permalink
Improved the efficiency of banc_table_updateids
Browse files Browse the repository at this point in the history
  • Loading branch information
alexanderbates committed Nov 24, 2024
1 parent 9658142 commit 4266ba0
Show file tree
Hide file tree
Showing 2 changed files with 45 additions and 30 deletions.
15 changes: 12 additions & 3 deletions R/banc-table.R
Original file line number Diff line number Diff line change
Expand Up @@ -573,11 +573,20 @@ banctable_updateids <- function(){

# Update directly
cat('updating column: banc_match ...\n')
bc.new <- banc_updateids(bc.new, root.column = "banc_match", supervoxel.column = "banc_match_supervoxel_id", position.column = "banc_match_position")
bc.new[!is.na(bc.new$banc_match),] <- banc_updateids(bc.new[!is.na(bc.new$banc_match),],
root.column = "banc_match",
supervoxel.column = "banc_match_supervoxel_id",
position.column = "banc_match_position")
cat('updating column: banc_png_match ...\n')
bc.new <- banc_updateids(bc.new, root.column = "banc_png_match", supervoxel.column = "banc_png_match_supervoxel_id", position.column = "banc_png_match_position")
bc.new[!is.na(bc.new$banc_png_match),] <- banc_updateids(bc.new[!is.na(bc.new$banc_png_match),],
root.column = "banc_png_match",
supervoxel.column = "banc_png_match_supervoxel_id",
position.column = "banc_png_match_position")
cat('updating column: banc_nblast_match ...\n')
bc.new <- banc_updateids(bc.new, root.column = "banc_nblast_match", supervoxel.column = "banc_nblast_match_supervoxel_id", position.column = "banc_nblast_match_position")
bc.new[!is.na(bc.new$banc_nblast_match),] <- banc_updateids(bc.new[!is.na(bc.new$banc_nblast_match),],
root.column = "banc_nblast_match",
supervoxel.column = "banc_nblast_match_supervoxel_id",
position.column = "banc_nblast_match_position")
bc.new <- bc.new %>%
dplyr::left_join(lookup %>%dplyr::distinct(lookup_root_id, .keep_all=TRUE),
by = c("banc_match"="lookup_root_id")) %>%
Expand Down
60 changes: 33 additions & 27 deletions R/ids.R
Original file line number Diff line number Diff line change
Expand Up @@ -182,14 +182,16 @@ banc_updateids <- function(x,
if(is.data.frame(x)){

# Update supervoxel IDs
if(all(c(position.column,supervoxel.column)%in%colnames(x))){
no.sp <- is.na(x[[supervoxel.column]])|x[[supervoxel.column]]=="0"
if(sum(no.sp)){
cat('determining missing supervoxel_ids ...\n')
x[no.sp,][[supervoxel.column]] <- unname(pbapply::pbsapply(x[no.sp,][[position.column]], function(row){
tryCatch(quiet_function(banc_xyz2id(row,rawcoords = TRUE, root = FALSE, ...)),
error = function(e) NA)
}))
if(!is.null(position.column)){
if(all(c(position.column,supervoxel.column)%in%colnames(x))){
no.sp <- is.na(x[[supervoxel.column]])|x[[supervoxel.column]]=="0"
if(sum(no.sp)){
cat('determining missing supervoxel_ids ...\n')
x[no.sp,][[supervoxel.column]] <- unname(pbapply::pbsapply(x[no.sp,][[position.column]], function(row){
tryCatch(quiet_function(banc_xyz2id(row,rawcoords = TRUE, root = FALSE, ...)),
error = function(e) NA)
}))
}
}
}

Expand All @@ -209,29 +211,33 @@ banc_updateids <- function(x,
}

# update based on supervoxels
if(supervoxel.column%in%colnames(x)){
cat('updating root_ids with a supervoxel_id...\n')
update <- unname(pbapply::pbsapply(x[old,][[supervoxel.column]], banc_rootid, ...))
bad <- is.na(update)|update=="0"
update <- update[!bad]
if(length(update)) x[old,][[root.column]][!bad] <- update
old[!bad] <- FALSE
if(!is.null(supervoxel.column)){
if(supervoxel.column%in%colnames(x)){
cat('updating root_ids with a supervoxel_id...\n')
update <- unname(pbapply::pbsapply(x[old,][[supervoxel.column]], banc_rootid, ...))
bad <- is.na(update)|update=="0"
update <- update[!bad]
if(length(update)) x[old,][[root.column]][!bad] <- update
old[!bad] <- FALSE
}
old[is.na(old)] <- TRUE
}
old[is.na(old)] <- TRUE

# update based on position
if(any(c("position","pt_position")%in%colnames(x)) && sum(old)){
cat('updating root_ids with a position ...\n')
update <- unname(pbapply::pbsapply(x[old,][[position.column]], function(row){
tryCatch(quiet_function(banc_xyz2id(row,rawcoords = TRUE, root = TRUE, ...)),
error = function(e) NA)
}))
bad <- is.na(update)|update=="0"
update <- update[!bad]
if(length(update)) x[old,][[root.column]][!bad] <- update
old[!bad] <- FALSE
if(!is.null(position.column)){
if(any(position.column%in%colnames(x)) && sum(old)){
cat('updating root_ids with a position ...\n')
update <- unname(pbapply::pbsapply(x[old,][[position.column]], function(row){
tryCatch(quiet_function(banc_xyz2id(row,rawcoords = TRUE, root = TRUE, ...)),
error = function(e) NA)
}))
bad <- is.na(update)|update=="0"
update <- update[!bad]
if(length(update)) x[old,][[root.column]][!bad] <- update
old[!bad] <- FALSE
}
old[is.na(old)] <- TRUE
}
old[is.na(old)] <- TRUE

# update based on root Ids
if(root.column%in%colnames(x) && sum(old)){
Expand Down

0 comments on commit 4266ba0

Please sign in to comment.