From 2c8dda4708002ced141a374854d824ef4741be2e Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 24 Aug 2022 16:20:55 +0200 Subject: [PATCH 01/46] Adapt to changes in rsfmri and suggestions for processing. --- R/rs_pipeline.R | 119 ++++++++++++++++++++++++++++++------------------ 1 file changed, 74 insertions(+), 45 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index a5ec461..b7180ff 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -2,7 +2,6 @@ #' #' @param functional Path to a functional dataset. #' @param anatomy Path to a corresponing anatomical dataset. -#' @param physfile Path to corresponding pyhsiological data. #' @param std_anat Path to standard anatomical file. #' @param std_white_matter Path to standard white matter mask. #' @param std_csf Path to standard CSF mask. @@ -17,20 +16,31 @@ rs_pipeline <- function( functional, anatomy, - physfile = NULL, std_anat, std_white_matter, std_csf, labels_img, labels_text, + magnitude_map, + phase_map, + dwell_time, + echo_spacing, + fnirt_conf, gsr = TRUE, tr = NULL, odd = NULL) { + old_scipen <- options(scipen = 200) + on.exit(options(old_scipen)) + std_anat <- normalizePath(std_anat) + std_brain <- normalizePath(std_brain) + std_hires <- normalizePath(std_hires) std_white_matter <- normalizePath(std_white_matter) std_csf <- normalizePath(std_csf) labels_img <- normalizePath(labels_img) labels_text <- normalizePath(labels_text) + mag_path <- normalizePath(magnitude_map) + pha_path <- normalizePath(phase_map) if (!is.null(physfile)) { input_files <- normalizePath(c(functional, anatomy, physfile)) @@ -39,54 +49,82 @@ rs_pipeline <- function( } input_dir <- dirname(functional) - print("Standardising orientation...") - ori_func <- rsfmri::fsl_reorient2std(input_files[1]) - ori_anat <- rsfmri::fsl_reorient2std(input_files[2]) + print_msg <- function(txt) { + print(paste(date(), txt)) + } + + print_msg("Standardising orientation...") + ori_func <- rsfmri::fsl_reorient2std(functional) + ori_anat <- rsfmri::fsl_reorient2std(anatomy) - print("Skull stripping...") + print_msg("Skull stripping...") skull_stripped <- rsfmri::skull_stripping(ori_func, anatomy = ori_anat) - print("Co-registering functional to standard...") - normalise <- rsfmri::register_functonal_to_standard( - skull_stripped[1], anatfile = skull_stripped[2], - standard = std_anat) + print_msg("Correcting motion...") + motion_cor <- rsfmri::fsl_mcflirt(ori_func) + motion_file <- paste0(motion_cor, ".par") - print("Extracting WM and CSF time course...") - wm_timecourse <- rsfmri::fsl_meants(normalise[1], + motion_check <- check_motion(parfile = motion_file, cutoff = 1, + plot = FALSE) + to_remove <- c(1:3, motion_check$flag_motion, motion_check$flag_spike) + + if (motion_check$exceeds_motion > 3 || + motion_check$exceeds_spike > min(c(20, nrow(rs_filtered) * 0.05))) { + stop("Excessive motion.") + } + + print_msg("Segmentation...") + pve_wm <- rsfmri::fsl_fast(skull_stripped[2], smooth_extent = 10) + binary_wm <- rsfmri::fsl_maths_binary_segmentation(pve_wm) + + print_msg("Generating Field Map...") + fm <- rsfmri::fsl_make_fieldmap(mag_path, pha_path, echo_spacing) + + print_msg("EPI B0 Field Map Correction...") + epi_reg <- rsfmri::fsl_epi_reg( + motion_cor, + anatomical = ori_anat, + anatomical_brain = skull_stripped[2], + anatomical_wm_seg = binary_wm, + fmap = fm$fmap, + magnitude_map = fm$mag_norm, + magnitude_brain = fm$mag , + pedir = "-y", + dwell_time = dwell_time + ) + + print_msg("Co-registering functional to standard...") + reg <- rsfmri::register_functonal_to_standard( + functional = motion_cor, bbr_warp = epi_reg, anatfile = ori_anat, + anat_extracted = skull_stripped[2], standard = std_anat, + standard_extracted = std_brain, standard_hires = std_hires, + fnirt_config = fnirt_conf) + + print_msg("Extracting WM and CSF time course...") + wm_timecourse <- rsfmri::fsl_meants(reg, outfile = file.path(input_dir, "wmtc.txt"), maskfile = std_white_matter) - csf_timecourse <- rsfmri::fsl_meants(normalise[1], + csf_timecourse <- rsfmri::fsl_meants(reg, outfile = file.path(input_dir, "csftc.txt"), maskfile = std_csf) if (gsr) { - gs_timecourse <- rsfmri::fsl_meants(normalise[1], + gs_timecourse <- rsfmri::fsl_meants(motion_cor, outfile = file.path(input_dir, "gs.txt"), maskfile = file.path(input_dir, "mean_mask.nii.gz")) } - if (!is.null(physfile) && !is.null(tr)) { - print("Generating physiological confounds...") - tr_s <- tr / 1000 - # need to sort out the other options to be more generalisable - physio_confounds <- rsfmri::fsl_pnm( - input_files[3], normalise[1], tr = tr_s) - physio_confounds <- file.path(input_dir, physio_confounds) - } - print("Correcting motion...") - motion_cor <- rsfmri::fsl_mcflirt(normalise[1]) if (!is.null(tr) && !is.null(odd)) { - print("Correcting slice scan time...") + print_msg("Correcting slice scan time...") slice_timed <- rsfmri::fsl_slicetimer( - motion_cor[1], tr = as.character(tr), odd = odd) + reg, tr = as.character(tr), odd = odd) } else { # TODO: Make these a list or so, so we can check the last element. - slice_timed <- motion_cor + slice_timed <- reg } # Build file containing noise to "regress out". - motion_file <- paste0(motion_cor, ".par") if (gsr) { noise <- noise_file(motion_file, wm_timecourse, csf_timecourse, gs_timecourse) @@ -103,18 +141,17 @@ rs_pipeline <- function( row.names = FALSE, col.names = FALSE) # call glm to get rid of all the noise - print("Removing noise...") + print_msg("Removing noise...") if (!is.null(physfile)) { - glm_out <- rsfmri::fsl_glm(slice_timed[1], outtype = "both", + glm_out <- rsfmri::fsl_glm(reg, outtype = "both", predictors = noise_file, demean = TRUE, physio_list = physio_confounds) } else { - glm_out <- rsfmri::fsl_glm(slice_timed[1], outtype = "both", + glm_out <- rsfmri::fsl_glm(reg, outtype = "both", predictors = noise_file, demean = TRUE) } - print("Extracting AALv4 time courses") + print_msg("Extracting region time courses") labels <- rsfmri::fsl_meants(glm_out[1], label = labels_img) - print(labels[1]) rs_tc <- readr::read_table2(labels[1], col_names = FALSE) rs_tc <- rs_tc[, apply(rs_tc, 2, function(x) !(all(is.na(x))))] @@ -123,7 +160,7 @@ rs_pipeline <- function( col_names = c("no", "name"), skip = 1) colnames(rs_tc) <- info[["name"]] - print("Filtering...") + print_msg("Filtering...") bandpass <- signal::butter(2, c(0.01, 0.15), "pass") rs_filtered <- scale(apply( @@ -132,15 +169,7 @@ rs_pipeline <- function( rs_filtered <- tibble::as_tibble(rs_filtered) - print("Scrub time series...") - motion_check <- check_motion(parfile = motion_file, cutoff = 1, - plot = FALSE) - to_remove <- c(1:3, motion_check$flag_motion, motion_check$flag_spike) - - if (motion_check$exceeds_motion > 3 || - motion_check$exceeds_spike > min(c(20, nrow(rs_filtered) * 0.05))) { - stop("Excessive motion.") - } + print_msg("Scrub time series...") rs_filtered <- rs_filtered[-to_remove, ] rs_list <- list() @@ -150,13 +179,13 @@ rs_pipeline <- function( x2sym <- rlang::sym("x2") corsym <- rlang::sym("cor") - print("Correlating") + print_msg("Correlating") rs_cor <- stats::cor(rs_filtered) rs_cor <- tibble::as_tibble(rs_cor, rownames = "x1") %>% tidyr::gather(!!x2sym, !!corsym, -!!x1sym) rs_list$correlation <- rs_cor - print("Done.") + print_msg("Done.") rs_list } -- GitLab From 3f6ccaa1120d6c4bf0cb82514d1904737d51cf12 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 25 Aug 2022 14:05:44 +0200 Subject: [PATCH 02/46] Update pipeline. --- R/rs_pipeline.R | 16 +++++++--------- 1 file changed, 7 insertions(+), 9 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index b7180ff..7712840 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -76,6 +76,7 @@ rs_pipeline <- function( print_msg("Segmentation...") pve_wm <- rsfmri::fsl_fast(skull_stripped[2], smooth_extent = 10) binary_wm <- rsfmri::fsl_maths_binary_segmentation(pve_wm) + pve_basename <- gsub("_\\d.nii.gz$", "", pve_wm) print_msg("Generating Field Map...") fm <- rsfmri::fsl_make_fieldmap(mag_path, pha_path, echo_spacing) @@ -101,20 +102,17 @@ rs_pipeline <- function( fnirt_config = fnirt_conf) print_msg("Extracting WM and CSF time course...") - wm_timecourse <- rsfmri::fsl_meants(reg, - outfile = file.path(input_dir, "wmtc.txt"), - maskfile = std_white_matter) - csf_timecourse <- rsfmri::fsl_meants(reg, - outfile = file.path(input_dir, "csftc.txt"), - maskfile = std_csf) + timecourses <- rsfmri::extract_csf_and_wm( + reg, pve_basename = pve_wm, std_brain = std_anat, + anat_to_mni_warp = file.path(input_dir, "t1_to_mni_warp.nii.gz") + ) + if (gsr) { gs_timecourse <- rsfmri::fsl_meants(motion_cor, outfile = file.path(input_dir, "gs.txt"), maskfile = file.path(input_dir, "mean_mask.nii.gz")) } - - if (!is.null(tr) && !is.null(odd)) { print_msg("Correcting slice scan time...") slice_timed <- rsfmri::fsl_slicetimer( @@ -126,7 +124,7 @@ rs_pipeline <- function( # Build file containing noise to "regress out". if (gsr) { - noise <- noise_file(motion_file, wm_timecourse, csf_timecourse, + noise <- noise_file(motion_file, timecourses[1], timecourses[2], gs_timecourse) } else { -- GitLab From 8bc6d97b122dbad65965b7b486e2fac53f0d8534 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 25 Aug 2022 14:25:41 +0200 Subject: [PATCH 03/46] Fix args & paths. --- R/rs_pipeline.R | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index 7712840..3702a93 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -17,8 +17,7 @@ rs_pipeline <- function( functional, anatomy, std_anat, - std_white_matter, - std_csf, + std_brain, labels_img, labels_text, magnitude_map, @@ -32,11 +31,10 @@ rs_pipeline <- function( old_scipen <- options(scipen = 200) on.exit(options(old_scipen)) + functional <- normalizePath(functional) + anatomy <- normalizePath(anatomy) std_anat <- normalizePath(std_anat) std_brain <- normalizePath(std_brain) - std_hires <- normalizePath(std_hires) - std_white_matter <- normalizePath(std_white_matter) - std_csf <- normalizePath(std_csf) labels_img <- normalizePath(labels_img) labels_text <- normalizePath(labels_text) mag_path <- normalizePath(magnitude_map) -- GitLab From 78de84fe5dcbfcb31864a2bc991310a48f9c80d4 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 25 Aug 2022 14:28:01 +0200 Subject: [PATCH 04/46] Remove rests of physfile. --- R/rs_pipeline.R | 18 +++++------------- 1 file changed, 5 insertions(+), 13 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index 3702a93..d83f1cd 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -40,11 +40,8 @@ rs_pipeline <- function( mag_path <- normalizePath(magnitude_map) pha_path <- normalizePath(phase_map) - if (!is.null(physfile)) { - input_files <- normalizePath(c(functional, anatomy, physfile)) - } else { - input_files <- normalizePath(c(functional, anatomy)) - } + + input_files <- normalizePath(c(functional, anatomy)) input_dir <- dirname(functional) print_msg <- function(txt) { @@ -138,14 +135,9 @@ rs_pipeline <- function( # call glm to get rid of all the noise print_msg("Removing noise...") - if (!is.null(physfile)) { - glm_out <- rsfmri::fsl_glm(reg, outtype = "both", - predictors = noise_file, demean = TRUE, - physio_list = physio_confounds) - } else { - glm_out <- rsfmri::fsl_glm(reg, outtype = "both", - predictors = noise_file, demean = TRUE) - } + glm_out <- rsfmri::fsl_glm(reg, outtype = "both", + predictors = noise_file, demean = TRUE) + print_msg("Extracting region time courses") labels <- rsfmri::fsl_meants(glm_out[1], label = labels_img) -- GitLab From b6882e9a8dd5d975293c744da75d405549b48503 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 25 Aug 2022 14:38:50 +0200 Subject: [PATCH 05/46] Refer to correct object. --- R/rs_pipeline.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index d83f1cd..49e5588 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -64,7 +64,7 @@ rs_pipeline <- function( to_remove <- c(1:3, motion_check$flag_motion, motion_check$flag_spike) if (motion_check$exceeds_motion > 3 || - motion_check$exceeds_spike > min(c(20, nrow(rs_filtered) * 0.05))) { + motion_check$exceeds_spike > min(c(20, nrow(motion_check$data) * 0.05))) { stop("Excessive motion.") } -- GitLab From 8f4fad2f33d9fefe627086903ac3e2874a1d57a3 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 25 Aug 2022 16:03:44 +0200 Subject: [PATCH 06/46] Remove unnused arg. --- R/rs_pipeline.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index 49e5588..12bc15a 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -93,7 +93,7 @@ rs_pipeline <- function( reg <- rsfmri::register_functonal_to_standard( functional = motion_cor, bbr_warp = epi_reg, anatfile = ori_anat, anat_extracted = skull_stripped[2], standard = std_anat, - standard_extracted = std_brain, standard_hires = std_hires, + standard_extracted = std_brain, fnirt_config = fnirt_conf) print_msg("Extracting WM and CSF time course...") -- GitLab From 28490c80d29849228505eb0fa405fcb317ccffff Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Fri, 26 Aug 2022 07:28:52 +0200 Subject: [PATCH 07/46] Fix noise file building, --- R/rs_pipeline.R | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index 12bc15a..f1a7dd8 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -120,10 +120,11 @@ rs_pipeline <- function( # Build file containing noise to "regress out". if (gsr) { noise <- noise_file(motion_file, timecourses[1], timecourses[2], - gs_timecourse) + gs_timecourse, first_deriv = TRUE, + second_deriv = TRUE, square = FALSE) } else { - noise <- noise_file(motion_file, wm_timecourse, csf_timecourse, + noise <- noise_file(motion_file, timecourses[1], timecourses[2], first_deriv = TRUE, second_deriv = TRUE, square = FALSE) } -- GitLab From 70fff4c106aee61f2d6cb62cb4409f2c01445fbf Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Fri, 26 Aug 2022 07:31:56 +0200 Subject: [PATCH 08/46] Fix PVE name. --- R/rs_pipeline.R | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index f1a7dd8..c9121ba 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -97,8 +97,9 @@ rs_pipeline <- function( fnirt_config = fnirt_conf) print_msg("Extracting WM and CSF time course...") + pve_use <- gsub("_\\d.nii.gz$", "", pve_wm) timecourses <- rsfmri::extract_csf_and_wm( - reg, pve_basename = pve_wm, std_brain = std_anat, + reg, pve_basename = pve_use, std_brain = std_anat, anat_to_mni_warp = file.path(input_dir, "t1_to_mni_warp.nii.gz") ) -- GitLab From 5e515321c862119a0edc47a633c47b3b8ecb9e15 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Fri, 26 Aug 2022 08:40:12 +0200 Subject: [PATCH 09/46] Fix handling of column names. --- R/rs_pipeline.R | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index c9121ba..70e2d02 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -146,9 +146,11 @@ rs_pipeline <- function( rs_tc <- readr::read_table2(labels[1], col_names = FALSE) rs_tc <- rs_tc[, apply(rs_tc, 2, function(x) !(all(is.na(x))))] - info <- readr::read_table(labels_text, - col_names = c("no", "name"), skip = 1) - colnames(rs_tc) <- info[["name"]] + info <- readr::read_table(labels_text, col_names = c("no", "name")) + colnames(rs_tc)[info$no] <- info$name + null_cols <- apply(rs_tc, 2, function(x) all(x == 0)) + rs_tc[null_cols] <- NULL + print_msg("Filtering...") bandpass <- signal::butter(2, c(0.01, 0.15), "pass") -- GitLab From 98470f7ac838d8e7ba3eab1749dc398e7c039799 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Fri, 26 Aug 2022 13:00:17 +0200 Subject: [PATCH 10/46] Update pipeline. * Fix docs. * Make it tidy up after itself. --- R/rs_pipeline.R | 67 +++++++++++++++++++++++++++++++--------------- man/rs_pipeline.Rd | 27 ++++++++++++------- 2 files changed, 63 insertions(+), 31 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index 70e2d02..f498aa8 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -1,12 +1,16 @@ #' Run a complete resting-state fMRI pipeline. #' #' @param functional Path to a functional dataset. -#' @param anatomy Path to a corresponing anatomical dataset. +#' @param anatomy Path to a corresponding anatomical dataset. #' @param std_anat Path to standard anatomical file. -#' @param std_white_matter Path to standard white matter mask. -#' @param std_csf Path to standard CSF mask. +#' @param std_brain Path to skull stripped standard file. #' @param labels_img Path to atlas image. #' @param labels_text Path to atlas label info file. +#' @param magnitude_map Path to magnitude B0 map. +#' @param phase_map Path to phase B0 map. +#' @param dwell_time Dwell time in s. +#' @param echo_spacing Echo spacing time in ms. +#' @param fnirt_conf Name of the FSL fnirt config file to use. #' @param gsr Boolean whether to use global signal regression. #' @param tr The TR of the data im ms. #' @param odd Bool indicating whether slices were acquired interleaved. @@ -32,17 +36,31 @@ rs_pipeline <- function( on.exit(options(old_scipen)) functional <- normalizePath(functional) - anatomy <- normalizePath(anatomy) + input_dir <- dirname(functional) + temp_name <- paste0("proc", as.numeric(Sys.time())) + temp_dir <- file.path(input_dir, temp_name) + dir.create(temp_dir) + + copy_to_temp <- function(in_file, temp_dir) { + old_path <- normalizePath(in_file) + base <- basename(in_file) + new <- file.path(temp_dir, base) + copy_success <- file.copy(old_path, new) + if (!copy_success) { + stop("could not copy") + } + new + } + + functional <- copy_to_temp(functional, temp_dir) + anatomy <- copy_to_temp(anatomy, temp_dir) + mag_path <- copy_to_temp(magnitude_map, temp_dir) + pha_path <- copy_to_temp(phase_map, temp_dir) + std_anat <- normalizePath(std_anat) std_brain <- normalizePath(std_brain) labels_img <- normalizePath(labels_img) labels_text <- normalizePath(labels_text) - mag_path <- normalizePath(magnitude_map) - pha_path <- normalizePath(phase_map) - - - input_files <- normalizePath(c(functional, anatomy)) - input_dir <- dirname(functional) print_msg <- function(txt) { print(paste(date(), txt)) @@ -64,14 +82,14 @@ rs_pipeline <- function( to_remove <- c(1:3, motion_check$flag_motion, motion_check$flag_spike) if (motion_check$exceeds_motion > 3 || - motion_check$exceeds_spike > min(c(20, nrow(motion_check$data) * 0.05))) { + motion_check$exceeds_spike > min( + c(20, nrow(motion_check$data) * 0.05))) { stop("Excessive motion.") } print_msg("Segmentation...") pve_wm <- rsfmri::fsl_fast(skull_stripped[2], smooth_extent = 10) binary_wm <- rsfmri::fsl_maths_binary_segmentation(pve_wm) - pve_basename <- gsub("_\\d.nii.gz$", "", pve_wm) print_msg("Generating Field Map...") fm <- rsfmri::fsl_make_fieldmap(mag_path, pha_path, echo_spacing) @@ -84,7 +102,7 @@ rs_pipeline <- function( anatomical_wm_seg = binary_wm, fmap = fm$fmap, magnitude_map = fm$mag_norm, - magnitude_brain = fm$mag , + magnitude_brain = fm$mag, pedir = "-y", dwell_time = dwell_time ) @@ -100,13 +118,13 @@ rs_pipeline <- function( pve_use <- gsub("_\\d.nii.gz$", "", pve_wm) timecourses <- rsfmri::extract_csf_and_wm( reg, pve_basename = pve_use, std_brain = std_anat, - anat_to_mni_warp = file.path(input_dir, "t1_to_mni_warp.nii.gz") + anat_to_mni_warp = file.path(temp_dir, "t1_to_mni_warp.nii.gz") ) if (gsr) { gs_timecourse <- rsfmri::fsl_meants(motion_cor, - outfile = file.path(input_dir, "gs.txt"), - maskfile = file.path(input_dir, "mean_mask.nii.gz")) + outfile = file.path(temp_dir, "gs.txt"), + maskfile = file.path(temp_dir, "mean_mask.nii.gz")) } if (!is.null(tr) && !is.null(odd)) { @@ -131,14 +149,14 @@ rs_pipeline <- function( } noise <- tibble::as_tibble(noise) - noise_file <- file.path(input_dir, "noise.txt") - utils::write.table(noise, file = file.path(input_dir, "noise.txt"), + noise_file <- file.path(temp_dir, "noise.txt") + utils::write.table(noise, file = file.path(temp_dir, "noise.txt"), row.names = FALSE, col.names = FALSE) # call glm to get rid of all the noise print_msg("Removing noise...") - glm_out <- rsfmri::fsl_glm(reg, outtype = "both", - predictors = noise_file, demean = TRUE) + glm_out <- rsfmri::fsl_glm(slice_timed, outtype = "both", + predictors = noise_file, demean = TRUE) print_msg("Extracting region time courses") labels <- rsfmri::fsl_meants(glm_out[1], label = labels_img) @@ -151,7 +169,6 @@ rs_pipeline <- function( null_cols <- apply(rs_tc, 2, function(x) all(x == 0)) rs_tc[null_cols] <- NULL - print_msg("Filtering...") bandpass <- signal::butter(2, c(0.01, 0.15), "pass") @@ -171,13 +188,19 @@ rs_pipeline <- function( x2sym <- rlang::sym("x2") corsym <- rlang::sym("cor") - print_msg("Correlating") + print_msg("Correlating...") rs_cor <- stats::cor(rs_filtered) rs_cor <- tibble::as_tibble(rs_cor, rownames = "x1") %>% tidyr::gather(!!x2sym, !!corsym, -!!x1sym) rs_list$correlation <- rs_cor + print_msg("Tidying up...") + file.copy(rs_tc, input_dir) + file.copy(glm_out[1], input_dir) + file.copy(motion_file, input_dir) + unlink(temp_dir, recursive = TRUE) + print_msg("Done.") rs_list } diff --git a/man/rs_pipeline.Rd b/man/rs_pipeline.Rd index 96d7ce9..ef09cd7 100644 --- a/man/rs_pipeline.Rd +++ b/man/rs_pipeline.Rd @@ -7,12 +7,15 @@ rs_pipeline( functional, anatomy, - physfile = NULL, std_anat, - std_white_matter, - std_csf, + std_brain, labels_img, labels_text, + magnitude_map, + phase_map, + dwell_time, + echo_spacing, + fnirt_conf, gsr = TRUE, tr = NULL, odd = NULL @@ -21,20 +24,26 @@ rs_pipeline( \arguments{ \item{functional}{Path to a functional dataset.} -\item{anatomy}{Path to a corresponing anatomical dataset.} - -\item{physfile}{Path to corresponding pyhsiological data.} +\item{anatomy}{Path to a corresponding anatomical dataset.} \item{std_anat}{Path to standard anatomical file.} -\item{std_white_matter}{Path to standard white matter mask.} - -\item{std_csf}{Path to standard CSF mask.} +\item{std_brain}{Path to skull stripped standard file.} \item{labels_img}{Path to atlas image.} \item{labels_text}{Path to atlas label info file.} +\item{magnitude_map}{Path to magnitude B0 map.} + +\item{phase_map}{Path to phase B0 map.} + +\item{dwell_time}{Dwell time in s.} + +\item{echo_spacing}{Echo spacing time in ms.} + +\item{fnirt_conf}{Name of the FSL fnirt config file to use.} + \item{gsr}{Boolean whether to use global signal regression.} \item{tr}{The TR of the data im ms.} -- GitLab From a6206c1135e7b9c5a12290aa6c922095ab76dc55 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Fri, 26 Aug 2022 14:03:08 +0200 Subject: [PATCH 11/46] Fix copying. --- R/rs_pipeline.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index f498aa8..2d7ee57 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -196,7 +196,7 @@ rs_pipeline <- function( rs_list$correlation <- rs_cor print_msg("Tidying up...") - file.copy(rs_tc, input_dir) + file.copy(labels[1], input_dir) file.copy(glm_out[1], input_dir) file.copy(motion_file, input_dir) unlink(temp_dir, recursive = TRUE) -- GitLab From 5e5801461f6180c70d54eb6798a3847fba3fdf40 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 28 Sep 2022 12:44:58 +0200 Subject: [PATCH 12/46] Return more Bayesian statistics. --- R/compare_measure_group.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/compare_measure_group.R b/R/compare_measure_group.R index 6fd54d6..4bb2b10 100644 --- a/R/compare_measure_group.R +++ b/R/compare_measure_group.R @@ -40,7 +40,7 @@ compare_measure_group <- function(rawlist, dv, ..., add_name = FALSE, dplyr::mutate(s.value = -log2(.data$p.value)) bayes <- rstanarm::stan_glm(frml, data = grplist, iter = 2000, refresh = 0) - bayes_tbl <- parameters::parameters(bayes) + bayes_tbl <- parameters::parameters(bayes, test = "all") list(lm = mod, lm_tbl = modtbl, anova = av, anova_tbl = tbl, -- GitLab From 86f1e06d4c4f9de4d0f530f10f756ba4b32ac4d9 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 28 Sep 2022 12:45:30 +0200 Subject: [PATCH 13/46] Update pipeline, so... * fieldmaps are optional * intermediate files can be kept --- R/rs_pipeline.R | 90 +++++++++++++++++++++++++++++++------------------ 1 file changed, 58 insertions(+), 32 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index 2d7ee57..e24226c 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -14,6 +14,8 @@ #' @param gsr Boolean whether to use global signal regression. #' @param tr The TR of the data im ms. #' @param odd Bool indicating whether slices were acquired interleaved. +#' @param keep_intermediate Should itermediate files be kept on disk? This is +#' useful for debugging. #' #' @return A list containing time courses and a pairwise correlation matrix. #' @export @@ -24,14 +26,15 @@ rs_pipeline <- function( std_brain, labels_img, labels_text, - magnitude_map, - phase_map, - dwell_time, - echo_spacing, + magnitude_map = NULL, + phase_map = NULL, + dwell_time = NULL, + echo_spacing = NULL, fnirt_conf, gsr = TRUE, tr = NULL, - odd = NULL) { + odd = NULL, + keep_intermediate = FALSE) { old_scipen <- options(scipen = 200) on.exit(options(old_scipen)) @@ -54,8 +57,11 @@ rs_pipeline <- function( functional <- copy_to_temp(functional, temp_dir) anatomy <- copy_to_temp(anatomy, temp_dir) - mag_path <- copy_to_temp(magnitude_map, temp_dir) - pha_path <- copy_to_temp(phase_map, temp_dir) + + if (!is.null(magnitude_map) | !is.null(phase_map)) { + mag_path <- copy_to_temp(magnitude_map, temp_dir) + pha_path <- copy_to_temp(phase_map, temp_dir) + } std_anat <- normalizePath(std_anat) std_brain <- normalizePath(std_brain) @@ -74,8 +80,9 @@ rs_pipeline <- function( skull_stripped <- rsfmri::skull_stripping(ori_func, anatomy = ori_anat) print_msg("Correcting motion...") - motion_cor <- rsfmri::fsl_mcflirt(ori_func) - motion_file <- paste0(motion_cor, ".par") + motion_cor <- rsfmri::fsl_mcflirt(ori_func, meanvol = TRUE) + mean_motion_reg <- gsub(".nii.gz", "_mean_reg.nii.gz", motion_cor) + motion_file <- gsub(".nii.gz", ".par", motion_cor) motion_check <- check_motion(parfile = motion_file, cutoff = 1, plot = FALSE) @@ -91,28 +98,45 @@ rs_pipeline <- function( pve_wm <- rsfmri::fsl_fast(skull_stripped[2], smooth_extent = 10) binary_wm <- rsfmri::fsl_maths_binary_segmentation(pve_wm) - print_msg("Generating Field Map...") - fm <- rsfmri::fsl_make_fieldmap(mag_path, pha_path, echo_spacing) - - print_msg("EPI B0 Field Map Correction...") - epi_reg <- rsfmri::fsl_epi_reg( - motion_cor, - anatomical = ori_anat, - anatomical_brain = skull_stripped[2], - anatomical_wm_seg = binary_wm, - fmap = fm$fmap, - magnitude_map = fm$mag_norm, - magnitude_brain = fm$mag, - pedir = "-y", - dwell_time = dwell_time - ) - - print_msg("Co-registering functional to standard...") - reg <- rsfmri::register_functonal_to_standard( - functional = motion_cor, bbr_warp = epi_reg, anatfile = ori_anat, - anat_extracted = skull_stripped[2], standard = std_anat, - standard_extracted = std_brain, - fnirt_config = fnirt_conf) + if (!is.null(magnitude_map) | !is.null(phase_map)) { + print_msg("Generating Field Map...") + fm <- rsfmri::fsl_make_fieldmap(mag_path, pha_path, echo_spacing) + + print_msg("EPI B0 Field Map Correction...") + epi_reg <- rsfmri::fsl_epi_reg( + mean_motion_reg, + anatomical = ori_anat, + anatomical_brain = skull_stripped[2], + anatomical_wm_seg = binary_wm, + fmap = fm$fmap, + magnitude_map = fm$mag_norm, + magnitude_brain = fm$mag, + pedir = "-y", + dwell_time = dwell_time + ) + + print_msg("Co-registering functional to standard...") + reg <- rsfmri::register_functonal_to_standard( + functional = motion_cor, bbr_warp = epi_reg, anatfile = ori_anat, + anat_extracted = skull_stripped[2], standard = std_anat, + standard_extracted = std_brain, + fnirt_config = fnirt_conf) + } else { + print_msg("Co-registering functional to standard (1/2)...") + epi_reg <- rsfmri::fsl_epi_reg( + motion_cor, + anatomical = ori_anat, + anatomical_brain = skull_stripped[2], + anatomical_wm_seg = binary_wm + ) + + print_msg("Co-registering functional to standard (2/2)...") + reg <- rsfmri::register_functonal_to_standard( + functional = motion_cor, anatfile = ori_anat, + anat_extracted = skull_stripped[2], standard = std_anat, + standard_extracted = std_brain, + fnirt_config = fnirt_conf) + } print_msg("Extracting WM and CSF time course...") pve_use <- gsub("_\\d.nii.gz$", "", pve_wm) @@ -199,7 +223,9 @@ rs_pipeline <- function( file.copy(labels[1], input_dir) file.copy(glm_out[1], input_dir) file.copy(motion_file, input_dir) - unlink(temp_dir, recursive = TRUE) + if (!keep_intermediate) { + unlink(temp_dir, recursive = TRUE) + } print_msg("Done.") rs_list -- GitLab From 2c0e701253712bf08b2f5f3eb2d27fc98245d4d5 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 28 Sep 2022 13:06:39 +0200 Subject: [PATCH 14/46] Try fixing parameters. --- R/compare_measure_group.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/compare_measure_group.R b/R/compare_measure_group.R index 4bb2b10..19b89cf 100644 --- a/R/compare_measure_group.R +++ b/R/compare_measure_group.R @@ -40,7 +40,7 @@ compare_measure_group <- function(rawlist, dv, ..., add_name = FALSE, dplyr::mutate(s.value = -log2(.data$p.value)) bayes <- rstanarm::stan_glm(frml, data = grplist, iter = 2000, refresh = 0) - bayes_tbl <- parameters::parameters(bayes, test = "all") + bayes_tbl <- parameters::model_parameters(bayes, test = "all") list(lm = mod, lm_tbl = modtbl, anova = av, anova_tbl = tbl, -- GitLab From 5a91bcb2116f9297c621098e880d7cd98e588641 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 28 Sep 2022 13:52:56 +0200 Subject: [PATCH 15/46] Fix params for real. --- R/compare_measure_group.R | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/R/compare_measure_group.R b/R/compare_measure_group.R index 19b89cf..d3e1f66 100644 --- a/R/compare_measure_group.R +++ b/R/compare_measure_group.R @@ -40,7 +40,8 @@ compare_measure_group <- function(rawlist, dv, ..., add_name = FALSE, dplyr::mutate(s.value = -log2(.data$p.value)) bayes <- rstanarm::stan_glm(frml, data = grplist, iter = 2000, refresh = 0) - bayes_tbl <- parameters::model_parameters(bayes, test = "all") + bayes_tbl <- parameters::model_parameters(bayes, + test = c("pd", "rope", "bf")) list(lm = mod, lm_tbl = modtbl, anova = av, anova_tbl = tbl, -- GitLab From 8d31c84947352a36509e537e1b1e5a3083c81b13 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Fri, 30 Sep 2022 10:56:40 +0200 Subject: [PATCH 16/46] Add scaling option to rspipeline. --- R/rs_pipeline.R | 8 ++++++++ man/rs_pipeline.Rd | 18 +++++++++++++----- 2 files changed, 21 insertions(+), 5 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index e24226c..6096c14 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -14,6 +14,8 @@ #' @param gsr Boolean whether to use global signal regression. #' @param tr The TR of the data im ms. #' @param odd Bool indicating whether slices were acquired interleaved. +#' @param scale_anat_to Optional value to scale the anatomical image resolution +#' to. #' @param keep_intermediate Should itermediate files be kept on disk? This is #' useful for debugging. #' @@ -34,6 +36,7 @@ rs_pipeline <- function( gsr = TRUE, tr = NULL, odd = NULL, + scale_anat_to = NULL, keep_intermediate = FALSE) { old_scipen <- options(scipen = 200) on.exit(options(old_scipen)) @@ -76,6 +79,11 @@ rs_pipeline <- function( ori_func <- rsfmri::fsl_reorient2std(functional) ori_anat <- rsfmri::fsl_reorient2std(anatomy) + if (!is.null(scale_anat_to)) { + print_msg("Rescaling anatomical data") + ori_anat <- rsfmri::rescale_image(ori_anat, res = 2) + } + print_msg("Skull stripping...") skull_stripped <- rsfmri::skull_stripping(ori_func, anatomy = ori_anat) diff --git a/man/rs_pipeline.Rd b/man/rs_pipeline.Rd index ef09cd7..16d4258 100644 --- a/man/rs_pipeline.Rd +++ b/man/rs_pipeline.Rd @@ -11,14 +11,16 @@ rs_pipeline( std_brain, labels_img, labels_text, - magnitude_map, - phase_map, - dwell_time, - echo_spacing, + magnitude_map = NULL, + phase_map = NULL, + dwell_time = NULL, + echo_spacing = NULL, fnirt_conf, gsr = TRUE, tr = NULL, - odd = NULL + odd = NULL, + scale_anat_to = NULL, + keep_intermediate = FALSE ) } \arguments{ @@ -49,6 +51,12 @@ rs_pipeline( \item{tr}{The TR of the data im ms.} \item{odd}{Bool indicating whether slices were acquired interleaved.} + +\item{scale_anat_to}{Optional value to scale the anatomical image resolution +to.} + +\item{keep_intermediate}{Should itermediate files be kept on disk? This is +useful for debugging.} } \value{ A list containing time courses and a pairwise correlation matrix. -- GitLab From 359c9bcaa7aa01ca4429e315344dc5ab43102ded Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 12 Oct 2022 09:25:08 +0200 Subject: [PATCH 17/46] Fix pipeline. --- R/rs_pipeline.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index 6096c14..fce0efc 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -140,7 +140,7 @@ rs_pipeline <- function( print_msg("Co-registering functional to standard (2/2)...") reg <- rsfmri::register_functonal_to_standard( - functional = motion_cor, anatfile = ori_anat, + functional = epi_reg, anatfile = ori_anat, anat_extracted = skull_stripped[2], standard = std_anat, standard_extracted = std_brain, fnirt_config = fnirt_conf) -- GitLab From 82a0db56297f1923280991aff326c04626559845 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Tue, 25 Oct 2022 14:08:50 +0200 Subject: [PATCH 18/46] Include AP/PA way of fieldmap generation. --- R/rs_pipeline.R | 23 +++++++++++++++++++++-- 1 file changed, 21 insertions(+), 2 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index fce0efc..2ae1361 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -31,6 +31,9 @@ rs_pipeline <- function( magnitude_map = NULL, phase_map = NULL, dwell_time = NULL, + ap_map = NULL, + pa_map = NULL, + readout_time = NULL, echo_spacing = NULL, fnirt_conf, gsr = TRUE, @@ -66,6 +69,11 @@ rs_pipeline <- function( pha_path <- copy_to_temp(phase_map, temp_dir) } + if (!is.null(ap_map) | !is.null(pa_map)) { + ap_path <- copy_to_temp(ap_map, temp_dir) + pa_path <- copy_to_temp(pa_path, temp_dir) + } + std_anat <- normalizePath(std_anat) std_brain <- normalizePath(std_brain) labels_img <- normalizePath(labels_img) @@ -106,9 +114,20 @@ rs_pipeline <- function( pve_wm <- rsfmri::fsl_fast(skull_stripped[2], smooth_extent = 10) binary_wm <- rsfmri::fsl_maths_binary_segmentation(pve_wm) - if (!is.null(magnitude_map) | !is.null(phase_map)) { + map_mag_pha <- all(c(!is.null(magnitude_map), !is.null(phase_map))) + map_ap_pa <- all(c(!is.null(ap_path), !is.null(pa_path))) + + if (map_mag_pha & mag_ap_pa) { + stop("Either use Mag/Pha map or AP/PA, not both.") + } + + if (mag_mag_pha | mag_ap_pa) { print_msg("Generating Field Map...") - fm <- rsfmri::fsl_make_fieldmap(mag_path, pha_path, echo_spacing) + if (mag_mag_pha) { + fm <- rsfmri::fsl_make_fieldmap(mag_path, pha_path, echo_spacing) + } else if (mag_ap_pa) { + fm <- rsfmri::fsl_make_fieldmap_pe(ap_map, pa_map, readout_time) + } print_msg("EPI B0 Field Map Correction...") epi_reg <- rsfmri::fsl_epi_reg( -- GitLab From dac8eb27140cc34685f7a70e1e106cd4782909a5 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Tue, 25 Oct 2022 15:44:48 +0200 Subject: [PATCH 19/46] fix --- R/rs_pipeline.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index 2ae1361..35447b8 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -71,7 +71,7 @@ rs_pipeline <- function( if (!is.null(ap_map) | !is.null(pa_map)) { ap_path <- copy_to_temp(ap_map, temp_dir) - pa_path <- copy_to_temp(pa_path, temp_dir) + pa_path <- copy_to_temp(pa_map, temp_dir) } std_anat <- normalizePath(std_anat) -- GitLab From 69ad2f3ca1ee8adb393ab71faa5f3b3b3bb34eb4 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Tue, 25 Oct 2022 16:08:53 +0200 Subject: [PATCH 20/46] fix --- R/rs_pipeline.R | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index 35447b8..cdf644c 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -117,15 +117,15 @@ rs_pipeline <- function( map_mag_pha <- all(c(!is.null(magnitude_map), !is.null(phase_map))) map_ap_pa <- all(c(!is.null(ap_path), !is.null(pa_path))) - if (map_mag_pha & mag_ap_pa) { + if (map_mag_pha & map_ap_pa) { stop("Either use Mag/Pha map or AP/PA, not both.") } - if (mag_mag_pha | mag_ap_pa) { + if (mag_mag_pha | map_ap_pa) { print_msg("Generating Field Map...") if (mag_mag_pha) { fm <- rsfmri::fsl_make_fieldmap(mag_path, pha_path, echo_spacing) - } else if (mag_ap_pa) { + } else if (map_ap_pa) { fm <- rsfmri::fsl_make_fieldmap_pe(ap_map, pa_map, readout_time) } -- GitLab From f53434464034d879cc0021cf9d5a9b48623b0fe4 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Tue, 25 Oct 2022 16:41:21 +0200 Subject: [PATCH 21/46] fix again --- R/rs_pipeline.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index cdf644c..414be56 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -121,9 +121,9 @@ rs_pipeline <- function( stop("Either use Mag/Pha map or AP/PA, not both.") } - if (mag_mag_pha | map_ap_pa) { + if (map_mag_pha | map_ap_pa) { print_msg("Generating Field Map...") - if (mag_mag_pha) { + if (map_mag_pha) { fm <- rsfmri::fsl_make_fieldmap(mag_path, pha_path, echo_spacing) } else if (map_ap_pa) { fm <- rsfmri::fsl_make_fieldmap_pe(ap_map, pa_map, readout_time) -- GitLab From 5e49bc255e1f7ad1979f596435e98ce8e1c0cd41 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 26 Oct 2022 08:14:49 +0200 Subject: [PATCH 22/46] Fix fieldmap generation. --- R/rs_pipeline.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index 414be56..60df303 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -126,7 +126,7 @@ rs_pipeline <- function( if (map_mag_pha) { fm <- rsfmri::fsl_make_fieldmap(mag_path, pha_path, echo_spacing) } else if (map_ap_pa) { - fm <- rsfmri::fsl_make_fieldmap_pe(ap_map, pa_map, readout_time) + fm <- rsfmri::fsl_make_fieldmap_pe(ap_path, pa_path, readout_time) } print_msg("EPI B0 Field Map Correction...") -- GitLab From a9240d8457e4875a83da08f00d69d953ed63d66e Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Fri, 28 Oct 2022 13:07:09 +0200 Subject: [PATCH 23/46] Make motion cutoff an option. --- R/rs_pipeline.R | 7 ++++++- man/rs_pipeline.Rd | 12 ++++++++++++ 2 files changed, 18 insertions(+), 1 deletion(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index 60df303..f35581c 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -9,6 +9,9 @@ #' @param magnitude_map Path to magnitude B0 map. #' @param phase_map Path to phase B0 map. #' @param dwell_time Dwell time in s. +#' @param ap_map Phase map in AP direction. +#' @param pa_map Phase map in PA direction. +#' @param readout_time Readout time for AP/PA fieldmaps. #' @param echo_spacing Echo spacing time in ms. #' @param fnirt_conf Name of the FSL fnirt config file to use. #' @param gsr Boolean whether to use global signal regression. @@ -16,6 +19,7 @@ #' @param odd Bool indicating whether slices were acquired interleaved. #' @param scale_anat_to Optional value to scale the anatomical image resolution #' to. +#' @param motion_cutoff Motion correction cutoff value in deg/mm. #' @param keep_intermediate Should itermediate files be kept on disk? This is #' useful for debugging. #' @@ -40,6 +44,7 @@ rs_pipeline <- function( tr = NULL, odd = NULL, scale_anat_to = NULL, + motion_cutoff = 1, keep_intermediate = FALSE) { old_scipen <- options(scipen = 200) on.exit(options(old_scipen)) @@ -100,7 +105,7 @@ rs_pipeline <- function( mean_motion_reg <- gsub(".nii.gz", "_mean_reg.nii.gz", motion_cor) motion_file <- gsub(".nii.gz", ".par", motion_cor) - motion_check <- check_motion(parfile = motion_file, cutoff = 1, + motion_check <- check_motion(parfile = motion_file, cutoff = motion_cutoff, plot = FALSE) to_remove <- c(1:3, motion_check$flag_motion, motion_check$flag_spike) diff --git a/man/rs_pipeline.Rd b/man/rs_pipeline.Rd index 16d4258..5d7de31 100644 --- a/man/rs_pipeline.Rd +++ b/man/rs_pipeline.Rd @@ -14,12 +14,16 @@ rs_pipeline( magnitude_map = NULL, phase_map = NULL, dwell_time = NULL, + ap_map = NULL, + pa_map = NULL, + readout_time = NULL, echo_spacing = NULL, fnirt_conf, gsr = TRUE, tr = NULL, odd = NULL, scale_anat_to = NULL, + motion_cutoff = 1, keep_intermediate = FALSE ) } @@ -42,6 +46,12 @@ rs_pipeline( \item{dwell_time}{Dwell time in s.} +\item{ap_map}{Phase map in AP direction.} + +\item{pa_map}{Phase map in PA direction.} + +\item{readout_time}{Readout time for AP/PA fieldmaps.} + \item{echo_spacing}{Echo spacing time in ms.} \item{fnirt_conf}{Name of the FSL fnirt config file to use.} @@ -55,6 +65,8 @@ rs_pipeline( \item{scale_anat_to}{Optional value to scale the anatomical image resolution to.} +\item{motion_cutoff}{Motion correction cutoff value in deg/mm.} + \item{keep_intermediate}{Should itermediate files be kept on disk? This is useful for debugging.} } -- GitLab From 8ede9f227db240ec5f7ccaaedf5ab461a3a50615 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Fri, 28 Oct 2022 13:49:39 +0200 Subject: [PATCH 24/46] Add defaults for optional paths. --- R/rs_pipeline.R | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index f35581c..d4ea45d 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -69,11 +69,15 @@ rs_pipeline <- function( functional <- copy_to_temp(functional, temp_dir) anatomy <- copy_to_temp(anatomy, temp_dir) + mag_path <- NULL + pha_path <- NULL if (!is.null(magnitude_map) | !is.null(phase_map)) { mag_path <- copy_to_temp(magnitude_map, temp_dir) pha_path <- copy_to_temp(phase_map, temp_dir) } + ap_path <- NULL + pa_path <- NULL if (!is.null(ap_map) | !is.null(pa_map)) { ap_path <- copy_to_temp(ap_map, temp_dir) pa_path <- copy_to_temp(pa_map, temp_dir) -- GitLab From f6b8bdb4e679237fc0b380bb12542441a29d2a60 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 10 Nov 2022 16:50:06 +0100 Subject: [PATCH 25/46] Fix bug in motion correction. --- R/check_motion.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/check_motion.R b/R/check_motion.R index 76f1d73..306c2df 100644 --- a/R/check_motion.R +++ b/R/check_motion.R @@ -58,7 +58,7 @@ check_motion <- function(rawdir = NULL, pattern = NULL, parfile = NULL, spikes <- apply(motion_data, 2, cdiff) - spikes[4:6] <- 100 * pi * spikes[4:6] / 360 + spikes[, 1:3] <- 100 * pi * spikes[, 1:3] / 360 has_spike <- rowSums(abs(spikes)) > 0.5 motion_data <- motion_data |> -- GitLab From eabf6ad766e54fa0f07cfcf4dc37f618399618b3 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 10 Nov 2022 17:36:19 +0100 Subject: [PATCH 26/46] Fix spike detection and change defaults. --- R/check_motion.R | 2 +- R/rs_pipeline.R | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/R/check_motion.R b/R/check_motion.R index 306c2df..a881816 100644 --- a/R/check_motion.R +++ b/R/check_motion.R @@ -59,7 +59,7 @@ check_motion <- function(rawdir = NULL, pattern = NULL, parfile = NULL, spikes <- apply(motion_data, 2, cdiff) spikes[, 1:3] <- 100 * pi * spikes[, 1:3] / 360 - has_spike <- rowSums(abs(spikes)) > 0.5 + has_spike <- rowSums(abs(spikes)) > spike_cutoff motion_data <- motion_data |> dplyr::mutate( diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index d4ea45d..37217d0 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -110,7 +110,7 @@ rs_pipeline <- function( motion_file <- gsub(".nii.gz", ".par", motion_cor) motion_check <- check_motion(parfile = motion_file, cutoff = motion_cutoff, - plot = FALSE) + spike_cutoff = 1.5, plot = FALSE) to_remove <- c(1:3, motion_check$flag_motion, motion_check$flag_spike) if (motion_check$exceeds_motion > 3 || -- GitLab From c6639ffcd802407518dde5ec45b64745450fb076 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 16 Nov 2022 14:42:08 +0100 Subject: [PATCH 27/46] Add dots to basic summary. --- R/basic_summary.R | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/R/basic_summary.R b/R/basic_summary.R index 76b3c40..b34840c 100644 --- a/R/basic_summary.R +++ b/R/basic_summary.R @@ -8,6 +8,7 @@ #' @param whole_graph If measure characterises for the entire graph, #' this should be set to true. #' @param outname Name for the grouping variable in the output. +#' @param ... Further variables to group by. #' #' If no measure is given the data is grouped by groups in the subjects #' table. @@ -18,13 +19,13 @@ #' @export basic_summary <- function(datalist, subjects, id_var, group_var, measure = NULL, whole_graph = FALSE, - outname = "group") { + outname = "group", ...) { split_tbls <- split_graph_list(datalist, subjects) gsym <- rlang::sym(outname) groups <- subjects %>% dplyr::rename({{ outname }} := {{ group_var }}) %>% - dplyr::group_by({{ gsym }}) %>% + dplyr::group_by({{ gsym }}, ...) %>% dplyr::group_keys() if (whole_graph) { -- GitLab From 085857f79acaa39e6363f596b3ff535ad7a2c4d5 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 16 Nov 2022 16:05:14 +0100 Subject: [PATCH 28/46] Revert "Add dots to basic summary." This reverts commit c6639ffcd802407518dde5ec45b64745450fb076 --- R/basic_summary.R | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/R/basic_summary.R b/R/basic_summary.R index b34840c..76b3c40 100644 --- a/R/basic_summary.R +++ b/R/basic_summary.R @@ -8,7 +8,6 @@ #' @param whole_graph If measure characterises for the entire graph, #' this should be set to true. #' @param outname Name for the grouping variable in the output. -#' @param ... Further variables to group by. #' #' If no measure is given the data is grouped by groups in the subjects #' table. @@ -19,13 +18,13 @@ #' @export basic_summary <- function(datalist, subjects, id_var, group_var, measure = NULL, whole_graph = FALSE, - outname = "group", ...) { + outname = "group") { split_tbls <- split_graph_list(datalist, subjects) gsym <- rlang::sym(outname) groups <- subjects %>% dplyr::rename({{ outname }} := {{ group_var }}) %>% - dplyr::group_by({{ gsym }}, ...) %>% + dplyr::group_by({{ gsym }}) %>% dplyr::group_keys() if (whole_graph) { -- GitLab From 4f43f4cfb06d5ce5459e83d41fdec2df5941cfb0 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Fri, 18 Nov 2022 09:07:47 +0100 Subject: [PATCH 29/46] Handle spike removal in a better way. --- R/rs_pipeline.R | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index 37217d0..b09013f 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -111,7 +111,6 @@ rs_pipeline <- function( motion_check <- check_motion(parfile = motion_file, cutoff = motion_cutoff, spike_cutoff = 1.5, plot = FALSE) - to_remove <- c(1:3, motion_check$flag_motion, motion_check$flag_spike) if (motion_check$exceeds_motion > 3 || motion_check$exceeds_spike > min( @@ -239,7 +238,8 @@ rs_pipeline <- function( rs_filtered <- tibble::as_tibble(rs_filtered) print_msg("Scrub time series...") - rs_filtered <- rs_filtered[-to_remove, ] + rs_filtered[c(motion_check$flag_motion, motion_check$flag_spike)] <- NA_real_ + rs_filtered <- rs_filtered[-c(1:3), ] rs_list <- list() rs_list$time_course <- rs_filtered @@ -249,7 +249,7 @@ rs_pipeline <- function( corsym <- rlang::sym("cor") print_msg("Correlating...") - rs_cor <- stats::cor(rs_filtered) + rs_cor <- stats::cor(rs_filtered, use = "complete.obs") rs_cor <- tibble::as_tibble(rs_cor, rownames = "x1") %>% tidyr::gather(!!x2sym, !!corsym, -!!x1sym) -- GitLab From 1b8353f452a9265d450a69433f7f13a565cef8b7 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 30 Nov 2022 15:17:10 +0100 Subject: [PATCH 30/46] reformat. --- R/compare_measure_group.R | 53 +++++++++++++++++++-------------------- 1 file changed, 26 insertions(+), 27 deletions(-) diff --git a/R/compare_measure_group.R b/R/compare_measure_group.R index d3e1f66..4142925 100644 --- a/R/compare_measure_group.R +++ b/R/compare_measure_group.R @@ -9,41 +9,40 @@ #' @export compare_measure_group <- function(rawlist, dv, ..., add_name = FALSE, remove = NULL) { - grplist <- lapply(seq_along(rawlist), - function(x) { - rawlist[[x]]$group <- names(rawlist)[x] - rawlist[[x]] - }) - grplist <- do.call("rbind", grplist) + grplist <- lapply(seq_along(rawlist), function(x) { + rawlist[[x]]$group <- names(rawlist)[x] + rawlist[[x]] + }) + grplist <- do.call("rbind", grplist) - if (!is.null(remove)) { - grplist <- grplist %>% dplyr::filter(.data$group != remove) - } + if (!is.null(remove)) { + grplist <- grplist %>% dplyr::filter(.data$group != remove) + } - additional_formula <- paste(..., sep = "+") - additional_formula <- ifelse(length(additional_formula) == 0, "", - paste0("+", additional_formula)) + additional_formula <- paste(..., sep = "+") + additional_formula <- ifelse(length(additional_formula) == 0, "", + paste0("+", additional_formula)) - if (add_name) { - frml <- stats::as.formula(paste(dv, "~ group * name", additional_formula)) - } else { - frml <- stats::as.formula(paste(dv, " ~ group", additional_formula)) - } - mod <- stats::lm(frml, data = grplist) - modtbl <- mod %>% - broom::tidy() %>% - dplyr::mutate(s.value = -log2(.data$p.value)) + if (add_name) { + frml <- stats::as.formula(paste(dv, "~ group * name", additional_formula)) + } else { + frml <- stats::as.formula(paste(dv, " ~ group", additional_formula)) + } + mod <- stats::lm(frml, data = grplist) + modtbl <- mod %>% + broom::tidy() %>% + dplyr::mutate(s.value = -log2(.data$p.value)) av <- car::Anova(mod, type = 3) tbl <- av %>% broom::tidy() %>% dplyr::mutate(s.value = -log2(.data$p.value)) - bayes <- rstanarm::stan_glm(frml, data = grplist, iter = 2000, refresh = 0) - bayes_tbl <- parameters::model_parameters(bayes, - test = c("pd", "rope", "bf")) + bayes <- rstanarm::stan_glm(frml, data = grplist, iter = 2000, refresh = 0) + bayes_tbl <- parameters::model_parameters( + bayes, test = c("pd", "rope", "bf")) - list(lm = mod, lm_tbl = modtbl, - anova = av, anova_tbl = tbl, - bayesian = bayes, bayesian_tbl = bayes_tbl) + list(lm = mod, lm_tbl = modtbl, + anova = av, anova_tbl = tbl, + bayesian = bayes, bayesian_tbl = bayes_tbl) } -- GitLab From 75cf08b03bc7ab3ab7de92441d129d58693d4aca Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 30 Nov 2022 15:17:19 +0100 Subject: [PATCH 31/46] make anova optional. --- R/compare_measure_group.R | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/R/compare_measure_group.R b/R/compare_measure_group.R index 4142925..3dfb8b9 100644 --- a/R/compare_measure_group.R +++ b/R/compare_measure_group.R @@ -33,10 +33,15 @@ compare_measure_group <- function(rawlist, dv, ..., add_name = FALSE, broom::tidy() %>% dplyr::mutate(s.value = -log2(.data$p.value)) - av <- car::Anova(mod, type = 3) - tbl <- av %>% - broom::tidy() %>% - dplyr::mutate(s.value = -log2(.data$p.value)) + if (anova) { + av <- car::Anova(mod, type = 3) + tbl <- av %>% + broom::tidy() %>% + dplyr::mutate(s.value = -log2(.data$p.value)) + } else { + av <- NA + tbl <- NA + } bayes <- rstanarm::stan_glm(frml, data = grplist, iter = 2000, refresh = 0) bayes_tbl <- parameters::model_parameters( -- GitLab From 6ffcfc4ac00462111ff571897b4c8fc8c9b1cc0a Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 30 Nov 2022 15:52:42 +0100 Subject: [PATCH 32/46] Update remotes. --- DESCRIPTION | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index f6d0a92..16f2e3e 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -41,6 +41,6 @@ Suggests: withr Remotes: gitlab::choh/littlehelpers, - gitlab::choh/rsfmri + git::https://git.rwth-aachen.de/christian.hohenfeld/rsfmri.git Depends: R (>= 2.10) -- GitLab From e72c32d1395f0ace129bad4669ae7bd6579fd266 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Wed, 30 Nov 2022 15:54:27 +0100 Subject: [PATCH 33/46] Make ANOVA actually optional. --- R/compare_measure_group.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/compare_measure_group.R b/R/compare_measure_group.R index 3dfb8b9..0a5363e 100644 --- a/R/compare_measure_group.R +++ b/R/compare_measure_group.R @@ -8,7 +8,7 @@ #' @importFrom rlang .data #' @export compare_measure_group <- function(rawlist, dv, ..., add_name = FALSE, - remove = NULL) { + remove = NULL, anova = TRUE) { grplist <- lapply(seq_along(rawlist), function(x) { rawlist[[x]]$group <- names(rawlist)[x] rawlist[[x]] -- GitLab From cba6a3dccca708f1e9ce92124a7d99bf7193fc7c Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 12:19:44 +0100 Subject: [PATCH 34/46] Fix CI --- .gitlab-ci.yml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/.gitlab-ci.yml b/.gitlab-ci.yml index beb6c1e..7bee86f 100644 --- a/.gitlab-ci.yml +++ b/.gitlab-ci.yml @@ -6,7 +6,7 @@ stages: before_script: - apt-get update - - apt-get --yes install libglpk-dev + - apt-get --yes install libglpk-dev libicu-dev - mkdir -p rlib - echo 'R_LIBS="rlib"' > .Renviron - echo 'R_LIBS_USER="rlib"' >> .Renviron @@ -14,7 +14,7 @@ before_script: cache: key: r-library - paths: + paths: - rlib prep: -- GitLab From d879a82eb4d6353e5ae45c8d442cfde4347d1170 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 12:33:56 +0100 Subject: [PATCH 35/46] Try installing stringr manually. --- .gitlab-ci.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitlab-ci.yml b/.gitlab-ci.yml index 7bee86f..ebb6b9d 100644 --- a/.gitlab-ci.yml +++ b/.gitlab-ci.yml @@ -21,7 +21,7 @@ prep: stage: .pre script: - R --version - - R -e "install.packages(c('devtools', 'usethis'))" + - R -e "install.packages(c('devtools', 'usethis', 'stringr'))" - R -e "devtools::install_gitlab('choh/littlehelpers')" - R -e "devtools::install_gitlab('choh/rsfmri')" - R -e "devtools::install_deps(dependencies = TRUE)" -- GitLab From 63c3299efbd290284687c4ba8a44986bf86e45a4 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 12:41:52 +0100 Subject: [PATCH 36/46] Try forcing source installation. --- .gitlab-ci.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitlab-ci.yml b/.gitlab-ci.yml index ebb6b9d..9c3dea4 100644 --- a/.gitlab-ci.yml +++ b/.gitlab-ci.yml @@ -21,7 +21,7 @@ prep: stage: .pre script: - R --version - - R -e "install.packages(c('devtools', 'usethis', 'stringr'))" + - R -e "install.packages(c('devtools', 'usethis'), type = 'source')" - R -e "devtools::install_gitlab('choh/littlehelpers')" - R -e "devtools::install_gitlab('choh/rsfmri')" - R -e "devtools::install_deps(dependencies = TRUE)" -- GitLab From 740cdfa664822fc9e8c677e365e76948071e70df Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 12:55:49 +0100 Subject: [PATCH 37/46] try forcing source repo. --- .gitlab-ci.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitlab-ci.yml b/.gitlab-ci.yml index 9c3dea4..716976c 100644 --- a/.gitlab-ci.yml +++ b/.gitlab-ci.yml @@ -21,7 +21,7 @@ prep: stage: .pre script: - R --version - - R -e "install.packages(c('devtools', 'usethis'), type = 'source')" + - R -e "install.packages(c('devtools', 'usethis'), type = 'source', repos = 'https://cran.uni-muenster.de/')" - R -e "devtools::install_gitlab('choh/littlehelpers')" - R -e "devtools::install_gitlab('choh/rsfmri')" - R -e "devtools::install_deps(dependencies = TRUE)" -- GitLab From bc88d1691f9736ce116c7e3c89fb34b6b5e46d83 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 13:03:52 +0100 Subject: [PATCH 38/46] Update .gitlab-ci.yml --- .gitlab-ci.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitlab-ci.yml b/.gitlab-ci.yml index 716976c..66f9014 100644 --- a/.gitlab-ci.yml +++ b/.gitlab-ci.yml @@ -21,7 +21,7 @@ prep: stage: .pre script: - R --version - - R -e "install.packages(c('devtools', 'usethis'), type = 'source', repos = 'https://cran.uni-muenster.de/')" + - R -e "install.packages(c('devtools', 'usethis', 'stringr'), type = 'source', repos = 'https://cran.uni-muenster.de/')" - R -e "devtools::install_gitlab('choh/littlehelpers')" - R -e "devtools::install_gitlab('choh/rsfmri')" - R -e "devtools::install_deps(dependencies = TRUE)" -- GitLab From e148bbdfd1931c576ca63d47a0c5197d65f5f9f4 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 13:10:39 +0100 Subject: [PATCH 39/46] Update .gitlab-ci.yml --- .gitlab-ci.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitlab-ci.yml b/.gitlab-ci.yml index 66f9014..6ef0241 100644 --- a/.gitlab-ci.yml +++ b/.gitlab-ci.yml @@ -21,7 +21,7 @@ prep: stage: .pre script: - R --version - - R -e "install.packages(c('devtools', 'usethis', 'stringr'), type = 'source', repos = 'https://cran.uni-muenster.de/')" + - R -e "install.packages(c('stringi', 'devtools', 'usethis', 'stringr'), type = 'source', repos = 'https://cran.uni-muenster.de/')" - R -e "devtools::install_gitlab('choh/littlehelpers')" - R -e "devtools::install_gitlab('choh/rsfmri')" - R -e "devtools::install_deps(dependencies = TRUE)" -- GitLab From b5e5e541ca746b9d163e8a3c788bc20c9740db60 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 13:14:53 +0100 Subject: [PATCH 40/46] Update .gitlab-ci.yml --- .gitlab-ci.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitlab-ci.yml b/.gitlab-ci.yml index 6ef0241..22aa3cb 100644 --- a/.gitlab-ci.yml +++ b/.gitlab-ci.yml @@ -23,7 +23,7 @@ prep: - R --version - R -e "install.packages(c('stringi', 'devtools', 'usethis', 'stringr'), type = 'source', repos = 'https://cran.uni-muenster.de/')" - R -e "devtools::install_gitlab('choh/littlehelpers')" - - R -e "devtools::install_gitlab('choh/rsfmri')" + - R -e "devtools::install_git('https://git.rwth-aachen.de/christian.hohenfeld/rsfmri.git')" - R -e "devtools::install_deps(dependencies = TRUE)" - R -e "devtools::install()" -- GitLab From 860bbc3182fb27c46d020ea7924bff7c3a2aa8a8 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 13:20:53 +0100 Subject: [PATCH 41/46] Update .gitlab-ci.yml --- .gitlab-ci.yml | 1 - 1 file changed, 1 deletion(-) diff --git a/.gitlab-ci.yml b/.gitlab-ci.yml index 22aa3cb..f633ba7 100644 --- a/.gitlab-ci.yml +++ b/.gitlab-ci.yml @@ -24,7 +24,6 @@ prep: - R -e "install.packages(c('stringi', 'devtools', 'usethis', 'stringr'), type = 'source', repos = 'https://cran.uni-muenster.de/')" - R -e "devtools::install_gitlab('choh/littlehelpers')" - R -e "devtools::install_git('https://git.rwth-aachen.de/christian.hohenfeld/rsfmri.git')" - - R -e "devtools::install_deps(dependencies = TRUE)" - R -e "devtools::install()" lintr: -- GitLab From 3030447bcf167fdd70adb7b3884d3b2386772b33 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 13:35:29 +0100 Subject: [PATCH 42/46] Update .gitlab-ci.yml --- .gitlab-ci.yml | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/.gitlab-ci.yml b/.gitlab-ci.yml index f633ba7..078d973 100644 --- a/.gitlab-ci.yml +++ b/.gitlab-ci.yml @@ -21,9 +21,9 @@ prep: stage: .pre script: - R --version - - R -e "install.packages(c('stringi', 'devtools', 'usethis', 'stringr'), type = 'source', repos = 'https://cran.uni-muenster.de/')" - - R -e "devtools::install_gitlab('choh/littlehelpers')" - - R -e "devtools::install_git('https://git.rwth-aachen.de/christian.hohenfeld/rsfmri.git')" + - R -e "install.packages(c('remotes', 'stringi', 'devtools', 'usethis', 'stringr'), type = 'source', repos = 'https://cran.uni-muenster.de/')" + - R -e "remotes::install_gitlab('choh/littlehelpers')" + - R -e "remotes::install_git('https://git.rwth-aachen.de/christian.hohenfeld/rsfmri.git')" - R -e "devtools::install()" lintr: -- GitLab From 3d22bccbbc2f73724d047328dabf34c74d9f896c Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 13:57:24 +0100 Subject: [PATCH 43/46] Update .gitlab-ci.yml file --- .gitlab-ci.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitlab-ci.yml b/.gitlab-ci.yml index 078d973..8c03b2c 100644 --- a/.gitlab-ci.yml +++ b/.gitlab-ci.yml @@ -21,7 +21,7 @@ prep: stage: .pre script: - R --version - - R -e "install.packages(c('remotes', 'stringi', 'devtools', 'usethis', 'stringr'), type = 'source', repos = 'https://cran.uni-muenster.de/')" + - R -e "install.packages(c('remotes', 'stringi', 'devtools', 'usethis', 'stringr', 'lintr'), type = 'source', repos = 'https://cran.uni-muenster.de/')" - R -e "remotes::install_gitlab('choh/littlehelpers')" - R -e "remotes::install_git('https://git.rwth-aachen.de/christian.hohenfeld/rsfmri.git')" - R -e "devtools::install()" -- GitLab From 92e9d9acfb767bd9e6d7df0671246b97bfc75585 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 14:32:19 +0100 Subject: [PATCH 44/46] Handle linter errors --- R/compare_measure_group.R | 3 ++- R/rs_pipeline.R | 13 ++++++++----- 2 files changed, 10 insertions(+), 6 deletions(-) diff --git a/R/compare_measure_group.R b/R/compare_measure_group.R index 0a5363e..808ce1b 100644 --- a/R/compare_measure_group.R +++ b/R/compare_measure_group.R @@ -24,7 +24,8 @@ compare_measure_group <- function(rawlist, dv, ..., add_name = FALSE, paste0("+", additional_formula)) if (add_name) { - frml <- stats::as.formula(paste(dv, "~ group * name", additional_formula)) + frml <- stats::as.formula( + paste(dv, "~ group * name", additional_formula)) } else { frml <- stats::as.formula(paste(dv, " ~ group", additional_formula)) } diff --git a/R/rs_pipeline.R b/R/rs_pipeline.R index b09013f..1eacfc2 100644 --- a/R/rs_pipeline.R +++ b/R/rs_pipeline.R @@ -25,6 +25,7 @@ #' #' @return A list containing time courses and a pairwise correlation matrix. #' @export +# nolint start: cyclocomp_linter rs_pipeline <- function( functional, anatomy, @@ -71,14 +72,14 @@ rs_pipeline <- function( mag_path <- NULL pha_path <- NULL - if (!is.null(magnitude_map) | !is.null(phase_map)) { + if (!is.null(magnitude_map) || !is.null(phase_map)) { mag_path <- copy_to_temp(magnitude_map, temp_dir) pha_path <- copy_to_temp(phase_map, temp_dir) } ap_path <- NULL pa_path <- NULL - if (!is.null(ap_map) | !is.null(pa_map)) { + if (!is.null(ap_map) || !is.null(pa_map)) { ap_path <- copy_to_temp(ap_map, temp_dir) pa_path <- copy_to_temp(pa_map, temp_dir) } @@ -125,11 +126,11 @@ rs_pipeline <- function( map_mag_pha <- all(c(!is.null(magnitude_map), !is.null(phase_map))) map_ap_pa <- all(c(!is.null(ap_path), !is.null(pa_path))) - if (map_mag_pha & map_ap_pa) { + if (map_mag_pha && map_ap_pa) { stop("Either use Mag/Pha map or AP/PA, not both.") } - if (map_mag_pha | map_ap_pa) { + if (map_mag_pha || map_ap_pa) { print_msg("Generating Field Map...") if (map_mag_pha) { fm <- rsfmri::fsl_make_fieldmap(mag_path, pha_path, echo_spacing) @@ -238,7 +239,8 @@ rs_pipeline <- function( rs_filtered <- tibble::as_tibble(rs_filtered) print_msg("Scrub time series...") - rs_filtered[c(motion_check$flag_motion, motion_check$flag_spike)] <- NA_real_ + rs_filtered[c( + motion_check$flag_motion, motion_check$flag_spike)] <- NA_real_ rs_filtered <- rs_filtered[-c(1:3), ] rs_list <- list() @@ -266,3 +268,4 @@ rs_pipeline <- function( print_msg("Done.") rs_list } +# nolint end -- GitLab From 6f369f33fb8e5d0f89ca3326cec6ceeaecec3ff5 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 14:32:26 +0100 Subject: [PATCH 45/46] Update docs. --- R/compare_measure_group.R | 1 + man/compare_measure_group.Rd | 11 ++++++++++- 2 files changed, 11 insertions(+), 1 deletion(-) diff --git a/R/compare_measure_group.R b/R/compare_measure_group.R index 808ce1b..2a23b3b 100644 --- a/R/compare_measure_group.R +++ b/R/compare_measure_group.R @@ -5,6 +5,7 @@ #' @param ... Strings giving variables to include in the model formula. #' @param add_name Whether to add interaction term group x name, default FALSE #' @param remove Name of a group to remove +#' @param anova Logical value specifying whether to compute an ANOVA. #' @importFrom rlang .data #' @export compare_measure_group <- function(rawlist, dv, ..., add_name = FALSE, diff --git a/man/compare_measure_group.Rd b/man/compare_measure_group.Rd index 4e2ca80..51aa314 100644 --- a/man/compare_measure_group.Rd +++ b/man/compare_measure_group.Rd @@ -4,7 +4,14 @@ \alias{compare_measure_group} \title{Compare a measure between groups.} \usage{ -compare_measure_group(rawlist, dv, ..., add_name = FALSE, remove = NULL) +compare_measure_group( + rawlist, + dv, + ..., + add_name = FALSE, + remove = NULL, + anova = TRUE +) } \arguments{ \item{rawlist}{A list of graphs split by groups.} @@ -16,6 +23,8 @@ compare_measure_group(rawlist, dv, ..., add_name = FALSE, remove = NULL) \item{add_name}{Whether to add interaction term group x name, default FALSE} \item{remove}{Name of a group to remove} + +\item{anova}{Logical value specifying whether to compute an ANOVA.} } \description{ Compare a measure between groups. -- GitLab From 9f26a7afe7f635192ff42ff22fa73ad2572e1ce7 Mon Sep 17 00:00:00 2001 From: Christian Hohenfeld Date: Thu, 1 Dec 2022 15:12:47 +0100 Subject: [PATCH 46/46] Bump version number. --- DESCRIPTION | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 16f2e3e..ee79766 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: rsAnalysis Title: High-Level Tools for rsfMRI analysis -Version: 0.4.5.9000 +Version: 0.4.6 Authors@R: person(given = "Christian", family = "Hohenfeld", -- GitLab