Skip to content

Commit

Permalink
Addressing comments
Browse files Browse the repository at this point in the history
  • Loading branch information
V. Raffuzzi(vr339) committed Jan 18, 2024
1 parent 435aab7 commit 18fbe55
Show file tree
Hide file tree
Showing 15 changed files with 151 additions and 152 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -75,8 +75,7 @@ subroutine test_aceNeutronDatabase()
! Initialise data
ptr => data
call data % init(dataDict, ptr, silent = .true.)
call data % activate([1,2])
call data % initMajorant(p % pRNG, silent = .true.)
call data % activate([1,2], silent = .true.)

!!<><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><>
!! Perform tests
Expand Down
142 changes: 96 additions & 46 deletions NuclearData/ceNeutronData/aceDatabase/aceNeutronDatabase_class.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3,12 +3,13 @@ module aceNeutronDatabase_class
use numPrecision
use endfConstants
use universalVariables
use genericProcedures, only : fatalError, numToChar, concatenate, quickSort, &
removeDuplicatesSorted, binarySearch
use dictionary_class, only : dictionary
use RNG_class, only : RNG
use charMap_class, only : charMap
use intMap_class, only : intMap
use errors_mod, only : fatalError
use genericProcedures, only : numToChar, concatenate, quickSort, &
removeDuplicatesSorted, binarySearch
use dictionary_class, only : dictionary
use RNG_class, only : RNG
use charMap_class, only : charMap
use intMap_class, only : intMap

! Nuclear Data Interfaces
use nuclearDatabase_inter, only : nuclearDatabase
Expand Down Expand Up @@ -55,7 +56,8 @@ module aceNeutronDatabase_class
!! Sample input:
!! nuclearData {
!! handles {
!! ce {type aceNeutronDatabase; DBRC (92238 94242); ures <1 or 0>; aceLibrary <nuclear data path> ;} }
!! ce { type aceNeutronDatabase; DBRC (92238 94242); ures < 1 or 0 >;
!! majorant < 1 or 0 >; aceLibrary <nuclear data path> ;} }
!!
!! Public Members:
!! nuclides -> array of aceNeutronNuclides with data
Expand All @@ -76,16 +78,18 @@ module aceNeutronDatabase_class
type(aceNeutronNuclide),dimension(:),pointer :: nuclides => null()
type(ceNeutronMaterial),dimension(:),pointer :: materials => null()
real(defReal), dimension(:), allocatable :: majorant
real(defReal), dimension(:), allocatable :: eGrid
real(defReal), dimension(:), allocatable :: eGridUnion
real(defReal), dimension(2) :: Ebounds = ZERO
integer(shortInt),dimension(:),allocatable :: activeMat

! Probability tables data
integer(shortInt),dimension(:),allocatable :: nucToZaid
logical(defBool) :: hasUrr = .false.
logical(defBool) :: hasUrr = .false.
logical(defBool) :: hasDBRC = .false.
logical(defBool) :: hasMajorant = .false.

contains

! nuclearDatabase Procedures
procedure :: kill
procedure :: matNamesMap
Expand All @@ -94,7 +98,6 @@ module aceNeutronDatabase_class
procedure :: getReaction
procedure :: init
procedure :: activate
procedure :: initMajorant

! ceNeutronDatabase Procedures
procedure :: energyBounds
Expand All @@ -108,6 +111,7 @@ module aceNeutronDatabase_class
! class Procedures
procedure :: init_urr
procedure :: init_DBRC
procedure :: initMajorant

end type aceNeutronDatabase

Expand Down Expand Up @@ -297,7 +301,7 @@ subroutine updateTotalMatXS(self, E, matIdx, rand)
class(aceNeutronDatabase), intent(in) :: self
real(defReal), intent(in) :: E
integer(shortInt), intent(in) :: matIdx
class(RNG), intent(inout) :: rand
class(RNG), optional, intent(inout) :: rand
integer(shortInt) :: i, nucIdx
real(defReal) :: dens

Expand Down Expand Up @@ -335,26 +339,46 @@ end subroutine updateTotalMatXS
subroutine updateMajorantXS(self, E, rand)
class(aceNeutronDatabase), intent(in) :: self
real(defReal), intent(in) :: E
class(RNG), intent(inout) :: rand
integer(shortInt) :: idx
class(RNG), optional, intent(inout) :: rand
integer(shortInt) :: idx, i, matIdx
real(defReal) :: f
character(100), parameter :: Here = 'updateMajorantXS (aceNeutronDatabase_class.f90)'

associate (maj => cache_majorantCache(1) )
maj % E = E

idx = binarySearch(self % eGrid, E)
! Get majorant via the precomputed unionised cross section
if (self % hasMajorant) then
idx = binarySearch(self % eGridUnion, E)

