Skip to content

Commit

Permalink
feat: Add functionality to output the (infimum of the) excursion alon…
Browse files Browse the repository at this point in the history
…g each branch

Adds a `nodeOperator` and `nodePropertyExtractor` to output these.
  • Loading branch information
abensonca committed Oct 6, 2023
1 parent e7bca54 commit 7f2cf52
Show file tree
Hide file tree
Showing 2 changed files with 327 additions and 0 deletions.
169 changes: 169 additions & 0 deletions source/nodes.operators.excursion.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,169 @@
!! Copyright 2009, 2010, 2011, 2012, 2013, 2014, 2015, 2016, 2017, 2018,
!! 2019, 2020, 2021, 2022, 2023
!! Andrew Benson <[email protected]>
!!
!! This file is part of Galacticus.
!!
!! Galacticus is free software: you can redistribute it and/or modify
!! it under the terms of the GNU General Public License as published by
!! the Free Software Foundation, either version 3 of the License, or
!! (at your option) any later version.
!!
!! Galacticus is distributed in the hope that it will be useful,
!! but WITHOUT ANY WARRANTY; without even the implied warranty of
!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
!! GNU General Public License for more details.
!!
!! You should have received a copy of the GNU General Public License
!! along with Galacticus. If not, see <http://www.gnu.org/licenses/>.

!!{
Implements a node operator class that collects and stores the (infimum of the) excursion corresponding to the mass accretion history for each node.
!!}

use :: Cosmological_Density_Field, only : cosmologicalMassVarianceClass, criticalOverdensityClass
use :: Linear_Growth , only : linearGrowthClass
use :: Cosmology_Functions , only : cosmologyFunctionsClass

!![
<nodeOperator name="nodeOperatorExcursion">
<description>A node operator class that collects and stores the (infimum of the) excursion corresponding to the mass accretion history for each node.</description>
</nodeOperator>
!!]
type, extends(nodeOperatorClass) :: nodeOperatorExcursion
!!{
A node operator class that collects and stores the mass accretion history of each node.
!!}
private
class (cosmologyFunctionsClass ), pointer :: cosmologyFunctions_ => null()
class (criticalOverdensityClass ), pointer :: criticalOverdensity_ => null()
class (cosmologicalMassVarianceClass ), pointer :: cosmologicalMassVariance_ => null()
class (linearGrowthClass ), pointer :: linearGrowth_ => null()
integer :: excursionOverdensityID , excursionVarianceID
double precision :: timePresent
contains
final :: excursionDestructor
procedure :: nodeInitialize => excursionNodeInitialize
end type nodeOperatorExcursion

interface nodeOperatorExcursion
!!{
Constructors for the {\normalfont \ttfamily excursion} node operator class.
!!}
module procedure excursionConstructorParameters
module procedure excursionConstructorInternal
end interface nodeOperatorExcursion

contains

function excursionConstructorParameters(parameters) result(self)
!!{
Constructor for the {\normalfont \ttfamily excursion} node operator class which takes a parameter set as input.
!!}
use :: Input_Parameters, only : inputParameters
implicit none
type (nodeOperatorExcursion ) :: self
type (inputParameters ), intent(inout) :: parameters
class(cosmologyFunctionsClass ), pointer :: cosmologyFunctions_
class(criticalOverdensityClass ), pointer :: criticalOverdensity_
class(cosmologicalMassVarianceClass), pointer :: cosmologicalMassVariance_
class(linearGrowthClass ), pointer :: linearGrowth_

!![
<objectBuilder class="cosmologyFunctions" name="cosmologyFunctions_" source="parameters"/>
<objectBuilder class="criticalOverdensity" name="criticalOverdensity_" source="parameters"/>
<objectBuilder class="linearGrowth" name="linearGrowth_" source="parameters"/>
<objectBuilder class="cosmologicalMassVariance" name="cosmologicalMassVariance_" source="parameters"/>
!!]
self=nodeOperatorExcursion(cosmologyFunctions_,cosmologicalMassVariance_,criticalOverdensity_,linearGrowth_)
!![
<inputParametersValidate source="parameters"/>
<objectDestructor name="criticalOverdensity_" />
<objectDestructor name="cosmologyFunctions_" />
<objectDestructor name="cosmologicalMassVariance_"/>
<objectDestructor name="linearGrowth_" />
!!]
return
end function excursionConstructorParameters

