Skip to content

Commit

Permalink
Merge branch 'CambridgeNuclear:main' into main
Browse files Browse the repository at this point in the history
  • Loading branch information
valeriaRaffuzzi authored Dec 12, 2023
2 parents 2deb8cf + 7a5c199 commit 5909f3f
Show file tree
Hide file tree
Showing 35 changed files with 1,251 additions and 190 deletions.
8 changes: 6 additions & 2 deletions .readthedocs.yaml
Original file line number Diff line number Diff line change
@@ -1,10 +1,14 @@

version: 2

build:
os: ubuntu-22.04
tools:
python: "3.11"

sphinx:
configuration: docs/conf.py

python:
version: 3.7
install:
- requirements: docs/requirements-rtd.txt
- requirements: docs/requirements-rtd.txt
Original file line number Diff line number Diff line change
Expand Up @@ -120,7 +120,7 @@ subroutine collide(self, p, tally ,thisCycle, nextCycle)
! Note: the ordering must not be changed between feeding the particle to the tally
! and updating the particle's preCollision state, otherwise this may cause certain
! tallies (e.g., collisionProbability) to return dubious results
call tally % reportInColl(p)
call tally % reportInColl(p, .false.)
call p % savePreCollision()

! Choose collision nuclide and general type (Scatter, Capture or Fission)
Expand Down Expand Up @@ -154,6 +154,9 @@ subroutine collide(self, p, tally ,thisCycle, nextCycle)
! Apply post collision implicit treatments
call self % cutoffs(p, collDat, thisCycle, nextCycle)

! Update particle collision counter
p % collisionN = p % collisionN + 1

! Report out-of-collision
call tally % reportOutColl(p, collDat % MT, collDat % muL)

Expand Down
69 changes: 56 additions & 13 deletions CollisionOperator/CollisionProcessors/neutronCEimp_class.f90
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ module neutronCEimp_class

! Scattering procedures
use scatteringKernels_func, only : asymptoticScatter, targetVelocity_constXS, &
asymptoticInelasticScatter
asymptoticInelasticScatter, targetVelocity_DBRCXS
implicit none
private

Expand All @@ -63,6 +63,8 @@ module neutronCEimp_class
!! kT is target material temperature in [MeV]. (default = 400.0)
!! thresh_A -> Mass threshold for explicit tratment of target nuclide movement [Mn].
!! Target movment is sampled if target mass A < thresh_A. (default = 1.0)
!! DBRCeMin -> Minimum energy to which DBRC is applied
!! DBRCeMax -> Maximum energy to which DBRC is applied
!! splitting -> splits particles above certain weight (on by default)
!! roulette -> roulettes particles below certain weight (off by defautl)
!! weightWindows -> uses a weight windows field (off by default)
Expand All @@ -88,9 +90,9 @@ module neutronCEimp_class
type, public, extends(collisionProcessor) :: neutronCEimp
private
!! Nuclear Data block pointer -> public so it can be used by subclasses (protected member)
class(ceNeutronDatabase), pointer, public :: xsData => null()
class(ceNeutronMaterial), pointer, public :: mat => null()
class(ceNeutronNuclide), pointer, public :: nuc => null()
class(ceNeutronDatabase), pointer, public :: xsData => null()
class(ceNeutronMaterial), pointer, public :: mat => null()
class(ceNeutronNuclide), pointer, public :: nuc => null()
class(uniFissSitesField), pointer :: ufsField => null()

!! Settings - private
Expand All @@ -101,6 +103,9 @@ module neutronCEimp_class
real(defReal) :: avWgt
real(defReal) :: thresh_E
real(defReal) :: thresh_A
real(defReal) :: DBRCeMin
real(defReal) :: DBRCeMax

! Variance reduction options
logical(defBool) :: weightWindows
logical(defBool) :: splitting
Expand Down Expand Up @@ -175,6 +180,10 @@ subroutine init(self, dict)
if( self % thresh_E < 0) call fatalError(Here,' -ve energyThreshold')
if( self % thresh_A < 0) call fatalError(Here,' -ve massThreshold')

! DBRC energy limits
call dict % getOrDefault(self % DBRCeMin,'DBRCeMin', (1.0E-8_defReal))
call dict % getOrDefault(self % DBRCeMax,'DBRCeMax', (200E-6_defReal))

if (self % splitting) then
if (self % maxWgt < 2 * self % minWgt) call fatalError(Here,&
'Upper weight bound must be at least twice the lower weight bound')
Expand Down Expand Up @@ -231,7 +240,7 @@ subroutine sampleCollision(self, p, collDat, thisCycle, nextCycle)
collDat % nucIdx = self % mat % sampleNuclide(p % E, p % pRNG)

