Skip to content

Commit

Permalink
Merge pull request #1 from flyconnectome/fix/cave-infrastructure
Browse files Browse the repository at this point in the history
Switch from Zetta to cave infrastructure
  • Loading branch information
jefferis authored Aug 23, 2021
2 parents 471954b + b83df54 commit f1d7eeb
Show file tree
Hide file tree
Showing 10 changed files with 57 additions and 53 deletions.
2 changes: 1 addition & 1 deletion .github/workflows/R-CMD-check.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ jobs:
shell: Rscript {0}

- name: writetoken
run: fafbseg::flywire_set_token(token=Sys.getenv("CHUNKEDGRAPH_SECRET"), domain='wclee.api.zetta.ai')
run: fafbseg::flywire_set_token(token=Sys.getenv("CHUNKEDGRAPH_SECRET"))
shell: Rscript {0}

- name: Check
Expand Down
20 changes: 12 additions & 8 deletions R/cloudvolume.R
Original file line number Diff line number Diff line change
Expand Up @@ -21,12 +21,16 @@ fanc_api_url <- function(endpoint="") {
#' @return The path to the token file (invisibly)
#' @export
fanc_set_token <- function(token=NULL) {
# check we have the
fafbseg::flywire_set_token(token=token, domain='wclee.api.zetta.ai')
# path=fafbseg::flywire_set_token(token=token, domain='cave.fanc-fly.com')
path=fafbseg::flywire_set_token(token=token)
# clear the token cache so the new one is immediately available
fanc_token(cached=FALSE)
invisible(path)
}

fanc_token <- function(cached=TRUE) {
fafbseg::chunkedgraph_token(url='wclee.api.zetta.ai', cached = cached)
# fafbseg::chunkedgraph_token(url='cave.fanc-fly.com', cached = cached)
fafbseg::chunkedgraph_token(cached = cached)
}

fanc_token_available <- function() {
Expand All @@ -42,24 +46,24 @@ fanc_token_available <- function() {
#' dr_fanc()
#' }
dr_fanc <- function() {
zetta_report()
fanc_api_report()
cat("\n\n")
res = fafbseg:::py_report()
cat("\n")
try(fafbseg:::check_cloudvolume_reticulate(min_version = "3.12"))
invisible(res)
}

zetta_report <- function() {
message("Zetta Neuroglancer / API access\n----")
fanc_api_report <- function() {
message("FANC Neuroglancer / CAVE API access\n----")

token=try(fanc_token(cached = F), silent = FALSE)
if(inherits(token, "try-error")) {
FUN=if(requireNamespace('usethis', quietly = T)) usethis::ui_todo else message
FUN(paste('No valid Zetta token found. Set your token by doing:\n',
FUN(paste('No valid FANC API token found. Set your token by doing:\n',
"{ui_code('fanc_set_token()')}"))
} else{
cat("Valid Zetta ChunkedGraph token is set!\n")
cat("Valid FANC API ChunkedGraph token is set!\n")
}
ff=dir(fafbseg:::cv_secretdir(), pattern = '-secret\\.json$')
if(length(ff)){
Expand Down
2 changes: 1 addition & 1 deletion R/ids.R
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ fanc_leaves <- function(x, integer64=TRUE, ...) {
#' @export
#' @importFrom nat xyzmatrix
#' @examples
#' # a point from neuroglancer, should map to 648518346479013777
#' # a point from neuroglancer, should map to 648518346498932033
#' fanc_xyz2id(cbind(34495, 82783, 1954), rawcoords=TRUE)
fanc_xyz2id <- function(xyz, rawcoords=FALSE, voxdims=c(4.3, 4.3, 45),
root=TRUE, ...){
Expand Down
2 changes: 1 addition & 1 deletion R/urls.R
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@
#' browseURL(fanc_scene())
#' }
fanc_scene <- function(ids=NULL) {
url="https://neuromancer-seung-import.appspot.com/?json_url=https://api.zetta.ai/json/325890137970388411"
url="https://neuromancer-seung-import.appspot.com/?json_url=https://global.daf-apis.com/nglstate/api/v1/5969075557629952"
url=sub("?json_url=", "?", url, fixed = T)
parts=unlist(strsplit(url, "?", fixed = T))
json=try(flywire_fetch(parts[2], token=fanc_token(), return = 'text', cache = TRUE))
Expand Down
34 changes: 15 additions & 19 deletions R/zetta-api.R
Original file line number Diff line number Diff line change
@@ -1,32 +1,28 @@
#' Fetch change log information for one or more neurons
#'
#' @details As of August 2021 this is a simple wrapper of
#' \code{fabseg::\link{flywire_change_log}}. For now the old (and less
#' convenient format) available from the zetta API can be obtained with the
#' private \code{fancr:::fanc_change_log_zetta} function.
#'
#' @param x One or more fanc ids in any format understandable by
#' \code{\link[fafbseg]{ngl_segments}}
#' @param ... Additional argument passed to \code{\link{pbsapply}} and then on
#' to \code{\link{flywire_fetch}} (via the private \code{fanc_fetch}).
#'
#' @return A list containing information on the changes applied to a given body
#'
#' \itemize{
#'
#' \item \code{n_splits},\code{n_mergers} The number of splits/mergers applied
#' to the neuron
#'
#' \item \code{user_info} A data.frame containing user ids or emails and the
#' number of splits/mergers
#'
#' \item \code{operations_ids} An integer vector of operation ids
#'
#' \item \code{past_ids} Previous ids associated with this body
#'
#' }
#' @return a \code{data.frame} See \code{fabseg::\link{flywire_change_log}} for
#' details
#' @export
#' @importFrom pbapply pbsapply
#' @inheritParams fafbseg::flywire_change_log
#' @examples
#' \donttest{
#' fanc_change_log("648518346473954669")
#' }
fanc_change_log <- function(x, ...) {

fanc_change_log <- function(x, tz="UTC", filtered=TRUE, OmitFailures=TRUE,
...) {
with_fanc(flywire_change_log(x=x, tz=tz, filtered = filtered, OmitFailures = OmitFailures, ...))
}

fanc_change_log_zetta <- function(x, ...) {
baseurl=fanc_api_url(endpoint = "root/")
x=fafbseg::ngl_segments(x, as_character = T)
if(length(x)>1) {
Expand Down
36 changes: 20 additions & 16 deletions man/fanc_change_log.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/fanc_xyz2id.Rd

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

2 changes: 1 addition & 1 deletion tests/testthat/test-ids.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
test_that("fanc_xyz2id works", {
expect_equal(fanc_xyz2id(cbind(34495, 82783, 1954), rawcoords=TRUE),
"648518346479013777")
"648518346498932033")

expect_equal(
fanc_xyz2id(cbind(34495, 82783, 1954), rawcoords=TRUE, root=F),
Expand Down
2 changes: 1 addition & 1 deletion tests/testthat/test-urls.R
Original file line number Diff line number Diff line change
@@ -1,3 +1,3 @@
test_that("fanc_scene works", {
expect_type(sc <- fanc_scene("648518346479013777"), 'character')
expect_type(sc <- fanc_scene("648518346498932033"), 'character')
})
8 changes: 4 additions & 4 deletions tests/testthat/test-zetta-api.R
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
test_that("changelog works", {
skip_if_offline()
skip_if_not(fanc_token_available(),
message="Unable to obtain a Zetta / FANC access token")
expect_type(res <- fanc_change_log("648518346473954669"), "list")
expect_named(res, c("n_splits", "n_mergers", "user_info", "operations_ids",
"past_ids"))
message="Unable to obtain a FANC access token")
expect_s3_class(res <- fanc_change_log("648518346473954669"), "data.frame")
expect_named(res, c("operation_id", "timestamp", "user_id", "before_root_ids",
"after_root_ids", "is_merge", "user_name"))
})

0 comments on commit f1d7eeb

Please sign in to comment.