Skip to content

Commit

Permalink
Added banc RGL views
Browse files Browse the repository at this point in the history
  • Loading branch information
alexanderbates committed Jul 3, 2024
1 parent ab75a46 commit fde9b39
Show file tree
Hide file tree
Showing 11 changed files with 81 additions and 48 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -4,3 +4,4 @@
.Ruserdata
docs
inst/doc
data-raw/*
3 changes: 2 additions & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ BugReports: https://github.com/flyconnectome/bancr/issues
Depends:
R (>= 2.10),
fafbseg (>= 0.13.0.9100),
Morpho,
fancr,
nat.flybrains
Imports:
nat,
Expand Down Expand Up @@ -47,6 +47,7 @@ Remotes:
natverse/fafbseg,
natverse/nat.flybrains,
natverse/nat.templatebrains
flyconnectome/fancr
Config/testthat/edition: 3
Encoding: UTF-8
Language: en-GB
Expand Down
2 changes: 1 addition & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ export(banc_voxdims)
export(banc_xyz2id)
export(choose_banc)
export(dr_banc)
export(read_banc_meshes)
export(banc_read_neuron_meshes)
export(with_banc)
import(bit64)
import(fafbseg)
Expand Down
22 changes: 15 additions & 7 deletions R/cave-tables.R
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,8 @@
#' points3d(nat::xyzmatrix(all_banc_soma_positions))
#' }
#'
banc_cave_tables <- function(datastack_name = getOption("fafbseg.cave.datastack_name"), select = NULL){
banc_cave_tables <- function(datastack_name = getOption("fafbseg.cave.datastack_name"),
select = NULL){
fac <- flywire_cave_client(datastack_name = datastack_name)
dsinfo <- fac$info$get_datastack_info()
if (!is.null(dsinfo$soma_table))
Expand All @@ -52,7 +53,7 @@ banc_cave_tables <- function(datastack_name = getOption("fafbseg.cave.datastack_
#' @export
banc_nuclei <- function (rootids = NULL,
nucleus_ids = NULL,
table = c("somas_v1b","somas_v1a"),
table = c("somas_v1a","somas_v1b"),
rawcoords = FALSE,
...) {
table <- match.arg(table)
Expand Down Expand Up @@ -84,7 +85,7 @@ banc_nuclei <- function (rootids = NULL,
nuclei %>% dplyr::mutate(pt_root_id = flywire_updateids(.data$pt_root_id,
svids = .data$pt_supervoxel_id))
}
}else {
}else{
nid <- paste(nucleus_ids, collapse = ",")
nidq <- reticulate::py_eval(sprintf("{\"id\": [%s]}",
nid), convert = F)
Expand All @@ -96,17 +97,24 @@ banc_nuclei <- function (rootids = NULL,
res
# apply coordinate transform
# res <- standard_nuclei(res)
if (isFALSE(rawcoords))
if (isTRUE(rawcoords))
res
else {
res %>% dplyr::mutate(dplyr::across(dplyr::ends_with("position"), function(x) nat::xyzmatrix2str(flywire_nm2raw(x))))
res %>% dplyr::mutate(dplyr::across(dplyr::ends_with("position"), function(x)
nat::xyzmatrix2str(fancr::banc_raw2nm(x))))
}
}

#' @export
banc_cell_info <- function(rootids = NULL){
banc_cell_info <- function(rootids = NULL, rawcoords = FALSE){
table <- "cell_info"
get_cave_table_data(table)
res <- get_cave_table_data(table)
if (isTRUE(rawcoords))
res
else {
res %>% dplyr::mutate(dplyr::across(dplyr::ends_with("position"), function(x)
nat::xyzmatrix2str(fancr::banc_raw2nm(x))))
}
}

#' @export
Expand Down
35 changes: 7 additions & 28 deletions R/meshes.R
Original file line number Diff line number Diff line change
Expand Up @@ -18,12 +18,12 @@
#' @seealso \code{fafbseg::\link{read_cloudvolume_meshes}}
#' @examples
#' \donttest{
#' neuron.mesh <- read_banc_meshes("720575941650432785")
#' neuron.mesh <- banc_read_neuron_meshes("720575941650432785")
#' plot3d(neuron.mesh, alpha = 0.1)
#' nucleus.mesh <- read_banc_meshes("72903876004544795")
#' nucleus.mesh <- banc_read_neuron_meshes("72903876004544795")
#' plot3d(nucleus.mesh, col = "black")
#' }
read_banc_meshes <- function(ids, savedir=NULL, format=c("ply", "obj"), ...) {
banc_read_neuron_meshes <- function(ids, savedir=NULL, format=c("ply", "obj"), ...) {
format=match.arg(format)
read_cloudvolume_meshes(ids, savedir = savedir, cloudvolume.url = banc_cloudvolume_url(set=FALSE), format=format, ...)
}
Expand Down Expand Up @@ -54,7 +54,7 @@ banc_read_nuclei_mesh <- function(ids, lod = 1L, savedir=NULL, method=c('vf', '
#' @export
#' @examples
#' \donttest{
#' m = read_banc_meshes("720575941650432785")
#' m = banc_read_neuron_meshes("720575941650432785")
#' m.brain = banc_decapitate(m)
#' m.vnc = banc_decapitate(m, invert = TRUE)
#' plot3d(m.brain, col = "red")
Expand Down Expand Up @@ -110,7 +110,7 @@ banc_decapitate <- function(x, invert = FALSE, reference = "BANC"){
#' @param url the URL that directs \code{bancr} to where BANC meshes are stored.
#' @return a mesh3d object for the specified mesh.
#' @export
#' @seealso \code{\link{read_banc_meshes}}
#' @seealso \code{\link{banc_read_neuron_meshes}}
#' @examples
#' \dontrun{
#' banc.mesh <- banc_read_neuroglancer_mesh()
Expand All @@ -122,12 +122,13 @@ banc_read_neuroglancer_mesh <- function(x = 1,
res <- httr::GET(completed_url, ...)
httr::stop_for_status(res)
bytes <- httr::content(res, as = "raw")
decode_neuroglancer_mesh(bytes)
malevnc:::decode_neuroglancer_mesh(bytes)
}

# convert cloudvolume python mesh to an R mesh3d object
# method vf just uses the vertex and face arrays
# ply writes out to Stanford ply format and reads back in again
# from hemibrainr
cvmesh2mesh <- function(x, method=c('vf', 'ply'), ...) {
method=match.arg(method)
if(method=='vf') {
Expand All @@ -148,25 +149,3 @@ cvmesh2mesh <- function(x, method=c('vf', 'ply'), ...) {
m
}

# from package: malevnc
decode_neuroglancer_mesh <- function (bytes, format = c("mesh3d", "raw")) {
format = match.arg(format)
con = rawConnection(bytes)
on.exit(close(con))
nverts = readBin(con, what = "int", size = 4, n = 1)
verts = readBin(con, what = "numeric", n = nverts * 3, size = 4)
nidxs = length(bytes)/4 - 1L - length(verts)
idx = readBin(con, what = "int", n = nidxs, size = 4)
if (format == "raw") {
structure(list(v = matrix(verts, ncol = 3, byrow = T),
i = matrix(idx, ncol = 3, byrow = T)), class = "ngmesh")
}
else {
rgl::tmesh3d(matrix(verts, nrow = 3, byrow = F), matrix(idx +
1L, nrow = 3, byrow = F), homogeneous = F)
}
}




1 change: 0 additions & 1 deletion R/seatable_start.R

This file was deleted.

19 changes: 16 additions & 3 deletions R/synapses.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,8 @@
#' @param overwrite Logical, whether or not to overwrite an extant \code{banc_data.sqlite} file.
#' @param n_max Numeric, the maximum number of rows ot read from \code{path} if you just want to see
#' a taster of the file.
#' @param Logical Whether or not to read all data columns in the target synapse \code{.csv}. Defaults to
#' \code{FALSE} in order to read only the essential presynapse position data.
#'
#' @return a data.frame
#'
Expand All @@ -20,7 +22,8 @@
#' }
banc_all_synapses <- function(path = "gs://zetta_lee_fly_cns_001_synapse/240623_run/assignment/final_edgelist.df",
overwrite = FALSE,
n_max = 2000){
n_max = 2000,
details = FALSE){

# Correct path to de-authenticate it, use https
path <- gsub("^gs\\:\\/","https://storage.googleapis.com",path)
Expand Down Expand Up @@ -66,11 +69,21 @@ banc_all_synapses <- function(path = "gs://zetta_lee_fly_cns_001_synapse/240623_

# Are we just sampling or going for the full thing?
if(!is.null(n_max)){
syns <- readr::read_csv(file=path, col_types = col.types, lazy = TRUE, n_max = n_max)
if(details){
syns <- readr::read_csv(file=path, col_types = col.types, lazy = TRUE, n_max = n_max)
}else{
syns <- readr::read_csv(file=path, col_types = col.types, lazy = TRUE, n_max = n_max,
select = c(presyn_segid, presyn_x, presyn_y, presyn_z, size))
}
return(syns)
}else if (!table_exists|overwrite){
# Get all synapses
syns <- readr::read_csv(file=path, col_types = col.types, lazy = TRUE)
if (details){
syns <- readr::read_csv(file=path, col_types = col.types, lazy = TRUE)
}else{
syns <- readr::read_csv(file=path, col_types = col.types, lazy = TRUE,
select = c(presyn_segid, presyn_x, presyn_y, presyn_z, size))
}

# Process

Expand Down
32 changes: 32 additions & 0 deletions R/xform.R
Original file line number Diff line number Diff line change
@@ -1 +1,33 @@

# for nm
banc_view <- function(){
rgl::rgl.viewpoint(userMatrix = structure(c(0.961547076702118, 0.037275392562151,
0.27209860086441, 0, 0.0369537360966206, -0.999296963214874,
0.00630810856819153, 0, 0.272142440080643, 0.00398948788642883,
-0.962248742580414, 0, 0, 0, 0, 1), dim = c(4L, 4L)), zoom = 0.822702646255493)
}

# for nm
banc_side_view <- function(){
rgl::rgl.viewpoint(userMatrix = structure(c(0.188666880130768, 0.137750864028931,
-0.972331881523132, 0, 0.130992725491524, -0.98479551076889,
-0.114099271595478, 0, -0.97326534986496, -0.105841755867004,
-0.203842639923096, 0, 0, 0, 0, 1), dim = c(4L, 4L)), zoom = 0.783526360988617)
}

# for nm
banc_front_view <- function(){
rgl::rgl.viewpoint(userMatrix = structure(c(0.99931389093399, 0.0139970388263464,
-0.0342894680798054, 0, -0.0321401171386242, -0.132316529750824,
-0.990686297416687, 0, -0.0184037387371063, 0.991108655929565,
-0.131775915622711, 0, 0, 0, 0, 1), dim = c(4L, 4L)), zoom = 0.613913536071777)
}

# for nm
banc_vnc_view <- function(){
rgl::rgl.viewpoint(userMatrix = structure(c(0.992902159690857, 0.113465532660484,
0.0356490463018417, 0, 0.103959240019321, -0.973584711551666,
0.203286483883858, 0, 0.0577733889222145, -0.198137611150742,
-0.978470027446747, 0, 33598.359375, 191755.796875, -6508.533203125,
1), dim = c(4L, 4L)), zoom = 0.505068242549896)
}
2 changes: 1 addition & 1 deletion man/banc_decapitate.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion man/banc_read_neuroglancer_mesh.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

10 changes: 5 additions & 5 deletions man/read_banc_meshes.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit fde9b39

Please sign in to comment.