self % nuc => ceNeutronNuclide_CptrCast(self % xsData % getNuclide(collDat % nucIdx))
if(.not.associated(self % mat)) call fatalError(Here, 'Failed to retive CE Neutron Nuclide')
if(.not.associated(self % mat)) call fatalError(Here, 'Failed to retrieve CE Neutron Nuclide')

! Select Main reaction channel
call self % nuc % getMicroXSs(microXss, p % E, p % pRNG)
Expand Down Expand Up @@ -307,6 +316,7 @@ subroutine implicit(self, p, collDat, thisCycle, nextCycle)
pTemp % dir = dir
pTemp % E = E_out
pTemp % wgt = wgt
pTemp % collisionN = 0

call nextCycle % detain(pTemp)
if (self % uniFissSites) call self % ufsField % storeFS(pTemp)
Expand Down Expand Up @@ -411,6 +421,7 @@ subroutine fission(self, p, collDat, thisCycle, nextCycle)
pTemp % dir = dir
pTemp % E = E_out
pTemp % wgt = wgt
pTemp % collisionN = 0

call nextCycle % detain(pTemp)
if (self % uniFissSites) call self % ufsField % storeFS(pTemp)
Expand All @@ -434,7 +445,7 @@ subroutine elastic(self, p, collDat, thisCycle, nextCycle)
class(particleDungeon),intent(inout) :: thisCycle
class(particleDungeon),intent(inout) :: nextCycle
class(uncorrelatedReactionCE), pointer :: reac
logical(defBool) :: isFixed
logical(defBool) :: isFixed, hasDBRC
character(100),parameter :: Here = 'elastic (neutronCEimp_class.f90)'

! Get reaction
Expand All @@ -445,7 +456,11 @@ subroutine elastic(self, p, collDat, thisCycle, nextCycle)
collDat % A = self % nuc % getMass()
collDat % kT = self % nuc % getkT()

isFixed = (p % E > collDat % kT * self % thresh_E) .and. (collDat % A > self % thresh_A)
! Check is DBRC is on
hasDBRC = self % nuc % hasDBRC()

isFixed = (.not. hasDBRC) .and. (p % E > collDat % kT * self % thresh_E) &
& .and. (collDat % A > self % thresh_A)

! Apply criterion for Free-Gas vs Fixed Target scattering
if (.not. reac % inCMFrame()) then
Expand Down Expand Up @@ -647,27 +662,54 @@ subroutine scatterFromMoving(self, p, collDat, reac)
class(particle), intent(inout) :: p
type(collisionData),intent(inout) :: collDat
class(uncorrelatedReactionCE), intent(in) :: reac
integer(shortInt) :: MT, nucIdx
class(ceNeutronNuclide), pointer :: ceNuc0K
integer(shortInt) :: nucIdx
real(defReal) :: A, kT, mu
real(defReal),dimension(3) :: V_n ! Neutron velocity (vector)
real(defReal) :: U_n ! Neutron speed (scalar)
real(defReal),dimension(3) :: dir_pre ! Pre-collision direction
real(defReal),dimension(3) :: dir_post ! Post-collicion direction
real(defReal),dimension(3) :: V_t, V_cm ! Target and CM velocity
real(defReal) :: phi, dummy
real(defReal) :: maj
logical(defBool) :: inEnergyRange, hasDBRC
character(100), parameter :: Here = 'ScatterFromMoving (neutronCEimp_class.f90)'

! Read data
MT = collDat % MT
nucIdx = collDat % nucIdx
! Read collision data
A = collDat % A
kT = collDat % kT
nucIdx = collDat % nucIdx

! Get neutron direction and velocity
dir_pre = p % dirGlobal()
V_n = dir_pre * sqrt(p % E)

! Sample velocity of target
V_t = targetVelocity_constXS(p % E, dir_pre, A, kT, p % pRNG)
! Sample target velocity with constant XS or with DBRC
! Check energy range
inEnergyRange = ((p % E <= self % DBRCeMax) .and. (self % DBRCeMin <= p % E))
! Check if DBRC is on for this target nuclide
hasDBRC = self % nuc % hasDBRC()

if (inEnergyRange .and. hasDBRC) then

! Retrieve 0K nuclide index from DBRC nuclide map
nucIdx = self % xsData % mapDBRCnuc % get(nucIdx)