function excursionConstructorInternal(cosmologyFunctions_,cosmologicalMassVariance_,criticalOverdensity_,linearGrowth_) result(self)
!!{
Internal constructor for the {\normalfont \ttfamily excursion} node operator class.
!!}
use :: Galacticus_Nodes, only : defaultBasicComponent
implicit none
type (nodeOperatorExcursion ) :: self
class(criticalOverdensityClass ), intent(in ), target :: criticalOverdensity_
class(cosmologyFunctionsClass ), intent(in ), target :: cosmologyFunctions_
class(cosmologicalMassVarianceClass), intent(in ), target :: cosmologicalMassVariance_
class(linearGrowthClass ), intent(in ), target :: linearGrowth_
!![
<constructorAssign variables="*cosmologyFunctions_, *criticalOverdensity_, *cosmologicalMassVariance_, *linearGrowth_"/>
!!]

self%timePresent=self%cosmologyFunctions_%cosmicTime(expansionFactor=1.0d0)
!![
<addMetaProperty component="basic" name="excursionTime" id="self%excursionOverdensityID" rank="1" isCreator="yes"/>
<addMetaProperty component="basic" name="excursionMass" id="self%excursionVarianceID" rank="1" isCreator="yes"/>
!!]
return
end function excursionConstructorInternal

subroutine excursionDestructor(self)
!!{
Destructor for the critical overdensity excursion set barrier class.
!!}
implicit none
type(nodeOperatorExcursion), intent(inout) :: self

!![
<objectDestructor name="self%cosmologyFunctions_" />
<objectDestructor name="self%criticalOverdensity_" />
<objectDestructor name="self%cosmologicalMassVariance_"/>
<objectDestructor name="self%linearGrowth_" />
!!]
return
end subroutine excursionDestructor

subroutine excursionNodeInitialize(self,node)
!!{
Record the mass accretion history of the node.
!!}
use :: Galacticus_Nodes, only : nodeComponentBasic
implicit none
class (nodeOperatorExcursion), intent(inout), target :: self
type (treeNode ), intent(inout), target :: node
double precision , dimension(:) , allocatable :: overdensities, variances
type (treeNode ) , pointer :: nodeWork
class (nodeComponentBasic ) , pointer :: basic
integer :: countNodes

if (associated(node%firstChild)) return
nodeWork => node
countNodes = 1
do while (nodeWork%isPrimaryProgenitor())
countNodes = countNodes +1
nodeWork => nodeWork %parent
end do
allocate(overdensities(countNodes))
allocate(variances (countNodes))
nodeWork => node
countNodes = 1
basic => nodeWork%basic()
overdensities(countNodes) = +self %criticalOverdensity_ %value (time=basic%time (),mass=basic%mass()) &
& /self %linearGrowth_ %value (time=basic%time () )
variances (countNodes) = +self %cosmologicalMassVariance_%rootVariance(time=self %timePresent ,mass=basic%mass())**2
do while (nodeWork%isPrimaryProgenitor())
countNodes = countNodes+1
nodeWork => nodeWork %parent
basic => nodeWork %basic ( )
overdensities(countNodes) = +self %criticalOverdensity_ %value (time=basic%time (),mass=basic%mass()) &
& /self %linearGrowth_ %value (time=basic%time () )
variances (countNodes) = +self %cosmologicalMassVariance_%rootVariance(time=self %timePresent ,mass=basic%mass())**2
end do
basic => node%basic()
call basic%floatRank1MetaPropertySet(self%excursionOverdensityID,overdensities)
call basic%floatRank1MetaPropertySet(self%excursionVarianceID ,variances )
return
end subroutine excursionNodeInitialize

158 changes: 158 additions & 0 deletions source/nodes.property_extractor.excursion.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,158 @@
!! Copyright 2009, 2010, 2011, 2012, 2013, 2014, 2015, 2016, 2017, 2018,
!! 2019, 2020, 2021, 2022, 2023
!! Andrew Benson <[email protected]>
!!
!! This file is part of Galacticus.
!!
!! Galacticus is free software: you can redistribute it and/or modify
!! it under the terms of the GNU General Public License as published by
!! the Free Software Foundation, either version 3 of the License, or
!! (at your option) any later version.
!!
!! Galacticus is distributed in the hope that it will be useful,
!! but WITHOUT ANY WARRANTY; without even the implied warranty of
!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
!! GNU General Public License for more details.
!!
!! You should have received a copy of the GNU General Public License
!! along with Galacticus. If not, see <http://www.gnu.org/licenses/>.