if(idx <= 0) then
call fatalError(Here,'Failed to find energy: '//numToChar(E)//&
' in unionised majorant grid')
end if
if(idx <= 0) then
call fatalError(Here,'Failed to find energy: '//numToChar(E)//&
' in unionised majorant grid')
end if

associate(E_top => self % eGrid(idx + 1), E_low => self % eGrid(idx))
f = (E - E_low) / (E_top - E_low)
end associate
associate(E_top => self % eGridUnion(idx + 1), E_low => self % eGridUnion(idx))
f = (E - E_low) / (E_top - E_low)
end associate

maj % xs = self % majorant(idx+1) * f + (ONE - f) * self % majorant(idx)

else ! Compute majorant on the fly

maj % xs = self % majorant(idx+1) * f + (ONE - f) * self % majorant(idx)
maj % xs = ZERO

! Loop over materials
do i = 1, size(self % activeMat)
matIdx = self % activeMat(i)

! Update if needed
if( cache_materialCache(matIdx) % E_tot /= E) then
call self % updateTotalMatXS(E, matIdx, rand)
end if

maj % xs = max(maj % xs, cache_materialCache(matIdx) % xss % total)
end do

end if

end associate

Expand All @@ -370,7 +394,7 @@ subroutine updateMacroXSs(self, E, matIdx, rand)
class(aceNeutronDatabase), intent(in) :: self
real(defReal), intent(in) :: E
integer(shortInt), intent(in) :: matIdx
class(RNG), intent(inout) :: rand
class(RNG), optional, intent(inout) :: rand
integer(shortInt) :: i, nucIdx
real(defReal) :: dens

Expand Down Expand Up @@ -410,7 +434,7 @@ subroutine updateTotalNucXS(self, E, nucIdx, rand)
class(aceNeutronDatabase), intent(in) :: self
real(defReal), intent(in) :: E
integer(shortInt), intent(in) :: nucIdx
class(RNG), intent(inout) :: rand
class(RNG), optional, intent(inout) :: rand
logical(defBool) :: needsSab