! Assign pointer for the 0K nuclide
ceNuc0K => ceNeutronNuclide_CptrCast(self % xsData % getNuclide(nucIdx))
if(.not.associated(ceNuc0K)) call fatalError(Here, 'Failed to retrieve CE Neutron Nuclide')

! Get elastic scattering 0K majorant
maj = self % xsData % getScattMicroMajXS(p % E, kT, A, nucIdx)

! Use DBRC to sample target velocity
V_t = targetVelocity_DBRCXS(ceNuc0K, p % E, dir_pre, A, kT, p % pRNG, maj)

else
! Constant cross section approximation
V_t = targetVelocity_constXS(p % E, dir_pre, A, kT, p % pRNG)

end if

! Calculate Centre-of-Mass velocity
V_cm = (V_n + V_t *A)/(A+1)
Expand All @@ -694,6 +736,7 @@ subroutine scatterFromMoving(self, p, collDat, reac)
p % E = U_n * U_n
call p % point(dir_post)
collDat % muL = dot_product(dir_pre, dir_post)

end subroutine scatterFromMoving


Expand Down
67 changes: 55 additions & 12 deletions CollisionOperator/CollisionProcessors/neutronCEstd_class.f90
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ module neutronCEstd_class

! Scattering procedures
use scatteringKernels_func, only : asymptoticScatter, targetVelocity_constXS, &
asymptoticInelasticScatter
asymptoticInelasticScatter, targetVelocity_DBRCXS
implicit none
private

