Skip to content

Commit 9380f67

Browse files
authored
Merge pull request #201 from natverse/feature/more-expanders
Direct support for flyem shorturls including via tinyurl
2 parents ac69794 + 12f35f8 commit 9380f67

16 files changed

+123
-59
lines changed

R/brainmaps-api.R

+3-3
Original file line numberDiff line numberDiff line change
@@ -506,11 +506,11 @@ read.neurons.brainmaps<-function(x, OmitFailures=NA, df=NULL, ... ) {
506506
#'
507507
#' @return A list containing the following fields \itemize{
508508
#'
509-
#' \item{\code{nvertices}}{ The number of vertices (n)}
509+
#' \item \code{nvertices} The number of vertices (n)
510510
#'
511-
#' \item{\code{nedges}}{ The number of edges (m)}
511+
#' \item \code{nedges} The number of edges (m)
512512
#'
513-
#' \item{\code{vertices}}{ A \code{n} x 3 matrix of vertex locations}
513+
#' \item \code{vertices} A \code{n} x 3 matrix of vertex locations
514514
#'
515515
#' }
516516
#' @export

R/flywire-api.R

+7-7
Original file line numberDiff line numberDiff line change
@@ -26,19 +26,19 @@
2626
#' or error. The default value (\code{TRUE}) will skip over errors, while
2727
#' \code{NA}) will result in a hard stop on error. See \code{\link{nlapply}}
2828
#' for more details.
29-
#' @return A data frame with values itemize{
29+
#' @return A data frame with values \itemize{
3030
#'
31-
#' \item{operation_id}{ a unique id for the edit}
31+
#' \item \code{operation_id} a unique id for the edit
3232
#'
33-
#' \item{timestamp}{ in POSIXct format, to the nearest ms}
33+
#' \item \code{timestamp} in POSIXct format, to the nearest ms
3434
#'
35-
#' \item{user_id}{ numeric id for the user responsible for the edit}
35+
#' \item \code{user_id} numeric id for the user responsible for the edit
3636
#'
37-
#' \item{is_merge}{ whether it was a merge or a split}
37+
#' \item \code{is_merge} whether it was a merge or a split
3838
#'
39-
#' \item{user_name}{ as a string}
39+
#' \item \code{user_name} as a string
4040
#'
41-
#' \item{before_root_ids and after_root_ids}{ as space separated strings}
41+
#' \item \code{before_root_ids and after_root_ids} as space separated strings
4242
#'
4343
#' }
4444
#'

R/flywire-fetch.R

+4-2
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,8 @@
1616
#' @inheritParams brainmaps_fetch
1717
#' @param return One of "parsed", "text" (for raw JSON), or "response"
1818
#' @param token Optional chunkedgraph token (otherwise the default one for the
19-
#' current segmentation will be used).
19+
#' current segmentation will be used). Use \code{NA} to suppress use of a
20+
#' token.
2021
#' @param config (optional) curl options, see \code{httr::\link[httr]{config}}
2122
#' for details.
2223
#'
@@ -51,7 +52,8 @@ flywire_fetch <- function(url,
5152
config = httr::config()
5253
if(is.null(token))
5354
token = chunkedgraph_token()
54-
config = c(config, add_headers(Authorization = paste("Bearer", token)))
55+
if(!isTRUE(is.na(token)))
56+
config = c(config, add_headers(Authorization = paste("Bearer", token)))
5557

5658
#Step 3: choose the actual request function to use, if cache on try the memoised one
5759
# otherwise use the retry from httr..

R/flywire-urls.R

+40-14
Original file line numberDiff line numberDiff line change
@@ -76,12 +76,22 @@ flywire_shortenurl <- function(x, include_base=TRUE, baseurl=NULL, cache=TRUE, .
7676

7777

7878
#' @description \code{flywire_expandurl} expands shortened URLs into a full
79-
#' neuroglancer JSON scene specification. If the active segmentation
79+
#' neuroglancer JSON scene specification. If the link references a specific
80+
#' version of neuroglancer on a specific host URL then that will be used as
81+
#' the base of the expanded URL. This is nearly always the case, but should
82+
#' this ever not be so, then if the active segmentation
8083
#' (\code{\link{choose_segmentation}}) is a flywire segmentation then that is
81-
#' used to define the initial part of the output URL, otherwise the
84+
#' used to define the initial part of the output URL. Failing this, the
8285
#' \code{flywire31} segmentation is used.
8386
#'
84-
#' \code{flywire_expandurl} will also expand tinyurl.com URLs.
87+
#' \code{flywire_expandurl} will also expand tinyurl.com URLs as well as those
88+
#' referencing a json fragment on a google cloud bucket (such as the flyem
89+
#' link shortener). If a tinyurl.com URL maps to a short URL referencing a
90+
#' json fragment, then they will successively be expanded.
91+
#'
92+
#' Finally, if the URL is actually already expanded, then this will be
93+
#' returned unmodified. This is a change in behaviour as of May 2024
94+
#' (previously an error was thrown).
8595
#' @param json.only Only return the JSON fragment rather than the neuroglancer
8696
#' URL
8797
#' @export
@@ -91,31 +101,47 @@ flywire_shortenurl <- function(x, include_base=TRUE, baseurl=NULL, cache=TRUE, .
91101
#' flywire_expandurl("https://globalv1.flywire-daf.com/nglstate/5747205470158848")
92102
#' flywire_expandurl("https://tinyurl.com/rmr58jpn")
93103
#' }
104+
#' \dontrun{
105+
#' flywire_expandurl("https://tinyurl.com/flywirehb2")
106+
#' }
94107
#' @rdname flywire_shortenurl
95108
flywire_expandurl <- function(x, json.only=FALSE, cache=TRUE, ...) {
96109
checkmate::assert_character(x, pattern="^http[s]{0,1}://")
97110
if(length(x)>1) {
98111
res=pbapply::pbsapply(x, flywire_expandurl, json.only=json.only, cache=cache, ...)
99112
return(res)
100113
}
114+
url=x
101115
if(grepl("tinyurl.com", x, fixed = TRUE)) {
102116
# head should redirect to expanded URL
103-
x=httr::HEAD(x)$url
104-
if(json.only)
105-
x=ngl_decode_scene(x, return.json = TRUE)
106-
return(x)
117+
url=httr::HEAD(x, config(followlocation=TRUE))$url
118+
# occasionally we seem to get this ... have to GET
119+
if(grepl("comsync.lijit.com", url, fixed = T))
120+
url=httr::GET(url, config(followlocation=TRUE))$url
121+
x=url
107122
}
108123

109-
if(isFALSE(su <- shorturl(x)))
110-
stop("This doesn't look like a shortened neuroglancer URL: ", x)
111-
x=flywire_fetch(su, cache=cache, return='text', ...)
124+
if(isFALSE(su <- shorturl(url))) {
125+
if(json.only) return(ngl_decode_scene(x, return.json = TRUE))
126+
else return(x)
127+
}
128+
# suppress use of token (with NA) if we are not talking to a CAVE link server
129+
stateserverurl=isTRUE(grepl("nglstate(/api/v[0-9])*/[0-9]+$", su))
130+
use_token=if(stateserverurl) NULL else NA
131+
x=flywire_fetch(su, cache=cache, return='text', token=use_token, ...)
112132

113133
if(isFALSE(json.only)) {
114-
# if we have a flywire segmentation active use that to encode URL
115-
flywire_active=isTRUE(grepl('flywire.ai', getOption('fafbseg.sampleurl')))
116-
x <- if (flywire_active)
134+
baseurl=try({
135+
pu=httr::parse_url(url)
136+
pu$fragment=NULL
137+
httr::build_url(pu)
138+
})
139+
x <- if(!inherits(baseurl, 'try-error')) {
140+
ngl_encode_url(x, baseurl = baseurl)
141+
} else if(flywire_active <- isTRUE(grepl('flywire.ai', getOption('fafbseg.sampleurl')))) {
142+
# if we have a flywire segmentation active use that to encode URL
117143
ngl_encode_url(x)
118-
else
144+
} else
119145
with_segmentation('flywire31', ngl_encode_url(x))
120146
}
121147
x

R/merge-groups.R

+3-3
Original file line numberDiff line numberDiff line change
@@ -9,10 +9,10 @@
99
#' @return vector of segment ids (in ascending order) or when
1010
#' \code{return.groups=TRUE} a \code{data.frame} with columns \itemize{
1111
#'
12-
#' \item{segment}{ the integer segment id, as a numeric (double) column}
12+
#' \item \code{segment} the integer segment id, as a numeric (double) column
1313
#'
14-
#' \item{group}{ an arbitrary group id starting from 1 OR the canonical
15-
#' segment id (see details), an integer or numeric (double), respectively}
14+
#' \item \code{group} an arbitrary group id starting from 1 OR the canonical
15+
#' segment id (see details), an integer or numeric (double), respectively
1616
#'
1717
#' }
1818
#' @details segment ids in \code{ffn16reseg-ms1000_md0.02_c0.6_iou0.7} always

R/read_merge_info.R

+2-2
Original file line numberDiff line numberDiff line change
@@ -14,9 +14,9 @@
1414
#'
1515
#' @return a \code{data.frame} with columns \itemize{
1616
#'
17-
#' \item{id1,id2}{ Segment ids to be merged}
17+
#' \item \code{id1,id2} Segment ids to be merged
1818
#'
19-
#' \item{x,y,z}{ Location (in nm) of merge point}
19+
#' \item \code{x,y,z} Location (in nm) of merge point
2020
#'
2121
#' }
2222
#' @export

R/urls.R

+15-2
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ ngl_decode_scene <- function(x, return.json=FALSE, simplifyVector = TRUE,
7777
# This looks like a URL
7878
# special case, expand shortened flywire URLs
7979
if (!isFALSE(su <- shorturl(x))) {
80-
saved_url = flywire_expandurl(su, json.only = FALSE, ...)
80+
saved_url = flywire_expandurl(x, json.only = FALSE, ...)
8181
x <- ngl_decode_scene(saved_url, return.json = T)
8282
} else {
8383
saved_url <- x
@@ -124,7 +124,20 @@ shorturl <- function(x) {
124124
if(px$hostname %in% c("tinyurl.com"))
125125
return(x)
126126
# looks like fully expanded fragment
127-
if(!is.null(px$fragment)) return(FALSE)
127+
if(!is.null(px$fragment)) {
128+
url <- px$fragment
129+
# remove middleauth prefix - we'll be using flywire_fetch to get the URL
130+
if(isTRUE(substr(url, 1, 12) == "!middleauth+"))
131+
url=paste0("!", substr(url,13,nchar(url)))
132+
133+
if(isTRUE(substr(url, 1, 6) == "!gs://")) {
134+
path = substr(url, 6, nchar(url))
135+
gu = "https://storage.googleapis.com"
136+
return(paste0(gu, path))
137+
} else if(isTRUE(substr(url, 1, 9) == "!https://")) {
138+
return(substr(url, 2, nchar(url)))
139+
} else return(FALSE)
140+
}
128141
if(!is.null(px$query$json_url))
129142
return(px$query$json_url)
130143
# may have been a bare URL, but in that case check path

man/brainmaps_skeleton.Rd

+3-3
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/find_merged_segments.Rd

+3-3
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/flywire_change_log.Rd

+7-7
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/flywire_dcvs.Rd

+2-1
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/flywire_fetch.Rd

+2-1
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/flywire_shortenurl.Rd

+16-3
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/read_mergeinfo.Rd

+2-2
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

tests/testthat/test-flywire.R

+10-6
Original file line numberDiff line numberDiff line change
@@ -99,15 +99,19 @@ test_that("can expand a flywire url to get segments", {
9999
"720575940637384518"
100100
)
101101
)
102+
# check long url comes back unaltered
103+
fsu=fafbseg::choose_segmentation('flywire31', set = F)$fafbseg.sampleurl
104+
expect_equal(flywire_expandurl(fsu), fsu)
102105

103-
expect_error(
104-
flywire_expandurl(
105-
fafbseg::choose_segmentation('flywire31', set = F)$fafbseg.sampleurl
106-
),
107-
'shortened neuroglancer'
108-
)
109106
expect_known_hash(flywire_expandurl('https://tinyurl.com/rmr58jpn'),
110107
hash = 'a5fb89f6f9')
108+
109+
# make sure we can expand a recursive tinyurl
110+
expect_equal(flywire_expandurl("https://tinyurl.com/flywirehb2"),
111+
flywire_expandurl("https://neuroglancer-demo.appspot.com/#!gs://flyem-user-links/short/2023-08-26.151006.json"))
112+
113+
expect_is(flywire_expandurl("https://spelunker.cave-explorer.org/#!middleauth+https://global.daf-apis.com/nglstate/api/v1/5939082989404160"),
114+
'character')
111115
})
112116

113117
test_that("flywire url handling", {

tests/testthat/test-urls.R

+4
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,10 @@ test_that("decode scene works", {
3030
u="https://neuromancer-seung-import.appspot.com/#!%7B%22layers%22:[%7B%22source%22:%22precomputed://gs://zetta_lee_fly_vnc_001_precomputed/fanc_v4_em%22,%22type%22:%22image%22,%22blend%22:%22default%22,%22shaderControls%22:%7B%7D,%22name%22:%22FANCv4%22%7D,%7B%22source%22:%22graphene://https://cave.fanc-fly.com/segmentation/table/mar2021_prod%22,%22type%22:%22segmentation_with_graph%22,%22colorSeed%22:1792288153,%22segmentColors%22:%7B%22648518346498254576%22:%22#1fe0f9%22%7D,%22segments%22:[%22648518346498254576%22],%22skeletonRendering%22:%7B%22mode2d%22:%22lines_and_points%22,%22mode3d%22:%22lines%22%7D,%22graphOperationMarker%22:[%7B%22annotations%22:[],%22tags%22:[]%7D,%7B%22annotations%22:[],%22tags%22:[]%7D],%22pathFinder%22:%7B%22color%22:%22#ffff00%22,%22pathObject%22:%7B%22annotationPath%22:%7B%22annotations%22:[],%22tags%22:[]%7D,%22hasPath%22:false%7D%7D,%22name%22:%22seg_Mar2021_proofreading%22%7D,%7B%22source%22:%22precomputed://gs://lee-lab_female-adult-nerve-cord/alignmentV4/synapses/postsynapses_May2021%22,%22type%22:%22image%22,%22blend%22:%22default%22,%22shader%22:%22void%20main()%20%7B%20emitRGBA(vec4(1,%200,%201,%20toNormalized(getDataValue())));%20%7D%22,%22shaderControls%22:%7B%7D,%22name%22:%22synapses_May2021%22,%22visible%22:false%7D,%7B%22type%22:%22segmentation%22,%22mesh%22:%22precomputed://gs://zetta_lee_fly_vnc_001_precomputed/vnc1_full_v3align_2/brain_regions%22,%22objectAlpha%22:0.1,%22hideSegmentZero%22:false,%22ignoreSegmentInteractions%22:true,%22segmentColors%22:%7B%221%22:%22#bfbfbf%22,%222%22:%22#d343d6%22%7D,%22segments%22:[%221%22,%222%22],%22skeletonRendering%22:%7B%22mode2d%22:%22lines_and_points%22,%22mode3d%22:%22lines%22%7D,%22name%22:%22volume%20outlines%22%7D],%22navigation%22:%7B%22pose%22:%7B%22position%22:%7B%22voxelSize%22:[4.300000190734863,4.300000190734863,45],%22voxelCoordinates%22:[48848.171875,114737.2109375,2690]%7D%7D,%22zoomFactor%22:11.839474231467724%7D,%22perspectiveZoom%22:6704.002738252677,%22showSlices%22:false,%22gpuMemoryLimit%22:4000000000,%22systemMemoryLimit%22:4000000000,%22concurrentDownloads%22:64,%22jsonStateServer%22:%22https://global.daf-apis.com/nglstate/api/v1/post%22,%22selectedLayer%22:%7B%22layer%22:%22seg_Mar2021_proofreading%22,%22visible%22:true%7D,%22layout%22:%22xy-3d%22%7D"
3131

3232
expect_s3_class(sc <- ngl_decode_scene(u), 'ngscene')
33+
expect_s3_class(ngl_decode_scene("https://tinyurl.com/rmr58jpn"), 'ngscene')
34+
expect_s3_class(ngl_decode_scene("https://neuroglancer-demo.appspot.com/#!gs://flyem-user-links/short/2023-08-26.151006.json"), 'ngscene')
35+
expect_s3_class(ngl_decode_scene("https://tinyurl.com/flywirehb2"), 'ngscene')
36+
expect_type(ngl_decode_scene("https://tinyurl.com/flywirehb2", return.json = T), 'character')
3337
})
3438

3539
test_that("we can work round toJSON array issue",{

0 commit comments

Comments
 (0)