diff --git a/DataStructures/dictionary_class.f90 b/DataStructures/dictionary_class.f90 index 4434dda6a..e07fa7cf6 100644 --- a/DataStructures/dictionary_class.f90 +++ b/DataStructures/dictionary_class.f90 @@ -32,6 +32,8 @@ module dictionary_class ! -> 1D array of shortInt - integer(shortInt) :: i(:) ! -> scalar character of length "charLen" defined below - character(charLen) :: c ! -> array of characters of length "charLen" defined below - character(charLen) :: c(:) + ! -> boolean logical - logical(defBool) :: b + ! -> array of boolean logicals - logical(defBool) :: b(:) ! -> another dictionary - type(dictionary) :: dict ! ! To add additional structure to store it is necessary to : @@ -100,7 +102,7 @@ module dictionary_class ! *** Note that dictionary is defined as pointer not allocatable ! *** This is because gfortran < 7.0 does not supports circular derived types with ! *** allocatable keyword. This line may change in the future - type(dictionary), pointer :: dict0_alloc => null() + type(dictionary), pointer :: dict0_alloc => null() ! dictContent type ID integer(shortInt) :: type = empty @@ -149,7 +151,9 @@ module dictionary_class getCharArray_alloc_new,& getCharArray_ptr_new,& getDict_new,& - getBool_new + getBool_new, & + getBoolArray_alloc_new,& + getBoolArray_ptr_new procedure,private :: getReal_new procedure,private :: getRealArray_alloc_new @@ -162,6 +166,8 @@ module dictionary_class procedure,private :: getCharArray_ptr_new procedure,private :: getDict_new procedure,private :: getBool_new + procedure,private :: getBoolArray_alloc_new + procedure,private :: getBoolArray_ptr_new generic :: getOrDefault => getOrDefault_real ,& getOrDefault_realArray_alloc ,& @@ -172,7 +178,9 @@ module dictionary_class getOrDefault_char ,& getOrDefault_charArray_alloc ,& getOrDefault_charArray_ptr, & - getOrDefault_bool + getOrDefault_bool, & + getOrDefault_boolArray_alloc, & + getOrDefault_boolArray_ptr procedure,private :: getOrDefault_real procedure,private :: getOrDefault_realArray_alloc @@ -184,6 +192,8 @@ module dictionary_class procedure,private :: getOrDefault_charArray_alloc procedure,private :: getOrDefault_charArray_ptr procedure,private :: getOrDefault_bool + procedure,private :: getOrDefault_boolArray_alloc + procedure,private :: getOrDefault_boolArray_ptr ! Keys inquiry procedures procedure :: keys @@ -779,6 +789,83 @@ subroutine getBool_new(self,value,keyword) call fatalError(Here,'Entry under keyword ' // keyword // ' is not an integer') end select end subroutine getBool_new + + !! + !! Loads a boolean rank 1 from dictionary into provided variable + !! If keyword is associated with an integer which is not 1 or 0, it returns an error. + !! Variable needs to be allocatable. It will be deallocated before assignment + !! + subroutine getBoolArray_alloc_new(self,value,keyword) + class(dictionary), intent(in) :: self + logical(defBool),dimension(:),allocatable,intent(inout) :: value + character(*),intent(in) :: keyword + integer(shortInt) :: idx + integer(shortInt),dimension(:),allocatable :: tempInt + character(100),parameter :: Here='getBoolArray_alloc_new (dictionary_class.f90)' + + idx = self % search(keyword, Here, fatal =.true.) + + if(allocated(value)) deallocate(value) + + select case (self % entries(idx) % getType()) + case(arrInt) + tempInt = self % entries(idx) % int1_alloc + allocate(value(size(tempInt))) + + if (any(tempInt < 0) .or. any(tempInt > 1)) then + call fatalError(Here,'Entry under keyword ' // keyword // ' has non-logical values (not 0 or 1).') + else + do idx = 1, size(tempInt) + value(idx) = tempInt(idx) == 1 + end do + end if + + case default + call fatalError(Here,'Entry under keyword ' // keyword // ' is not an int array.') + + end select + + end subroutine getBoolArray_alloc_new + + !! + !! Loads a boolean rank 1 from dictionary into provided variable. + !! If keyword is associated with an integer which is not 1 or 0, it returns an error. + !! Variable needs to be pointer. It will be deallocated before assignment + !! + subroutine getBoolArray_ptr_new(self,value,keyword) + class(dictionary), intent(in) :: self + logical(defBool),dimension(:),pointer,intent(inout) :: value + character(*),intent(in) :: keyword + integer(shortInt) :: idx, N + integer(shortInt),dimension(:),allocatable :: tempInt + character(100),parameter :: Here='getBoolArray_ptr_new (dictionary_class.f90)' + + idx = self % search(keyword, Here, fatal =.true.) + + if(associated(value)) deallocate(value) + + select case (self % entries(idx) % getType()) + case(arrInt) + + N = size(self % entries(idx) % int1_alloc) + allocate(value(N)) + allocate(tempInt(N)) + tempInt = self % entries(idx) % int1_alloc + + if (any(tempInt < 0) .or. any(tempInt > 1)) then + call fatalError(Here,'Entry under keyword ' // keyword // ' has non-logical values (not 0 or 1).') + else + do idx = 1, N + value(idx) = tempInt(idx) == 1 + end do + end if + + case default + call fatalError(Here,'Entry under keyword ' // keyword // ' is not an int array.') + + end select + + end subroutine getBoolArray_ptr_new !! !! Loads a real rank 0 from a dictionary into provided variable @@ -1044,6 +1131,57 @@ subroutine getOrDefault_bool(self,value,keyword,default) end if end subroutine getOrDefault_bool + !! + !! Loads a boolean rank 1 from a dictionary. + !! Variable needs to be allocatable. It will be deallocated before assignment + !! + subroutine getOrDefault_boolArray_alloc(self, value, keyword, default) + class(dictionary), intent(in) :: self + logical(defBool),dimension(:),allocatable,intent(inout) :: value + character(*),intent(in) :: keyword + logical(defBool),dimension(:),intent(in) :: default + integer(shortInt) :: idx + character(100),parameter :: Here='getOrDefault_boolArray_alloc (dictionary_class.f90)' + + idx = self % search(keyword, Here, fatal =.false.) + + if(allocated(value)) deallocate(value) + + if (idx == targetNotFound) then + value = default + else + call self % get(value, keyword) + end if + end subroutine getOrDefault_boolArray_alloc + + + !! + !! Loads a boolean rank 1 from a dictionary. + !! Variable needs to be pointer. It will be deallocated before assignment + !! + !! For further details refer to doc of getOrDefault_real + !! + subroutine getOrDefault_boolArray_ptr(self, value, keyword, default) + class(dictionary), intent(in) :: self + logical(defBool),dimension(:),pointer,intent(inout) :: value + character(*),intent(in) :: keyword + logical(defBool),dimension(:),intent(in) :: default + integer(shortInt) :: idx + character(100),parameter :: Here='getOrDefault_boolArray_ptr (dictionary_class.f90)' + + idx = self % search(keyword, Here, fatal =.false.) + + if(associated(value)) deallocate(value) + + if (idx == targetNotFound) then + allocate(value(size(default))) + value = default + else + call self % get(value, keyword) + end if + + end subroutine getOrDefault_boolArray_ptr + !! !! Returns an array of all keywords !! diff --git a/Geometry/Surfaces/box_class.f90 b/Geometry/Surfaces/box_class.f90 index 221903c9b..21e7f0d6a 100644 --- a/Geometry/Surfaces/box_class.f90 +++ b/Geometry/Surfaces/box_class.f90 @@ -347,7 +347,7 @@ subroutine explicitBC(self, r, u) r0 = r(ax) - self % origin(ax) ! Skip if particle is well inside the domain - if (abs(r0) <= self % halfwidth(ax) - self % surfTol()) cycle axis + if (abs(r0) <= self % halfwidth(ax) * (ONE - self % surfTol())) cycle axis ! Choose correct BC if (r0 < ZERO) then @@ -396,7 +396,7 @@ subroutine transformBC(self, r, u) ! Calculate halfwidth reduced by the surface_tolerance ! Necessary to capture particles at the boundary - a_bar = self % halfwidth - self % surfTol() + a_bar = self % halfwidth * (ONE - self % surfTol()) ! Calculate distance (in # of transformations) in each direction Ri = ceiling(abs(r - self % origin) / a_bar) / 2 diff --git a/Geometry/Surfaces/squareCylinder_class.f90 b/Geometry/Surfaces/squareCylinder_class.f90 index 5e41d95ec..196c17027 100644 --- a/Geometry/Surfaces/squareCylinder_class.f90 +++ b/Geometry/Surfaces/squareCylinder_class.f90 @@ -402,7 +402,7 @@ subroutine explicitBC(self, r, u) r0 = r(ax) - self % origin(i) ! Skip if particle is well inside the domain - if (abs(r0) <= self % halfwidth(i) - self % surfTol()) cycle axis + if (abs(r0) <= self % halfwidth(i) * (ONE- self % surfTol())) cycle axis ! Choose correct BC if (r0 < ZERO) then @@ -452,7 +452,7 @@ subroutine transformBC(self, r, u) ! Calculate halfwidth reduced by the surface_tolerance ! Necessary to capture particles at the boundary - a_bar = self % halfwidth - self % surfTol() + a_bar = self % halfwidth * (ONE - self % surfTol()) ! Calculate distance (in # of transformations) in each direction Ri = ceiling(abs(r(self % plane) - self % origin) / a_bar) / 2 diff --git a/Geometry/Universes/Tests/latUniverse_test.f90 b/Geometry/Universes/Tests/latUniverse_test.f90 index 6384dac7f..99b005133 100644 --- a/Geometry/Universes/Tests/latUniverse_test.f90 +++ b/Geometry/Universes/Tests/latUniverse_test.f90 @@ -18,11 +18,15 @@ module latUniverse_test character(*), parameter :: UNI1_DEF = & "id 1; type latUniverse; origin (0.0 0.0 0.0); rotation (0.0 0.0 0.0); & &pitch (1.0 2.0 3.0); shape (3 2 2); padMat void; & - &map ( 3 4 5 & + & map ( 3 4 5 & & 7 4 8 & & & & 1 2 3 & & 4 5 6); " + !& offsetMap ( 1 1 1 & + !& 0 1 1 & + !& 1 1 1 & + !& 1 1 1 ); & character(*), parameter :: UNI2_DEF = & "id 2; type latUniverse; pitch (1.0 2.0 0.0); shape (2 1 0); padMat u<1>; & @@ -389,6 +393,17 @@ subroutine test_cellOffset() ref = [0.0_defReal, 1.0_defReal, 1.5_defReal] @assertEqual(ref, uni1 % cellOffset(pos), TOL) + + !! Inside but at the position without an offset + !pos % r = [-1.5_defReal, 1.0_defReal, -0.5_defReal] + !pos % dir = [-ONE, ONE, -ONE] + !pos % dir = pos % dir / norm2(pos % dir) + !pos % uniIdx = 8 + !pos % cellIdx = 0 + !pos % localId = 4 + + !ref = [0.0_defReal, 0.0_defReal, 0.0_defReal] + !@assertEqual(ref, uni1 % cellOffset(pos), TOL) ! Outside pos % r = [-7.0_defReal, 0.0_defReal, 0.5_defReal] diff --git a/Geometry/Universes/latUniverse_class.f90 b/Geometry/Universes/latUniverse_class.f90 index ca950e9cd..1060e36c4 100644 --- a/Geometry/Universes/latUniverse_class.f90 +++ b/Geometry/Universes/latUniverse_class.f90 @@ -20,6 +20,9 @@ module latUniverse_class integer(shortInt), parameter :: X_MIN = -1, X_MAX = -2, Y_MIN = -3, Y_MAX = -4, Z_MIN = -5, & Z_MAX = -6, OUTLINE_SURF = -7 + ! Options for the offset map + integer(shortInt), parameter :: local = 1, noOffset = 0 + !! !! 2D or 3D Cartesian lattice with constant pitch !! @@ -32,7 +35,9 @@ module latUniverse_class !! Background cell can have any filling given by keyword (material or universe) !! !! Every lattice cell has an offset to its centre (so the centre of the nested universe - !! is in the center of the lattice cell). + !! is in the center of the lattice cell). Optionally an offset map can be provided, determining + !! whether to apply an offset in a given cell position. This can disables the local universe + !! offset. Alternatively a single offset flag can be provided, disabling offset in all cells. !! !! Minimum lattice pitch is set to 10 * SURF_TOL !! @@ -47,7 +52,12 @@ module latUniverse_class !! map ( 1 2 3 // Top layer !! 4 5 6 // Lower Y row !! 7 8 9 // Bottom layer - !! 10 11 12 ) + !! 10 11 12 ); + !! #offsetMap ( 1 1 1 + !! # 1 0 1 + !! # 1 0 1 + !! # 1 1 1 ); + !! # offset 1; !! } !! !! Sample Input Dictionary (2D): @@ -70,18 +80,22 @@ module latUniverse_class !! a_bar -> Halfwidth of lattice cell reduced by surface tolerance !! outline -> Box type surface that is a boundary between lattice & background !! outLocalID -> LocalID of the background cell + !! offset -> Flag to disable all offsets + !! offsetMap -> Map determining which cells have a lattice offset or not !! !! Interface: !! universe interface !! type, public, extends(universe) :: latUniverse private - real(defReal), dimension(3) :: pitch = ZERO - integer(shortInt), dimension(3) :: sizeN = 0 - real(defReal), dimension(3) :: corner = ZERO - real(defReal), dimension(3) :: a_bar = ZERO - type(box) :: outline - integer(shortInt) :: outLocalID = 0 + real(defReal), dimension(3) :: pitch = ZERO + integer(shortInt), dimension(3) :: sizeN = 0 + real(defReal), dimension(3) :: corner = ZERO + real(defReal), dimension(3) :: a_bar = ZERO + type(box) :: outline + integer(shortInt) :: outLocalID = 0 + logical(defBool) :: offset = .true. + integer(shortInt), dimension(:), allocatable :: offsetMap contains ! Superclass procedures procedure :: init @@ -111,7 +125,7 @@ subroutine init(self, fill, dict, cells, surfs, mats) type(charMap), intent(in) :: mats real(defReal), dimension(:), allocatable :: temp integer(shortInt), dimension(:), allocatable :: tempI - integer(shortInt) :: N, i, j, outFill + integer(shortInt) :: N, i, j, outFill, val type(dictionary) :: tempDict integer(shortInt), dimension(:,:), allocatable :: tempMap character(nameLen) :: name @@ -120,6 +134,9 @@ subroutine init(self, fill, dict, cells, surfs, mats) ! Setup the base class ! With: id, origin rotations... call self % setupBase(dict) + + ! Perform offsets on every cell? + call dict % getOrDefault(self % offset, 'offset', .true.) ! Load pitch call dict % get(temp, 'pitch') @@ -152,11 +169,11 @@ subroutine init(self, fill, dict, cells, surfs, mats) ! Check for invalid pitch if (any(self % pitch < 10 * SURF_TOL)) then - call fatalError(Here, 'Pitch size must be larger than: '//numToChar( 10 * SURF_TOL)) - end if + call fatalError(Here, 'Pitch size must be larger than: '//numToChar( 10 * SURF_TOL)) + end if ! Calculate halfwidth and corner - self % a_bar = self % pitch * HALF - SURF_TOL + self % a_bar = self % pitch * HALF - self % pitch * SURF_TOL self % corner = -(self % sizeN * HALF * self % pitch) ! Calculate local ID of the background @@ -173,6 +190,11 @@ subroutine init(self, fill, dict, cells, surfs, mats) ! Construct fill array call dict % get(tempI, 'map') + ! Ensure size matches sizeN + if (size(tempI) /= product(self % sizeN)) call fatalError(Here, & + 'Lattice map size not equal to size implied by shape. Respectively: '//& + numToChar(size(tempI))//' '//numToChar(product(self % sizeN))) + ! Flip array up-down for more natural input ! Reshape into rank 2 array tempMap = reshape(tempI, [self % sizeN(1), self % sizeN(2) * self % sizeN(3)]) @@ -195,6 +217,46 @@ subroutine init(self, fill, dict, cells, surfs, mats) end do end do fill(self % outLocalID) = outFill + deallocate(tempI, tempMap) + + ! Check whether there is an offset map + if (dict % isPresent('offsetMap')) then + + if (.not. self % offset) call fatalError(Here, 'Cannot have both an offset map '//& + 'and no offset.') + + call dict % get(tempI, 'offsetMap') + + ! Ensure size matches sizeN + if (size(tempI) /= product(self % sizeN)) call fatalError(Here, & + 'Offset map size not equal to size implied by shape. Respectively: '//& + numToChar(size(tempI))//' '//numToChar(product(self % sizeN))) + + ! Flip array up-down for more natural input + ! Reshape into rank 2 array + tempMap = reshape(tempI, [self % sizeN(1), self % sizeN(2) * self % sizeN(3)]) + N = size(tempMap, 2) + do i = 1, N/2 + call swap(tempMap(:,i), tempMap(:,N - i + 1)) + end do + + allocate(self % offsetMap(product(self % sizeN) + 1)) + N = size(tempMap, 1) + do j = 1, size(tempMap, 2) + do i = 1, N + val = tempMap(i,j) + self % offsetMap(i + (j-1) * N) = val + + ! Check that the entries are valid + if (val /= local .and. val /= noOffset) call fatalError(Here,& + 'Invalid entry to the offset map. Must be one of '//numToChar(local)//& + ' '//numToChar(noOffset)//'. Contains: '//numToChar(val)) + end do + end do + ! Add an entry for the padMat + self % offsetMap(self % outLocalID) = noOffset + + end if end subroutine init @@ -254,12 +316,12 @@ end subroutine findCell !! subroutine distance(self, d, surfIdx, coords) class(latUniverse), intent(inout) :: self - real(defReal), intent(out) :: d - integer(shortInt), intent(out) :: surfIdx - type(coord), intent(in) :: coords - real(defReal), dimension(3) :: r_bar, u, bounds - real(defReal) :: test_d - integer(shortInt) :: i, ax + real(defReal), intent(out) :: d + integer(shortInt), intent(out) :: surfIdx + type(coord), intent(in) :: coords + real(defReal), dimension(3) :: r_bar, u, bounds + real(defReal) :: test_d + integer(shortInt) :: i, ax ! Catch case if particle is outside the lattice if (coords % localID == self % outLocalID) then @@ -331,13 +393,20 @@ function cellOffset(self, coords) result (offset) class(latUniverse), intent(in) :: self type(coord), intent(in) :: coords real(defReal), dimension(3) :: offset + logical(defBool) :: doOffset - if (coords % localID == self % outLocalID) then - offset = ZERO - + if (allocated(self % offsetMap)) then + doOffset = self % offsetMap(coords % localID) == local else + doOffset = self % offset + end if + + if (doOffset .and. coords % localID /= self % outLocalID) then offset = (get_ijk(coords % localID, self % sizeN) - HALF) * self % pitch + self % corner + else + offset = ZERO + end if end function cellOffset @@ -358,6 +427,8 @@ elemental subroutine kill(self) self % a_bar = ZERO call self % outline % kill() self % outLocalID = 0 + if (allocated(self % offsetMap)) deallocate(self % offsetMap) + self % offset = .true. end subroutine kill diff --git a/Geometry/Universes/universe_inter.f90 b/Geometry/Universes/universe_inter.f90 index c903a50bd..47afcca57 100644 --- a/Geometry/Universes/universe_inter.f90 +++ b/Geometry/Universes/universe_inter.f90 @@ -38,11 +38,12 @@ module universe_inter !! } !! !! Private Members: - !! uniId -> Id of the universe - !! uniIdx -> Index of the universe - !! origin -> Location of the origin of the universe co-ordinates in the frame of higher universe - !! rotMat -> Rotation matrix for rotation with respect to the higher universe - !! rot -> rotation flag. True is universe is rotated + !! uniId -> Id of the universe + !! uniIdx -> Index of the universe + !! origin -> Location of the origin of the universe co-ordinates in the frame of higher universe + !! rotMat -> Rotation matrix for rotation with respect to the higher universe + !! rot -> rotation flag. True if universe is rotated + !! globalTrans -> global transformation flag. True if universe coordinates should be evaluated in global frame !! !! Interface: !! id -> Get Id of the universe @@ -60,11 +61,12 @@ module universe_inter !! type, public, abstract :: universe private - integer(shortInt) :: uniId = 0 + integer(shortInt), public :: uniId = 0 integer(shortInt) :: uniIdx = 0 real(defReal), dimension(3) :: origin = ZERO real(defReal), dimension(3,3) :: rotMat = ZERO logical(defBool) :: rot = .false. + logical(defBool) :: globalTrans = .false. contains ! Build procedures procedure, non_overridable :: id @@ -81,6 +83,7 @@ module universe_inter procedure(distance), deferred :: distance procedure(cross), deferred :: cross procedure(cellOffset), deferred :: cellOffset + procedure :: transformToGlobal end type universe abstract interface @@ -316,6 +319,11 @@ subroutine setupBase(self, dict) call self % setTransform(rotation=temp) end if + ! Load global translation + if (dict % isPresent('global')) then + call dict % get(self % globalTrans, 'global') + end if + end subroutine setupBase !! @@ -401,13 +409,28 @@ end subroutine enter elemental subroutine kill(self) class(universe), intent(inout) :: self - self % uniIdx = 0 - self % uniId = 0 - self % origin = ZERO - self % rotMat = ZERO - self % rot = .false. + self % uniIdx = 0 + self % uniId = 0 + self % origin = ZERO + self % rotMat = ZERO + self % rot = .false. + self % globalTrans = .false. end subroutine kill + + !! + !! Should co-ordinates be transformed to the global frame? + !! + !! Args: + !! doTrans -> Bool deciding whether to transform the co-ordinates + !! + function transformToGlobal(self) result(doTrans) + class(universe), intent(in) :: self + logical(defBool) :: doTrans + + doTrans = self % globalTrans + + end function transformToGlobal !!<><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><><> !! Utility Functions diff --git a/Geometry/coord_class.f90 b/Geometry/coord_class.f90 index d7900d9a7..5bc9b2daa 100644 --- a/Geometry/coord_class.f90 +++ b/Geometry/coord_class.f90 @@ -18,6 +18,7 @@ module coord_class !! r -> Position !! dir -> Direction !! isRotated -> Is rotated wrt previous (higher by 1) level + !! isGlobal -> Is the coordinate reverted to level 1? !! rotMat -> Rotation matrix wrt previous level !! uniIdx -> Index of the occupied universe !! uniRootID -> Location of the occupied universe in geometry graph @@ -33,6 +34,7 @@ module coord_class real(defReal), dimension(3) :: r = ZERO real(defReal), dimension(3) :: dir = ZERO logical(defBool) :: isRotated = .false. + logical(defBool) :: isGlobal = .false. real(defReal), dimension(3,3) :: rotMat = ZERO integer(shortInt) :: uniIdx = 0 integer(shortInt) :: uniRootID = 0 @@ -45,7 +47,7 @@ module coord_class end type coord !! - !! List of co-ordinates at diffrent level of a geometry + !! List of co-ordinates at different level of a geometry !! !! Specifies the position of a particle in space !! @@ -160,6 +162,7 @@ elemental subroutine kill_coord(self) self % r = ZERO self % dir = ZERO self % isRotated = .false. + self % isGlobal = .false. self % rotMat = ZERO self % uniIdx = 0 self % uniRootID = 0 diff --git a/Geometry/geometryStd_class.f90 b/Geometry/geometryStd_class.f90 index d53e33020..8a10311b7 100644 --- a/Geometry/geometryStd_class.f90 +++ b/Geometry/geometryStd_class.f90 @@ -438,7 +438,7 @@ subroutine diveToMat(self, coords, start) integer(shortInt), intent(in) :: start integer(shortInt) :: rootID, localID, fill, id, i class(universe), pointer :: uni - real(defReal), dimension(3) :: offset + real(defReal), dimension(3) :: offset, r character(100), parameter :: Here = 'diveToMat (geometryStd_class.f90)' do i = start, HARDCODED_MAX_NEST @@ -462,13 +462,21 @@ subroutine diveToMat(self, coords, start) ! Get cell offset offset = uni % cellOffset(coords % lvl(i)) - + ! Get nested universe uni => self % geom % unis % getPtr_fast(fill) + + ! Does this level revert to the global frame? + ! Unrotate direction as well? + if (uni % transformToGlobal()) then + r = coords % lvl(1) % r + else + r = coords % lvl(i) % r - offset + end if ! Enter nested univers call coords % addLevel() - call uni % enter(coords % lvl(i+1), coords % lvl(i) % r - offset, coords % lvl(i) % dir) + call uni % enter(coords % lvl(i+1), r, coords % lvl(i) % dir) coords % lvl(i+1) % uniRootID = id ! Must be after enter where coord has intent out end if diff --git a/InputFiles/Benchmarks/BEAVRS/BEAVRS2D b/InputFiles/Benchmarks/BEAVRS/BEAVRS2D index 0ace8d16c..899a59c71 100644 --- a/InputFiles/Benchmarks/BEAVRS/BEAVRS2D +++ b/InputFiles/Benchmarks/BEAVRS/BEAVRS2D @@ -114,7 +114,8 @@ geometry { thickGrid {type simpleCell; id 55; surfaces (90 -91); filltype mat; material Inconel;} thinGrid {type simpleCell; id 56; surfaces (-92 93); filltype mat; material Inconel;} - pressureVessel { type simpleCell; id 7; surfaces (-1 2); filltype mat; material CarbonSteel;} + ! Does not use surface 1 to define it as that bounds the geometry + pressureVessel { type simpleCell; id 7; surfaces (2); filltype mat; material CarbonSteel;} RPVLiner { type simpleCell; id 8; surfaces (-2 3); filltype mat; material SS304;} outerWater1 {type simpleCell; id 9; surfaces (-3 4 ); filltype mat; material Water;} diff --git a/InputFiles/Benchmarks/BEAVRS/BEAVRS b/InputFiles/Benchmarks/BEAVRS/BEAVRS_ARO similarity index 88% rename from InputFiles/Benchmarks/BEAVRS/BEAVRS rename to InputFiles/Benchmarks/BEAVRS/BEAVRS_ARO index 52e5cb575..89434cfe9 100644 --- a/InputFiles/Benchmarks/BEAVRS/BEAVRS +++ b/InputFiles/Benchmarks/BEAVRS/BEAVRS_ARO @@ -1,16 +1,13 @@ !! !! 3D BEAVRS benchmark -!! This is not a fully faithful replica of BEAVRS at HZP: !! all rods are fully withdrawn. -!! In reality, some rods are partially inserted. -!! TODO: add rods in the appropriate assemblies at the -!! correct heights! +!! This could definitely be better written !! type eigenPhysicsPackage; pop 10000000; active 50; -inactive 200; +inactive 250; XSdata ce; dataType ce; @@ -216,7 +213,8 @@ geometry { thickGrid {type simpleCell; id 555; surfaces (90 ); filltype mat; material Inconel;} thinGrid {type simpleCell; id 556; surfaces (92 ); filltype mat; material Zircaloy;} - pressureVessel { type simpleCell; id 7; surfaces (-1 2); filltype mat; material CarbonSteel;} + // Don't need to bound PV by 1 since it is the bounding surface of the geometry. + pressureVessel { type simpleCell; id 7; surfaces ( 2); filltype mat; material CarbonSteel;} RPVLiner { type simpleCell; id 8; surfaces (-2 3); filltype mat; material SS304;} outerWater1 {type simpleCell; id 9; surfaces (-3 4 ); filltype mat; material Water;} @@ -472,6 +470,9 @@ geometry { GT35 {type simpleCell; id 373; surfaces (-131 132); filltype uni; universe 1005;} GT20 {type simpleCell; id 374; surfaces (-132); filltype uni; universe 1001;} + // Extra GT cells without dashpot for empty instrumentation tubes + CGT98 {type simpleCell; id 379; surfaces (-123 126); filltype uni; universe 9112;} + // control rod, axial layering // Used (probably with some modification) only when fully inserted //CR460 {type simpleCell; id 448; surfaces (-120 121); filltype uni; universe 1002;} @@ -753,9 +754,15 @@ geometry { //instr. tube instrumentTube { - id 14; + id 15; type cellUniverse; cells (198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217);} + + //empty instr. tube + emptyInstrumentTube { + id 11; + type cellUniverse; + cells (353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 379 370 371 372 373 374);} //burnable absorber BP { @@ -764,6 +771,33 @@ geometry { cells (218 219 220 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252);} + // Lattice of instrumentation tubes + instLattice { + type latUniverse; + id 14; + origin (0 0 0); + pitch (21.50364 21.50364 0.0); + shape (15 15 0); + global 1; + padMat Water; + map ( + 11 11 11 11 11 11 15 11 11 15 11 11 11 11 11 + 11 11 15 11 11 15 11 15 11 11 11 11 11 11 11 + 11 11 11 11 11 11 11 15 11 15 11 15 11 15 11 + 11 15 15 11 11 11 11 15 11 11 11 11 11 11 11 + 11 11 11 11 15 11 11 11 15 11 15 11 15 11 11 + 15 11 15 11 11 15 11 15 11 11 11 11 11 15 11 + 11 11 11 15 11 11 15 11 11 15 11 11 15 11 11 + 15 11 15 11 15 11 15 11 11 15 11 15 15 15 11 + 11 15 11 11 11 11 11 11 15 11 15 11 11 11 15 + 11 11 11 11 15 11 15 11 11 11 11 15 11 11 11 + 15 11 11 11 15 11 11 15 11 11 15 11 11 11 15 + 11 11 11 11 11 15 11 11 15 11 11 15 11 11 11 + 11 11 15 11 15 11 11 15 11 11 11 11 11 15 11 + 11 11 15 11 11 11 15 11 11 15 11 15 11 11 11 + 11 11 11 11 15 11 11 15 11 11 11 11 11 11 11 + ); + } // Lattices w/o grid @@ -792,7 +826,8 @@ geometry { 24 24 24 12 24 24 24 24 24 24 24 24 24 12 24 24 24 24 24 24 24 24 12 24 24 12 24 24 12 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 - 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); + } // assembly with sleeves at different heights A0E24Sleeve { @@ -827,7 +862,8 @@ geometry { 16 16 16 12 16 16 16 16 16 16 16 16 16 12 16 16 16 16 16 16 16 16 12 16 16 12 16 16 12 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 - 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16); } + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16); + } A0E16Sleeve { id 14160; @@ -862,7 +898,9 @@ geometry { 31 31 31 12 31 31 31 31 31 31 31 31 31 12 31 31 31 31 31 31 31 31 12 31 31 12 31 31 12 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A0E31Sleeve { id 14310; @@ -898,7 +936,9 @@ geometry { 31 31 31 12 31 31 31 31 31 31 31 31 31 12 31 31 31 31 31 31 31 31 12 31 31 12 31 31 12 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A6BE31BSleeve { @@ -934,7 +974,9 @@ geometry { 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 31 31 31 31 31 10 31 31 12 31 31 10 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A6BE31TSleeve { id 6031120; @@ -969,7 +1011,9 @@ geometry { 31 31 31 10 31 31 31 31 31 31 31 31 31 12 31 31 31 31 31 31 31 31 10 31 31 12 31 31 12 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A6BE31RSleeve { id 603130; @@ -1004,7 +1048,9 @@ geometry { 31 31 31 12 31 31 31 31 31 31 31 31 31 10 31 31 31 31 31 31 31 31 12 31 31 12 31 31 10 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A6BE31LSleeve { id 603190; @@ -1039,7 +1085,9 @@ geometry { 31 31 31 12 31 31 31 31 31 31 31 31 31 12 31 31 31 31 31 31 31 31 12 31 31 12 31 31 12 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A15BE31BRSleeve { id 153150; @@ -1074,7 +1122,9 @@ geometry { 31 31 31 12 31 31 31 31 31 31 31 31 31 12 31 31 31 31 31 31 31 31 12 31 31 12 31 31 12 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A15BE31BLSleeve { id 153170; @@ -1109,7 +1159,9 @@ geometry { 31 31 31 10 31 31 31 31 31 31 31 31 31 12 31 31 31 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A15BE31TRSleeve { id 153110; @@ -1144,7 +1196,9 @@ geometry { 31 31 31 12 31 31 31 31 31 31 31 31 31 10 31 31 31 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A15BE31TLSleeve { id 1531110; @@ -1179,7 +1233,9 @@ geometry { 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A16BE31Sleeve { id 16310; @@ -1214,7 +1270,9 @@ geometry { 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A20BE31Sleeve { id 20310; @@ -1249,7 +1307,9 @@ geometry { 24 24 24 10 24 24 24 24 24 24 24 24 24 10 24 24 24 24 24 24 24 24 10 24 24 12 24 24 10 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 - 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); + + } A12BE24Sleeve { id 12240; @@ -1284,7 +1344,9 @@ geometry { 24 24 24 10 24 24 24 24 24 24 24 24 24 10 24 24 24 24 24 24 24 24 10 24 24 10 24 24 10 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 - 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); + + } A16BE24Sleeve { id 16240; @@ -1320,7 +1382,9 @@ geometry { 24 24 24 13 24 24 24 24 24 24 24 24 24 13 24 24 24 24 24 24 24 24 13 24 24 13 24 24 13 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 - 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); + + } A0E24USleeve { id 24240; @@ -1354,7 +1418,8 @@ geometry { 16 16 16 13 16 16 16 16 16 16 16 16 16 13 16 16 16 16 16 16 16 16 13 16 16 13 16 16 13 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 - 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16); } + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16); + } // sleeved A0E16USleeve { @@ -1390,7 +1455,9 @@ geometry { 31 31 31 13 31 31 31 31 31 31 31 31 31 13 31 31 31 31 31 31 31 31 13 31 31 13 31 31 13 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A0E31USleeve { id 24310; @@ -1426,7 +1493,9 @@ geometry { 31 31 31 13 31 31 31 31 31 31 31 31 31 13 31 31 31 31 31 31 31 31 13 31 31 13 31 31 13 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A6BE31BUSleeve { @@ -1462,7 +1531,9 @@ geometry { 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 31 31 31 31 31 10 31 31 13 31 31 10 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A6BE31TUSleeve { id 7031120; @@ -1497,7 +1568,9 @@ geometry { 31 31 31 10 31 31 31 31 31 31 31 31 31 13 31 31 31 31 31 31 31 31 10 31 31 13 31 31 13 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A6BE31RUSleeve { id 703130; @@ -1532,7 +1605,9 @@ geometry { 31 31 31 13 31 31 31 31 31 31 31 31 31 10 31 31 31 31 31 31 31 31 13 31 31 13 31 31 10 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A6BE31LUSleeve { id 703190; @@ -1567,7 +1642,9 @@ geometry { 31 31 31 13 31 31 31 31 31 31 31 31 31 13 31 31 31 31 31 31 31 31 13 31 31 13 31 31 13 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A15BE31BRUSleeve { id 253150; @@ -1602,7 +1679,9 @@ geometry { 31 31 31 13 31 31 31 31 31 31 31 31 31 13 31 31 31 31 31 31 31 31 13 31 31 13 31 31 13 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A15BE31BLUSleeve { id 253170; @@ -1637,7 +1716,10 @@ geometry { 31 31 31 10 31 31 31 31 31 31 31 31 31 13 31 31 31 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + + } A15BE31TRUSleeve { id 253110; @@ -1672,7 +1754,9 @@ geometry { 31 31 31 13 31 31 31 31 31 31 31 31 31 10 31 31 31 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A15BE31TLUSleeve { id 2531110; @@ -1707,7 +1791,9 @@ geometry { 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A16BE31USleeve { id 26310; @@ -1742,7 +1828,9 @@ geometry { 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 - 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); + + } A20BE31USleeve { id 30310; @@ -1777,7 +1865,9 @@ geometry { 24 24 24 10 24 24 24 24 24 24 24 24 24 10 24 24 24 24 24 24 24 24 10 24 24 13 24 24 10 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 - 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); + + } A12BE24USleeve { id 22240; @@ -1812,7 +1902,8 @@ geometry { 24 24 24 10 24 24 24 24 24 24 24 24 24 10 24 24 24 24 24 24 24 24 10 24 24 10 24 24 10 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 - 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); + } A16BE24USleeve { id 26240; @@ -1933,7 +2024,7 @@ viz { output imgZ; what material; centre (0.0 0.0 232.0); - //width (400.0 400.0); + width (100.0 100.0); axis z; res (4000 4000); } @@ -1946,222 +2037,219 @@ nuclearData { } materials { - - // Note that commented nuclide densities are included in the specification - // but are not available in the JEFF-3.11 data library - - Air { + + Air { temp 566; composition { - 18036.06 7.8730E-09; - 18038.06 1.4844E-09; - 18040.06 2.3506E-06; - 6012.06 6.7539E-08; - //6013.06 7.5658E-10; - 7014.06 1.9680E-04; - 7015.06 7.2354E-07; - 8016.06 5.2866E-05; - 8017.06 2.0084E-08; - //8018.06 1.0601E-07; - } + 18036.01 7.8730E-09; + 18038.01 1.4844E-09; + 18040.01 2.3506E-06; + 6012.01 6.7539E-08; + 6013.01 7.5658E-10; + 7014.01 1.9680E-04; + 7015.01 7.2354E-07; + 8016.01 5.2866E-05; + 8017.01 2.0084E-08; + 8018.01 1.0601E-07; } + } SS304 { temp 566; composition { - 24050.06 7.6778E-04; - 24052.06 1.4806E-02; - 24053.06 1.6789E-03; - 24054.06 4.1791E-04; - 26054.06 3.4620E-03; - 26056.06 5.4345E-02; - 26057.06 1.2551E-03; - 26058.06 1.6703E-04; - 25055.06 1.7604E-03; - 28058.06 5.6089E-03; - 28060.06 2.1605E-03; - 28061.06 9.3917E-05; - 28062.06 2.9945E-04; - 28064.06 7.6261E-05; - 14028.06 9.5281E-04; - 14029.06 4.8381E-05; - 14030.06 3.1893E-05; } + 24050.01 7.6778E-04; + 24052.01 1.4806E-02; + 24053.01 1.6789E-03; + 24054.01 4.1791E-04; + 26054.01 3.4620E-03; + 26056.01 5.4345E-02; + 26057.01 1.2551E-03; + 26058.01 1.6703E-04; + 25055.01 1.7604E-03; + 28058.01 5.6089E-03; + 28060.01 2.1605E-03; + 28061.01 9.3917E-05; + 28062.01 2.9945E-04; + 28064.01 7.6261E-05; + 14028.01 9.5281E-04; + 14029.01 4.8381E-05; + 14030.01 3.1893E-05; } } Helium { temp 566; composition { - 2003.06 4.8089E-10; - 2004.06 2.4044E-04; } + 2003.01 4.8089E-10; + 2004.01 2.4044E-04; } } BorosilicateGlass { temp 566; composition { - 13027.06 1.7352E-03; - 5010.06 9.6506E-04; - 5011.06 3.9189E-03; - 8016.06 4.6514E-02; - 8017.06 1.7671E-05; - //8018.06 9.3268E-05; - 14028.06 1.6926E-02; - 14029.06 8.5944E-04; - 14030.06 5.6654E-04; } + 13027.01 1.7352E-03; + 5010.01 9.6506E-04; + 5011.01 3.9189E-03; + 8016.01 4.6514E-02; + 8017.01 1.7671E-05; + 8018.01 9.3268E-05; + 14028.01 1.6926E-02; + 14029.01 8.5944E-04; + 14030.01 5.6654E-04; } } Water { temp 566; - moder {1001.06 (lwj3.11 lwj3.09); } + moder {1001.01 (h-h2o.52 h-h2o.53); } composition { - 5010.06 7.9714E-06; - 5011.06 3.2247E-05; - 1001.06 4.9456E-02; - 1002.06 7.7035E-06; - 8016.06 2.4673E-02; - 8017.06 9.3734E-06; - //8018.06 4.9474E-05; + 5010.01 7.9714E-06; + 5011.01 3.2247E-05; + 1001.01 4.9456E-02; + 1002.01 7.7035E-06; + 8016.01 2.4673E-02; + 8017.01 9.3734E-06; + 8018.01 4.9474E-05; } } Zircaloy { temp 566; composition { - 24050.06 3.2962E-06; - 24052.06 6.3564E-05; - 24053.06 7.2076E-06; - 24054.06 1.7941E-06; - 26054.06 8.6698E-06; - 26056.06 1.3610E-04; - 26057.06 3.1431E-06; - 26058.06 4.1829E-07; - 8016.06 3.0744E-04; - 8017.06 1.1680E-07; - //8018.03 6.1648E-07; - 50112.06 4.6735E-06; - 50114.06 3.1799E-06; - 50115.06 1.6381E-06; - 50116.06 7.0055E-05; - 50117.06 3.7003E-05; - 50118.06 1.1669E-04; - 50119.06 4.1387E-05; - 50120.06 1.5697E-04; - 50122.06 2.2308E-05; - 50124.06 2.7897E-05; - 40090.06 2.1828E-02; - 40091.06 4.7601E-03; - 40092.06 7.2759E-03; - 40094.06 7.3734E-03; - 40096.06 1.1879E-03; } + 24050.01 3.2962E-06; + 24052.01 6.3564E-05; + 24053.01 7.2076E-06; + 24054.01 1.7941E-06; + 26054.01 8.6698E-06; + 26056.01 1.3610E-04; + 26057.01 3.1431E-06; + 26058.01 4.1829E-07; + 8016.01 3.0744E-04; + 8017.01 1.1680E-07; + 8018.01 6.1648E-07; + 50112.01 4.6735E-06; + 50114.01 3.1799E-06; + 50115.01 1.6381E-06; + 50116.01 7.0055E-05; + 50117.01 3.7003E-05; + 50118.01 1.1669E-04; + 50119.01 4.1387E-05; + 50120.01 1.5697E-04; + 50122.01 2.2308E-05; + 50124.01 2.7897E-05; + 40090.01 2.1828E-02; + 40091.01 4.7601E-03; + 40092.01 7.2759E-03; + 40094.01 7.3734E-03; + 40096.01 1.1879E-03; } } Inconel{ temp 566; composition { - 24050.06 7.8239E-04; - 24052.06 1.5088E-02; - 24053.06 1.7108E-03; - 24054.06 4.2586E-04; - 26054.06 1.4797E-03; - 26056.06 2.3229E-02; - 26057.06 5.3645E-04; - 26058.06 7.1392E-05; - 25055.06 7.8201E-04; - 28058.06 2.9320E-02; - 28060.06 1.1294E-02; - 28061.06 4.9094E-04; - 28062.06 1.5653E-03; - 28064.06 3.9864E-04; - 14028.06 5.6757E-04; - 14029.06 2.8820E-05; - 14030.06 1.8998E-05; } + 24050.01 7.8239E-04; + 24052.01 1.5088E-02; + 24053.01 1.7108E-03; + 24054.01 4.2586E-04; + 26054.01 1.4797E-03; + 26056.01 2.3229E-02; + 26057.01 5.3645E-04; + 26058.01 7.1392E-05; + 25055.01 7.8201E-04; + 28058.01 2.9320E-02; + 28060.01 1.1294E-02; + 28061.01 4.9094E-04; + 28062.01 1.5653E-03; + 28064.01 3.9864E-04; + 14028.01 5.6757E-04; + 14029.01 2.8820E-05; + 14030.01 1.8998E-05; } } B4C{ temp 566; composition { - 5010.06 1.5206E-02; - 5011.06 6.1514E-02; - 6012.06 1.8972E-02; - //6013.06 2.1252E-04; + 5010.01 1.5206E-02; + 5011.01 6.1514E-02; + 6012.01 1.8972E-02; + 6013.01 2.1252E-04; } } Ag-In-Cd{ temp 566; composition { - 47107.06 2.3523E-02; - 47109.06 2.1854E-02; - 48106.06 3.3882E-05; - 48108.06 2.4166E-05; - 48110.06 3.3936E-04; - 48111.06 3.4821E-04; - 48112.06 6.5611E-04; - 48113.06 3.3275E-04; - 48114.06 7.8252E-04; - 48116.06 2.0443E-04; - 49113.06 3.4219E-04; - 49115.06 7.6511E-03; } + 47107.01 2.3523E-02; + 47109.01 2.1854E-02; + 48106.01 3.3882E-05; + 48108.01 2.4166E-05; + 48110.01 3.3936E-04; + 48111.01 3.4821E-04; + 48112.01 6.5611E-04; + 48113.01 3.3275E-04; + 48114.01 7.8252E-04; + 48116.01 2.0443E-04; + 49113.01 3.4219E-04; + 49115.01 7.6511E-03; } } UO2-16 { temp 566; tms 1; composition { - 8016.03 4.5897E-02; - 8017.03 1.7436E-05; - //8018.03 9.2032E-05; - 92234.03 3.0131E-06; - 92235.03 3.7503E-04; - 92238.03 2.2625E-02;} + 8016.00 4.5897E-02; + 8017.00 1.7436E-05; + 8018.00 9.2032E-05; + 92234.00 3.0131E-06; + 92235.00 3.7503E-04; + 92238.00 2.2625E-02;} } UO2-24 { temp 566; tms 1; composition { - 8016.03 4.5830E-02; - 8017.03 1.7411E-05; - //8018.03 9.1898E-05; - 92234.03 4.4842E-06; - 92235.03 5.5814E-04; - 92238.03 2.2407E-02;} + 8016.00 4.5830E-02; + 8017.00 1.7411E-05; + 8018.00 9.1898E-05; + 92234.00 4.4842E-06; + 92235.00 5.5814E-04; + 92238.00 2.2407E-02;} } UO2-31 { temp 566; tms 1; composition { - 8016.03 4.5853E-02; - 8017.03 1.7420E-05; - //8018.03 9.1942E-05; - 92234.03 5.7987E-06; - 92235.03 7.2175E-04; - 92238.03 2.2253E-02;} + 8016.00 4.5853E-02; + 8017.00 1.7420E-05; + 8018.00 9.1942E-05; + 92234.00 5.7987E-06; + 92235.00 7.2175E-04; + 92238.00 2.2253E-02;} } UO2-32 { temp 566; tms 1; composition { - 8016.03 4.6029E-02; - 8017.03 1.7487E-05; - //8018.03 9.2296E-05; - 92234.03 5.9959E-06; - 92235.03 7.4630E-04; - 92238.03 2.2317E-02; + 8016.00 4.6029E-02; + 8017.00 1.7487E-05; + 8018.00 9.2296E-05; + 92234.00 5.9959E-06; + 92235.00 7.4630E-04; + 92238.00 2.2317E-02; } } - + UO2-34 { temp 566; tms 1; composition { - 8016.03 4.6110E-02; - 8017.03 1.7517E-05; - //8018.03 9.2459E-05; - 92234.03 6.4018E-06; - 92235.03 7.9681E-04; - 92238.03 2.2307E-02;} + 8016.00 4.6110E-02; + 8017.00 1.7517E-05; + 8018.00 9.2459E-05; + 92234.00 6.4018E-06; + 92235.00 7.9681E-04; + 92238.00 2.2307E-02;} } // vanadium51 was stated twice in carbonsteel below @@ -2169,95 +2257,94 @@ nuclearData { CarbonSteel { temp 566; composition { - 13027.06 4.3523E-05; - 5010.06 2.5833E-06; - 5011.06 1.0450E-05; - 6012.06 1.0442E-03; - //6013.06 1.1697E-05 ; - 20040.06 1.7043E-05; - 20042.06 1.1375E-07; - 20043.06 2.3734E-08; - 20044.06 3.6673E-07; - 20046.06 7.0322E-10; - 20048.06 3.2875E-08; - 24050.06 1.3738E-05; - 24052.06 2.6493E-04; - 24053.06 3.0041E-05; - 24054.06 7.4778E-06; - 29063.06 1.0223E-04; - 29065.06 4.5608E-05; - 26054.06 4.7437E-03; - 26056.06 7.4465E-02; - 26057.06 1.7197E-03; - 26058.06 2.2886E-04; - 25055.06 6.4126E-04; - 42100.06 2.9814E-05; - 42092.06 4.4822E-05; - 42094.06 2.8110E-05; - 42095.06 4.8567E-05; - 42096.06 5.1015E-05; - 42097.06 2.9319E-05; - 42098.06 7.4327E-05; - 41093.06 5.0559E-06; - 28058.06 4.0862E-04; - 28060.06 1.5740E-04; - 28061.06 6.8420E-06; - 28062.06 2.1815E-05; - 28064.06 5.5557E-06; - 15031.06 3.7913E-05; - 16032.06 3.4808E-05; - 16033.06 2.7420E-07; - 16034.06 1.5368E-06; - 16036.06 5.3398E-09; - 14028.06 6.1702E-04; - 14029.06 3.1330E-05; - 14030.06 2.0653E-05; - 22046.06 1.2144E-06; - 22047.06 1.0952E-06; - 22048.06 1.0851E-05; - 22049.06 7.9634E-07; - 22050.06 7.6249E-07; - //23050.06 1.1526E-07; - 23051.06 4.5989E-05; + 13027.01 4.3523E-05; + 5010.01 2.5833E-06; + 5011.01 1.0450E-05; + 6012.01 1.0442E-03; + 6013.01 1.1697E-05 ; + 20040.01 1.7043E-05; + 20042.01 1.1375E-07; + 20043.01 2.3734E-08; + 20044.01 3.6673E-07; + 20046.01 7.0322E-10; + 20048.01 3.2875E-08; + 24050.01 1.3738E-05; + 24052.01 2.6493E-04; + 24053.01 3.0041E-05; + 24054.01 7.4778E-06; + 29063.01 1.0223E-04; + 29065.01 4.5608E-05; + 26054.01 4.7437E-03; + 26056.01 7.4465E-02; + 26057.01 1.7197E-03; + 26058.01 2.2886E-04; + 25055.01 6.4126E-04; + 42100.01 2.9814E-05; + 42092.01 4.4822E-05; + 42094.01 2.8110E-05; + 42095.01 4.8567E-05; + 42096.01 5.1015E-05; + 42097.01 2.9319E-05; + 42098.01 7.4327E-05; + 41093.01 5.0559E-06; + 28058.01 4.0862E-04; + 28060.01 1.5740E-04; + 28061.01 6.8420E-06; + 28062.01 2.1815E-05; + 28064.01 5.5557E-06; + 15031.01 3.7913E-05; + 16032.01 3.4808E-05; + 16033.01 2.7420E-07; + 16034.01 1.5368E-06; + 16036.01 5.3398E-09; + 14028.01 6.1702E-04; + 14029.01 3.1330E-05; + 14030.01 2.0653E-05; + 22046.01 1.2144E-06; + 22047.01 1.0952E-06; + 22048.01 1.0851E-05; + 22049.01 7.9634E-07; + 22050.01 7.6249E-07; + 23050.01 1.1526E-07; + 23051.01 4.5989E-05; } } SupportPlateSS { temp 566; composition { - 24050.06 3.5223E-04; - 24052.06 6.7924E-03; - 24053.06 7.7020E-04; - 24054.06 1.9172E-04; - 26054.06 1.5882E-03; - 26056.06 2.4931E-02; - 26057.06 5.7578E-04; - 26058.06 7.6625E-05; - 25055.06 8.0762E-04; - 28058.06 2.5731E-03; - 28060.06 9.9117E-04; - 28061.06 4.3085E-05; - 28062.06 1.3738E-04; - 28064.06 3.4985E-05; - 14028.06 4.3711E-04; - 14029.06 2.2195E-05; - 14030.06 1.4631E-05;} + 24050.01 3.5223E-04; + 24052.01 6.7924E-03; + 24053.01 7.7020E-04; + 24054.01 1.9172E-04; + 26054.01 1.5882E-03; + 26056.01 2.4931E-02; + 26057.01 5.7578E-04; + 26058.01 7.6625E-05; + 25055.01 8.0762E-04; + 28058.01 2.5731E-03; + 28060.01 9.9117E-04; + 28061.01 4.3085E-05; + 28062.01 1.3738E-04; + 28064.01 3.4985E-05; + 14028.01 4.3711E-04; + 14029.01 2.2195E-05; + 14030.01 1.4631E-05;} } SupportPlateBW { temp 566; - moder {1001.06 (lwj3.11 lwj3.09); } + moder {1001.01 (h-h2o.52 h-h2o.53); } composition { - 5010.06 1.0559E-05; - 5011.06 4.2716E-05; - 1001.06 6.5512E-02; - 1002.06 1.0204E-05; - 8016.06 3.2683E-02; - 8017.06 1.2416E-05; - //8018.06 6.5535E-05; + 5010.01 1.0559E-05; + 5011.01 4.2716E-05; + 1001.01 6.5512E-02; + 1002.01 1.0204E-05; + 8016.01 3.2683E-02; + 8017.01 1.2416E-05; + 8018.01 6.5535E-05; } } - } } diff --git a/InputFiles/Benchmarks/BEAVRS/BEAVRS_HZP b/InputFiles/Benchmarks/BEAVRS/BEAVRS_HZP new file mode 100644 index 000000000..09102661b --- /dev/null +++ b/InputFiles/Benchmarks/BEAVRS/BEAVRS_HZP @@ -0,0 +1,2468 @@ +!! +!! 3D BEAVRS benchmark +!! At HZP, the D bank of rods is partially inserted up +!! to 15 steps inserted / 213 steps withdrawn. +!! A step corresponds to an increment of 1.58193cm. +!! Hence the D bank is inserted by 23.7255cm. +!! +!! This could probably be written in a much more efficient and +!! understandable way! For example, by being more clever with +!! transformations. +!! +type eigenPhysicsPackage; + +pop 10000000; +active 100; +inactive 250; +XSdata ce; +dataType ce; + +collisionOperator { neutronCE {type neutronCEstd;}} + +transportOperator { + !type transportOperatorDT; + type transportOperatorHT; cache 1; + } + +inactiveTally { + shannon { + type shannonEntropyClerk; + map {type multiMap; + maps (xax yax zax); + xax { type spaceMap; grid lin; min -161.2773; max 161.2773; N 15; axis x;} + yax { type spaceMap; grid lin; min -161.2773; max 161.2773; N 15; axis y;} + zax { type spaceMap; grid lin; min 36.748; max 402.508; N 15; axis z;} + } + cycles 250; + } + +} + +activeTally { + pinFissRadial { type collisionClerk; response (fission); fission { type macroResponse; MT -6;} + map {type multiMap; maps (xax yax); + xax {type spaceMap; axis x; grid lin; N 255; min -161.2773; max 161.2773; } + yax {type spaceMap; axis y; grid lin; N 255; min -161.2773; max 161.2773; } + } + } + pinFlxRadial { type collisionClerk; response (flx); flx { type fluxResponse;} + map {type multiMap; maps (xax yax emap); + xax {type spaceMap; axis x; grid lin; N 255; min -161.2773; max 161.2773; } + yax {type spaceMap; axis y; grid lin; N 255; min -161.2773; max 161.2773; } + emap {type energyMap; grid unstruct; bins (1.0E-11 0.625E-6 20); } + } + } + assemblyFissRadial { type collisionClerk; response (fission); fission { type macroResponse; MT -6;} + map {type multiMap; maps (xax yax); + xax {type spaceMap; axis x; grid lin; N 15; min -161.2773; max 161.2773; } + yax {type spaceMap; axis y; grid lin; N 15; min -161.2773; max 161.2773; } + } + } + fissionAxial { type collisionClerk; response (fission); fission { type macroResponse; MT -6;} + map {type spaceMap; axis z; grid lin; N 60; min 36.748; max 402.508;} + } + !fissionYZ { type collisionClerk; response (fission); fission { type macroResponse; MT -6;} + ! map {type multiMap; maps (yax zax); + ! yax {type spaceMap; axis y; grid lin; N 255; min -161.2773; max 161.2773; } + ! zax {type spaceMap; axis z; grid lin; N 60; min 36.748; max 402.508;} + ! } + ! } +} + +geometry { + type geometryStd; + boundary ( 0 0 0 0 0 0); + graph {type shrunk;} + + surfaces { + + // thickness specifications for RPV and RPV liner + outerRPV { id 1; type zTruncCylinder; radius 241.3; origin (0.0 0.0 230.0); halfwidth 230; } + innerRPV { id 2; type zCylinder; radius 219.710; origin (0.0 0.0 0.0); } + innerRPVLiner { id 3; type zCylinder; radius 219.150; origin (0.0 0.0 0.0); } + + // thickness specifications for neutron shield + outerBoundNS { id 4; type zCylinder; radius 201.630; origin (0.0 0.0 0.0); } + innerBoundNS { id 5; type zCylinder; radius 194.84; origin (0.0 0.0 0.0); } + + // thickness specifications for core barrel + outerCoreBarrel { id 6; type zCylinder; radius 193.675; origin (0.0 0.0 0.0); } + innerCoreBarrel { id 7; type zCylinder; radius 187.96; origin (0.0 0.0 0.0); } + + // four planes that intersect to bound the Neutron shield panel + P1 { id 8; type plane; coeffs (-0.48480962025 0.87461970714 0.0 0.0);} + P2 { id 9; type plane; coeffs (-0.87461970714 0.48480962025 0.0 0.0);} + P3 { id 10; type plane; coeffs (-0.87461970714 -0.48480962025 0.0 0.0);} + P4 { id 11; type plane; coeffs (-0.48480962025 -0.87461970714 0.0 0.0);} + + // bounding widths for baffle on various sides + // right & left refers to the side of the reactor that it is on + // close/away refers to its location in relation to the LATTICE it is a part of + // (NOT the reactor itself) + rightClose { id 50; type plane; coeffs (1.0 0.0 0.0 8.36662);} + rightAway { id 51; type plane; coeffs (1.0 0.0 0.0 10.58912);} + leftClose { id 52; type plane; coeffs (-1.0 0.0 0.0 8.36662);} + leftAway { id 53; type plane; coeffs (-1.0 0.0 0.0 10.58912);} + bottomClose { id 54; type plane; coeffs (0.0 -1.0 0.0 8.36662);} + bottomAway { id 55; type plane; coeffs (0.0 -1.0 0.0 10.58912);} + topClose { id 56; type plane; coeffs (0.0 1.0 0.0 8.36662);} + topAway { id 57; type plane; coeffs (0.0 1.0 0.0 10.58912);} + + // thickness specifications for grid with thickness of 0.0198cm (Inconel) + pinThickGridInner { id 90; type zSquareCylinder; origin (0.0 0.0 0.0); halfwidth (0.61015 0.61015 0.0); } + pinThickGridOuter { id 91; type zSquareCylinder; origin (0.0 0.0 0.0); halfwidth (0.62992 0.62992 0.0); } + + // thickness specifications for grid with thickness of 0.0194cm (Zircaloy) + pinThinGridInner { id 92; type zSquareCylinder; origin (0.0 0.0 0.0); halfwidth (0.61049 0.61049 0.0); } + pinThinGridOuter { id 93; type zSquareCylinder; origin (0.0 0.0 0.0); halfwidth (0.62992 0.62992 0.0); } + + // inner and outer surfaces of assembly sleeves (both SS and Zircaloy) + assemblySleeveInner { id 94; type zSquareCylinder; origin (0.0 0.0 0.0); halfwidth (10.70864 10.70864 0.0); } + assemblySleeveOuter { id 95; type zSquareCylinder; origin (0.0 0.0 0.0); halfwidth (10.74798 10.74798 0.0); } + + + // Axial planes across core height + // Names are based on axial heights + plane460 { id 100; type plane; coeffs (0.0 0.0 1.0 460.0 ); } + plane431p876 { id 101; type plane; coeffs (0.0 0.0 1.0 431.876); } + plane423p049 { id 102; type plane; coeffs (0.0 0.0 1.0 423.049); } + plane421p532 { id 103; type plane; coeffs (0.0 0.0 1.0 421.532); } + plane419p704 { id 104; type plane; coeffs (0.0 0.0 1.0 419.704); } + plane417p164 { id 105; type plane; coeffs (0.0 0.0 1.0 417.164); } + plane415p164 { id 106; type plane; coeffs (0.0 0.0 1.0 415.164); } + plane411p806 { id 107; type plane; coeffs (0.0 0.0 1.0 411.806); } + plane403p778 { id 108; type plane; coeffs (0.0 0.0 1.0 403.778); } + plane402p508 { id 109; type plane; coeffs (0.0 0.0 1.0 402.508); } + plane401p238 { id 110; type plane; coeffs (0.0 0.0 1.0 401.238); } + plane364p725 { id 111; type plane; coeffs (0.0 0.0 1.0 364.725); } + plane359p01 { id 112; type plane; coeffs (0.0 0.0 1.0 359.01 ); } + plane312p528 { id 113; type plane; coeffs (0.0 0.0 1.0 312.528); } + plane306p813 { id 114; type plane; coeffs (0.0 0.0 1.0 306.813); } + plane260p331 { id 115; type plane; coeffs (0.0 0.0 1.0 260.331); } + plane254p616 { id 116; type plane; coeffs (0.0 0.0 1.0 254.616); } + plane208p134 { id 117; type plane; coeffs (0.0 0.0 1.0 208.134); } + plane202p419 { id 118; type plane; coeffs (0.0 0.0 1.0 202.419); } + plane155p937 { id 119; type plane; coeffs (0.0 0.0 1.0 155.937); } + plane150p222 { id 120; type plane; coeffs (0.0 0.0 1.0 150.222); } + plane143p428 { id 121; type plane; coeffs (0.0 0.0 1.0 143.428); } + plane103p74 { id 122; type plane; coeffs (0.0 0.0 1.0 103.74 ); } + plane98p025 { id 123; type plane; coeffs (0.0 0.0 1.0 98.025 ); } + plane41p828 { id 124; type plane; coeffs (0.0 0.0 1.0 41.828 ); } + plane40p558 { id 125; type plane; coeffs (0.0 0.0 1.0 40.558 ); } + plane40p52 { id 126; type plane; coeffs (0.0 0.0 1.0 40.52 ); } + plane39p958 { id 127; type plane; coeffs (0.0 0.0 1.0 39.958 ); } + plane38p66 { id 128; type plane; coeffs (0.0 0.0 1.0 38.66 ); } + plane37p1621 { id 129; type plane; coeffs (0.0 0.0 1.0 37.1621); } + plane36p748 { id 130; type plane; coeffs (0.0 0.0 1.0 36.748 ); } + plane35 { id 131; type plane; coeffs (0.0 0.0 1.0 35.0 ); } + plane20 { id 132; type plane; coeffs (0.0 0.0 1.0 20.0 ); } + plane0 { id 133; type plane; coeffs (0.0 0.0 1.0 0.0 ); } + + planeSteelBottom { id 134; type plane; coeffs (0.0 0.0 1.0 400.638); } + planeCRLowerBottom { id 135; type plane; coeffs (0.0 0.0 1.0 402.508); } // same as 109 on withdrawal + planeCRUpperBottom { id 136; type plane; coeffs (0.0 0.0 1.0 504.108); } // out of core on withdrawal + + !plane322p1861 {id 137; type plane; coeffs (0 0 1 322.18609);} + plane478p512 {id 137; type plane; coeffs (0 0 1 478.51249);} + !plane220p586 {id 138; type plane; coeffs (0 0 1 220.5861);} + plane378p783 {id 138; type plane; coeffs (0 0 1 378.783);} + !plane218p716 {id 139; type plane; coeffs (0 0 1 218.71609);} + planep376p913 {id 139; type plane; coeffs (0 0 1 376.9125);} + + } + + cells { + + // assembly wrappers and surrounding water at various heights + wrapper1 {type simpleCell; id 2001; surfaces (94 -95 129 -126); filltype mat; material SS304;} + wrapper2 {type simpleCell; id 2002; surfaces (94 -95 123 -122); filltype mat; material Zircaloy;} + wrapper3 {type simpleCell; id 2003; surfaces (94 -95 120 -119); filltype mat; material Zircaloy;} + wrapper4 {type simpleCell; id 2004; surfaces (94 -95 118 -117); filltype mat; material Zircaloy;} + wrapper5 {type simpleCell; id 2005; surfaces (94 -95 116 -115); filltype mat; material Zircaloy;} + wrapper6 {type simpleCell; id 2006; surfaces (94 -95 114 -113); filltype mat; material Zircaloy;} + wrapper7 {type simpleCell; id 2007; surfaces (94 -95 112 -111); filltype mat; material Zircaloy;} + wrapper8 {type simpleCell; id 2008; surfaces (94 -95 107 -106); filltype mat; material SS304;} + + assemWater0 {type simpleCell; id 2009; surfaces (94 -129); filltype mat; material Water;} + assemWater1 {type simpleCell; id 2010; surfaces (94 -95 126 -123); filltype mat; material Water;} + assemWater2 {type simpleCell; id 2011; surfaces (94 -95 122 -120); filltype mat; material Water;} + assemWater3 {type simpleCell; id 2012; surfaces (94 -95 119 -118); filltype mat; material Water;} + assemWater4 {type simpleCell; id 2013; surfaces (94 -95 117 -116); filltype mat; material Water;} + assemWater5 {type simpleCell; id 2014; surfaces (94 -95 115 -114); filltype mat; material Water;} + assemWater6 {type simpleCell; id 2015; surfaces (94 -95 113 -112); filltype mat; material Water;} + assemWater7 {type simpleCell; id 2016; surfaces (94 -95 111 -107); filltype mat; material Water;} + assemWater8 {type simpleCell; id 2017; surfaces (94 -95 106); filltype mat; material Water;} + assemWaterEx {type simpleCell; id 2018; surfaces (95); filltype mat; material Water;} + + // assemblies inside the wrappers + assem1424 {type simpleCell; id 2019; surfaces (-94); filltype uni; universe 1424;} + assem1416 {type simpleCell; id 2020; surfaces (-94); filltype uni; universe 1416;} + assem1431 {type simpleCell; id 2021; surfaces (-94); filltype uni; universe 1431;} + assem60316 {type simpleCell; id 2022; surfaces (-94); filltype uni; universe 60316;} + assem603112 {type simpleCell; id 2023; surfaces (-94); filltype uni; universe 603112;} + assem60313 {type simpleCell; id 2024; surfaces (-94); filltype uni; universe 60313;} + assem60319 {type simpleCell; id 2025; surfaces (-94); filltype uni; universe 60319;} + assem15315 {type simpleCell; id 2026; surfaces (-94); filltype uni; universe 15315;} + assem15317 {type simpleCell; id 2027; surfaces (-94); filltype uni; universe 15317;} + assem15311 {type simpleCell; id 2028; surfaces (-94); filltype uni; universe 15311;} + assem153111 {type simpleCell; id 2029; surfaces (-94); filltype uni; universe 153111;} + assem1631 {type simpleCell; id 2030; surfaces (-94); filltype uni; universe 1631;} + assem2031 {type simpleCell; id 2031; surfaces (-94); filltype uni; universe 2031;} + assem1224 {type simpleCell; id 2032; surfaces (-94); filltype uni; universe 1224;} + assem1624 {type simpleCell; id 2033; surfaces (-94); filltype uni; universe 1624;} + + // unrodded assemblies in wrappers + assem2424 {type simpleCell; id 2034; surfaces (-94); filltype uni; universe 2424;} + assem2416 {type simpleCell; id 2035; surfaces (-94); filltype uni; universe 2416;} + assem2431 {type simpleCell; id 2036; surfaces (-94); filltype uni; universe 2431;} + assem70316 {type simpleCell; id 2037; surfaces (-94); filltype uni; universe 70316;} + assem703112 {type simpleCell; id 2038; surfaces (-94); filltype uni; universe 703112;} + assem70313 {type simpleCell; id 2039; surfaces (-94); filltype uni; universe 70313;} + assem70319 {type simpleCell; id 2040; surfaces (-94); filltype uni; universe 70319;} + assem25315 {type simpleCell; id 2041; surfaces (-94); filltype uni; universe 25315;} + assem25317 {type simpleCell; id 2042; surfaces (-94); filltype uni; universe 25317;} + assem25311 {type simpleCell; id 2043; surfaces (-94); filltype uni; universe 25311;} + assem253111 {type simpleCell; id 2044; surfaces (-94); filltype uni; universe 253111;} + assem2631 {type simpleCell; id 2045; surfaces (-94); filltype uni; universe 2631;} + assem3031 {type simpleCell; id 2046; surfaces (-94); filltype uni; universe 3031;} + assem2224 {type simpleCell; id 2047; surfaces (-94); filltype uni; universe 2224;} + assem2624 {type simpleCell; id 2048; surfaces (-94); filltype uni; universe 2624;} + + // rodded assemblies in wrappers + assem1425 {type simpleCell; id 2049; surfaces (-94); filltype uni; universe 1425;} + assem1417 {type simpleCell; id 2050; surfaces (-94); filltype uni; universe 1417;} + + // pin grids - thick at the top and bottom, thin in fuelled region + thickGrid {type simpleCell; id 555; surfaces (90 ); filltype mat; material Inconel;} + thinGrid {type simpleCell; id 556; surfaces (92 ); filltype mat; material Zircaloy;} + + // Don't need to bound PV by 1 since it is the bounding surface of the geometry. + pressureVessel { type simpleCell; id 7; surfaces (2); filltype mat; material CarbonSteel;} + RPVLiner { type simpleCell; id 8; surfaces (-2 3); filltype mat; material SS304;} + outerWater1 {type simpleCell; id 9; surfaces (-3 4 ); filltype mat; material Water;} + + // Neutron shields + NS1 { type simpleCell; id 10; surfaces (-4 5 -8 9); filltype mat; material SS304;} + NS2 { type simpleCell; id 11; surfaces (-4 5 8 -9); filltype mat; material SS304;} + NS3 { type simpleCell; id 12; surfaces (-4 5 -10 11); filltype mat; material SS304;} + NS4 { type simpleCell; id 13; surfaces (-4 5 10 -11); filltype mat; material SS304;} + + // Water in the arc between neutron shields + outerWaterSeg1 {type simpleCell; id 14; surfaces (-4 5 ); filltype mat; material Water;} + outerWater2 {type simpleCell; id 15; surfaces (-5 6 ); filltype mat; material Water;} + + // Outer core + coreBarrel { type simpleCell; id 16; surfaces (-6 7); filltype mat; material SS304;} + core {type simpleCell; id 17; surfaces (-5); filltype uni; universe 9999;} + + + // Gridded pins + + // THICK GRID + // 2.4% in grid + grid24Thick {type simpleCell; id 253; surfaces (-90); filltype uni; universe 24000;} + // guide tube in grid + gridGTThick {type simpleCell; id 254; surfaces (-90); filltype uni; universe 12000;} + // 3.1% in grid + grid31Thick {type simpleCell; id 255; surfaces (-90); filltype uni; universe 31000;} + // 1.6 % in grid + grid16Thick {type simpleCell; id 256; surfaces (-90); filltype uni; universe 16000;} + // instrumentation tube in grid + gridITThick {type simpleCell; id 257; surfaces (-90); filltype uni; universe 14000;} + // empty GT at dashpot in grid + gridGTDPThick {type simpleCell; id 258; surfaces (-90); filltype uni; universe 1010;} + // pin upper fuel plenum in grid + gridFPPThick {type simpleCell; id 259; surfaces (-90); filltype uni; universe 1008;} + // stainless steel in guide tube in grid + gridSSGThick {type simpleCell; id 260; surfaces (-90); filltype uni; universe 1023;} + // stainless steel in dash pot in grid + gridSSDPThick {type simpleCell; id 261; surfaces (-90); filltype uni; universe 1024;} + // BP plenum in grid + gridBPPThick {type simpleCell; id 262; surfaces (-90); filltype uni; universe 1012;} + // Lower rodded GT in grid + gridLRGTThick {type simpleCell; id 263; surfaces (-90); filltype uni; universe 1014;} + // Upper rodded GT in grid + gridURGTThick {type simpleCell; id 463; surfaces (-90); filltype uni; universe 1013;} + + // THIN GRID + // 2.4% in grid + grid24Thin {type simpleCell; id 264; surfaces (-92); filltype uni; universe 24000;} + // guide tube in grid + gridGTThin {type simpleCell; id 265; surfaces (-92); filltype uni; universe 12000;} + // burnable poison in grid + gridBPThin {type simpleCell; id 266; surfaces (-92); filltype uni; universe 1000;} + // 3.1% in grid + grid31Thin {type simpleCell; id 267; surfaces (-92); filltype uni; universe 31000;} + // 1.6 % in grid + grid16Thin {type simpleCell; id 268; surfaces (-92); filltype uni; universe 16000;} + // instrumentation tube in grid + gridITThin {type simpleCell; id 269; surfaces (-92); filltype uni; universe 14000;} + // empty GT at dashpot in grid + gridGTDPThin {type simpleCell; id 270; surfaces (-92); filltype uni; universe 1010;} + // pin upper fuel plenum in grid + gridFPPThin {type simpleCell; id 271; surfaces (-92); filltype uni; universe 1008;} + // stainless steel in guide tube in grid + gridSSGTThin {type simpleCell; id 272; surfaces (-92); filltype uni; universe 1023;} + // stainless steel in dash pot in grid + gridSSDPThin {type simpleCell; id 273; surfaces (-92); filltype uni; universe 1024;} + // BP plenum in grid + gridBPPThin {type simpleCell; id 274; surfaces (-92); filltype uni; universe 1012;} + // Lower rodded GT in grid (not used when rods fully withdrawn) + gridLRGTThin {type simpleCell; id 275; surfaces (-92); filltype uni; universe 1014;} + // Upper rodded GT in grid (not used when rods fully withdrawn) + gridURGTThin {type simpleCell; id 475; surfaces (-92); filltype uni; universe 1013;} + + + // 3.1% enriched pins, axial layering + 31FP460 {type simpleCell; id 100; surfaces ( 101); filltype uni; universe 1001;} + 31FP431 {type simpleCell; id 101; surfaces (-101 102); filltype uni; universe 1003;} + 31FP423 {type simpleCell; id 102; surfaces (-102 104); filltype uni; universe 1001;} + 31FP419 {type simpleCell; id 103; surfaces (-104 105); filltype uni; universe 1006;} + 31FP417 {type simpleCell; id 104; surfaces (-105 106); filltype uni; universe 1008;} + 31FP415 {type simpleCell; id 105; surfaces (-106 107); filltype uni; universe 1017;} + 31FP411 {type simpleCell; id 106; surfaces (-107 109); filltype uni; universe 1008;} + 31FP402 {type simpleCell; id 107; surfaces (-109 111); filltype uni; universe 31000;} + 31FP364 {type simpleCell; id 108; surfaces (-111 112); filltype uni; universe 9231;} + 31FP359 {type simpleCell; id 109; surfaces (-112 113); filltype uni; universe 31000;} + 31FP312 {type simpleCell; id 110; surfaces (-113 114); filltype uni; universe 9231;} + 31FP306 {type simpleCell; id 111; surfaces (-114 115); filltype uni; universe 31000;} + 31FP260 {type simpleCell; id 112; surfaces (-115 116); filltype uni; universe 9231;} + 31FP254 {type simpleCell; id 113; surfaces (-116 117); filltype uni; universe 31000;} + 31FP208 {type simpleCell; id 114; surfaces (-117 118); filltype uni; universe 9231;} + 31FP202 {type simpleCell; id 115; surfaces (-118 119); filltype uni; universe 31000;} + 31FP155 {type simpleCell; id 116; surfaces (-119 120); filltype uni; universe 9231;} + 31FP150 {type simpleCell; id 117; surfaces (-120 122); filltype uni; universe 31000;} + 31FP103 {type simpleCell; id 118; surfaces (-122 123); filltype uni; universe 9231;} + 31FP98 {type simpleCell; id 119; surfaces (-123 126); filltype uni; universe 31000;} + 31FP4052 {type simpleCell; id 120; surfaces (-126 129); filltype uni; universe 1131;} + 31FP37 {type simpleCell; id 121; surfaces (-129 130); filltype uni; universe 31000;} + 31FP36 {type simpleCell; id 122; surfaces (-130 131); filltype uni; universe 1006;} + 31FP35 {type simpleCell; id 123; surfaces (-131 132); filltype uni; universe 1003;} + 31FP20 {type simpleCell; id 124; surfaces (-132 ); filltype uni; universe 1001;} + + + //2.4% enriched pins, axial layering + 24FP460 {type simpleCell; id 125; surfaces ( 101); filltype uni; universe 1001;} + 24FP431 {type simpleCell; id 126; surfaces (-101 102); filltype uni; universe 1003;} + 24FP423 {type simpleCell; id 127; surfaces (-102 104); filltype uni; universe 1001;} + 24FP419 {type simpleCell; id 128; surfaces (-104 105); filltype uni; universe 1006;} + 24FP417 {type simpleCell; id 129; surfaces (-105 106); filltype uni; universe 1008;} + 24FP415 {type simpleCell; id 130; surfaces (-106 107); filltype uni; universe 1017;} + 24FP411 {type simpleCell; id 131; surfaces (-107 109); filltype uni; universe 1008;} + 24FP402 {type simpleCell; id 132; surfaces (-109 111); filltype uni; universe 24000;} + 24FP364 {type simpleCell; id 133; surfaces (-111 112); filltype uni; universe 9224;} + 24FP359 {type simpleCell; id 134; surfaces (-112 113); filltype uni; universe 24000;} + 24FP312 {type simpleCell; id 135; surfaces (-113 114); filltype uni; universe 9224;} + 24FP306 {type simpleCell; id 136; surfaces (-114 115); filltype uni; universe 24000;} + 24FP260 {type simpleCell; id 137; surfaces (-115 116); filltype uni; universe 9224;} + 24FP254 {type simpleCell; id 138; surfaces (-116 117); filltype uni; universe 24000;} + 24FP208 {type simpleCell; id 139; surfaces (-117 118); filltype uni; universe 9224;} + 24FP202 {type simpleCell; id 140; surfaces (-118 119); filltype uni; universe 24000;} + 24FP155 {type simpleCell; id 141; surfaces (-119 120); filltype uni; universe 9224;} + 24FP150 {type simpleCell; id 142; surfaces (-120 122); filltype uni; universe 24000;} + 24FP103 {type simpleCell; id 143; surfaces (-122 123); filltype uni; universe 9224;} + 24FP98 {type simpleCell; id 144; surfaces (-123 126); filltype uni; universe 24000;} + 24FP4052 {type simpleCell; id 145; surfaces (-126 129); filltype uni; universe 1124;} + 24FP37 {type simpleCell; id 146; surfaces (-129 130); filltype uni; universe 24000;} + 24FP36 {type simpleCell; id 147; surfaces (-130 131); filltype uni; universe 1006;} + 24FP35 {type simpleCell; id 148; surfaces (-131 132); filltype uni; universe 1003;} + 24FP20 {type simpleCell; id 149; surfaces (-132); filltype uni; universe 1001;} + + //1.6% enriched pins, axial layering + 16FP460 {type simpleCell; id 150; surfaces ( 101); filltype uni; universe 1001;} + 16FP431 {type simpleCell; id 151; surfaces (-101 102); filltype uni; universe 1003;} + 16FP423 {type simpleCell; id 152; surfaces (-102 104); filltype uni; universe 1001;} + 16FP419 {type simpleCell; id 153; surfaces (-104 105); filltype uni; universe 1006;} + 16FP417 {type simpleCell; id 154; surfaces (-105 106); filltype uni; universe 1008;} + 16FP415 {type simpleCell; id 155; surfaces (-106 107); filltype uni; universe 1017;} + 16FP411 {type simpleCell; id 156; surfaces (-107 109); filltype uni; universe 1008;} + 16FP402 {type simpleCell; id 157; surfaces (-109 111); filltype uni; universe 16000;} + 16FP364 {type simpleCell; id 158; surfaces (-111 112); filltype uni; universe 9216;} + 16FP359 {type simpleCell; id 159; surfaces (-112 113); filltype uni; universe 16000;} + 16FP312 {type simpleCell; id 160; surfaces (-113 114); filltype uni; universe 9216;} + 16FP306 {type simpleCell; id 161; surfaces (-114 115); filltype uni; universe 16000;} + 16FP260 {type simpleCell; id 162; surfaces (-115 116); filltype uni; universe 9216;} + 16FP254 {type simpleCell; id 163; surfaces (-116 117); filltype uni; universe 16000;} + 16FP208 {type simpleCell; id 164; surfaces (-117 118); filltype uni; universe 9216;} + 16FP202 {type simpleCell; id 165; surfaces (-118 119); filltype uni; universe 16000;} + 16FP155 {type simpleCell; id 166; surfaces (-119 120); filltype uni; universe 9216;} + 16FP150 {type simpleCell; id 167; surfaces (-120 122); filltype uni; universe 16000;} + 16FP103 {type simpleCell; id 168; surfaces (-122 123); filltype uni; universe 9216;} + 16FP98 {type simpleCell; id 169; surfaces (-123 126); filltype uni; universe 16000;} + 16FP4052 {type simpleCell; id 170; surfaces (-126 129); filltype uni; universe 1116;} + 16FP37 {type simpleCell; id 171; surfaces (-129 130); filltype uni; universe 16000;} + 16FP36 {type simpleCell; id 172; surfaces (-130 131); filltype uni; universe 1006;} + 16FP35 {type simpleCell; id 173; surfaces (-131 132); filltype uni; universe 1003;} + 16FP20 {type simpleCell; id 174; surfaces (-132); filltype uni; universe 1001;} + + + //guide tube, with CR, axial layering + GC460 {type simpleCell; id 175; surfaces ( 101); filltype uni; universe 1014;} + GC431 {type simpleCell; id 176; surfaces (-101 106); filltype uni; universe 1014;} // Nozzle/support plate BW? Replaced just with rod + GC415 {type simpleCell; id 177; surfaces (-106 107); filltype uni; universe 1018;} // Rodded w/ grid + GC411 {type simpleCell; id 178; surfaces (-107 109); filltype uni; universe 1014;} + GC402 {type simpleCell; id 179; surfaces (-109 134); filltype uni; universe 1015;} + GC400 {type simpleCell; id 180; surfaces (-134 111); filltype uni; universe 12000;} + GC364 {type simpleCell; id 181; surfaces (-111 112); filltype uni; universe 9112;} + GC359 {type simpleCell; id 182; surfaces (-112 113); filltype uni; universe 12000;} + GC312 {type simpleCell; id 183; surfaces (-113 114); filltype uni; universe 9112;} + GC306 {type simpleCell; id 184; surfaces (-114 115); filltype uni; universe 12000;} + GC260 {type simpleCell; id 185; surfaces (-115 116); filltype uni; universe 9112;} + GC254 {type simpleCell; id 186; surfaces (-116 117); filltype uni; universe 12000;} + GC208 {type simpleCell; id 187; surfaces (-117 118); filltype uni; universe 9112;} + GC202 {type simpleCell; id 188; surfaces (-118 119); filltype uni; universe 12000;} + GC155 {type simpleCell; id 189; surfaces (-119 120); filltype uni; universe 9112;} + GC150 {type simpleCell; id 190; surfaces (-120 122); filltype uni; universe 12000;} + GC103 {type simpleCell; id 191; surfaces (-122 123); filltype uni; universe 9112;} + GC98 {type simpleCell; id 192; surfaces (-123 126); filltype uni; universe 1010;} + GC4052 {type simpleCell; id 193; surfaces (-126 127); filltype uni; universe 12000;} + GC39 {type simpleCell; id 194; surfaces (-127 129); filltype uni; universe 1019;} + GC37 {type simpleCell; id 195; surfaces (-129 131); filltype uni; universe 1010;} + GC35 {type simpleCell; id 196; surfaces (-131 132); filltype uni; universe 1005;} + GC20 {type simpleCell; id 197; surfaces (-132); filltype uni; universe 1001;} + + + // instrumentation tube, axial layering + IT460 {type simpleCell; id 198; surfaces ( 102); filltype uni; universe 1001;} + IT423 {type simpleCell; id 199; surfaces (-102 106); filltype uni; universe 14000;} + IT415 {type simpleCell; id 200; surfaces (-106 107); filltype uni; universe 1114;} + IT411 {type simpleCell; id 201; surfaces (-107 111); filltype uni; universe 14000;} + IT364 {type simpleCell; id 202; surfaces (-111 112); filltype uni; universe 9114;} + IT359 {type simpleCell; id 203; surfaces (-112 113); filltype uni; universe 14000;} + IT312 {type simpleCell; id 204; surfaces (-113 114); filltype uni; universe 9114;} + IT306 {type simpleCell; id 205; surfaces (-114 115); filltype uni; universe 14000;} + IT260 {type simpleCell; id 206; surfaces (-115 116); filltype uni; universe 9114;} + IT254 {type simpleCell; id 207; surfaces (-116 117); filltype uni; universe 14000;} + IT208 {type simpleCell; id 208; surfaces (-117 118); filltype uni; universe 9114;} + IT202 {type simpleCell; id 209; surfaces (-118 119); filltype uni; universe 14000;} + IT155 {type simpleCell; id 210; surfaces (-119 120); filltype uni; universe 9114;} + IT150 {type simpleCell; id 211; surfaces (-120 122); filltype uni; universe 14000;} + IT103 {type simpleCell; id 212; surfaces (-122 123); filltype uni; universe 9114;} + IT98 {type simpleCell; id 213; surfaces (-123 126); filltype uni; universe 14000;} + IT4052 {type simpleCell; id 214; surfaces (-126 129); filltype uni; universe 1114;} + IT37 {type simpleCell; id 215; surfaces (-129 131); filltype uni; universe 14000;} + IT35 {type simpleCell; id 216; surfaces (-131 132); filltype uni; universe 1005;} + IT20 {type simpleCell; id 217; surfaces (-132 ); filltype uni; universe 1011;} + + + // burnable absorber, axial layering + BA460 {type simpleCell; id 218; surfaces ( 101); filltype uni; universe 1001;} + BA431 {type simpleCell; id 219; surfaces (-101 102); filltype uni; universe 1002;} + BA423 {type simpleCell; id 220; surfaces (-102 103); filltype uni; universe 1023;} + BA421 {type simpleCell; id 230; surfaces (-103 106); filltype uni; universe 1012;} + BA415 {type simpleCell; id 231; surfaces (-106 107); filltype uni; universe 1027;} + BA411 {type simpleCell; id 232; surfaces (-107 110); filltype uni; universe 1012;} + BA401 {type simpleCell; id 233; surfaces (-110 111); filltype uni; universe 1000;} + BA364 {type simpleCell; id 234; surfaces (-111 112); filltype uni; universe 1110;} + BA359 {type simpleCell; id 235; surfaces (-112 113); filltype uni; universe 1000;} + BA312 {type simpleCell; id 236; surfaces (-113 114); filltype uni; universe 1110;} + BA306 {type simpleCell; id 237; surfaces (-114 115); filltype uni; universe 1000;} + BA260 {type simpleCell; id 238; surfaces (-115 116); filltype uni; universe 1110;} + BA254 {type simpleCell; id 239; surfaces (-116 117); filltype uni; universe 1000;} + BA208 {type simpleCell; id 240; surfaces (-117 118); filltype uni; universe 1110;} + BA202 {type simpleCell; id 241; surfaces (-118 119); filltype uni; universe 1000;} + BA155 {type simpleCell; id 242; surfaces (-119 120); filltype uni; universe 1110;} + BA150 {type simpleCell; id 243; surfaces (-120 122); filltype uni; universe 1000;} + BA103 {type simpleCell; id 244; surfaces (-122 123); filltype uni; universe 1110;} + BA98 {type simpleCell; id 245; surfaces (-123 125); filltype uni; universe 1000;} + BA4055 {type simpleCell; id 246; surfaces (-125 126); filltype uni; universe 1023;} + BA4052 {type simpleCell; id 247; surfaces (-126 127); filltype uni; universe 1021;} + BA39 {type simpleCell; id 248; surfaces (-127 128); filltype uni; universe 1025;} + BA38 {type simpleCell; id 249; surfaces (-128 129); filltype uni; universe 1019;} + BA37 {type simpleCell; id 250; surfaces (-129 131); filltype uni; universe 1010;} + BA35 {type simpleCell; id 251; surfaces (-131 132); filltype uni; universe 1005;} + BA20 {type simpleCell; id 252; surfaces (-132 ); filltype uni; universe 1001;} + + //guide tube, no CR, axial layering + GT460 {type simpleCell; id 353; surfaces ( 101); filltype uni; universe 1001;} + GT431 {type simpleCell; id 354; surfaces (-101 102); filltype uni; universe 1005;} + GT423 {type simpleCell; id 355; surfaces (-102 106); filltype uni; universe 12000;} + GT415 {type simpleCell; id 356; surfaces (-106 107); filltype uni; universe 1112;} + GT411 {type simpleCell; id 357; surfaces (-107 111); filltype uni; universe 12000;} + GT364 {type simpleCell; id 358; surfaces (-111 112); filltype uni; universe 9112;} + GT359 {type simpleCell; id 359; surfaces (-112 113); filltype uni; universe 12000;} + GT312 {type simpleCell; id 360; surfaces (-113 114); filltype uni; universe 9112;} + GT306 {type simpleCell; id 361; surfaces (-114 115); filltype uni; universe 12000;} + GT260 {type simpleCell; id 362; surfaces (-115 116); filltype uni; universe 9112;} + GT254 {type simpleCell; id 363; surfaces (-116 117); filltype uni; universe 12000;} + GT208 {type simpleCell; id 364; surfaces (-117 118); filltype uni; universe 9112;} + GT202 {type simpleCell; id 365; surfaces (-118 119); filltype uni; universe 12000;} + GT155 {type simpleCell; id 366; surfaces (-119 120); filltype uni; universe 9112;} + GT150 {type simpleCell; id 367; surfaces (-120 122); filltype uni; universe 12000;} + GT103 {type simpleCell; id 368; surfaces (-122 123); filltype uni; universe 9112;} + GT98 {type simpleCell; id 369; surfaces (-123 126); filltype uni; universe 1010;} + GT4052 {type simpleCell; id 370; surfaces (-126 127); filltype uni; universe 12000;} + GT39 {type simpleCell; id 371; surfaces (-127 129); filltype uni; universe 1019;} + GT37 {type simpleCell; id 372; surfaces (-129 131); filltype uni; universe 1010;} + GT35 {type simpleCell; id 373; surfaces (-131 132); filltype uni; universe 1005;} + GT20 {type simpleCell; id 374; surfaces (-132); filltype uni; universe 1001;} + + // Extra GT cells without dashpot for empty instrumentation tubes + CGT98 {type simpleCell; id 469; surfaces (-123 126); filltype uni; universe 9112;} + + //guide tube, partially inserted CR, axial layering + // Note: universe is basically a combo of fully and partially inserted rods + GP460 {type simpleCell; id 375; surfaces ( 101); filltype uni; universe 1014;} + GP431 {type simpleCell; id 376; surfaces (-101 102); filltype uni; universe 1014;} + GP423 {type simpleCell; id 377; surfaces (-102 106); filltype uni; universe 1014;} + GP415 {type simpleCell; id 378; surfaces (-106 107); filltype uni; universe 1132;} + GP411 {type simpleCell; id 379; surfaces (-107 138); filltype uni; universe 1014;} + GP378 {type simpleCell; id 380; surfaces (-138 139); filltype uni; universe 1023;} + GP377 {type simpleCell; id 381; surfaces (-139 111); filltype uni; universe 12000;} + GP364 {type simpleCell; id 382; surfaces (-111 112); filltype uni; universe 9112;} + GP359 {type simpleCell; id 383; surfaces (-112 113); filltype uni; universe 12000;} + GP312 {type simpleCell; id 384; surfaces (-113 114); filltype uni; universe 9112;} + GP306 {type simpleCell; id 385; surfaces (-114 115); filltype uni; universe 12000;} + GP260 {type simpleCell; id 386; surfaces (-115 116); filltype uni; universe 9112;} + GP254 {type simpleCell; id 387; surfaces (-116 117); filltype uni; universe 12000;} + GP208 {type simpleCell; id 388; surfaces (-117 118); filltype uni; universe 9112;} + GP202 {type simpleCell; id 389; surfaces (-118 119); filltype uni; universe 12000;} + GP155 {type simpleCell; id 390; surfaces (-119 120); filltype uni; universe 9112;} + GP150 {type simpleCell; id 391; surfaces (-120 122); filltype uni; universe 12000;} + GP103 {type simpleCell; id 392; surfaces (-122 123); filltype uni; universe 9112;} + GP98 {type simpleCell; id 393; surfaces (-123 126); filltype uni; universe 1010;} + GP4052 {type simpleCell; id 394; surfaces (-126 127); filltype uni; universe 12000;} + GP39 {type simpleCell; id 395; surfaces (-127 129); filltype uni; universe 1019;} + GP37 {type simpleCell; id 396; surfaces (-129 131); filltype uni; universe 1010;} + GP35 {type simpleCell; id 397; surfaces (-131 132); filltype uni; universe 1005;} + GP20 {type simpleCell; id 398; surfaces (-132); filltype uni; universe 1001;} + + // control rod, axial layering + // Used (probably with some modification) only when fully inserted + //CR460 {type simpleCell; id 448; surfaces (-120 121); filltype uni; universe 1002;} + //CR415 {type simpleCell; id 449; surfaces (-126 403); filltype uni; universe 1013;} + //CR403 {type simpleCell; id 450; surfaces (-403 402); filltype uni; universe 1015;} + //CR402 {type simpleCell; id 451; surfaces (-402 1430); filltype uni; universe 1013;} + //CR143 {type simpleCell; id 452; surfaces (-1430 41); filltype uni; universe 1014;} + //CR41 {type simpleCell; id 453; surfaces (-41 143); filltype uni; universe 1002;} + //CR39 {type simpleCell; id 454; surfaces (-143 147); filltype uni; universe 1001;} + //CR35 {type simpleCell; id 455; surfaces (-147 148); filltype uni; universe 1005;} + //CR20 {type simpleCell; id 456; surfaces (-148 149); filltype uni; universe 1001;} + + + + outsideLeftBaffle { type simpleCell; id 52; surfaces (-50); filltype mat; material Water;} + leftBaffle { type simpleCell; id 53; surfaces (50 -51); filltype mat; material SS304;} + insideLeftBaffle { type simpleCell; id 54; surfaces (51); filltype mat; material Water;} + + outsideRightBaffle { type simpleCell; id 55; surfaces (-52); filltype mat; material Water;} + RightBaffle { type simpleCell; id 56; surfaces (52 -53); filltype mat; material SS304;} + insideRightBaffle { type simpleCell; id 57; surfaces (53); filltype mat; material Water;} + + outsideTopBaffle { type simpleCell; id 58; surfaces (-54); filltype mat; material Water;} + TopBaffle { type simpleCell; id 59; surfaces (54 -55); filltype mat; material SS304;} + insideTopBaffle { type simpleCell; id 60; surfaces (55); filltype mat; material Water;} + + outsideBottomBaffle { type simpleCell; id 61; surfaces (-56); filltype mat; material Water;} + BottomBaffle { type simpleCell; id 62; surfaces (56 -57); filltype mat; material SS304;} + insideBottomBaffle { type simpleCell; id 63; surfaces (57); filltype mat; material Water;} + + topLeftCornerBaffle1 { type simpleCell; id 64; surfaces (52 -53 -57); filltype mat; material SS304;} + topLeftCornerBaffle2 { type simpleCell; id 65; surfaces (56 -57 -52); filltype mat; material SS304;} + topLeftCornerGap1 { type simpleCell; id 66; surfaces (57); filltype mat; material Water;} + topLeftCornerGap2 { type simpleCell; id 67; surfaces (53); filltype mat; material Water;} + topLeftMajorGap { type simpleCell; id 68; surfaces (-56 -52); filltype mat; material Water;} + + topRightCornerBaffle1 { type simpleCell; id 69; surfaces (-57 50 -51); filltype mat; material SS304;} + topRightCornerBaffle2 { type simpleCell; id 70; surfaces (-50 56 -57); filltype mat; material SS304;} + topRightCornerGap1 { type simpleCell; id 71; surfaces (57); filltype mat; material Water;} + topRightCornerGap2 { type simpleCell; id 72; surfaces (51); filltype mat; material Water;} + topRightMajorGap { type simpleCell; id 73; surfaces (-56 -50); filltype mat; material Water;} + + bottomLeftCornerBaffle1 { type simpleCell; id 74; surfaces (-55 52 -53); filltype mat; material SS304;} + bottomLeftCornerBaffle2 { type simpleCell; id 75; surfaces (-55 54 -52); filltype mat; material SS304;} + bottomLeftCornerGap1 { type simpleCell; id 76; surfaces (55); filltype mat; material Water;} + bottomLeftCornerGap2 { type simpleCell; id 77; surfaces (53); filltype mat; material Water;} + bottomLeftMajorGap { type simpleCell; id 78; surfaces (-54 -52); filltype mat; material Water;} + + bottomRightCornerBaffle1 { type simpleCell; id 79; surfaces (-51 50 -55); filltype mat; material SS304;} + bottomRightCornerBaffle2 { type simpleCell; id 80; surfaces (-55 54 -50); filltype mat; material SS304;} + bottomRightCornerGap1 { type simpleCell; id 81; surfaces (51); filltype mat; material Water;} + bottomRightCornerGap2 { type simpleCell; id 82; surfaces (55); filltype mat; material Water;} + bottomRightMajorGap { type simpleCell; id 83; surfaces (-50 -54); filltype mat; material Water;} + + + TLSG1 { type simpleCell; id 84; surfaces (-56 -52); filltype mat; material Water;} + TLSG2 { type simpleCell; id 85; surfaces (-56 52); filltype mat; material Water;} + TLSG3 { type simpleCell; id 86; surfaces (56 -52); filltype mat; material Water;} + topLeftSquare { type simpleCell; id 87; surfaces (56 52); filltype mat; material SS304;} + + TRSG1 { type simpleCell; id 88; surfaces (-56 50); filltype mat; material Water;} + TRSG2 { type simpleCell; id 89; surfaces (-56 -50); filltype mat; material Water;} + TRSG3 { type simpleCell; id 90; surfaces (56 -50); filltype mat; material Water;} + topRightSquare { type simpleCell; id 91; surfaces (56 50); filltype mat; material SS304;} + + BLSG1 { type simpleCell; id 92; surfaces (54 -52); filltype mat; material Water;} + BLSG2 { type simpleCell; id 93; surfaces (-54 52); filltype mat; material Water;} + BLSG3 { type simpleCell; id 94; surfaces (-54 -52); filltype mat; material Water;} + bottomLeftSquare { type simpleCell; id 95; surfaces (54 52); filltype mat; material SS304;} + + BRSG1 { type simpleCell; id 96; surfaces (-54 50); filltype mat; material Water;} + BRSG2 { type simpleCell; id 97; surfaces (54 -50); filltype mat; material Water;} + BRSG3 { type simpleCell; id 98; surfaces (-54 -50); filltype mat; material Water;} + bottomRightSquare { type simpleCell; id 99; surfaces (54 50); filltype mat; material SS304;} + } + + universes { + root { id 1; type rootUniverse; border 1; fill u<8888>; } + + // Pin universes + + //Burnable poison + pinBPaboveDP { id 1000; type pinUniverse; radii (0.21400 0.23051 0.24130 0.42672 0.43688 0.48387 0.56134 0.60198 0.0); + fills (Air SS304 Helium BorosilicateGlass Helium SS304 Water Zircaloy Water);} + pinBPPlenumGeometry { id 1012; type pinUniverse; radii ( 0.21400 0.23051 0.43688 0.48387 0.50419 0.54610 0.0); + fills (Air SS304 Helium SS304 Water Zircaloy Water);} + + //guide tubes + pinGTaboveDP { id 12000; type pinUniverse; radii (0.56134 0.60198 0.0 ); fills (Water Zircaloy Water);} + pinGTatDP { id 1010; type pinUniverse; radii (0.50419 0.54610 0.0); fills (Water Zircaloy Water);} + + //INST Tube + pinIT { id 14000; type pinUniverse; radii (0.43688 0.48387 0.56134 0.60198 0.0 ); + fills (Air Zircaloy Water Zircaloy Water);} + pinBareInstrumentThimble { id 1011; type pinUniverse; radii (0.43688 0.48387 0.0); fills (Air Zircaloy Water);} + + // Fuel pins + pin16 { id 16000; type pinUniverse; radii (0.39218 0.40005 0.45720 0.0); + fills (UO2-16 Helium Zircaloy Water);} + pin24 { id 24000; type pinUniverse; radii (0.39218 0.40005 0.45720 0.0); + fills (UO2-24 Helium Zircaloy Water);} + pin31 { id 31000; type pinUniverse; radii (0.39218 0.40005 0.45720 0.0); + fills (UO2-31 Helium Zircaloy Water);} + // Higher enrichments not used + //pin32 { id 32000; type pinUniverse; radii (0.39218 0.40005 0.45720 0.0); + // fills (UO2-32 Helium Zircaloy Water);} + //pin34 { id 34000; type pinUniverse; radii (0.39218 0.40005 0.45720 0.0); + // fills (UO2-34 Helium Zircaloy Water);} + + pinWater { id 1001; type pinUniverse; radii ( 0.0); fills (Water);} + + + // Solid pins, assumed radius to be that of a fuel pin (0.45720) + pinNozzle_SupportSteel { id 1003; type pinUniverse; radii ( 0.45720 0.0); fills (SupportPlateSS Water);} + pinSupportPlateBW { id 1005; type pinUniverse; radii ( 0.45720 0.0); fills (SupportPlateBW Water);} + pinZircaloy { id 1006; type pinUniverse; radii ( 0.45720 0.0); fills (Zircaloy Water);} + + + SSinDashPot { id 1024; type pinUniverse; radii (0.50419 0.54610 0.0); fills (SS304 Zircaloy Water);} + SSinGuideTube { id 1023; type pinUniverse; radii ( 0.56134 0.60198 0.0); fills (SS304 Zircaloy Water);} + SSnoGuideTube { id 1002; type pinUniverse; radii ( 0.56134 0.0); fills (SS304 Water);} + + + pinUpperFuelPlenum { id 1008; type pinUniverse; radii ( 0.06459 0.40005 0.45720 0.0); + fills (Inconel Helium Zircaloy Water);} + + // Control rod pins + pinControlRodUpper { id 1013; type pinUniverse; radii ( 0.37338 0.38608 0.48387 0.56134 0.60198 0.0); + fills (B4C Helium SS304 Water Zircaloy Water);} + pinControlRodLower { id 1014; type pinUniverse; radii ( 0.38227 0.38608 0.48387 0.56134 0.60198 0.0); + fills (Ag-In-Cd Helium SS304 Water Zircaloy Water);} + pinControlRodSpacer { id 1015; type pinUniverse; radii ( 0.37845 0.38608 0.48387 0.56134 0.60198 0.0); + fills (SS304 Helium SS304 Water Zircaloy Water);} + pinControlRodPlenum { id 1016; type pinUniverse; radii ( 0.06459 0.38608 0.48387 0.56134 0.60198 0.0); + fills (Inconel Helium SS304 Water Zircaloy Water);} + + // pins that have grids + fuelRodPlenumWithGridThick { + id 1017; + type cellUniverse; + cells ( 259 555);} + + GTRodThick { + id 1018; + type cellUniverse; + cells (263 555);} + + dashPotGuideTubeGridThick { + id 1019; + type cellUniverse; + cells ( 258 555);} + + dashPotGuideTubeGridThin { + id 1020; + type cellUniverse; + cells ( 270 556);} + + SSinGuideTubeThick { + id 1021; + type cellUniverse; + cells ( 260 555);} + + SSinGuideTubeThin { + id 1022; + type cellUniverse; + cells ( 272 556);} + + SSinDashPotThick { + id 1025; + type cellUniverse; + cells ( 261 555);} + + SSinDashPotThin { + id 1026; + type cellUniverse; + cells ( 273 556);} + + BPPlenumThick { + id 1027; + type cellUniverse; + cells ( 262 555);} + + BPPlenumThin { + id 1028; + type cellUniverse; + cells ( 274 556);} + + BPaboveDPThin { + id 1110; + type cellUniverse; + cells (266 556);} + + GTThick { + id 1112; + type cellUniverse; + cells (254 555);} + + ITThick { + id 1114; + type cellUniverse; + cells (257 555);} + + pin16Thick { + id 1116; + type cellUniverse; + cells (256 555);} + + pin24Thick { + id 1124; + type cellUniverse; + cells (253 555);} + + pin31Thick { + id 1131; + type cellUniverse; + cells (255 555);} + + LowerRodGTThick { + id 1132; + type cellUniverse; + cells (263 555);} + + UpperRodGTThick { + id 1133; + type cellUniverse; + cells (463 555);} + + BPThin { // Is this necessary given 1110, BPaboveDPThin??? + id 9110; + type cellUniverse; + cells (266 556);} + + GTThin { + id 9112; + type cellUniverse; + cells (265 556);} + + ITThin { + id 9114; + type cellUniverse; + cells (269 556);} + + pin16Thin { + id 9216; + type cellUniverse; + cells (268 556);} + + pin24Thin { + id 9224; + type cellUniverse; + cells (264 556);} + + pin31Thin { + id 9231; + type cellUniverse; + cells (267 556);} + + LowerRodGTThin { + id 9232; + type cellUniverse; + cells (275 556);} + + UpperRodGTThin { + id 9233; + type cellUniverse; + cells (475 556);} + + // Axial stacks of universes to make up full pins + + // 3.1 % + fuelPin31 { + id 31; + type cellUniverse; + cells ( 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124);} + + // 2.4 % + fuelPin24 { + id 24; + type cellUniverse; + cells ( 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149);} + + //1.6 % + fuelPin16 { + id 16; + type cellUniverse; + cells ( 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174);} + + //burnable absorber + BP { + id 10; + type cellUniverse; + cells (218 219 220 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252);} + + // guide tube, with CR + GuideTubeRodded { + id 12; + type cellUniverse; + cells (175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197);} + + //control rod, fully retracted + GuideTubeEmpty { + id 13; + type cellUniverse; + cells (353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 369 370 371 372 373 374);} + + //instr. tube + instrumentTube { + id 15; + type cellUniverse; + cells (198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217);} + + //empty instr. tube + emptyInstrumentTube { + id 11; + type cellUniverse; + cells (353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 469 370 371 372 373 374);} + + + // control rod, partially inserted + GuideTubePartial { + id 17; + type cellUniverse; + cells (375 376 377 378 379 380 381 382 383 384 385 386 387 388 389 390 391 392 393 394 395 396 397 398); + + } + + // Lattice of instrumentation tubes + instLattice { + type latUniverse; + id 14; + origin (0 0 0); + pitch (21.50364 21.50364 0.0); + shape (15 15 0); + padMat Water; + global 1; + map ( + 11 11 11 11 11 11 15 11 11 15 11 11 11 11 11 + 11 11 15 11 11 15 11 15 11 11 11 11 11 11 11 + 11 11 11 11 11 11 11 15 11 15 11 15 11 15 11 + 11 15 15 11 11 11 11 15 11 11 11 11 11 11 11 + 11 11 11 11 15 11 11 11 15 11 15 11 15 11 11 + 15 11 15 11 11 15 11 15 11 11 11 11 11 15 11 + 11 11 11 15 11 11 15 11 11 15 11 11 15 11 11 + 15 11 15 11 15 11 15 11 11 15 11 15 15 15 11 + 11 15 11 11 11 11 11 11 15 11 15 11 11 11 15 + 11 11 11 11 15 11 15 11 11 11 11 15 11 11 11 + 15 11 11 11 15 11 11 15 11 11 15 11 11 11 15 + 11 11 11 11 11 15 11 11 15 11 11 15 11 11 11 + 11 11 15 11 15 11 11 15 11 11 11 11 11 15 11 + 11 11 15 11 11 11 15 11 11 15 11 15 11 11 11 + 11 11 11 11 15 11 11 15 11 11 11 11 11 11 11 + ); + } + + + + // Lattices w/o grid + // Names represent AE + A0E24 { + id 1424; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 12 24 24 12 24 24 12 24 24 24 24 24 + 24 24 24 12 24 24 24 24 24 24 24 24 24 12 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 12 24 24 12 24 24 12 24 24 12 24 24 12 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 12 24 24 12 24 24 14 24 24 12 24 24 12 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 12 24 24 12 24 24 12 24 24 12 24 24 12 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 12 24 24 24 24 24 24 24 24 24 12 24 24 24 + 24 24 24 24 24 12 24 24 12 24 24 12 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + + // assembly with sleeves at different heights + A0E24Sleeve { + id 14240; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2019 + );} + + + A0E16 { + id 1416; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 12 16 16 12 16 16 12 16 16 16 16 16 + 16 16 16 12 16 16 16 16 16 16 16 16 16 12 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 12 16 16 12 16 16 12 16 16 12 16 16 12 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 12 16 16 12 16 16 14 16 16 12 16 16 12 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 12 16 16 12 16 16 12 16 16 12 16 16 12 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 12 16 16 16 16 16 16 16 16 16 12 16 16 16 + 16 16 16 16 16 12 16 16 12 16 16 12 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16); } + + A0E16Sleeve { + id 14160; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2020 + ); + } + + A0E31 { + id 1431; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 12 31 31 12 31 31 12 31 31 31 31 31 + 31 31 31 12 31 31 31 31 31 31 31 31 31 12 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 12 31 31 12 31 31 12 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 12 31 31 14 31 31 12 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 12 31 31 12 31 31 12 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 12 31 31 31 31 31 31 31 31 31 12 31 31 31 + 31 31 31 31 31 12 31 31 12 31 31 12 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A0E31Sleeve { + id 14310; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2021 + ); + } + + + A6BE31B { + id 60316; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 10 31 31 12 31 31 10 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 12 31 31 12 31 31 12 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 12 31 31 14 31 31 12 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 12 31 31 12 31 31 12 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 12 31 31 31 31 31 31 31 31 31 12 31 31 31 + 31 31 31 31 31 12 31 31 12 31 31 12 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + + A6BE31BSleeve { + id 603160; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2022 + ); + } + + A6BE31T { + id 603112; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 12 31 31 12 31 31 12 31 31 31 31 31 + 31 31 31 12 31 31 31 31 31 31 31 31 31 12 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 12 31 31 12 31 31 12 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 12 31 31 14 31 31 12 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 12 31 31 12 31 31 12 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 10 31 31 12 31 31 10 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A6BE31TSleeve { + id 6031120; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2023 + ); + } + + A6BE31R { + id 60313; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 10 31 31 12 31 31 12 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 12 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 12 31 31 12 31 31 12 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 12 31 31 14 31 31 12 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 12 31 31 12 31 31 12 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 12 31 31 31 + 31 31 31 31 31 10 31 31 12 31 31 12 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A6BE31RSleeve { + id 603130; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2024 + ); + } + + A6BE31L { + id 60319; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 12 31 31 12 31 31 10 31 31 31 31 31 + 31 31 31 12 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 12 31 31 12 31 31 12 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 12 31 31 14 31 31 12 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 12 31 31 12 31 31 12 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 12 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 12 31 31 12 31 31 10 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A6BE31LSleeve { + id 603190; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2025 + ); + } + + A15BE31BR { + id 15315; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 12 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 10 31 31 10 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 14 31 31 10 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 10 31 31 10 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 12 31 31 31 31 31 31 31 31 31 12 31 31 31 + 31 31 31 31 31 12 31 31 12 31 31 12 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A15BE31BRSleeve { + id 153150; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2026 + ); + } + + A15BE31BL { + id 15317; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 12 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 10 31 31 10 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 10 31 31 14 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 10 31 31 10 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 12 31 31 31 31 31 31 31 31 31 12 31 31 31 + 31 31 31 31 31 12 31 31 12 31 31 12 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A15BE31BLSleeve { + id 153170; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2027 + ); + } + + A15BE31TR { + id 15311; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 12 31 31 12 31 31 12 31 31 31 31 31 + 31 31 31 12 31 31 31 31 31 31 31 31 31 12 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 10 31 31 10 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 14 31 31 10 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 10 31 31 10 31 31 12 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 12 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A15BE31TRSleeve { + id 153110; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2028 + ); + } + + A15BE31TL { + id 153111; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 12 31 31 12 31 31 12 31 31 31 31 31 + 31 31 31 12 31 31 31 31 31 31 31 31 31 12 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 10 31 31 10 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 10 31 31 14 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 12 31 31 10 31 31 10 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 12 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A15BE31TLSleeve { + id 1531110; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2029 + ); + } + + A16BE31 { + id 1631; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 12 31 31 12 31 31 12 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 12 31 31 14 31 31 12 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 12 31 31 12 31 31 12 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A16BE31Sleeve { + id 16310; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2030 + ); + } + + A20BE31 { + id 2031; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 12 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 12 31 31 14 31 31 12 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 12 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A20BE31Sleeve { + id 20310; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2031 + ); + } + + A12BE24 { + id 1224; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 10 24 24 12 24 24 10 24 24 24 24 24 + 24 24 24 10 24 24 24 24 24 24 24 24 24 10 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 10 24 24 12 24 24 12 24 24 12 24 24 10 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 12 24 24 12 24 24 14 24 24 12 24 24 12 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 10 24 24 12 24 24 12 24 24 12 24 24 10 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 10 24 24 24 24 24 24 24 24 24 10 24 24 24 + 24 24 24 24 24 10 24 24 12 24 24 10 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + + A12BE24Sleeve { + id 12240; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2032 + ); + } + + A16BE24 { + id 1624; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 10 24 24 10 24 24 10 24 24 24 24 24 + 24 24 24 10 24 24 24 24 24 24 24 24 24 10 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 10 24 24 12 24 24 12 24 24 12 24 24 10 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 10 24 24 12 24 24 14 24 24 12 24 24 10 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 10 24 24 12 24 24 12 24 24 12 24 24 10 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 10 24 24 24 24 24 24 24 24 24 10 24 24 24 + 24 24 24 24 24 10 24 24 10 24 24 10 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + + A16BE24Sleeve { + id 16240; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2033 + ); + } + + // Unrodded assemblies + A0E24U { + id 2424; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 13 24 24 13 24 24 13 24 24 24 24 24 + 24 24 24 13 24 24 24 24 24 24 24 24 24 13 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 13 24 24 13 24 24 13 24 24 13 24 24 13 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 13 24 24 13 24 24 14 24 24 13 24 24 13 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 13 24 24 13 24 24 13 24 24 13 24 24 13 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 13 24 24 24 24 24 24 24 24 24 13 24 24 24 + 24 24 24 24 24 13 24 24 13 24 24 13 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + + A0E24USleeve { + id 24240; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2034 + );} + + A0E16U { + id 2416; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 13 16 16 13 16 16 13 16 16 16 16 16 + 16 16 16 13 16 16 16 16 16 16 16 16 16 13 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 13 16 16 13 16 16 13 16 16 13 16 16 13 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 13 16 16 13 16 16 14 16 16 13 16 16 13 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 13 16 16 13 16 16 13 16 16 13 16 16 13 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 13 16 16 16 16 16 16 16 16 16 13 16 16 16 + 16 16 16 16 16 13 16 16 13 16 16 13 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16); } + + // sleeved + A0E16USleeve { + id 24160; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2035 + ); + } + + A0E31U { + id 2431; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 13 31 31 13 31 31 13 31 31 31 31 31 + 31 31 31 13 31 31 31 31 31 31 31 31 31 13 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 13 31 31 13 31 31 13 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 13 31 31 14 31 31 13 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 13 31 31 13 31 31 13 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 13 31 31 31 31 31 31 31 31 31 13 31 31 31 + 31 31 31 31 31 13 31 31 13 31 31 13 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A0E31USleeve { + id 24310; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2036 + ); + } + + + A6BE31BU { + id 70316; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 10 31 31 13 31 31 10 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 13 31 31 13 31 31 13 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 13 31 31 14 31 31 13 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 13 31 31 13 31 31 13 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 13 31 31 31 31 31 31 31 31 31 13 31 31 31 + 31 31 31 31 31 13 31 31 13 31 31 13 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + + A6BE31BUSleeve { + id 703160; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2037 + ); + } + + A6BE31TU { + id 703112; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 13 31 31 13 31 31 13 31 31 31 31 31 + 31 31 31 13 31 31 31 31 31 31 31 31 31 13 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 13 31 31 13 31 31 13 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 13 31 31 14 31 31 13 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 13 31 31 13 31 31 13 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 10 31 31 13 31 31 10 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A6BE31TUSleeve { + id 7031120; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2038 + ); + } + + A6BE31RU { + id 70313; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 10 31 31 13 31 31 13 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 13 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 13 31 31 13 31 31 13 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 13 31 31 14 31 31 13 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 13 31 31 13 31 31 13 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 13 31 31 31 + 31 31 31 31 31 10 31 31 13 31 31 13 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A6BE31RUSleeve { + id 703130; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2039 + ); + } + + A6BE31LU { + id 70319; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 13 31 31 13 31 31 10 31 31 31 31 31 + 31 31 31 13 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 13 31 31 13 31 31 13 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 13 31 31 14 31 31 13 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 13 31 31 13 31 31 13 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 13 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 13 31 31 13 31 31 10 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A6BE31LUSleeve { + id 703190; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2040 + ); + } + + A15BE31BRU { + id 25315; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 13 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 10 31 31 10 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 14 31 31 10 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 10 31 31 10 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 13 31 31 31 31 31 31 31 31 31 13 31 31 31 + 31 31 31 31 31 13 31 31 13 31 31 13 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A15BE31BRUSleeve { + id 253150; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2041 + ); + } + + A15BE31BLU { + id 25317; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 13 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 10 31 31 10 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 10 31 31 14 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 10 31 31 10 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 13 31 31 31 31 31 31 31 31 31 13 31 31 31 + 31 31 31 31 31 13 31 31 13 31 31 13 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A15BE31BLUSleeve { + id 253170; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2042 + ); + } + + A15BE31TRU { + id 25311; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 13 31 31 13 31 31 13 31 31 31 31 31 + 31 31 31 13 31 31 31 31 31 31 31 31 31 13 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 10 31 31 10 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 14 31 31 10 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 10 31 31 10 31 31 13 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 13 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A15BE31TRUSleeve { + id 253110; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2043 + ); + } + + A15BE31TLU { + id 253111; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 13 31 31 13 31 31 13 31 31 31 31 31 + 31 31 31 13 31 31 31 31 31 31 31 31 31 13 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 10 31 31 10 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 10 31 31 14 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 13 31 31 10 31 31 10 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 13 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A15BE31TLUSleeve { + id 2531110; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2044 + ); + } + + A16BE31U { + id 2631; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 13 31 31 13 31 31 13 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 13 31 31 14 31 31 13 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 13 31 31 13 31 31 13 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A16BE31USleeve { + id 26310; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2045 + ); + } + + A20BE31U { + id 3031; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 13 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 13 31 31 14 31 31 13 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 10 31 31 10 31 31 13 31 31 10 31 31 10 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 10 31 31 31 31 31 31 31 31 31 10 31 31 31 + 31 31 31 31 31 10 31 31 10 31 31 10 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 + 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 31 ); } + + A20BE31USleeve { + id 30310; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2046 + ); + } + + A12BE24U { + id 2224; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 10 24 24 13 24 24 10 24 24 24 24 24 + 24 24 24 10 24 24 24 24 24 24 24 24 24 10 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 10 24 24 13 24 24 13 24 24 13 24 24 10 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 13 24 24 13 24 24 14 24 24 13 24 24 13 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 10 24 24 13 24 24 13 24 24 13 24 24 10 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 10 24 24 24 24 24 24 24 24 24 10 24 24 24 + 24 24 24 24 24 10 24 24 13 24 24 10 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + + A12BE24USleeve { + id 22240; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2047 + ); + } + + A16BE24U { + id 2624; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 10 24 24 10 24 24 10 24 24 24 24 24 + 24 24 24 10 24 24 24 24 24 24 24 24 24 10 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 10 24 24 13 24 24 13 24 24 13 24 24 10 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 10 24 24 13 24 24 14 24 24 13 24 24 10 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 10 24 24 13 24 24 13 24 24 13 24 24 10 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 10 24 24 24 24 24 24 24 24 24 10 24 24 24 + 24 24 24 24 24 10 24 24 10 24 24 10 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + + A16BE24USleeve { + id 26240; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2048 + ); + } + + A0E24DBank { + id 1425; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 17 24 24 17 24 24 17 24 24 24 24 24 + 24 24 24 17 24 24 24 24 24 24 24 24 24 17 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 17 24 24 17 24 24 17 24 24 17 24 24 17 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 17 24 24 17 24 24 14 24 24 17 24 24 17 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 17 24 24 17 24 24 17 24 24 17 24 24 17 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 17 24 24 24 24 24 24 24 24 24 17 24 24 24 + 24 24 24 24 24 17 24 24 17 24 24 17 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 + 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 24 ); } + + // assembly with sleeves at different heights + A0E24SleeveDBank { + id 14250; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2049 + );} + + A0E16DBank { + id 1417; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.26 1.26 0.0); + shape (17 17 0); + padMat Water; + map ( + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 17 16 16 17 16 16 17 16 16 16 16 16 + 16 16 16 17 16 16 16 16 16 16 16 16 16 17 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 17 16 16 17 16 16 17 16 16 17 16 16 17 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 17 16 16 17 16 16 14 16 16 17 16 16 17 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 17 16 16 17 16 16 17 16 16 17 16 16 17 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 17 16 16 16 16 16 16 16 16 16 17 16 16 16 + 16 16 16 16 16 17 16 16 17 16 16 17 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 + 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16); + + } + + A0E16SleeveDBank { + id 14170; + type cellUniverse; + cells ( + 2001 2002 2003 2004 2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 + 2016 2017 2018 2050 + ); + } + + + leftBaffleUni { + id 5222; + type cellUniverse; + cells (52 53 54);} + + + rightBaffleUni { + id 5223; + type cellUniverse; + cells (55 56 57);} + + topBaffleUni { + id 5224; + type cellUniverse; + cells (58 59 60);} + + bottomBaffleUni { + id 5225; + type cellUniverse; + cells (61 62 63);} + + + topLeft { + id 5226; + type cellUniverse; + cells (64 65 66 67 68);} + + topRight { + id 5227; + type cellUniverse; + cells ( 69 70 71 72 73);} + + BottomLeft { + id 5228; + type cellUniverse; + cells ( 74 75 76 77 78);} + + BottomRight { + id 5229; + type cellUniverse; + cells ( 79 80 81 82 83);} + + + SQTL { + id 1500; + type cellUniverse; + cells (84 85 86 87);} + + + SQTR { + id 1600; + type cellUniverse; + cells (88 89 90 91);} + + SQBL { + id 1700; + type cellUniverse; + cells (92 93 94 95);} + + SQBR { + id 1800; + type cellUniverse; + cells (96 97 98 99);} + + + latCore { + id 9999; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (21.50364 21.50364 0.0); + shape (17 17 0); + padMat Water; + map ( + 1001 1001 1001 1001 1800 5224 5224 5224 5224 5224 5224 5224 1700 1001 1001 1001 1001 + 1001 1001 1800 5224 5229 24310 7031120 24310 7031120 24310 7031120 24310 5228 5224 1700 1001 1001 + 1001 1800 5229 24310 14310 26310 14160 30310 14160 30310 14160 26310 14310 24310 5228 1700 1001 + 1001 5222 24310 2531110 26240 14160 26240 14160 26240 14160 26240 14160 26240 253110 24310 5223 1001 + 1800 5229 14310 26240 14250 26240 24160 22240 14160 22240 24160 26240 14250 26240 14310 5228 1700 + 5222 24310 26310 14160 26240 24160 22240 24160 22240 24160 22240 24160 26240 14160 26310 24310 5223 + 5222 703190 14160 26240 24160 22240 14160 22240 14160 22240 14160 22240 24160 26240 14160 703130 5223 + 5222 24310 30310 14160 22240 24160 22240 24160 26240 24160 22240 24160 22240 14160 30310 24310 5223 + 5222 703190 14160 26240 14160 22240 14160 26240 14170 26240 14160 22240 14160 26240 14160 703130 5223 + 5222 24310 30310 14160 22240 24160 22240 24160 26240 24160 22240 24160 22240 14160 30310 24310 5223 + 5222 703190 14160 26240 24160 22240 14160 22240 14160 22240 14160 22240 24160 26240 14160 703130 5223 + 5222 24310 26310 14160 26240 24160 22240 24160 22240 24160 22240 24160 26240 14160 26310 24310 5223 + 1600 5227 14310 26240 14250 26240 24160 22240 14160 22240 24160 26240 14250 26240 14310 5226 1500 + 1001 5222 24310 253170 26240 14160 26240 14160 26240 14160 26240 14160 26240 253150 24310 5223 1001 + 1001 1600 5227 24310 14310 26310 14160 30310 14160 30310 14160 26310 14310 24310 5226 1500 1001 + 1001 1001 1600 5225 5227 24310 703160 24310 703160 24310 703160 24310 5226 5225 1500 1001 1001 + 1001 1001 1001 1001 1600 5225 5225 5225 5225 5225 5225 5225 1500 1001 1001 1001 1001 ); } + + coreAndStructures { + id 8888; + type cellUniverse; + cells (7 8 9 10 11 12 13 14 15 16 17);} + + + + } +} + + +viz { + bmpZ { + type bmp; + output imgXY; + what material; + centre (0 0 167.74); + width (100 100); + axis z; + res (2000 2000); + } + bmpYZ { + type bmp; + output imgYZ; + what material; + centre (0.0 0.0 230.0); + !width (400.0 400.0); + axis x; + res (2000 2000); + } + bmpXZ { + type bmp; + output imgXZ; + what material; + centre (0.0 0.0 230.0); + !width (400.0 400.0); + axis x; + res (2000 2000); + } +} + + +nuclearData { + handles { + ce {type aceNeutronDatabase; aceLibrary $SCONE_ACE; ures 0; } + } + + materials { + + Air { + temp 566; + composition { + 18036.01 7.8730E-09; + 18038.01 1.4844E-09; + 18040.01 2.3506E-06; + 6012.01 6.7539E-08; + 6013.01 7.5658E-10; + 7014.01 1.9680E-04; + 7015.01 7.2354E-07; + 8016.01 5.2866E-05; + 8017.01 2.0084E-08; + //8018.01 1.0601E-07; + } + } + + SS304 { + temp 566; + composition { + 24050.01 7.6778E-04; + 24052.01 1.4806E-02; + 24053.01 1.6789E-03; + 24054.01 4.1791E-04; + 26054.01 3.4620E-03; + 26056.01 5.4345E-02; + 26057.01 1.2551E-03; + 26058.01 1.6703E-04; + 25055.01 1.7604E-03; + 28058.01 5.6089E-03; + 28060.01 2.1605E-03; + 28061.01 9.3917E-05; + 28062.01 2.9945E-04; + 28064.01 7.6261E-05; + 14028.01 9.5281E-04; + 14029.01 4.8381E-05; + 14030.01 3.1893E-05; } + } + + Helium { + temp 566; + composition { + 2003.01 4.8089E-10; + 2004.01 2.4044E-04; } + } + + BorosilicateGlass { + temp 566; + composition { + 13027.01 1.7352E-03; + 5010.01 9.6506E-04; + 5011.01 3.9189E-03; + 8016.01 4.6514E-02; + 8017.01 1.7671E-05; + 8018.01 9.3268E-05; + 14028.01 1.6926E-02; + 14029.01 8.5944E-04; + 14030.01 5.6654E-04; } + } + + Water { + temp 566; + moder {1001.01 (h-h2o.52 h-h2o.53); } + composition { + 5010.01 7.9714E-06; + 5011.01 3.2247E-05; + 1001.01 4.9456E-02; + 1002.01 7.7035E-06; + 8016.01 2.4673E-02; + 8017.01 9.3734E-06; + 8018.01 4.9474E-05; + } + } + + Zircaloy { + temp 566; + composition { + 24050.01 3.2962E-06; + 24052.01 6.3564E-05; + 24053.01 7.2076E-06; + 24054.01 1.7941E-06; + 26054.01 8.6698E-06; + 26056.01 1.3610E-04; + 26057.01 3.1431E-06; + 26058.01 4.1829E-07; + 8016.01 3.0744E-04; + 8017.01 1.1680E-07; + 8018.01 6.1648E-07; + 50112.01 4.6735E-06; + 50114.01 3.1799E-06; + 50115.01 1.6381E-06; + 50116.01 7.0055E-05; + 50117.01 3.7003E-05; + 50118.01 1.1669E-04; + 50119.01 4.1387E-05; + 50120.01 1.5697E-04; + 50122.01 2.2308E-05; + 50124.01 2.7897E-05; + 40090.01 2.1828E-02; + 40091.01 4.7601E-03; + 40092.01 7.2759E-03; + 40094.01 7.3734E-03; + 40096.01 1.1879E-03; } + } + + Inconel{ + temp 566; + composition { + 24050.01 7.8239E-04; + 24052.01 1.5088E-02; + 24053.01 1.7108E-03; + 24054.01 4.2586E-04; + 26054.01 1.4797E-03; + 26056.01 2.3229E-02; + 26057.01 5.3645E-04; + 26058.01 7.1392E-05; + 25055.01 7.8201E-04; + 28058.01 2.9320E-02; + 28060.01 1.1294E-02; + 28061.01 4.9094E-04; + 28062.01 1.5653E-03; + 28064.01 3.9864E-04; + 14028.01 5.6757E-04; + 14029.01 2.8820E-05; + 14030.01 1.8998E-05; } + } + + B4C{ + temp 566; + composition { + 5010.01 1.5206E-02; + 5011.01 6.1514E-02; + 6012.01 1.8972E-02; + 6013.01 2.1252E-04; + } + } + + Ag-In-Cd{ + temp 566; + composition { + 47107.01 2.3523E-02; + 47109.01 2.1854E-02; + 48106.01 3.3882E-05; + 48108.01 2.4166E-05; + 48110.01 3.3936E-04; + 48111.01 3.4821E-04; + 48112.01 6.5611E-04; + 48113.01 3.3275E-04; + 48114.01 7.8252E-04; + 48116.01 2.0443E-04; + 49113.01 3.4219E-04; + 49115.01 7.6511E-03; } + } + + UO2-16 { + temp 566; + tms 1; + composition { + 8016.00 4.5897E-02; + 8017.00 1.7436E-05; + 8018.00 9.2032E-05; + 92234.00 3.0131E-06; + 92235.00 3.7503E-04; + 92238.00 2.2625E-02;} + } + + UO2-24 { + temp 566; + tms 1; + composition { + 8016.00 4.5830E-02; + 8017.00 1.7411E-05; + 8018.00 9.1898E-05; + 92234.00 4.4842E-06; + 92235.00 5.5814E-04; + 92238.00 2.2407E-02;} + } + + UO2-31 { + temp 566; + tms 1; + composition { + 8016.00 4.5853E-02; + 8017.00 1.7420E-05; + 8018.00 9.1942E-05; + 92234.00 5.7987E-06; + 92235.00 7.2175E-04; + 92238.00 2.2253E-02;} + } + + UO2-32 { + temp 566; + tms 1; + composition { + 8016.00 4.6029E-02; + 8017.00 1.7487E-05; + 8018.00 9.2296E-05; + 92234.00 5.9959E-06; + 92235.00 7.4630E-04; + 92238.00 2.2317E-02; + } + } + + UO2-34 { + temp 566; + tms 1; + composition { + 8016.00 4.6110E-02; + 8017.00 1.7517E-05; + 8018.00 9.2459E-05; + 92234.00 6.4018E-06; + 92235.00 7.9681E-04; + 92238.00 2.2307E-02;} + } + + // vanadium51 was stated twice in carbonsteel below + // in the beavrs pdf - typo? + CarbonSteel { + temp 566; + composition { + 13027.01 4.3523E-05; + 5010.01 2.5833E-06; + 5011.01 1.0450E-05; + 6012.01 1.0442E-03; + 6013.01 1.1697E-05 ; + 20040.01 1.7043E-05; + 20042.01 1.1375E-07; + 20043.01 2.3734E-08; + 20044.01 3.6673E-07; + 20046.01 7.0322E-10; + 20048.01 3.2875E-08; + 24050.01 1.3738E-05; + 24052.01 2.6493E-04; + 24053.01 3.0041E-05; + 24054.01 7.4778E-06; + 29063.01 1.0223E-04; + 29065.01 4.5608E-05; + 26054.01 4.7437E-03; + 26056.01 7.4465E-02; + 26057.01 1.7197E-03; + 26058.01 2.2886E-04; + 25055.01 6.4126E-04; + 42100.01 2.9814E-05; + 42092.01 4.4822E-05; + 42094.01 2.8110E-05; + 42095.01 4.8567E-05; + 42096.01 5.1015E-05; + 42097.01 2.9319E-05; + 42098.01 7.4327E-05; + 41093.01 5.0559E-06; + 28058.01 4.0862E-04; + 28060.01 1.5740E-04; + 28061.01 6.8420E-06; + 28062.01 2.1815E-05; + 28064.01 5.5557E-06; + 15031.01 3.7913E-05; + 16032.01 3.4808E-05; + 16033.01 2.7420E-07; + 16034.01 1.5368E-06; + 16036.01 5.3398E-09; + 14028.01 6.1702E-04; + 14029.01 3.1330E-05; + 14030.01 2.0653E-05; + 22046.01 1.2144E-06; + 22047.01 1.0952E-06; + 22048.01 1.0851E-05; + 22049.01 7.9634E-07; + 22050.01 7.6249E-07; + 23050.01 1.1526E-07; + 23051.01 4.5989E-05; + } + } + + SupportPlateSS { + temp 566; + composition { + 24050.01 3.5223E-04; + 24052.01 6.7924E-03; + 24053.01 7.7020E-04; + 24054.01 1.9172E-04; + 26054.01 1.5882E-03; + 26056.01 2.4931E-02; + 26057.01 5.7578E-04; + 26058.01 7.6625E-05; + 25055.01 8.0762E-04; + 28058.01 2.5731E-03; + 28060.01 9.9117E-04; + 28061.01 4.3085E-05; + 28062.01 1.3738E-04; + 28064.01 3.4985E-05; + 14028.01 4.3711E-04; + 14029.01 2.2195E-05; + 14030.01 1.4631E-05;} + } + + SupportPlateBW { + temp 566; + moder {1001.01 (h-h2o.52 h-h2o.53); } + composition { + 5010.01 1.0559E-05; + 5011.01 4.2716E-05; + 1001.01 6.5512E-02; + 1002.01 1.0204E-05; + 8016.01 3.2683E-02; + 8017.01 1.2416E-05; + 8018.01 6.5535E-05; + } + } + + + +} +} diff --git a/InputFiles/Benchmarks/LDR50/LDR50 b/InputFiles/Benchmarks/LDR50/LDR50 new file mode 100644 index 000000000..bfe7bd27a --- /dev/null +++ b/InputFiles/Benchmarks/LDR50/LDR50 @@ -0,0 +1,1395 @@ +type eigenPhysicsPackage; + +pop 2000000; +active 100; +inactive 100; +XSdata ce; +dataType ce; +outputFile LDR50; + +collisionOperator { neutronCE {type neutronCEstd;}} + +transportOperator { + !type transportOperatorDT; + type transportOperatorHT; cache 1; + } + +inactiveTally { + shannon { + type shannonEntropyClerk; + map {type multiMap; + maps (xax yax zax); + xax { type spaceMap; grid lin; min -75.26; max 75.26; N 15; axis x;} + yax { type spaceMap; grid lin; min -75.26; max 75.26; N 15; axis y;} + zax { type spaceMap; grid lin; min 11.748; max 111.748; N 15; axis z;} + } + cycles 250; + } + +} + +activeTally { + k_eff { type keffAnalogClerk;} + pinFissRadial { type collisionClerk; response (fission); fission { type macroResponse; MT -6;} + map {type multiMap; maps (xax yax); + xax {type spaceMap; axis x; grid lin; N 119; min -75.26274; max 75.26274; } + yax {type spaceMap; axis y; grid lin; N 119; min -75.26274; max 75.26274; } + } + } + assemblyFissRadial { type collisionClerk; response (fission); fission { type macroResponse; MT -6;} + map {type multiMap; maps (xax yax); + xax {type spaceMap; axis x; grid lin; N 7; min -75.26274; max 75.26274; } + yax {type spaceMap; axis y; grid lin; N 7; min -75.26274; max 75.26274; } + } + } + fissionAxial { type collisionClerk; response (fission); fission { type macroResponse; MT -6;} + map {type spaceMap; axis z; grid unstruct; bins (11.748 17.463 22.998625 28.53425 34.069875 39.6055 45.141125 50.67675 56.212375 61.748 67.463 72.998625 78.53425 84.069875 89.6055 95.141125 100.67675 106.212375 111.748);} + } +} + +geometry { + type geometryStd; + boundary ( 0 0 0 0 0 0); + graph {type shrunk;} + + surfaces { + + // Boundary surface + boundary {id 1; type zTruncCylinder; origin (0 0 50.9855); radius 135; halfwidth 67.7335; } + core {id 100; type zCylinder; origin (0 0 0); radius 91;} + + // Grid for lower and middle spacers + gridZr {id 2; type zSquareCylinder; origin (0.0 0.0 0.0); halfwidth (0.61049 0.61049 0.0);} + outerGridZr {id 3; type zSquareCylinder; origin (0.0 0.0 0.0); halfwidth (0.62992 0.62992 0.0);} + + // Grid for upper spacer + gridInc {id 4; type zSquareCylinder; origin (0.0 0.0 0.0); halfwidth (0.61015 0.61015 0.0);} + + // Spacer grid height + SG3_top {id 10; type zPlane; z0 103.358;} + SG3_bottom {id 11; type zPlane; z0 100;} + + SG2_top {id 12; type zPlane; z0 55.715;} + SG2_bottom {id 13; type zPlane; z0 50.0;} + + SG1_top {id 14; type zPlane; z0 5.715;} + SG1_bottom {id 15; type zPlane; z0 0.0;} + + // Assembly wrappers + wrapInner {id 16; type zSquareCylinder; origin (0.0 0.0 0.0); halfwidth (10.70864 10.70864 0.0);} + wrapOuter {id 17; type zSquareCylinder; origin (0.0 0.0 0.0); halfwidth (10.74798 10.74798 0.0);} + + // All rods in + !R2_Plane1 {id 40; type zPlane; z0 100.0; } + !R2_Plane2 {id 41; type zPlane; z0 60.0; } + !R2_Plane3 {id 42; type zPlane; z0 0.0; } + !safeRodPlane1 {id 43; type zPlane; z0 100.0; } + !safeRodPlane2 {id 44; type zPlane; z0 5.0; } + !safeRodPlane3 {id 45; type zPlane; z0 0.0; } + !R3_Plane1 {id 46; type zPlane; z0 100.0; } + !R3_Plane2 {id 47; type zPlane; z0 60.0; } + !R3_Plane3 {id 48; type zPlane; z0 0.0; } + !R5_Plane1 {id 49; type zPlane; z0 100.0; } + !R5_Plane2 {id 50; type zPlane; z0 60.0; } + !R5_Plane3 {id 51; type zPlane; z0 0.0; } + !R6_Plane1 {id 52; type zPlane; z0 100.0; } + !R6_Plane2 {id 53; type zPlane; z0 60.0; } + !R6_Plane3 {id 54; type zPlane; z0 0.0; } + + // All rods out + R2_Plane1 {id 40; type zPlane; z0 200.0; } + R2_Plane2 {id 41; type zPlane; z0 160.0; } + R2_Plane3 {id 42; type zPlane; z0 100.0; } + safeRodPlane1 {id 43; type zPlane; z0 200.0; } + safeRodPlane2 {id 44; type zPlane; z0 105.0; } + safeRodPlane3 {id 45; type zPlane; z0 100.0; } + R3_Plane1 {id 46; type zPlane; z0 200.0; } + R3_Plane2 {id 47; type zPlane; z0 160.0; } + R3_Plane3 {id 48; type zPlane; z0 100.0; } + R5_Plane1 {id 49; type zPlane; z0 200.0; } + R5_Plane2 {id 50; type zPlane; z0 160.0; } + R5_Plane3 {id 51; type zPlane; z0 100.0; } + R6_Plane1 {id 52; type zPlane; z0 200.0; } + R6_Plane2 {id 53; type zPlane; z0 160.0; } + R6_Plane3 {id 54; type zPlane; z0 100.0; } + + // Critical rodded + // Rod height + // R2 at 70% insertion - so added 30cm + // Plane between steel and upper absorber + !R2_Plane1 {id 40; type zPlane; z0 130.0; } + !R2_Plane2 {id 41; type zPlane; z0 90.0; } + !R2_Plane3 {id 42; type zPlane; z0 30.0; } + + + // Safety rods + // Untouched from ARO + // Added 100cm to fully remove from assembly + // Plane between steel and upper absorber + !safeRodPlane1 {id 43; type zPlane; z0 200.0; } + !safeRodPlane2 {id 44; type zPlane; z0 105.0; } + !safeRodPlane3 {id 45; type zPlane; z0 100.0; } + + // R3 + // 100% insertion so add 0cm + // Plane between steel and upper absorber + !R3_Plane1 {id 46; type zPlane; z0 100.0; } + !R3_Plane2 {id 47; type zPlane; z0 60.0; } + !R3_Plane3 {id 48; type zPlane; z0 0.0; } + + + // R5 + // 98% insertion so add 2cm + // Plane between steel and upper absorber + !R5_Plane1 {id 49; type zPlane; z0 102.0; } + !R5_Plane2 {id 50; type zPlane; z0 62.0; } + !R5_Plane3 {id 51; type zPlane; z0 2.0; } + + // R6 + // 98% insertion so add 2cm + !R6_Plane1 {id 52; type zPlane; z0 102.0; } + !R6_Plane2 {id 53; type zPlane; z0 62.0; } + !R6_Plane3 {id 54; type zPlane; z0 2.0; } + + + // Others planes across the core + upperNozzleTop { id 20; type zPlane; z0 118.719;} + upperNozzleBottom { id 21; type zPlane; z0 109.892;} + fuelTop {id 22; type zPlane; z0 106.547;} + plenumTop {id 23; type zPlane; z0 104.007;} + activeFuelTop {id 24; type zPlane; z0 100.0;} + activeFuelBottom {id 25; type zPlane; z0 0.0;} + plugsBottom {id 26; type zPlane; z0 -1.748;} + lowerSupportPlateBottom {id 28; type zPlane; z0 -16.748;} + + } + + cells { + + // Cell for lower grid + gridZrLow {id 2; type simpleCell; surfaces (2 15 -14); filltype mat; material Zircaloy;} + gridZrMid {id 3; type simpleCell; surfaces (2 13 -12); filltype mat; material Zircaloy;} + // Cell for upper grid + gridInc {id 4; type simpleCell; surfaces (4 11 -10); filltype mat; material Inconel;} + + // Cells for water surrounding grid + waterBelow {id 5; type simpleCell; surfaces (-15); filltype mat; material Water;} + waterAtGrid1 {id 6; type simpleCell; surfaces (-2 15 -14); filltype mat; material Water;} + waterBetween1 {id 7; type simpleCell; surfaces (14 -13); filltype mat; material Water;} + waterAtGrid2 {id 8; type simpleCell; surfaces (-2 13 -12); filltype mat; material Water;} + waterBetween2 {id 9; type simpleCell; surfaces (12 -11); filltype mat; material Water;} + waterAtGrid3 {id 10; type simpleCell; surfaces (-4 11 -10); filltype mat; material Water;} + waterAbove {id 11; type simpleCell; surfaces (10); filltype mat; material Water;} + + // Cells for wrappers + wrapperLow {id 12; type simpleCell; surfaces (16 -17 15 -14); filltype mat; material Zircaloy;} + wrapperMid {id 13; type simpleCell; surfaces (16 -17 13 -12); filltype mat; material Zircaloy;} + wrapperHig {id 14; type simpleCell; surfaces (16 -17 11 -10); filltype mat; material SS304;} + // Cells for not-wrappers + belowWrapper {id 15; type simpleCell; surfaces (-15); filltype mat; material Water;} + insideWrapper1 {id 16; type simpleCell; surfaces (-16 15 -14); filltype mat; material Water;} + outsideWrapper1 {id 17; type simpleCell; surfaces (17 15 -14); filltype mat; material Water;} + betweenWrappers1 {id 18; type simpleCell; surfaces (14 -13); filltype mat; material Water;} + insideWrapper2 {id 19; type simpleCell; surfaces (-16 13 -12); filltype mat; material Water;} + outsideWrapper2 {id 20; type simpleCell; surfaces (17 13 -12); filltype mat; material Water;} + betweenWrappers2 {id 21; type simpleCell; surfaces (12 -11); filltype mat; material Water;} + insideWrapper3 {id 22; type simpleCell; surfaces (-16 11 -10); filltype mat; material Water;} + outsideWrapper3 {id 23; type simpleCell; surfaces (17 11 -10); filltype mat; material Water;} + aboveWrapper {id 24; type simpleCell; surfaces (10); filltype mat; material Water;} + + // Cell for rods - different cells for each bank to allow different heights + rodSteelS1 {id 500; type simpleCell; surfaces (43); filltype uni; universe 60;} + rodUpperS1 {id 501; type simpleCell; surfaces (-43 44); filltype uni; universe 62;} + rodLowerS1 {id 502; type simpleCell; surfaces (-44 45); filltype uni; universe 61;} + rodBeneathS1 {id 503; type simpleCell; surfaces (-45); filltype mat; material Water;} + + rodSteelR2 {id 510; type simpleCell; surfaces (40); filltype uni; universe 60;} + rodUpperR2 {id 511; type simpleCell; surfaces (-40 41); filltype uni; universe 62;} + rodLowerR2 {id 512; type simpleCell; surfaces (-41 42); filltype uni; universe 61;} + rodBeneathR2 {id 513; type simpleCell; surfaces (-42); filltype mat; material Water;} + + rodSteelR3 {id 520; type simpleCell; surfaces (46); filltype uni; universe 60;} + rodUpperR3 {id 521; type simpleCell; surfaces (-46 47); filltype uni; universe 62;} + rodLowerR3 {id 522; type simpleCell; surfaces (-47 48); filltype uni; universe 61;} + rodBeneathR3 {id 523; type simpleCell; surfaces (-48); filltype mat; material Water;} + + rodSteelS4 {id 530; type simpleCell; surfaces (43); filltype uni; universe 60;} + rodUpperS4 {id 531; type simpleCell; surfaces (-43 44); filltype uni; universe 62;} + rodLowerS4 {id 532; type simpleCell; surfaces (-44 45); filltype uni; universe 61;} + rodBeneathS4 {id 533; type simpleCell; surfaces (-45); filltype mat; material Water;} + + rodSteelR5 {id 540; type simpleCell; surfaces (49); filltype uni; universe 60;} + rodUpperR5 {id 541; type simpleCell; surfaces (-49 50); filltype uni; universe 62;} + rodLowerR5 {id 542; type simpleCell; surfaces (-50 51); filltype uni; universe 61;} + rodBeneathR5 {id 543; type simpleCell; surfaces (-51); filltype mat; material Water;} + + rodSteelR6 {id 550; type simpleCell; surfaces (52); filltype uni; universe 60;} + rodUpperR6 {id 551; type simpleCell; surfaces (-52 53); filltype uni; universe 62;} + rodLowerR6 {id 552; type simpleCell; surfaces (-53 54); filltype uni; universe 61;} + rodBeneathR6 {id 553; type simpleCell; surfaces (-54); filltype mat; material Water;} + + rodSteelS7 {id 560; type simpleCell; surfaces (43); filltype uni; universe 60;} + rodUpperS7 {id 561; type simpleCell; surfaces (-43 44); filltype uni; universe 62;} + rodLowerS7 {id 562; type simpleCell; surfaces (-44 45); filltype uni; universe 61;} + rodBeneathS7 {id 563; type simpleCell; surfaces (-45); filltype mat; material Water;} + + rodSteelS8 {id 570; type simpleCell; surfaces (43); filltype uni; universe 60;} + rodUpperS8 {id 571; type simpleCell; surfaces (-43 44); filltype uni; universe 62;} + rodLowerS8 {id 572; type simpleCell; surfaces (-44 45); filltype uni; universe 61;} + rodBeneathS8 {id 573; type simpleCell; surfaces (-45); filltype mat; material Water;} + + // Cells for assembly stacks + // These ones are generic to all assemblies + topNozzle {id 120; type simpleCell; surfaces (21); filltype mat; material Water_Steel_Mix;} + aboveAssembly {id 121; type simpleCell; surfaces (-21 22 ); filltype uni; universe 320;} + topPlugs {id 122; type simpleCell; surfaces (-22 23 ); filltype uni; universe 300;} + plenum {id 123; type simpleCell; surfaces (-23 24 ); filltype uni; universe 310;} + bottomPlugs {id 124; type simpleCell; surfaces (-25 26); filltype uni; universe 300;} + supportPlate {id 125; type simpleCell; surfaces (-26); filltype mat; material Water_Steel_Mix;} + + // These ones are specific to different assemblies + assembly1 {id 126; type simpleCell; surfaces (-24 25); filltype uni; universe 440;} + assembly2 {id 127; type simpleCell; surfaces (-24 25); filltype uni; universe 400;} + assembly3 {id 128; type simpleCell; surfaces (-24 25); filltype uni; universe 450;} + assembly4 {id 129; type simpleCell; surfaces (-24 25); filltype uni; universe 460;} + assembly5 {id 130; type simpleCell; surfaces (-24 25); filltype uni; universe 470;} + assembly6 {id 131; type simpleCell; surfaces (-24 25); filltype uni; universe 420;} + + core {id 100; type simpleCell; surfaces (-100); filltype uni; universe 888;} + everythingElse {id 101; type simpleCell; surfaces (100); filltype mat; material Water;} + } + + universes { + + // Pin universes + // Each fuel pin + pin14 { id 140; type pinUniverse; radii (0.4095 0.41790 0.47500 0.0); fills (UO2-14 Air Zircaloy u<99>);} + pin15 { id 150; type pinUniverse; radii (0.4095 0.41790 0.47500 0.0); fills (UO2-15 Air Zircaloy u<99>);} + pin18 { id 180; type pinUniverse; radii (0.4095 0.41790 0.47500 0.0); fills (UO2-18 Air Zircaloy u<99>);} + pin24 { id 240; type pinUniverse; radii (0.4095 0.41790 0.47500 0.0); fills (UO2-24 Air Zircaloy u<99>);} + pin15_6 { id 156; type pinUniverse; radii (0.4095 0.41790 0.47500 0.0); fills (UO2-15-Gd-6 Air Zircaloy u<99>);} + pin18_6 { id 186; type pinUniverse; radii (0.4095 0.41790 0.47500 0.0); fills (UO2-18-Gd-6 Air Zircaloy u<99>);} + pin24_5 { id 245; type pinUniverse; radii (0.4095 0.41790 0.47500 0.0); fills (UO2-24-Gd-5 Air Zircaloy u<99>);} + pin24_9 { id 249; type pinUniverse; radii (0.4095 0.41790 0.47500 0.0); fills (UO2-24-Gd-9 Air Zircaloy u<99>);} + + // Zr plug + zrPlug { id 20; type pinUniverse; radii (0.475 0.0); fills (Zircaloy u<99>);} + + // Rod plenum + plenum { id 30; type pinUniverse; radii (0.06459 0.4179 0.475 0); fills (SS304 Air Zircaloy u<99>);} + + // Guide tube + guideTube { id 40; type pinUniverse; radii (0.48387 0.50419 0.54610 0.0); fills (u<777> Water Zircaloy u<99>);} + + // Instrumentation tube + instTube { id 90; type pinUniverse; radii (0.50419 0.54610 0.0); fills (Water Zircaloy u<99>);} + + // CR upper part with steel + CRSteelUpper {id 60; type pinUniverse; radii (0.0); fills (SS304);} + + // CR lower absorber part with Inconel + lowerCR {id 61; type pinUniverse; radii (0.0); fills (Inconel);} + + // CR upper absorber part with B4C + upperCR {id 62; type pinUniverse; radii (0.43310 0.43688 0.0); fills (B4C Air SS304);} + + // Coolant channel with grids + channel {id 99; type cellUniverse; cells (2 3 4 5 6 7 8 9 10 11); } + + // wrapper + wrapper {id 98; type cellUniverse; cells (12 13 14 15 16 17 18 19 20 21 22 23 24);} + + // Assemblies, at various heights + // Include an extra pin layer for the sleeve + zrPlugs { + id 300; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (19 19 0); + offsetMap ( + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + ); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 98 + 98 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 98 + 98 20 20 20 20 20 40 20 20 40 20 20 40 20 20 20 20 20 98 + 98 20 20 20 40 20 20 20 20 20 20 20 20 20 40 20 20 20 98 + 98 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 98 + 98 20 20 40 20 20 40 20 20 40 20 20 40 20 20 40 20 20 98 + 98 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 98 + 98 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 98 + 98 20 20 40 20 20 40 20 20 90 20 20 40 20 20 40 20 20 98 + 98 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 98 + 98 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 98 + 98 20 20 40 20 20 40 20 20 40 20 20 40 20 20 40 20 20 98 + 98 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 98 + 98 20 20 20 40 20 20 20 20 20 20 20 20 20 40 20 20 20 98 + 98 20 20 20 20 20 40 20 20 40 20 20 40 20 20 20 20 20 98 + 98 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 98 + 98 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + fuelPlenum { + id 310; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (19 19 0); + offsetMap ( + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + ); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 98 + 98 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 98 + 98 30 30 30 30 30 40 30 30 40 30 30 40 30 30 30 30 30 98 + 98 30 30 30 40 30 30 30 30 30 30 30 30 30 40 30 30 30 98 + 98 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 98 + 98 30 30 40 30 30 40 30 30 40 30 30 40 30 30 40 30 30 98 + 98 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 98 + 98 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 98 + 98 30 30 40 30 30 40 30 30 90 30 30 40 30 30 40 30 30 98 + 98 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 98 + 98 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 98 + 98 30 30 40 30 30 40 30 30 40 30 30 40 30 30 40 30 30 98 + 98 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 98 + 98 30 30 30 40 30 30 30 30 30 30 30 30 30 40 30 30 30 98 + 98 30 30 30 30 30 40 30 30 40 30 30 40 30 30 30 30 30 98 + 98 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 98 + 98 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 30 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + spaceBelowNozzles { + id 320; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (19 19 0); + offsetMap ( + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + ); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 40 98 98 40 98 98 40 98 98 98 98 98 98 + 98 98 98 98 40 98 98 98 98 98 98 98 98 98 40 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 40 98 98 40 98 98 40 98 98 40 98 98 40 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 40 98 98 40 98 98 90 98 98 40 98 98 40 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 40 98 98 40 98 98 40 98 98 40 98 98 40 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 40 98 98 98 98 98 98 98 98 98 40 98 98 98 98 + 98 98 98 98 98 98 40 98 98 40 98 98 40 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + // Fuel assemblies + // 1.4% enriched + fuel2 { + id 400; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (19 19 0); + offsetMap ( + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + ); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 98 + 98 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 98 + 98 140 140 140 140 140 40 140 140 40 140 140 40 140 140 140 140 140 98 + 98 140 140 140 40 140 140 140 140 140 140 140 140 140 40 140 140 140 98 + 98 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 98 + 98 140 140 40 140 140 40 140 140 40 140 140 40 140 140 40 140 140 98 + 98 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 98 + 98 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 98 + 98 140 140 40 140 140 40 140 140 90 140 140 40 140 140 40 140 140 98 + 98 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 98 + 98 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 98 + 98 140 140 40 140 140 40 140 140 40 140 140 40 140 140 40 140 140 98 + 98 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 98 + 98 140 140 140 40 140 140 140 140 140 140 140 140 140 40 140 140 140 98 + 98 140 140 140 140 140 40 140 140 40 140 140 40 140 140 140 140 140 98 + 98 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 98 + 98 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 140 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + // 1.8% enriched + fuel6 { + id 420; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (19 19 0); + offsetMap ( + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + ); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 180 180 180 40 180 180 40 180 180 40 180 180 180 180 180 98 + 98 180 180 180 40 180 180 180 180 180 180 180 180 180 40 180 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 40 180 180 40 180 180 40 180 180 40 180 180 40 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 40 180 180 40 180 180 90 180 180 40 180 180 40 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 40 180 180 40 180 180 40 180 180 40 180 180 40 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 180 40 180 180 180 180 180 180 180 180 180 40 180 180 180 98 + 98 180 180 180 180 180 40 180 180 40 180 180 40 180 180 180 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + // 1.5% enriched + 6% Gd + fuel1 { + id 440; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (19 19 0); + offsetMap ( + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + ); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 98 + 98 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 98 + 98 150 150 150 150 150 40 150 150 40 150 150 40 150 150 150 150 150 98 + 98 150 150 150 40 150 150 150 150 150 150 150 150 150 40 150 150 150 98 + 98 150 150 150 150 150 150 156 150 150 150 156 150 150 150 150 150 150 98 + 98 150 150 40 150 150 40 150 150 40 150 150 40 150 150 40 150 150 98 + 98 150 150 150 150 156 150 150 150 150 150 150 150 156 150 150 150 150 98 + 98 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 98 + 98 150 150 40 150 150 40 150 150 90 150 150 40 150 150 40 150 150 98 + 98 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 98 + 98 150 150 150 150 156 150 150 150 150 150 150 150 156 150 150 150 150 98 + 98 150 150 40 150 150 40 150 150 40 150 150 40 150 150 40 150 150 98 + 98 150 150 150 150 150 150 156 150 150 150 156 150 150 150 150 150 150 98 + 98 150 150 150 40 150 150 150 150 150 150 150 150 150 40 150 150 150 98 + 98 150 150 150 150 150 40 150 150 40 150 150 40 150 150 150 150 150 98 + 98 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 98 + 98 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 150 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + // 1.8% enriched + 6% Gd + fuel3 { + id 450; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (19 19 0); + offsetMap ( + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + ); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 180 180 180 40 180 180 40 180 180 40 180 180 180 180 180 98 + 98 180 180 180 40 180 180 180 180 180 180 180 180 180 40 180 180 180 98 + 98 180 180 180 180 186 180 180 180 180 180 180 180 186 180 180 180 180 98 + 98 180 180 40 180 180 40 180 180 40 180 180 40 180 180 40 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 40 180 180 40 180 180 90 180 180 40 180 180 40 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 40 180 180 40 180 180 40 180 180 40 180 180 40 180 180 98 + 98 180 180 180 180 186 180 180 180 180 180 180 180 186 180 180 180 180 98 + 98 180 180 180 40 180 180 180 180 180 180 180 180 180 40 180 180 180 98 + 98 180 180 180 180 180 40 180 180 40 180 180 40 180 180 180 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 180 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + // 2.4% enriched + 5% Gd + fuel4 { + id 460; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (19 19 0); + offsetMap ( + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + ); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 98 + 98 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 98 + 98 240 240 240 240 240 40 240 240 40 240 240 40 240 240 240 240 240 98 + 98 240 240 240 40 240 240 240 240 240 240 240 240 240 40 240 240 240 98 + 98 240 240 240 240 240 240 245 240 240 240 245 240 240 240 240 240 240 98 + 98 240 240 40 240 240 40 240 240 40 240 240 40 240 240 40 240 240 98 + 98 240 240 240 240 245 240 240 240 240 240 240 240 245 240 240 240 240 98 + 98 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 98 + 98 240 240 40 240 240 40 240 240 90 240 240 40 240 240 40 240 240 98 + 98 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 98 + 98 240 240 240 240 245 240 240 240 240 240 240 240 245 240 240 240 240 98 + 98 240 240 40 240 240 40 240 240 40 240 240 40 240 240 40 240 240 98 + 98 240 240 240 240 240 240 245 240 240 240 245 240 240 240 240 240 240 98 + 98 240 240 240 40 240 240 240 240 240 240 240 240 240 40 240 240 240 98 + 98 240 240 240 240 240 40 240 240 40 240 240 40 240 240 240 240 240 98 + 98 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 98 + 98 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + // 2.4% enriched + 9% Gd + fuel5 { + id 470; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (19 19 0); + offsetMap ( + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 + 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 + ); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 98 + 98 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 98 + 98 240 240 240 240 240 40 240 240 40 240 240 40 240 240 240 240 240 98 + 98 240 240 240 40 240 240 240 240 240 240 240 240 240 40 240 240 240 98 + 98 240 240 240 240 240 240 249 240 240 240 249 240 240 240 240 240 240 98 + 98 240 240 40 240 240 40 240 240 40 240 240 40 240 240 40 240 240 98 + 98 240 240 240 240 249 240 240 240 240 240 240 240 249 240 240 240 240 98 + 98 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 98 + 98 240 240 40 240 240 40 240 240 90 240 240 40 240 240 40 240 240 98 + 98 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 98 + 98 240 240 240 240 249 240 240 240 240 240 240 240 249 240 240 240 240 98 + 98 240 240 40 240 240 40 240 240 40 240 240 40 240 240 40 240 240 98 + 98 240 240 240 240 240 240 249 240 240 240 249 240 240 240 240 240 240 98 + 98 240 240 240 40 240 240 240 240 240 240 240 240 240 40 240 240 240 98 + 98 240 240 240 240 240 40 240 240 40 240 240 40 240 240 240 240 240 98 + 98 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 98 + 98 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 240 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + // Make each fuel assembly stack + assembly1 {id 111; type cellUniverse; cells (120 121 122 123 124 125 126 );} + assembly2 {id 222; type cellUniverse; cells (120 121 122 123 124 125 127 );} + assembly3 {id 333; type cellUniverse; cells (120 121 122 123 124 125 128 );} + assembly4 {id 444; type cellUniverse; cells (120 121 122 123 124 125 129 );} + assembly5 {id 555; type cellUniverse; cells (120 121 122 123 124 125 130 );} + assembly6 {id 666; type cellUniverse; cells (120 121 122 123 124 125 131 );} + reflector {id 999; type pinUniverse; radii (0.0); fills (SS304);} + water {id 998; type pinUniverse; radii (0.0); fills (Water);} + + // Core lattice + lattice { + id 888; + type latUniverse; + shape (9 9 0); + pitch (21.50364 21.50364 0); + padMat Water; + map ( + 999 999 999 999 999 999 999 999 999 + 999 999 999 444 666 444 999 999 999 + 999 999 555 333 222 333 555 999 999 + 999 444 333 222 222 222 333 444 999 + 999 666 222 222 111 222 222 666 999 + 999 444 333 222 222 222 333 444 999 + 999 999 555 333 222 333 555 999 999 + 999 999 999 444 666 444 999 999 999 + 999 999 999 999 999 999 999 999 999 + ); + } + + // Make individual rods + rodS1 {id 81; type cellUniverse; cells (500 501 502 503);} + rodR2 {id 82; type cellUniverse; cells (510 511 512 513);} + rodR3 {id 83; type cellUniverse; cells (520 521 522 523);} + rodS4 {id 84; type cellUniverse; cells (530 531 532 533);} + rodR5 {id 85; type cellUniverse; cells (540 541 542 543);} + rodR6 {id 86; type cellUniverse; cells (550 551 552 553);} + rodS7 {id 87; type cellUniverse; cells (560 561 562 563);} + rodS8 {id 88; type cellUniverse; cells (570 571 572 573);} + + // Place rods into assemblies + S1 { + id 509; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (17 17 0); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 81 98 98 81 98 98 81 98 98 98 98 98 + 98 98 98 81 98 98 98 98 98 98 98 98 98 81 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 81 98 98 81 98 98 81 98 98 81 98 98 81 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 81 98 98 81 98 98 98 98 98 81 98 98 81 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 81 98 98 81 98 98 81 98 98 81 98 98 81 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 81 98 98 98 98 98 98 98 98 98 81 98 98 98 + 98 98 98 98 98 81 98 98 81 98 98 81 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + R2 { + id 519; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (17 17 0); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 82 98 98 82 98 98 82 98 98 98 98 98 + 98 98 98 82 98 98 98 98 98 98 98 98 98 82 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 82 98 98 82 98 98 82 98 98 82 98 98 82 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 82 98 98 82 98 98 98 98 98 82 98 98 82 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 82 98 98 82 98 98 82 98 98 82 98 98 82 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 82 98 98 98 98 98 98 98 98 98 82 98 98 98 + 98 98 98 98 98 82 98 98 82 98 98 82 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + R3 { + id 529; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (17 17 0); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 83 98 98 83 98 98 83 98 98 98 98 98 + 98 98 98 83 98 98 98 98 98 98 98 98 98 83 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 83 98 98 83 98 98 83 98 98 83 98 98 83 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 83 98 98 83 98 98 98 98 98 83 98 98 83 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 83 98 98 83 98 98 83 98 98 83 98 98 83 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 83 98 98 98 98 98 98 98 98 98 83 98 98 98 + 98 98 98 98 98 83 98 98 83 98 98 83 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + S4 { + id 539; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (17 17 0); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 84 98 98 84 98 98 84 98 98 98 98 98 + 98 98 98 84 98 98 98 98 98 98 98 98 98 84 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 84 98 98 84 98 98 84 98 98 84 98 98 84 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 84 98 98 84 98 98 98 98 98 84 98 98 84 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 84 98 98 84 98 98 84 98 98 84 98 98 84 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 84 98 98 98 98 98 98 98 98 98 84 98 98 98 + 98 98 98 98 98 84 98 98 84 98 98 84 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + R5 { + id 549; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (17 17 0); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 85 98 98 85 98 98 85 98 98 98 98 98 + 98 98 98 85 98 98 98 98 98 98 98 98 98 85 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 85 98 98 85 98 98 85 98 98 85 98 98 85 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 85 98 98 85 98 98 98 98 98 85 98 98 85 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 85 98 98 85 98 98 85 98 98 85 98 98 85 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 85 98 98 98 98 98 98 98 98 98 85 98 98 98 + 98 98 98 98 98 85 98 98 85 98 98 85 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + R6 { + id 559; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (17 17 0); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 86 98 98 86 98 98 86 98 98 98 98 98 + 98 98 98 86 98 98 98 98 98 98 98 98 98 86 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 86 98 98 86 98 98 86 98 98 86 98 98 86 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 86 98 98 86 98 98 98 98 98 86 98 98 86 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 86 98 98 86 98 98 86 98 98 86 98 98 86 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 86 98 98 98 98 98 98 98 98 98 86 98 98 98 + 98 98 98 98 98 86 98 98 86 98 98 86 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + S7 { + id 569; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (17 17 0); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 87 98 98 87 98 98 87 98 98 98 98 98 + 98 98 98 87 98 98 98 98 98 98 98 98 98 87 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 87 98 98 87 98 98 87 98 98 87 98 98 87 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 87 98 98 87 98 98 98 98 98 87 98 98 87 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 87 98 98 87 98 98 87 98 98 87 98 98 87 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 87 98 98 98 98 98 98 98 98 98 87 98 98 98 + 98 98 98 98 98 87 98 98 87 98 98 87 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + S8 { + id 579; + type latUniverse; + pitch (1.25984 1.25984 0); + padMat Water; + shape (17 17 0); + map ( + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 88 98 98 88 98 98 88 98 98 98 98 98 + 98 98 98 88 98 98 98 98 98 98 98 98 98 88 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 88 98 98 88 98 98 88 98 98 88 98 98 88 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 88 98 98 88 98 98 98 98 98 88 98 98 88 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 88 98 98 88 98 98 88 98 98 88 98 98 88 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 88 98 98 98 98 98 98 98 98 98 88 98 98 98 + 98 98 98 98 98 88 98 98 88 98 98 88 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 98 + ); + } + + // Control rod layout + rodBanks { + id 777; + type latUniverse; + shape (7 7 0); + pitch (21.50364 21.50364 0); + padMat Water; + global 1; + map ( + 998 998 569 539 569 998 998 + 998 579 559 529 559 579 998 + 569 559 549 519 549 559 569 + 539 529 519 509 519 529 539 + 569 559 549 519 549 559 569 + 998 579 559 529 559 579 998 + 998 998 569 539 569 998 998 + ); + } + + + coreAndStructures { + id 8888; + type cellUniverse; + cells (100 101);} + !cells (100 101 102);} + + root { id 1; type rootUniverse; border 1; fill u<8888>; } + + + } +} + + +viz { + bmpZ { + type bmp; + output imgXY; + what material; + centre (0.0 0.0 106.0); + width (30 30); + axis z; + res (4000 4000); + } + bmpX { + type bmp; + output imgYZ; + what material; + centre (0.0 0.0 50.9855); + width (40 135.467); + axis x; + res (2500 6000); + } + plugs { + type bmp; + output plugs; + what material; + centre (0.0 0.0 101.0); + width (22 22); + axis z; + res (2000 2000); + } +} + + +nuclearData { + handles { + ce {type aceNeutronDatabase; aceLibrary $SCONE_ACE; ures 0; } + } + + materials { + + // Note that commented nuclide densities are included in the specification + // but are not available in the JEFF-3.11 data library + + Air { + temp 300; + rgb (255 255 255); + composition { + // Should be C-nat! + 6012.03 6.8296E-09; + 8016.03 5.2864E-06; + 8017.03 2.0137E-09; + 7014.03 1.9681E-05; + 7015.03 7.1900E-08; + 18036.03 7.9414E-10; + 18038.03 1.4915E-10; + 18040.03 2.3506E-07; + } + } + + Zircaloy { + temp 300; + rgb (200 200 200); + composition { + 8016.03 3.0743E-04; + 8017.03 1.1711E-07; + 24050.03 3.2962E-06; + 24052.03 6.3564E-05; + 24053.03 7.2076E-06; + 24054.03 1.7941E-06; + 26054.03 8.6699E-06; + 26056.03 1.3610E-04; + 26057.03 3.1431E-06; + 26058.03 4.1829E-07; + 40090.03 2.1827E-02; + 40091.03 4.7600E-03; + 40092.03 7.2758E-03; + 40094.03 7.3734E-03; + 40096.03 1.1879E-03; + 50112.03 4.6735E-06; + 50114.03 3.1799E-06; + 50115.03 1.6381E-06; + 50116.03 7.0055E-05; + 50117.03 3.7003E-05; + 50118.03 1.1669E-04; + 50119.03 4.1387E-05; + 50120.03 1.5697E-04; + 50122.03 2.2308E-05; + 50124.03 2.7897E-05; + } + } + + SS304 { + temp 300; + rgb (150 150 150); + composition { + // Should be C-nat! + 6012.03 1.60571E-4; + 14028.03 7.90951E-04; + 14029.03 4.01809E-05; + 14030.03 2.65192E-05; + 15031.03 3.57736E-05; + 16032.03 2.14077E-05; + 16033.03 1.69026E-07; + 16034.03 9.57813E-07; + 16036.03 2.25368E-09; + 24050.03 7.64894E-04; + 24052.03 1.47502E-02; + 24053.03 1.67256E-03; + 24054.03 4.16335E-04; + 25055.03 8.76912E-04; + 26054.03 3.53833E-03; + 26056.03 5.55443E-02; + 26057.03 1.28276E-03; + 26058.03 1.70711E-04; + 28058.03 5.16868E-03; + 28060.03 1.99098E-03; + 28061.03 8.65460E-05; + 28062.03 2.75949E-04; + 28064.03 7.02755E-05; + } + } + + Inconel { + temp 300; + rgb (125 100 100); + composition { + 6012.03 3.00006E-4; + 5010.03 4.53924E-6; + 5011.03 1.82711E-5; + 13027.03 9.13968E-4; + 14028.03 5.14997E-04; + 14029.03 2.61622E-05; + 14030.03 1.72669E-05; + 15031.03 2.22926E-05; + 16032.03 2.04552E-05; + 16033.03 1.61506E-07; + 16034.03 9.15200E-07; + 16036.03 2.15341E-09; + 22046.03 7.65049E-5; + 22047.03 6.89942E-5; + 22048.03 6.83630E-4; + 22049.03 5.01687E-5; + 22050.03 4.80359E-5; + 24050.03 7.83068E-04; + 24052.03 1.51007E-02; + 24053.03 1.7123E-03; + 24054.03 4.26227E-04; + 25055.03 2.85484E-04; + 26054.03 8.77557E-04; + 26056.03 1.37758E-02; + 26057.03 3.18143E-04; + 26058.03 4.23389E-05; + 27059.03 7.61569E-04; + 28058.03 3.00327E-02; + 28060.03 1.15686E-02; + 28061.03 5.02878E-04; + 28062.03 1.60341E-03; + 28064.03 4.08338E-04; + 29063.03 1.46519E-04; + 29065.03 6.53667E-05; + 41093.03 2.72076E-03; + 42092.03 2.31589E-04; + 42094.03 1.44724E-04; + 42095.03 2.49308E-04; + 42096.03 2.61538E-04; + 42097.03 1.49898E-04; + 42098.03 3.79293E-04; + 42100.03 1.51623E-04; + } + } + + B4C { + rgb (140 35 70); + temp 300; + composition { + 5010.03 1.06751E-01; + 5011.03 1.07878E-02; + // Should be C-nat + 6012.03 2.74893E-02; + } + } + + Water { + temp 300; + rgb (200 200 255); + moder {1001.03 (lwj3.00); } + composition { + 1001.03 6.66172E-02; + 1002.03 7.66186E-06; + 8016.03 3.32315E-02; + 8017.03 1.26587E-05; + //8018.03 6.82905E-05; + } + } + + Water_Steel_Mix { + rgb (160 150 160); + moder {1001.03 (lwj3.00); } + temp 300; + composition { + 1001.03 5.51590E-02; + 1002.03 6.34402E-06; + // Should be C-nat! + 6012.03 2.76183E-05; + 8016.03 2.75157E-02; + 8017.03 1.04814E-05; + //8018.03 5.65445E-05; + 14028.03 1.36044E-04; + 14029.03 6.91111E-06; + 14030.03 4.56130E-06; + 15031.03 6.15307E-06; + 16032.03 3.68212E-06; + 16033.03 2.90724E-08; + 16034.03 1.64744E-07; + 16036.03 3.87633E-10; + 24050.03 1.31562E-04; + 24052.03 2.53704E-03; + 24053.03 2.87680E-04; + 24054.03 7.16096E-05; + 25055.03 1.50829E-04; + 26054.03 6.08593E-04; + 26056.03 9.55362E-03; + 26057.03 2.20635E-04; + 26058.03 2.93624E-05; + 28058.03 8.89012E-04; + 28060.03 3.42448E-04; + 28061.03 1.48859E-05; + 28062.03 4.74633E-05; + 28064.03 1.20874E-05; + } + } + + UO2-14 { + temp 300; + rgb (17 35 237); + composition { + 8016.03 4.59248E-02; + 92234.03 2.61533E-05; + 92235.03 3.25521E-04; + 92238.03 2.26107E-02; + } + } + + UO2-15 { + rgb (255 150 150); + temp 300; + composition { + 8016.03 4.59253E-02; + 92234.03 2.80214E-05; + 92235.03 3.48772E-04; + 92238.03 2.25859E-02;} + } + + UO2-18 { + temp 300; + rgb (245 144 235); + composition { + 8016.03 4.59271E-02; + 92234.03 3.36255E-05; + 92235.03 4.18525E-04; + 92238.03 2.25114E-02;} + } + + UO2-24 { + temp 300; + rgb (255 255 125); + composition { + 8016.03 4.59305E-02; + 92234.03 4.48335E-05; + 92235.03 5.58027E-04; + 92238.03 2.23624E-02;} + } + + UO2-15-Gd-6 { + temp 300; + rgb (13 120 54); + composition { + 92234.03 2.63401E-05; + 92235.03 3.27846E-04; + 92238.03 2.12307E-02; + 8016.03 4.62484E-02; + 64152.03 4.10474E-06; + 64154.03 4.47417E-05; + 64155.03 3.03751E-04; + 64156.03 4.20121E-04; + 64157.03 3.21196E-04; + 64158.03 5.09808E-04; + 64160.03 4.48650E-04; + } + } + + UO2-18-Gd-6 { + temp 300; + rgb (13 120 54); + composition { + 92234.03 3.16079E-05; + 92235.03 3.93413E-04; + 92238.03 2.11607E-02; + 8016.03 4.62500E-02; + 64152.03 4.10474E-06; + 64154.03 4.47417E-05; + 64155.03 3.03751E-04; + 64156.03 4.20121E-04; + 64157.03 3.21196E-04; + 64158.03 5.09808E-04; + 64160.03 4.48650E-04; + } + } + UO2-24-Gd-5 { + temp 300; + rgb (13 120 54); + composition { + 92234.03 4.25918E-05; + 92235.03 5.30126E-04; + 92238.03 2.12443E-02; + 8016.03 4.61995E-02; + 64152.03 3.42062E-06; + 64154.03 3.72847E-05; + 64155.03 2.53126E-04; + 64156.03 3.50101E-04; + 64157.03 2.67664E-04; + 64158.03 4.24840E-04; + 64160.03 3.73875E-04; + } + } + + UO2-24-Gd-9 { + temp 300; + rgb (13 120 54); + composition { + 92234.03 4.07985E-05; + 92235.03 5.07805E-04; + 92238.03 2.03498E-02; + 8016.03 4.64146E-02; + 64152.03 6.15711E-06; + 64154.03 6.71125E-05; + 64155.03 4.55627E-04; + 64156.03 6.30182E-04; + 64157.03 4.81795E-04; + 64158.03 7.64712E-04; + 64160.03 6.72974E-04; + } + } + + +} +} diff --git a/InputFiles/CROCUS_2D b/InputFiles/CROCUS_2D new file mode 100644 index 000000000..f4a3b69a7 --- /dev/null +++ b/InputFiles/CROCUS_2D @@ -0,0 +1,201 @@ +!! +!! 2D model of the CROCUS reactor +!! Composition and geometry taken from IRPhE +!! +type eigenPhysicsPackage; + +pop 100000; +active 500; +inactive 100; +XSdata ce; +dataType ce; +outputFile CROCUS_2D; + +// Specify output format default asciiMATLAB +//outputFormat asciiJSON; + +collisionOperator { neutronCE {type neutronCEstd;} } + +transportOperator {// type transportOperatorST; + cache 1; + type transportOperatorHT; + } + +inactiveTally {} + +activeTally { + fluxRadial { type collisionClerk; response (flx); flx { type fluxResponse;} + map {type multiMap; maps (xax yax emap); + xax {type spaceMap; axis x; grid lin; N 240; min -60.0; max 60.0; } + yax {type spaceMap; axis y; grid lin; N 240; min -60.0; max 60.0; } + emap {type energyMap; grid unstruct; bins (1.0E-11 0.625E-6 20); } + } + } +} + +geometry { + type geometryStd; + boundary ( 0 0 0 0 1 1); + graph {type shrunk;} + + surfaces { + boundary { id 1; type zTruncCylinder; origin (0.0 0.0 0.0); radius 60; halfwidth 60;} + } + + cells { + // in {id 1; surfaces ( -1); filltype uni; universe 401;} + // out {id 2; surfaces (1); filltype outside; } + } + + universes { + root { id 1; type rootUniverse; border 1; fill u<10>; } + + // Pin universes + pinUO2 { id 2; type pinUniverse; radii (0.526 0.545 0.63 0.0 ); fills (uo2 void clad water);} + pinUMet {id 3; type pinUniverse; radii (0.85 0.8675 0.965 0.0 ); fills (umet void clad water);} + water {id 4; type pinUniverse; radii (0.0 ); fills (water);} + + // Lattices + inner { + id 5; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (1.837 1.837 0.0); + shape (22 22 0); + padMat water; + map ( + + 4 4 4 4 4 4 4 4 2 2 2 2 2 2 4 4 4 4 4 4 4 4 + 4 4 4 4 4 4 4 4 2 2 2 2 2 2 4 4 4 4 4 4 4 4 + 4 4 4 4 4 2 2 2 2 2 2 2 2 2 2 2 2 4 4 4 4 4 + 4 4 4 4 4 2 2 2 2 2 2 2 2 2 2 2 2 4 4 4 4 4 + 4 4 4 4 4 2 2 2 2 2 2 2 2 2 2 2 2 4 4 4 4 4 + 4 4 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 4 4 + 4 4 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 4 4 + 4 4 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 4 4 + 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 + 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 + 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 + 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 + 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 + 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 + 4 4 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 4 4 + 4 4 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 4 4 + 4 4 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 4 4 + 4 4 4 4 4 2 2 2 2 2 2 2 2 2 2 2 2 4 4 4 4 4 + 4 4 4 4 4 2 2 2 2 2 2 2 2 2 2 2 2 4 4 4 4 4 + 4 4 4 4 4 2 2 2 2 2 2 2 2 2 2 2 2 4 4 4 4 4 + 4 4 4 4 4 4 4 4 2 2 2 2 2 2 4 4 4 4 4 4 4 4 + 4 4 4 4 4 4 4 4 2 2 2 2 2 2 4 4 4 4 4 4 4 4 + ); + } + + outer { + id 10; + type latUniverse; + origin (0.0 0.0 0.0); + pitch (2.917 2.917 0.0); + shape (20 20 0); + padMat water; + map ( + 4 4 4 4 4 4 4 3 3 3 3 3 3 4 4 4 4 4 4 4 + 4 4 4 4 3 3 3 3 3 3 3 3 3 3 3 4 4 4 4 4 + 4 4 4 3 3 3 3 3 3 3 3 3 3 3 3 3 3 4 4 4 + 4 4 3 3 3 3 3 3 5 5 5 5 3 3 3 3 3 3 4 4 + 4 3 3 3 3 3 5 5 5 5 5 5 5 5 3 3 3 3 4 4 + 4 3 3 3 3 3 5 5 5 5 5 5 5 5 3 3 3 3 3 4 + 3 3 3 3 5 5 5 5 5 5 5 5 5 5 5 5 3 3 3 4 + 3 3 3 3 5 5 5 5 5 5 5 5 5 5 5 5 3 3 3 3 + 3 3 3 5 5 5 5 5 5 5 5 5 5 5 5 5 5 3 3 3 + 3 3 3 5 5 5 5 5 5 5 5 5 5 5 5 5 5 3 3 3 + 3 3 3 5 5 5 5 5 5 5 5 5 5 5 5 5 5 3 3 3 + 3 3 3 5 5 5 5 5 5 5 5 5 5 5 5 5 5 3 3 3 + 3 3 3 3 5 5 5 5 5 5 5 5 5 5 5 5 3 3 3 3 + 4 3 3 3 5 5 5 5 5 5 5 5 5 5 5 5 3 3 3 3 + 4 3 3 3 3 3 5 5 5 5 5 5 5 5 3 3 3 3 3 4 + 4 4 3 3 3 3 5 5 5 5 5 5 5 5 3 3 3 3 3 4 + 4 4 3 3 3 3 3 3 5 5 5 5 3 3 3 3 3 3 4 4 + 4 4 4 3 3 3 3 3 3 3 3 3 3 3 3 3 3 4 4 4 + 4 4 4 4 4 3 3 3 3 3 3 3 3 3 3 3 4 4 4 4 + 4 4 4 4 4 4 4 3 3 3 3 3 3 4 4 4 4 4 4 4 + ); + offsetMap ( + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + 1 1 1 1 1 1 1 1 0 0 0 0 1 1 1 1 1 1 1 1 + 1 1 1 1 1 1 0 0 0 0 0 0 0 0 1 1 1 1 1 1 + 1 1 1 1 1 1 0 0 0 0 0 0 0 0 1 1 1 1 1 1 + 1 1 1 1 0 0 0 0 0 0 0 0 0 0 0 0 1 1 1 1 + 1 1 1 1 0 0 0 0 0 0 0 0 0 0 0 0 1 1 1 1 + 1 1 1 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 1 1 + 1 1 1 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 1 1 + 1 1 1 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 1 1 + 1 1 1 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1 1 1 + 1 1 1 1 0 0 0 0 0 0 0 0 0 0 0 0 1 1 1 1 + 1 1 1 1 0 0 0 0 0 0 0 0 0 0 0 0 1 1 1 1 + 1 1 1 1 1 1 0 0 0 0 0 0 0 0 1 1 1 1 1 1 + 1 1 1 1 1 1 0 0 0 0 0 0 0 0 1 1 1 1 1 1 + 1 1 1 1 1 1 1 1 0 0 0 0 1 1 1 1 1 1 1 1 + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + ); + } + } + +} + + +viz { + bmp { + type bmp; + output img; + what material; + centre (0.0 0.0 0.0); + !width (80.0 80.0); + axis z; + offset -17; + res (1500 1500); + } +} + + +nuclearData { + handles { + ce {type aceNeutronDatabase; aceLibrary $SCONE_ACE;} + } + materials { + + water { + temp 300; + rgb (0 0 139); + moder { 1001.03 (lwj3.00); } + composition { + 1001.03 6.67578E-2; + 8016.03 3.33789E-2; } + } + + clad { + temp 300; + composition { + 13027.03 6.02611E-2;} + } + + uo2 { + temp 300; + composition { + 92235.03 4.30565E-4; + 92238.03 2.31145E-2; + 8016.03 4.70902E-2; } + } + + umet { + temp 300; + composition { + 92235.03 4.5316E-4; + 92238.03 4.68003E-2;} + } + +} +} diff --git a/PhysicsPackages/CMakeLists.txt b/PhysicsPackages/CMakeLists.txt index a1db7a1f4..29cd7cc94 100644 --- a/PhysicsPackages/CMakeLists.txt +++ b/PhysicsPackages/CMakeLists.txt @@ -3,8 +3,9 @@ add_sources( ./physicsPackage_inter.f90 ./physicsPackageFactory_func.f90 ./eigenPhysicsPackage_class.f90 - ./fixedSourcePhysicsPackage_class.f90 + ./fixedSourcePhysicsPackage_class.f90 ./vizPhysicsPackage_class.f90 ./rayVolPhysicsPackage_class.f90 + ./pointVolPhysicsPackage_class.f90 ) #./dynamPhysicsPackage_class.f90) diff --git a/PhysicsPackages/physicsPackageFactory_func.f90 b/PhysicsPackages/physicsPackageFactory_func.f90 index 48de37e1c..aff0f57ac 100644 --- a/PhysicsPackages/physicsPackageFactory_func.f90 +++ b/PhysicsPackages/physicsPackageFactory_func.f90 @@ -15,6 +15,7 @@ module physicsPackageFactory_func use fixedSourcePhysicsPackage_class, only : fixedSourcePhysicsPackage use vizPhysicsPackage_class, only : vizPhysicsPackage use rayVolPhysicsPackage_class, only : rayVolPhysicsPackage + use pointVolPhysicsPackage_class, only : pointVolPhysicsPackage ! use dynamPhysicsPackage_class, only : dynamPhysicsPackage implicit none @@ -27,7 +28,8 @@ module physicsPackageFactory_func character(nameLen),dimension(*),parameter :: AVAILABLE_physicsPackages = [ 'eigenPhysicsPackage ',& 'fixedSourcePhysicsPackage',& 'vizPhysicsPackage ',& - 'rayVolPhysicsPackage '] + 'rayVolPhysicsPackage ',& + 'pointVolPhysicsPackage '] !! !! Public interface @@ -62,6 +64,9 @@ function new_physicsPackage(dict) result(new) case('rayVolPhysicsPackage') allocate( rayVolPhysicsPackage :: new) + + case('pointVolPhysicsPackage') + allocate( pointVolPhysicsPackage :: new) case default print *, AVAILABLE_physicsPackages diff --git a/PhysicsPackages/pointVolPhysicsPackage_class.f90 b/PhysicsPackages/pointVolPhysicsPackage_class.f90 new file mode 100644 index 000000000..a63123fa3 --- /dev/null +++ b/PhysicsPackages/pointVolPhysicsPackage_class.f90 @@ -0,0 +1,347 @@ +module pointVolPhysicsPackage_class + + use numPrecision + use universalVariables + use genericProcedures, only : fatalError, numToChar, rotateVector, printFishLineR + use hashFunctions_func, only : FNV_1 + use dictionary_class, only : dictionary + use rng_class, only : RNG + use physicsPackage_inter, only : physicsPackage + + ! Timers + use timer_mod, only : registerTimer, timerStart, timerStop, & + timerTime, timerReset, secToChar + + ! Geometry + use coord_class, only : coordList + use geometry_inter, only : geometry, distCache + use geometryReg_mod, only : gr_geomPtr => geomPtr, gr_geomIdx => geomIdx, & + gr_kill => kill + use geometryFactory_func, only : new_geometry + + ! Nuclear Data + use materialMenu_mod, only : mm_nMat => nMat, mm_matName => matName + use nuclearDataReg_mod, only : ndReg_init => init ,& + ndReg_getMatNames => getMatNames, & + ndReg_kill => kill + + implicit none + private + + ! Parameters + integer(shortInt), parameter :: CSUM = 1, CSUM2 = 2 + + !! + !! Physics package to perform point-sampling-based volume calculation + !! + !! Calculates relative volume of different materials in the problem by performing + !! point-sampling in the geometry. The volume is normalised that the total domain + !! volume is 1.0. + !! + !! Points are sampled uniformly within the geometry bounding box. + !! + !! This Physics Package exists to serve as a geometry debugging and benchmarking tool. + !! Maybe in future it will be useful for burn-up? + !! + !! Sample Input Dictionary: + !! PP { + !! type pointVolPhysicsPackage; + !! pop 2000; // Number of points per cycle + !! cycles 100; // Number of cycles + !! #seed 86868;# // Optional RNG seed + !! geometry {} + !! nuclearData {} + !! } + !! + !! Private Members + !! geom -> Pointer to the geometry + !! geomIdx -> Index of the geometry in geometry Registry + !! rand -> Random number generator + !! timerMain -> Index of the timer defined to measure calculation time + !! N_cycles -> Number of cycles + !! res -> Array to accumulate total number of points in each material. Contains + !! cumulative sum over cycles (CSUM) and cumulative sum of squares over + !! cycles (CSUM2) + !! score -> Array containing point scores on a given cycle. + !! + !! Interface: + !! physicsPackage interface + !! + type, public, extends(physicsPackage) :: pointVolPhysicsPackage + private + ! Components + class(geometry), pointer :: geom + integer(shortInt) :: geomIdx = 0 + type(RNG) :: rand + integer(shortInt) :: timerMain = 0 + + ! Settings + integer(shortInt) :: pop = 0 + integer(shortInt) :: N_cycles = 0 + + ! Results space + integer(longInt), dimension(:), allocatable :: score + real(defReal), dimension(:,:), allocatable :: res + + contains + ! Superclass procedures + procedure :: init + procedure :: run + procedure :: kill + + ! Private procedures + procedure, private :: cycles + procedure, private :: printResults + procedure, private :: printSettings + end type pointVolPhysicsPackage + +contains + + !! + !! Initialise Physics Package from dictionary + !! + !! See physicsPackage_inter for details + !! + subroutine init(self,dict) + class(pointVolPhysicsPackage), intent(inout) :: self + class(dictionary), intent(inout) :: dict + integer(shortInt) :: seed_temp + integer(longInt) :: seed + character(10) :: time + character(8) :: date + character(:),allocatable :: string + class(dictionary),pointer :: tempDict + character(nameLen) :: geomName + character(100), parameter :: Here = 'init (pointVolPhysicsPackage_class.f90)' + + ! Load settings + call dict % get(self % pop, 'pop') + call dict % get(self % N_cycles, 'cycles') + + ! Check settings + if (self % pop < 1) call fatalError(Here,'Must sample > 0 points in the geometry.') + if (self % N_cycles < 1) call fatalError(Here,'Must perform at least > 0 sampling cycles.') + + ! Register timer + self % timerMain = registerTimer('transportTime') + + ! Initialise RNG + if( dict % isPresent('seed')) then + call dict % get(seed_temp,'seed') + + else + ! Obtain time string and hash it to obtain random seed + call date_and_time(date, time) + string = date // time + call FNV_1(string,seed_temp) + + end if + seed = seed_temp + call self % rand % init(seed) + + ! Build Nuclear Data + call ndReg_init(dict % getDictPtr("nuclearData")) + + ! Build geometry + tempDict => dict % getDictPtr('geometry') + geomName = 'pointVolGeom' + call new_geometry(tempDict, geomName) + self % geomIdx = gr_geomIdx(geomName) + self % geom => gr_geomPtr(self % geomIdx) + + ! Allocate results space + allocate(self % res(mm_nMat(), 2)) + self % res = ZERO + allocate(self % score(mm_nMat())) + self % score = 0 + + end subroutine init + + !! + !! Run calculation + !! + !! See physicsPackage_inter for details + !! + subroutine run(self) + class(pointVolPhysicsPackage), intent(inout) :: self + + call self % printSettings() + call self % cycles(self % rand) + call self % printResults() + + end subroutine run + + !! + !! Perform cycles of the stochastic volume calculation with point sampling. + !! + !! Randomly places the starting point based on uniform distribution. + !! + !! Args: + !! rand [inout] -> Initialised random number generator + !! + !! NOTE: + !! RNG needs to be given as an argument `class(RNG)` to prevent inlining. Compiler (gcc 8.3) + !! produced erroneous code without it. Same random number would be produced for different calls + !! of `get` function. + !! + subroutine cycles(self, rand) + class(pointVolPhysicsPackage), intent(inout) :: self + class(RNG), intent(inout) :: rand + real(defReal), dimension(3) :: rand3, bottom, top, u + real(defReal), dimension(3), save :: r + integer(shortInt) :: gen, point + integer(shortInt), save :: matIdx, uniqueId, i + type(RNG), save :: pRNG + real(defReal) :: elapsed_T, end_T, T_toEnd, cycle_T + character(100), parameter :: Here = 'cycles (pointVolPhysicsPackage_class.f90)' + !$omp threadprivate(pRNG, r, matIdx, uniqueId, i) + + !$omp parallel + pRNG = rand + !$omp end parallel + + ! Reset and start timer + call timerReset(self % timerMain) + call timerStart(self % timerMain) + + ! Get lower an upper corner of bounding box + associate (aabb => self % geom % bounds()) + bottom = aabb(1:3) + top = aabb(4:6) + end associate + + u = [ONE, ZERO, ZERO] + + ! Perform clculation + do gen = 1, self % N_cycles + !$omp parallel do + do point = 1, self % pop + + ! Set seed + call pRNG % stride( (gen-1) * self % pop + point ) + + ! Find starting point that is inside the geometry + i = 0 + + rejection : do + rand3(1) = pRNG % get() + rand3(2) = pRNG % get() + rand3(3) = pRNG % get() + r = bottom + (top - bottom) * rand3 + + ! Exit if point is inside the geometry + call self % geom % whatIsAt(matIdx, uniqueId, r, u) + if (matIdx /= OUTSIDE_MAT) exit rejection + + i = i + 1 + if (i > 1000) then + call fatalError(Here, 'Infinite loop when searching for a point in the geometry.') + end if + end do rejection + + ! Found something + if (matIdx /= VOID_MAT) then + !$omp atomic + self % score(matIdx) = self % score(matIdx) + 1 + end if + + end do + !$omp end parallel do + + ! Calculate times + call timerStop(self % timerMain) + cycle_T = timerTime(self % timerMain) - elapsed_T + elapsed_T = timerTime(self % timerMain) + + ! Predict time to end + end_T = real(self % N_cycles, defReal) * elapsed_T / gen + T_toEnd = max(ZERO, end_T - elapsed_T) + + ! Display progress + call printFishLineR(gen) + print * + print *, 'Cycle: ', numToChar(gen), ' of ', numToChar(self % N_cycles) + print *, 'Pop: ', numToChar(self % pop) + print *, 'Elapsed time: ', trim(secToChar(elapsed_T)) + print *, 'End time: ', trim(secToChar(end_T)) + print *, 'Time to end: ', trim(secToChar(T_toEnd)) + + ! Process scores + ! Is this susceptible to round-off? + self % res(:, CSUM) = self % res(:, CSUM) + real(self % score(:), defReal) / self % pop + self % res(:, CSUM2) = self % res(:, CSUM2) + (real(self % score(:), defReal) / self % pop)**2 + self % score = 0 + + end do + + end subroutine cycles + + !! + !! Output calculation results to the console + !! + !! Convert cumulative sums to mean and absolute standard deviation and + !! print them to the console. + !! + !! Args: + !! None + !! + subroutine printResults(self) + class(pointVolPhysicsPackage), intent(in) :: self + real(defReal) :: mean, SD, var + integer(shortInt) :: i + + print * + print *, "RELATIVE VOLUME FOR MATERIALS: " + do i = 1, mm_nMat() + mean = self % res(i, CSUM) / self % N_cycles + var = self % res(i, CSUM2) / self % N_cycles - mean**2 + SD = ONE/(self % N_cycles - 1) * sqrt(var) + print '(A, A, A, ES12.5, A, ES12.5)', " Material: ", mm_matName(i), " Vol", mean, " +/-", SD + end do + + end subroutine printResults + + !! + !! Print settings of the point-sampling volume calculation + !! + !! Args: + !! None + !! + subroutine printSettings(self) + class(pointVolPhysicsPackage), intent(in) :: self + + print *, repeat("<>", MAX_COL/2) + print *, "/\/\ POINT-SAMPLING RELATIVE VOLUME CALCULATION /\/\" + print *, "Total Cycles: ", numToChar(self % N_cycles) + print *, "Points per cycle: ", numToChar(self % pop) + print *, "Initial RNG Seed: ", numToChar(self % rand % getSeed()) + print * + print *, repeat("<>", MAX_COL/2) + + end subroutine printSettings + + !! + !! Return to uninitialised state + !! + subroutine kill(self) + class(pointVolPhysicsPackage), intent(inout) :: self + + ! Clean Nuclear Data & Geometries + call gr_kill() + call ndreg_kill() + + ! Clean contents + self % geom => null() + self % geomIdx = 0 + !call self % rand % kill() + self % timerMain = 0 + + self % pop = 0 + self % N_cycles = 0 + + if (allocated(self % res)) deallocate(self % res) + if (allocated(self % score)) deallocate(self % score) + + end subroutine kill + +end module pointVolPhysicsPackage_class diff --git a/SharedModules/genericProcedures.f90 b/SharedModules/genericProcedures.f90 index ddcf9f286..086c6ed69 100644 --- a/SharedModules/genericProcedures.f90 +++ b/SharedModules/genericProcedures.f90 @@ -13,8 +13,10 @@ module genericProcedures interface swap module procedure swap_shortInt module procedure swap_defReal + module procedure swap_defBool module procedure swap_char_nameLen module procedure swap_defReal_defReal + module procedure swap_defBool_defBool end interface interface quickSort @@ -1348,7 +1350,7 @@ elemental subroutine swap_shortInt(i1,i2) end subroutine swap_shortInt !! - !! Swap to reals + !! Swap two reals !! elemental subroutine swap_defReal(r1,r2) real(defReal), intent(inout) :: r1 @@ -1384,6 +1386,44 @@ elemental subroutine swap_defReal_defReal(r1_1, r1_2, r2_1, r2_2) r2_2 = temp2 end subroutine swap_defReal_defReal + + !! + !! Swap two bools + !! + elemental subroutine swap_defBool(r1,r2) + logical(defBool), intent(inout) :: r1 + logical(defBool), intent(inout) :: r2 + logical(defBool) :: temp + + temp = r1 + r1 = r2 + r2 = temp + + end subroutine swap_defBool + + !! + !! Swap two pair of bools + !! + elemental subroutine swap_defBool_defBool(r1_1, r1_2, r2_1, r2_2) + logical(defBool), intent(inout) :: r1_1 + logical(defBool), intent(inout) :: r1_2 + logical(defBool), intent(inout) :: r2_1 + logical(defBool), intent(inout) :: r2_2 + logical(defBool) :: temp1, temp2 + + ! Load first pair into temps + temp1 = r1_1 + temp2 = r1_2 + + ! Assign values of 2nd pair to 1st pair + r1_1 = r2_1 + r1_2 = r2_2 + + ! Assign values of 1st pair to 2nd pair + r2_1 = temp1 + r2_2 = temp2 + + end subroutine swap_defBool_defBool !! !! Swap character of length nameLen diff --git a/SharedModules/universalVariables.f90 b/SharedModules/universalVariables.f90 index fdb8a2d57..90d54e732 100644 --- a/SharedModules/universalVariables.f90 +++ b/SharedModules/universalVariables.f90 @@ -7,7 +7,7 @@ module universalVariables ! *** DON't CHANGE THIS. HARDCODED IS FINE ! CHANGE THIS: NUMBER MUST BE CALCULATED DURING INITIAL GEOMETRY PROCESSING ! Problematic for separating modules! - integer(shortInt), parameter, public :: HARDCODED_MAX_NEST = 8 + integer(shortInt), parameter, public :: HARDCODED_MAX_NEST = 12 integer(shortInt), parameter, public :: MAX_OUTGOING_PARTICLES = 5 ! CHANGE THIS: NUMBER WILL DEPEND ON SYSTEM ARCHITECTURE diff --git a/docs/User Manual.rst b/docs/User Manual.rst index 56cc5eb9f..ae6b7708e 100644 --- a/docs/User Manual.rst +++ b/docs/User Manual.rst @@ -117,7 +117,7 @@ Example: :: rayVolPhysicsPackage #################### -rayVolPhysicsPackage, used to perform ray-tracing based volume calculation +rayVolPhysicsPackage, used to perform ray-tracing based volume calculations. * pop: number of rays used per cycle * cycles: number of cycles @@ -143,6 +143,24 @@ Example: :: geometry { } nuclearData { } +pointVolPhysicsPackage +###################### + +pointVolPhysicsPackage, used to perform point-sampling based volume calculations. + +* pop: number of points used per cycle +* cycles: number of cycles +* seed (*optional*): initial seed for the pseudo random number generator + +Example: :: + + type pointVolPhysicsPackage; + pop 1000000; + cycles 100; + + geometry { } + nuclearData { } + vizPhysicsPackage ################# @@ -613,6 +631,10 @@ Similarly to the surfaces and cells, the **universes** in the geometry can be de { id ; type ; *keywords* } } +One can disable the translation of a given universe, should it be nested in others, by the use +of the keyword ``global 1;``. This evaluates a particle's position in the universe using the +global frame of reference. + Several ``universeTypes`` are possible: * cellUniverse, composed of the union of different cells. Note that overlaps are @@ -667,6 +689,13 @@ Example: :: origin of the universe. [cm] - rotation (*optional*, default = (0.0 0.0 0.0)): (x y z) array with the rotation angles in degrees applied to the universe. [°] + - offsetMap (*optional*, default = all elements offset): map that specifies which elements + of the lattice are offset with respect to the lattice origin. Elements with 1 are offset, + while elements with a 0 are not. Must have the same size as the map. Allows creating, e.g., + BWR assemblies with water rods covering multiple lattice elements. + - offset (*optional*, default = true): enables/disables the offset of all entries in + the latUniverse. Has relatively specialised use cases, e.g., imposing a discretisation + by placing another universe inside the lattice. Example: ::