Expand All @@ -51,6 +51,8 @@ module neutronCEstd_class
!! kT is target material temperature in [MeV]. (default = 400.0)
!! thresh_A -> Mass threshold for explicit tratment of target nuclide movement [Mn].
!! Target movment is sampled if target mass A < thresh_A. (default = 1.0)
!! DBRCeMin -> Minimum energy to which DBRC is applied
!! DBRCeMax -> Maximum energy to which DBRC is applied
!!
!! Sample dictionary input:
!! collProcName {
Expand All @@ -73,6 +75,8 @@ module neutronCEstd_class
real(defReal) :: maxE
real(defReal) :: thresh_E
real(defReal) :: thresh_A
real(defReal) :: DBRCeMin
real(defReal) :: DBRCeMax

contains
! Initialisation procedure
Expand Down Expand Up @@ -122,6 +126,10 @@ subroutine init(self, dict)
if( self % thresh_E < 0) call fatalError(Here,' -ve energyThreshold')
if( self % thresh_A < 0) call fatalError(Here,' -ve massThreshold')

! DBRC energy limits
call dict % getOrDefault(self % DBRCeMin,'DBRCeMin', (1.0E-8_defReal))
call dict % getOrDefault(self % DBRCeMax,'DBRCeMax', (200E-6_defReal))

end subroutine init

!!
Expand Down Expand Up @@ -154,7 +162,7 @@ subroutine sampleCollision(self, p, collDat, thisCycle, nextCycle)
collDat % nucIdx = self % mat % sampleNuclide(p % E, p % pRNG)

self % nuc => ceNeutronNuclide_CptrCast(self % xsData % getNuclide(collDat % nucIdx))
if(.not.associated(self % mat)) call fatalError(Here, 'Failed to retive CE Neutron Nuclide')
if(.not.associated(self % mat)) call fatalError(Here, 'Failed to retrieve CE Neutron Nuclide')

! Select Main reaction channel
call self % nuc % getMicroXSs(microXss, p % E, p % pRNG)
Expand Down Expand Up @@ -222,6 +230,7 @@ subroutine implicit(self, p, collDat, thisCycle, nextCycle)
pTemp % dir = dir
pTemp % E = E_out
pTemp % wgt = wgt
pTemp % collisionN = 0

call nextCycle % detain(pTemp)
end do
Expand Down Expand Up @@ -263,13 +272,13 @@ end subroutine fission
!! All CE elastic scattering happens in the CM frame
!!
subroutine elastic(self, p, collDat, thisCycle, nextCycle)
class(neutronCEstd), intent(inout) :: self
class(particle), intent(inout) :: p
type(collisionData), intent(inout) :: collDat
class(particleDungeon),intent(inout) :: thisCycle
class(particleDungeon),intent(inout) :: nextCycle
class(neutronCEstd), intent(inout) :: self
class(particle), intent(inout) :: p
type(collisionData), intent(inout) :: collDat
class(particleDungeon),intent(inout) :: thisCycle
class(particleDungeon),intent(inout) :: nextCycle
class(uncorrelatedReactionCE), pointer :: reac
logical(defBool) :: isFixed
logical(defBool) :: isFixed, hasDBRC
character(100),parameter :: Here = 'elastic (neutronCEstd_class.f90)'

! Get reaction
Expand All @@ -280,7 +289,11 @@ subroutine elastic(self, p, collDat, thisCycle, nextCycle)
collDat % A = self % nuc % getMass()
collDat % kT = self % nuc % getkT()

isFixed = (p % E > collDat % kT * self % thresh_E) .and. (collDat % A > self % thresh_A)
! Check is DBRC is on
hasDBRC = self % nuc % hasDBRC()

isFixed = (.not. hasDBRC) .and. (p % E > collDat % kT * self % thresh_E) &
& .and. (collDat % A > self % thresh_A)

! Apply criterion for Free-Gas vs Fixed Target scattering
if (.not. reac % inCMFrame()) then
Expand Down Expand Up @@ -404,24 +417,54 @@ subroutine scatterFromMoving(self, p, collDat, reac)
class(particle), intent(inout) :: p
type(collisionData),intent(inout) :: collDat
class(uncorrelatedReactionCE), intent(in) :: reac
class(ceNeutronNuclide), pointer :: ceNuc0K
integer(shortInt) :: nucIdx
real(defReal) :: A, kT, mu
real(defReal),dimension(3) :: V_n ! Neutron velocity (vector)
real(defReal) :: U_n ! Neutron speed (scalar)
real(defReal),dimension(3) :: dir_pre ! Pre-collision direction
real(defReal),dimension(3) :: dir_post ! Post-collicion direction
real(defReal),dimension(3) :: V_t, V_cm ! Target and CM velocity
real(defReal) :: phi, dummy
real(defReal) :: maj
logical(defBool) :: inEnergyRange, hasDBRC
character(100), parameter :: Here = 'ScatterFromMoving (neutronCEstd_class.f90)'

! Read data
! Read collision data
A = collDat % A
kT = collDat % kT
nucIdx = collDat % nucIdx

! Get neutron direction and velocity
dir_pre = p % dirGlobal()
V_n = dir_pre * sqrt(p % E)

! Sample velocity of target
V_t = targetVelocity_constXS(p % E, dir_pre, A, kT, p % pRNG)
! Sample target velocity with constant XS or with DBRC
! Check energy range
inEnergyRange = ((p % E <= self % DBRCeMax) .and. (self % DBRCeMin <= p % E))
! Check if DBRC is on for this target nuclide
hasDBRC = self % nuc % hasDBRC()

if (inEnergyRange .and. hasDBRC) then

! Retrieve 0K nuclide index from DBRC nuclide map
nucIdx = self % xsData % mapDBRCnuc % get(nucIdx)

! Assign pointer for the 0K nuclide
ceNuc0K => ceNeutronNuclide_CptrCast(self % xsData % getNuclide(nucIdx))
if(.not.associated(ceNuc0K)) call fatalError(Here, 'Failed to retrieve CE Neutron Nuclide')

! Get elastic scattering 0K majorant
maj = self % xsData % getScattMicroMajXS(p % E, kT, A, nucIdx)

! Use DBRC to sample target velocity
V_t = targetVelocity_DBRCXS(ceNuc0K, p % E, dir_pre, A, kT, p % pRNG, maj)

else
! Constant cross section approximation
V_t = targetVelocity_constXS(p % E, dir_pre, A, kT, p % pRNG)

end if

! Calculate Centre-of-Mass velocity
V_cm = (V_n + V_t *A)/(A+1)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -175,6 +175,7 @@ subroutine implicit(self, p, collDat, thisCycle, nextCycle)
pTemp % dir = dir
pTemp % G = G_out
pTemp % wgt = wgt
pTemp % collisionN = 0

call nextCycle % detain(pTemp)
end do
Expand Down
2 changes: 1 addition & 1 deletion CollisionOperator/collisionOperator_class.f90
Original file line number Diff line number Diff line change
Expand Up @@ -114,7 +114,7 @@ subroutine collide(self, p, tally, thisCycle, nextCycle)
class(particleDungeon),intent(inout) :: thisCycle
class(particleDungeon),intent(inout) :: nextCycle
integer(shortInt) :: idx, procType
character(100), parameter :: Here = 'collide ( collisionOperator_class.f90)'
character(100), parameter :: Here = 'collide (collisionOperator_class.f90)'

! Select processing index with ternary expression
if(p % isMG) then
Expand Down
Loading

0 comments on commit 5909f3f

Please sign in to comment.