!![
<nodePropertyExtractor name="nodePropertyExtractorExcursion">
<description>
A node property extractor which extracts the (infimum of the) excursion corresponding to the mass accretion history for each node.
</description>
</nodePropertyExtractor>
!!]
type, extends(nodePropertyExtractorList) :: nodePropertyExtractorExcursion
!!{
A property extractor which extracts the (infimum of the) excursion corresponding to the mass accretion history for each node.
!!}
private
integer :: excursionOverdensityID, excursionVarianceID
contains
procedure :: elementCount => excursionElementCount
procedure :: extract => excursionExtract
procedure :: names => excursionNames
procedure :: descriptions => excursionDescriptions
procedure :: unitsInSI => excursionUnitsInSI
end type nodePropertyExtractorExcursion

interface nodePropertyExtractorExcursion
!!{
Constructors for the ``excursion'' output extractor class.
!!}
module procedure excursionConstructorParameters
module procedure excursionConstructorInternal
end interface nodePropertyExtractorExcursion

contains

function excursionConstructorParameters(parameters) result(self)
!!{
Constructor for the ``excursion'' property extractor class which takes a parameter set as input.
!!}
use :: Input_Parameters, only : inputParameter, inputParameters
implicit none
type(nodePropertyExtractorExcursion) :: self
type(inputParameters ), intent(inout) :: parameters

self=nodePropertyExtractorExcursion()
!![
<inputParametersValidate source="parameters"/>
!!]
return
end function excursionConstructorParameters

function excursionConstructorInternal() result(self)
!!{
Internal constructor for the ``excursion'' output extractor property extractor class.
!!}
implicit none
type(nodePropertyExtractorExcursion) :: self

!![
<addMetaProperty component="basic" name="excursionTime" id="self%excursionOverdensityID" rank="1" isCreator="no"/>
<addMetaProperty component="basic" name="excursionMass" id="self%excursionVarianceID" rank="1" isCreator="no"/>
!!]
return
end function excursionConstructorInternal

integer function excursionElementCount(self)
!!{
Return a count of the number of properties extracted.
!!}
implicit none
class(nodePropertyExtractorExcursion), intent(inout) :: self

excursionElementCount=2
return
end function excursionElementCount

function excursionExtract(self,node,instance) result(excursion)
!!{
Implement a excursion output extractor.
!!}
use :: Galacticus_Nodes, only : nodeComponentBasic
implicit none
double precision , dimension(:,:), allocatable :: excursion
class (nodePropertyExtractorExcursion), intent(inout) :: self
type (treeNode ), intent(inout) :: node
type (multiCounter ), intent(inout) , optional :: instance
class (nodeComponentBasic ) , pointer :: basic
double precision , dimension(: ), allocatable :: overdensities, variances
!$GLC attributes unused :: instance
!$GLC attributes initialized :: overdensities, variances

basic => node %basic ( )
overdensities = basic%floatRank1MetaPropertyGet(self%excursionOverdensityID)
variances = basic%floatRank1MetaPropertyGet(self%excursionVarianceID )
allocate(excursion(size(overdensities),2))
excursion(:,1)=overdensities
excursion(:,2)=variances
return
end function excursionExtract

subroutine excursionNames(self,names)
!!{
Return the names of the {\normalfont \ttfamily excursion} properties.
!!}
implicit none
class(nodePropertyExtractorExcursion), intent(inout) :: self
type (varying_string ), intent(inout), dimension(:) , allocatable :: names
!$GLC attributes unused :: self

allocate(names(2))
names(1)=var_str('haloExcursionOverdensity')
names(2)=var_str('haloExcursionVariance' )
return
end subroutine excursionNames

subroutine excursionDescriptions(self,descriptions)
!!{
Return the descriptions of the {\normalfont \ttfamily excursion} properties.
!!}
implicit none
class(nodePropertyExtractorExcursion), intent(inout) :: self
type (varying_string ), intent(inout), dimension(:) , allocatable :: descriptions
!$GLC attributes unused :: self

allocate(descriptions(2))
descriptions(1)=var_str("The overdensity in the infimum of the halo's excursion.")
descriptions(2)=var_str("The variance in the infimum of the halo's excursion." )
return
end subroutine excursionDescriptions

function excursionUnitsInSI(self) result(unitsInSI)
!!{
Return the units of the {\normalfont \ttfamily excursion} properties in the SI system.
!!}
implicit none
double precision , dimension(:) , allocatable :: unitsInSI
class (nodePropertyExtractorExcursion), intent(inout) :: self
!$GLC attributes unused :: self

allocate(unitsInSI(2))
unitsInSI=1.0d0
return
end function excursionUnitsInSI

0 comments on commit 7f2cf52

Please sign in to comment.