Skip to content

Commit

Permalink
Added support for GIfTI and FreeSurfer surfaces
Browse files Browse the repository at this point in the history
  • Loading branch information
dipterix committed Sep 11, 2024
1 parent 53fa43a commit 3beb468
Show file tree
Hide file tree
Showing 34 changed files with 2,993,452 additions and 130 deletions.
4 changes: 2 additions & 2 deletions CRAN-SUBMISSION
Original file line number Diff line number Diff line change
@@ -1,3 +1,3 @@
Version: 0.0.1
Date: 2024-09-09 04:24:18 UTC
SHA: fe32ae4e4f7c9d5917c8ecd81c2746bf012804b4
Date: 2024-09-09 12:54:50 UTC
SHA: 53fa43a53ee02067f73f9ed64daad9d840dcd394
4 changes: 4 additions & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,8 @@ Imports:
freesurferformats,
fs,
fst (>= 0.9.0),
gifti (>= 0.8.0),
grDevices,
hdf5r,
jsonlite,
oro.nifti,
Expand All @@ -33,8 +35,10 @@ Imports:
readNSx (>= 0.0.5),
rpyANTs (>= 0.0.3),
stringr,
utils,
yaml
Suggests:
reticulate,
rgl,
rpymat (>= 0.1.7),
RNifti (>= 1.7.0)
39 changes: 23 additions & 16 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -21,47 +21,54 @@ S3method(close,pynwb.NWBHDF5IO)
S3method(dim,LazyH5)
S3method(exp,LazyH5)
S3method(format,ieegio_get_channel)
S3method(format,ieegio_surface)
S3method(format,ieegio_volume)
S3method(io_write_mgz,ants.core.ants_image.ANTsImage)
S3method(io_write_mgz,array)
S3method(io_write_mgz,ieegio_mgh)
S3method(io_write_mgz,ieegio_volume)
S3method(io_write_mgz,nifti)
S3method(io_write_mgz,niftiImage)
S3method(io_write_nii,ants.core.ants_image.ANTsImage)
S3method(io_write_nii,array)
S3method(io_write_nii,ieegio_mgh)
S3method(io_write_nii,ieegio_nifti)
S3method(io_write_nii,nifti)
S3method(io_write_nii,niftiImage)
S3method(length,LazyH5)
S3method(merge,ieegio_surface)
S3method(names,ieegio_volume)
S3method(plot,ieegio_surface)
S3method(print,ieegio_get_channel)
S3method(print,ieegio_surface)
S3method(print,ieegio_volume)
S3method(print,nwb.proxy)
S3method(write_mgz,ants.core.ants_image.ANTsImage)
S3method(write_mgz,array)
S3method(write_mgz,ieegio_mgh)
S3method(write_mgz,ieegio_volume)
S3method(write_mgz,nifti)
S3method(write_mgz,niftiImage)
S3method(write_nii,ants.core.ants_image.ANTsImage)
S3method(write_nii,array)
S3method(write_nii,ieegio_mgh)
S3method(write_nii,ieegio_nifti)
S3method(write_nii,nifti)
S3method(write_nii,niftiImage)
export(ieegio_sample_data)
export(install_pynwb)
export(io_h5_names)
export(io_h5_valid)
export(io_read_fs)
export(io_read_fst)
export(io_read_gii)
export(io_read_h5)
export(io_read_ini)
export(io_read_json)
export(io_read_mat)
export(io_read_mgz)
export(io_read_nii)
export(io_read_yaml)
export(io_write_fst)
export(io_write_h5)
export(io_write_json)
export(io_write_mat)
export(io_write_mgz)
export(io_write_nii)
export(io_write_yaml)
export(pynwb_module)
export(read_bci2000)
export(read_brainvis)
export(read_edf)
export(read_mgz)
export(read_nii)
export(read_nsx)
export(read_nwb)
export(write_mgz)
export(write_nii)
export(read_surface)
importFrom(R6,R6Class)
27 changes: 27 additions & 0 deletions R/aaa-docs.R
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,33 @@
#'
NULL