associate (nucCache => cache_nuclideCache(nucIdx), &
Expand Down Expand Up @@ -445,7 +469,7 @@ subroutine updateMicroXSs(self, E, nucIdx, rand)
class(aceNeutronDatabase), intent(in) :: self
real(defReal), intent(in) :: E
integer(shortInt), intent(in) :: nucIdx
class(RNG), intent(inout) :: rand
class(RNG), optional, intent(inout) :: rand

associate (nucCache => cache_nuclideCache(nucIdx), &
nuc => self % nuclides(nucIdx) )
Expand Down Expand Up @@ -665,6 +689,9 @@ subroutine init(self, dict, ptr, silent )
self % Ebounds(2) = min(self % Ebounds(2), self % nuclides(i) % eGrid(j))
end do

! Read unionised majorant flag
call dict % getOrDefault(self % hasMajorant, 'majorant', .false.)

! If on, initialise probability tables for ures
if (self % hasUrr) then
call self % init_urr()
Expand Down Expand Up @@ -773,9 +800,11 @@ end subroutine init_DBRC
!!
!! See nuclearDatabase documentation for details
!!
subroutine activate(self, activeMat)
subroutine activate(self, activeMat, silent)
class(aceNeutronDatabase), intent(inout) :: self
integer(shortInt), dimension(:), intent(in) :: activeMat
logical(defBool), optional, intent(in) :: silent
logical(defBool) :: loud

! Load active materials
if(allocated(self % activeMat)) deallocate(self % activeMat)
Expand All @@ -788,32 +817,53 @@ subroutine activate(self, activeMat)
call cache_init(size(self % materials), size(self % nuclides))
end if

! If unionised majorant cross section is requested, build it
if (self % hasMajorant) then

! Set build console output flag
if (present(silent)) then
loud = .not. silent
else
loud = .true.
end if

! Check if probability tables are on
if (self % hasUrr) then

! Switch off majorant
self % hasMajorant = .false.

if (loud) then
print '(A)', 'Unionised majorant cross section will not be contructed &
& due to the use of URR probability tables treatment'
end if

else

! Precompute majorant cross section
call self % initMajorant(loud)

end if

end if

end subroutine activate

!!
!! Precomputes majorant cross section
!!
!! See nuclearDatabase documentation for details
!!
subroutine initMajorant(self, rand, silent)
subroutine initMajorant(self, loud)
class(aceNeutronDatabase), intent(inout) :: self
class(RNG), intent(inout) :: rand
logical(defBool), intent(in), optional :: silent
logical(defBool) :: loud
logical(defBool), intent(in) :: loud
real(defReal), dimension(:), allocatable :: tmpGrid
integer(shortInt) :: i, j, matIdx, nNuc, nucIdx, isDone
type(intMap) :: nucMap
real(defReal) :: E, maj
integer(shortInt), parameter :: IN_SET = 1, NOT_PRESENT = 0

! Set build console output flag
if(present(silent)) then
loud = .not.silent
else
loud = .true.
end if

if (loud) print '(A)', 'Building unionised energy grid'
if (loud) print '(A)', 'Building CE unionised energy grid'

! Initialise energy grid
matIdx = self % activeMat(1)
Expand Down Expand Up @@ -855,21 +905,21 @@ subroutine initMajorant(self, rand, silent)
end do

! Save final grid
self % eGrid = tmpGrid
self % eGridUnion = tmpGrid

if (loud) then
print '(A)', 'Unionised energy grid has size: '//numToChar(size(self % eGrid))//&
'. Now building unionised majorant cross section'
print '(A)', 'CE unionised energy grid has size: '//numToChar(size(self % eGridUnion))//&
'. Now building CE unionised majorant cross section'
end if

! Allocate unionised majorant
allocate(self % majorant(size(self % eGrid)))
allocate(self % majorant(size(self % eGridUnion)))

! Loop over all the energies
do i = 1, size(self % eGrid)
do i = 1, size(self % eGridUnion)

! Retrieve current energy
E = self % eGrid(i)
E = self % eGridUnion(i)

! Correct for energies higher or lower than the allowed boundaries
if (E < self % EBounds(1)) E = self % EBounds(1)
Expand All @@ -885,7 +935,7 @@ subroutine initMajorant(self, rand, silent)
matIdx = self % activeMat(j)

! Calculate current material cross section and compare
call self % updateTotalMatXS(E, matIdx, rand)
call self % updateTotalMatXS(E, matIdx)
maj = max(maj, cache_materialCache(matIdx) % xss % total)

end do
Expand All @@ -895,7 +945,7 @@ subroutine initMajorant(self, rand, silent)

end do

if (loud) print '(A)', 'Unionised majorant cross section completed'
if (loud) print '(A)', 'CE unionised majorant cross section completed'

end subroutine initMajorant

Expand Down
10 changes: 5 additions & 5 deletions NuclearData/ceNeutronData/ceNeutronDatabase_inter.f90
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ subroutine updateTotalMatXS(self, E, matIdx, rand)
class(ceNeutronDatabase), intent(in) :: self
real(defReal), intent(in) :: E
integer(shortInt), intent(in) :: matIdx
class(RNG), intent(inout) :: rand
class(RNG), optional, intent(inout) :: rand
end subroutine updateTotalMatXS

!!
Expand All @@ -125,7 +125,7 @@ subroutine updateMajorantXS(self, E, rand)
import :: ceNeutronDatabase, defReal, RNG
class(ceNeutronDatabase), intent(in) :: self
real(defReal), intent(in) :: E
class(RNG), intent(inout) :: rand
class(RNG), optional, intent(inout) :: rand
end subroutine updateMajorantXS

!!
Expand All @@ -147,7 +147,7 @@ subroutine updateMacroXSs(self, E, matIdx, rand)
class(ceNeutronDatabase), intent(in) :: self
real(defReal), intent(in) :: E
integer(shortInt), intent(in) :: matIdx
class(RNG), intent(inout) :: rand
class(RNG), optional, intent(inout) :: rand
end subroutine updateMacroXSs

!!
Expand All @@ -169,7 +169,7 @@ subroutine updateTotalXS(self, E, nucIdx, rand)
class(ceNeutronDatabase), intent(in) :: self
real(defReal), intent(in) :: E
integer(shortInt), intent(in) :: nucIdx
class(RNG), intent(inout) :: rand
class(RNG), optional, intent(inout) :: rand
end subroutine updateTotalXS

!!
Expand All @@ -191,7 +191,7 @@ subroutine updateMicroXSs(self, E, nucIdx, rand)
class(ceNeutronDatabase), intent(in) :: self
real(defReal), intent(in) :: E
integer(shortInt), intent(in) :: nucIdx
class(RNG), intent(inout) :: rand
class(RNG), optional, intent(inout) :: rand
end subroutine updateMicroXSs

!!
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -74,8 +74,7 @@ subroutine testBaseMgNeutronDatabaseWithP0()
call databaseDef % init(1)
call databaseDef % store('PN','P0')
call database % init(databaseDef, data_ptr, silent = .true.)
call database % activate([1])
call database % initMajorant(p % pRNG, silent = .true.)
call database % activate([1], silent = .true.)

! Varify number of groups
@assertEqual(4, database % nGroups())
Expand Down Expand Up @@ -201,8 +200,7 @@ subroutine testBaseMgNeutronDatabaseWithP1()
call databaseDef % init(1)
call databaseDef % store('PN','P1')
call database % init(databaseDef, data_ptr, silent = .true.)
call database % activate([1])
call database % initMajorant(p % pRNG, silent = .true.)
call database % activate([1], silent = .true.)

! Varify number of groups
@assertEqual(4, database % nGroups())
Expand Down
Loading

0 comments on commit 18fbe55

Please sign in to comment.