Skip to content

Commit

Permalink
Merge pull request #63 from ANTsX/JayParc
Browse files Browse the repository at this point in the history
ENH:  Add Jay STPT parcellation.
  • Loading branch information
ntustison authored May 30, 2024
2 parents 2ca9c26 + 913bf3e commit df2faf0
Show file tree
Hide file tree
Showing 3 changed files with 42 additions and 16 deletions.
8 changes: 6 additions & 2 deletions R/getANTsXNetData.R
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,9 @@ getANTsXNetData <- function(
"bsplineT2MouseTemplate",
"bsplineT2MouseTemplateBrainMask",
"DevCCF_P56_MRI_T2_50um",
"DevCCF_P56_MRI_T2_50um_BrainParcellationNickMask"
"DevCCF_P56_MRI_T2_50um_BrainParcellationNickMask",
"DevCCF_P04_STPT_50um",
"DevCCF_P04_STPT_50um_BrainParcellationJayMask"
),
targetFileName, antsxnetCacheDirectory = NULL )
{
Expand Down Expand Up @@ -106,7 +108,9 @@ getANTsXNetData <- function(
bsplineT2MouseTemplate = "https://figshare.com/ndownloader/files/44706247",
bsplineT2MouseTemplateBrainMask = "https://figshare.com/ndownloader/files/44869285",
DevCCF_P56_MRI_T2_50um = "https://figshare.com/ndownloader/files/44706244",
DevCCF_P56_MRI_T2_50um_BrainParcellationNickMask = "https://figshare.com/ndownloader/files/44706238"
DevCCF_P56_MRI_T2_50um_BrainParcellationNickMask = "https://figshare.com/ndownloader/files/44706238",
DevCCF_P04_STPT_50um = "https://figshare.com/ndownloader/files/46711546",
DevCCF_P04_STPT_50um_BrainParcellationJayMask = "https://figshare.com/ndownloader/files/46712656"
)

if( missing( targetFileName ) )
Expand Down
4 changes: 3 additions & 1 deletion R/getPretrainedNetwork.R
Original file line number Diff line number Diff line change
Expand Up @@ -110,6 +110,7 @@ getPretrainedNetwork <- function(
"mouseMriBrainExtraction",
"mouseT2wBrainExtraction3D",
"mouseT2wBrainParcellation3DNick",
"mouseSTPTBrainParcellation3DJay",
"protonLungMri",
"protonLobes",
"pulmonaryArteryWeights",
Expand Down Expand Up @@ -234,7 +235,8 @@ getPretrainedNetwork <- function(
mraVesselWeights_160 = "https://figshare.com/ndownloader/files/46406029",
mouseMriBrainExtraction = "https://figshare.com/ndownloader/files/44714947",
mouseT2wBrainExtraction3D = "https://figshare.com/ndownloader/files/44943715",
mouseT2wBrainParcellation3DNick = "https://figshare.com/ndownloader/files/44714944",
mouseT2wBrainParcellation3DNick = "https://figshare.com/ndownloader/files/44714944",
mouseSTPTBrainParcellation3DJay = "https://figshare.com/ndownloader/files/46710592",
protonLungMri = "https://ndownloader.figshare.com/files/13606799",
protonLobes = "https://figshare.com/ndownloader/files/30678455",
pulmonaryAirwayWeights = "https://figshare.com/ndownloader/files/45187168",
Expand Down
46 changes: 33 additions & 13 deletions R/mouse.R
Original file line number Diff line number Diff line change
Expand Up @@ -131,22 +131,35 @@ mouseBrainExtraction <- function( image,
#' @export
mouseBrainParcellation <- function( image,
mask = NULL, returnIsotropicOutput = FALSE,
whichParcellation = c( "nick" ),
whichParcellation = c( "nick", "jay" ),
antsxnetCacheDirectory = NULL, verbose = FALSE )
{

if( whichParcellation == "nick" )
if( whichParcellation == "nick" || whichParcellation == "jay" )
{
templateSpacing <- c( 0.075, 0.075, 0.075 )
templateCropSize <- c( 176, 176, 176 )

template <- antsImageRead( getANTsXNetData( "DevCCF_P56_MRI_T2_50um" ) )
if( whichParcellation == "nick" )
{
templateString <- "DevCCF P56 T2w"
template <- antsImageRead( getANTsXNetData( "DevCCF_P56_MRI_T2_50um" ) )
templateMatch <- rankIntensity( template )
templateMask <- antsImageRead( getANTsXNetData( "DevCCF_P56_MRI_T2_50um_BrainParcellationNickMask" ) )
weightsFileName <- getPretrainedNetwork( "mouseT2wBrainParcellation3DNick" )
} else if( whichParcellation == "jay" ) {
templateString <- "DevCCF P04 STPT"
template <- antsImageRead( getANTsXNetData( "DevCCF_P04_STPT_50um" ) )
templateMatch <- histogramEqualizeImage( template )
templateMask <- antsImageRead( getANTsXNetData( "DevCCF_P04_STPT_50um_BrainParcellationJayMask" ) )
weightsFileName <- getPretrainedNetwork( "mouseSTPTBrainParcellation3DJay" )
}
templateMatch <- (( templateMatch - ANTsR::min( templateMatch ) ) /
( ANTsR::max( templateMatch ) - ANTsR::min( templateMatch ) ))

antsSetSpacing( template, c( 0.05, 0.05, 0.05 ) )
template <- resampleImage( template, templateSpacing, useVoxels = FALSE, interpType = 4 )
template <- padOrCropImageToSize( template, templateCropSize )
templateRi <- rankIntensity( template )

templateMask <- antsImageRead( getANTsXNetData( "DevCCF_P56_MRI_T2_50um_BrainParcellationNickMask" ) )
antsSetSpacing( templateMask, c( 0.05, 0.05, 0.05 ) )
templateMask <- resampleImage( templateMask, templateSpacing, useVoxels = FALSE, interpType = 1 )
templateMask <- padOrCropImageToSize( templateMask, templateCropSize )
Expand All @@ -159,7 +172,7 @@ mouseBrainParcellation <- function( image,
singleLabel <- thresholdImage( templateMask, i, i, 1, 0 )
prior <- smoothImage( singleLabel, sigma = 0.003, sigmaInPhysicalCoordinates = TRUE )
templatePriors[[i]] <- prior
}
}

if( is.null( mask ) )
{
Expand All @@ -179,13 +192,21 @@ mouseBrainParcellation <- function( image,

if ( verbose )
{
message( "Preprocessing: Warping to DevCCF P56 T2w mouse template." )
message( paste0( "Preprocessing: Warping to ", templateString, " mouse template." ) )
}

reg <- antsRegistration( template, imageBrain, typeofTransform = "antsRegistrationSyNQuick[a]", verbose = verbose )
reg <- antsRegistration( template, imageBrain,
typeofTransform = "antsRegistrationSyNQuick[a]",
verbose = verbose )

imageWarped <- rankIntensity( reg$warpedmovout )
imageWarped <- histogramMatchImage( imageWarped, templateRi )
imageWarped <- NULL
if ( whichParcellation == "nick" )
{
imageWarped <- rankIntensity( reg$warpedmovout )
} else {
imageWarped <- antsImageClone( reg$warpedmovout )
}
imageWarped <- histogramMatchImage( imageWarped, templateMatch )
imageWarped <- iMath( imageWarped, "Normalize" )

numberOfFilters <- c( 16, 32, 64, 128, 256 )
Expand All @@ -196,7 +217,6 @@ mouseBrainParcellation <- function( image,
numberOfOutputs = numberOfClassificationLabels, mode = "classification",
numberOfFilters = numberOfFilters,
convolutionKernelSize = 3, deconvolutionKernelSize = 2 )
weightsFileName <- getPretrainedNetwork( "mouseT2wBrainParcellation3DNick" )
unetModel$load_weights( weightsFileName )

batchX <- array( data = 0, dim = c( 1, dim( template ), channelSize ) )
Expand Down Expand Up @@ -237,7 +257,7 @@ mouseBrainParcellation <- function( image,
segmentationImage <- matrixToImages( segmentationMatrix, referenceImage * 0 + 1 )[[1]] - 1

results <- list( segmentationImage = segmentationImage,
probabilityImages = probabilityImages )
probabilityImages = probabilityImages )
return( results )
} else {
stop( "Unrecognized parcellation." )
Expand Down

0 comments on commit df2faf0

Please sign in to comment.