#' @name read_surface
#' @title Read surface files
#' @description
#' Supports reading surface geometry, annotation, measurement, and
#' time-series data.
#' Please use the high-level function \code{read_surface}, which calls
#' other low-level functions internally.
#'
#' @param file path the file
#' @param type type of the data; ignored if the file format is 'GIfTI'. For
#' 'FreeSurfer' files, supported types are
#' \describe{
#' \item{\code{'geometry'}}{contains positions of mesh vertex nodes and face indices;}
#' \item{\code{'annotations'}}{annotation file (usually with file extension \code{'annot'}) containing a color look-up table and an array of color keys. These files are used to display discrete values on the surface such as brain atlas;}
#' \item{\code{'measurements'}}{measurement file such as \code{'sulc'} and \code{'curv'} files, containing numerical values (often with continuous domain) for each vertex node}
#' }
#' @param format format of the file, see 'Arguments' section in
#' \code{\link[freesurferformats]{read.fs.surface}} (when file type is
#' \code{'geometry'}) and \code{\link[freesurferformats]{read.fs.curv}}
#' (when file type is \code{'measurements'})
#' @param name name of the data; default is the file name
#' @param ... for \code{read_surface}, the arguments will be passed to
#' \code{io_read_fs} if the file is a 'FreeSurfer' file.
#' @returns A surface object container
#'
#'
NULL

#' @name read_brainvis
#' @title Read 'BrainVision' data
Expand Down
11 changes: 7 additions & 4 deletions R/aaa.R
Original file line number Diff line number Diff line change
@@ -1,10 +1,13 @@
#' @importFrom R6 R6Class
NULL

# Formats:
# matlab, brainvision, edf, hdf5
# nsx/nev, nifti, mgh/z
# json
NIFTI_XFORM_CODE <- list(
"NIFTI_XFORM_UNKNOWN" = "Unknown",
"NIFTI_XFORM_SCANNER_ANAT" = "ScannerAnat",
"NIFTI_XFORM_ALIGNED_ANAT" = "AlignedAnat",
"NIFTI_XFORM_TALAIRACH" = "Talairach",
"NIFTI_XFORM_MNI_152" = "MNI152"
)

parse_svec <- function(text, sep = ',', connect = '-:|', sort = FALSE, unique = TRUE){
connect <- unique(unlist(strsplit(connect, '')))
Expand Down
197 changes: 197 additions & 0 deletions R/freesurfer.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,197 @@

fs_lut <- local({
lut <- NULL
impl <- function() {
# /Users/dipterix/Dropbox (Personal)/projects/ieegio/inst/lookup_table
"inst/lookup_table/FreeSurferColorLUT.json"
path <- system.file("lookup_table", "FreeSurferColorLUT.json", package = "ieegio")
lut <- io_read_json(path)
data.table::rbindlist(lut$`__global_data__.VolumeColorLUT`$map)
}
function() {
if(is.null(lut)) {
lut <<- impl()
}
lut
}
})

#' @rdname read_surface
#' @export
io_read_fs <- function(file, type = c("geometry", "annotations", "measurements"),
format = "auto", name = basename(file), ...) {

type <- match.arg(type)

# DIPSAUS DEBUG START
# f_geom <- "/Users/dipterix/rave_data/raw_dir/AnonSEEG_old2/rave-imaging/fs/surf/lh.pial"
# f_annot <- "/Users/dipterix/rave_data/raw_dir/AnonSEEG_old2/rave-imaging/fs/label/lh.aparc.annot"
#
# file <- f_geom
# format <- "auto"
# name = basename(file)



re <- switch(
type,
"geometry" = {
surf <- freesurferformats::read.fs.surface(file, format = format)
header <- structure(
class = "fs_geometry",
list(internal = surf$internal, mesh_face_type = surf$mesh_face_type)
)
# try to get c_ras
transforms <- list(
Unknown = structure(
diag(1, 4),
source_space = "Unknown",
target_space = "Unknown"
)
)

suppressWarnings({
tryCatch(
{
line1 <- readLines(file, n = 1L, encoding = "ascii")
n <- c(
nchar(line1, type = "bytes"), 8,
length(surf$vertices) * 4,
length(surf$faces) * 4
)
extra_bytes <- file.size(file) - sum(n)
if(length(extra_bytes)) {
conn <- base::file(file, "rb")
on.exit({ close(conn) })
invisible({ readBin(conn, "raw", n = sum(n)) })
extra <- readBin(conn, "raw", n = extra_bytes, endian = "big")
extra <- intToUtf8(extra)
extra <- trimws(strsplit(extra, "\n")[[1]])
extra <- extra[startsWith(extra, "cras ")]
cras <- strsplit(extra, "=", fixed = TRUE)[[1]][[2]]
cras <- strsplit(trimws(cras), " ")[[1]]
cras <- cras[cras != ""]
cras <- as.numeric(cras)
if(length(cras) == 3 && !anyNA(cras)) {
names(transforms) <- "ScannerAnat"
transforms$ScannerAnat[1:3, 4] <- cras
}
}
},
error = function(...) {}
)
})

return(new_surface(header = header, geometry = list(
vertices = t(cbind(surf$vertices[, c(1, 2, 3)], 1)),
faces = t(surf$faces),
face_start = 1L,
transforms = transforms,
meta = list(Name = name)
)))
},
"annotations" = {
# list(
# label_table = parse_label_table(gii$label),
# data_table = NULL,
# meta = list()
# )
annot <- freesurferformats::read.fs.annot(file, default_label_name = "Unlabeled")
# lut <- fs_lut()

annot_name <- name

label_table <- data.table::data.table(
Key = annot$colortable_df$struct_index,
Label = annot$colortable_df$struct_name,
Red = annot$colortable_df$r / 255,
Green = annot$colortable_df$g / 255,
Blue = annot$colortable_df$b / 255,
Color = annot$colortable_df$hex_color_string_rgb
)

# annot$vertices
lut <- structure(
names = as.character(label_table$Label),
label_table$Key
)
unames <- as.character(unique(annot$label_names))
unames <- unames[!unames %in% label_table$Label]
if(length(unames)) {
lut[unames] <- 0
}
data_table <- data.table::data.table(V = unname(lut[annot$label_names]))

names(data_table) <- annot_name
annotations <- list(
label_table = label_table,
data_table = data_table,
meta = structure(names = annot_name, list(annot$metadata))
)
node_index <- annot$vertices
if(length(node_index)) {
node_index <- list(
node_index = as.integer(node_index) + 1L,
node_index_start = 1L
)
} else {
node_index <- NULL
}
return(
new_surface(
header = structure(
class = "fs_annot",
list(orig_ctab = annot$colortable_df)
),
annotations = annotations,
sparse_node_index = node_index
)
)
},
"measurements" = {
meas <- freesurferformats::read.fs.curv(file, format = format, with_header = TRUE)

data_table <- data.table::data.table(V = meas$data)
names(data_table) <- name
measurements <- list(
data_table = data_table,
meta = list()
)
return(
new_surface(
header = structure(
class = "fs_measurement",
meas$header
),
measurements = measurements
)
)
},
"color" = {

},
"time_series" = {

}
)


# if(FALSE) {
# f_geom <- "/Users/dipterix/rave_data/raw_dir/AnonSEEG_old2/rave-imaging/fs/surf/lh.pial"
# f_annot <- "/Users/dipterix/rave_data/raw_dir/AnonSEEG_old2/rave-imaging/fs/label/lh.aparc.annot"
# f_meas <- "/Users/dipterix/rave_data/raw_dir/AnonSEEG_old2/rave-imaging/fs/surf/lh.curv"
#
# file <- f_meas
# x <- merge(
# io_read_fs(f_geom, "geometry"),
# io_read_fs(f_annot, "annot"),
# io_read_fs(f_meas, "mea")
# )
# plot(x, name = c("measure", "lh.curv"), col = c("black", "white", "black"))
# }


re

}

Loading

0 comments on commit 3beb468

Please sign in to comment.