Skip to content

Commit 6d0150d

Browse files
committed
Merge remote-tracking branch 'MAIN/main' into feature/update-to-main-20240401
2 parents ab7bd14 + 87913b5 commit 6d0150d

File tree

11 files changed

+808
-304
lines changed

11 files changed

+808
-304
lines changed

config_src/drivers/nuopc_cap/mom_cap.F90

+119-21
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ module MOM_cap_mod
1616
use MOM_domains, only: MOM_infra_init, MOM_infra_end
1717
use MOM_file_parser, only: get_param, log_version, param_file_type, close_param_file
1818
use MOM_get_input, only: get_MOM_input, directories
19-
use MOM_domains, only: pass_var
19+
use MOM_domains, only: pass_var, pe_here
2020
use MOM_error_handler, only: MOM_error, FATAL, is_root_pe
2121
use MOM_grid, only: ocean_grid_type, get_global_grid_size
2222
use MOM_ocean_model_nuopc, only: ice_ocean_boundary_type
@@ -29,6 +29,7 @@ module MOM_cap_mod
2929
use MOM_cap_methods, only: med2mod_areacor, state_diagnose
3030
use MOM_cap_methods, only: ChkErr
3131
use MOM_ensemble_manager, only: ensemble_manager_init
32+
use MOM_coms, only: sum_across_PEs
3233

3334
#ifdef CESMCOUPLED
3435
use shr_log_mod, only: shr_log_setLogUnit
@@ -842,6 +843,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
842843
type(ocean_grid_type) , pointer :: ocean_grid
843844
type(ocean_internalstate_wrapper) :: ocean_internalstate
844845
integer :: npet, ntiles
846+
integer :: npes ! number of PEs (from FMS).
845847
integer :: nxg, nyg, cnt
846848
integer :: isc,iec,jsc,jec
847849
integer, allocatable :: xb(:),xe(:),yb(:),ye(:),pe(:)
@@ -868,6 +870,8 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
868870
integer :: lsize
869871
integer :: ig,jg, ni,nj,k
870872
integer, allocatable :: gindex(:) ! global index space
873+
integer, allocatable :: gindex_ocn(:) ! global index space for ocean cells (excl. masked cells)
874+
integer, allocatable :: gindex_elim(:) ! global index space for eliminated cells
871875
character(len=128) :: fldname
872876
character(len=256) :: cvalue
873877
character(len=256) :: frmt ! format specifier for several error msgs
@@ -891,6 +895,11 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
891895
real(ESMF_KIND_R8) :: min_areacor_glob(2)
892896
real(ESMF_KIND_R8) :: max_areacor_glob(2)
893897
character(len=*), parameter :: subname='(MOM_cap:InitializeRealize)'
898+
integer :: niproc, njproc
899+
integer :: ip, jp, pe_ix
900+
integer :: num_elim_blocks ! number of blocks to be eliminated
901+
integer :: num_elim_cells_global, num_elim_cells_local, num_elim_cells_remaining
902+
integer, allocatable :: cell_mask(:,:)
894903
real(8) :: MPI_Wtime, timeirls
895904
!--------------------------------
896905

@@ -937,19 +946,19 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
937946
rc = ESMF_FAILURE
938947
call ESMF_LogWrite(subname//' ntiles must be 1', ESMF_LOGMSG_ERROR)
939948
endif
940-
ntiles = mpp_get_domain_npes(ocean_public%domain)
941-
write(tmpstr,'(a,1i6)') subname//' ntiles = ',ntiles
949+
npes = mpp_get_domain_npes(ocean_public%domain)
950+
write(tmpstr,'(a,1i6)') subname//' npes = ',npes
942951
call ESMF_LogWrite(trim(tmpstr), ESMF_LOGMSG_INFO)
943952

944953
!---------------------------------
945954
! get start and end indices of each tile and their PET
946955
!---------------------------------
947956

948-
allocate(xb(ntiles),xe(ntiles),yb(ntiles),ye(ntiles),pe(ntiles))
957+
allocate(xb(npes),xe(npes),yb(npes),ye(npes),pe(npes))
949958
call mpp_get_compute_domains(ocean_public%domain, xbegin=xb, xend=xe, ybegin=yb, yend=ye)
950959
call mpp_get_pelist(ocean_public%domain, pe)
951960
if (dbug > 1) then
952-
do n = 1,ntiles
961+
do n = 1,npes
953962
write(tmpstr,'(a,6i6)') subname//' tiles ',n,pe(n),xb(n),xe(n),yb(n),ye(n)
954963
call ESMF_LogWrite(trim(tmpstr), ESMF_LOGMSG_INFO)
955964
enddo
@@ -971,17 +980,102 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
971980
call get_global_grid_size(ocean_grid, ni, nj)
972981
lsize = ( ocean_grid%iec - ocean_grid%isc + 1 ) * ( ocean_grid%jec - ocean_grid%jsc + 1 )
973982

974-
! Create the global index space for the computational domain
975-
allocate(gindex(lsize))
976-
k = 0
977-
do j = ocean_grid%jsc, ocean_grid%jec
978-
jg = j + ocean_grid%jdg_offset
979-
do i = ocean_grid%isc, ocean_grid%iec
980-
ig = i + ocean_grid%idg_offset
981-
k = k + 1 ! Increment position within gindex
982-
gindex(k) = ni * (jg - 1) + ig
983+
num_elim_blocks = 0
984+
num_elim_cells_global = 0
985+
num_elim_cells_local = 0
986+
num_elim_cells_remaining = 0
987+
988+
! Compute the number of eliminated blocks (specified in MOM_mask_table)
989+
if (associated(ocean_grid%Domain%maskmap)) then
990+
njproc = size(ocean_grid%Domain%maskmap, 1)
991+
niproc = size(ocean_grid%Domain%maskmap, 2)
992+
993+
do ip = 1, niproc
994+
do jp = 1, njproc
995+
if (.not. ocean_grid%Domain%maskmap(jp,ip)) then
996+
num_elim_blocks = num_elim_blocks+1
997+
endif
998+
enddo
983999
enddo
984-
enddo
1000+
endif
1001+
1002+
! Apply land block elimination to ESMF gindex
1003+
! (Here we assume that each processor gets assigned a single tile. If multi-tile implementation is to be added
1004+
! in MOM6 NUOPC cap in the future, below code must be updated accordingly.)
1005+
if (num_elim_blocks>0) then
1006+
1007+
allocate(cell_mask(ni, nj), source=0)
1008+
allocate(gindex_ocn(lsize))
1009+
k = 0
1010+
do j = ocean_grid%jsc, ocean_grid%jec
1011+
jg = j + ocean_grid%jdg_offset
1012+
do i = ocean_grid%isc, ocean_grid%iec
1013+
ig = i + ocean_grid%idg_offset
1014+
k = k + 1 ! Increment position within gindex
1015+
gindex_ocn(k) = ni * (jg - 1) + ig
1016+
cell_mask(ig, jg) = 1
1017+
enddo
1018+
enddo
1019+
call sum_across_PEs(cell_mask, ni*nj)
1020+
1021+
if (maxval(cell_mask) /= 1 ) then
1022+
call MOM_error(FATAL, "Encountered cells shared by multiple PEs while attempting to determine masked cells.")
1023+
endif
1024+
1025+
num_elim_cells_global = ni * nj - sum(cell_mask)
1026+
num_elim_cells_local = num_elim_cells_global / npes
1027+
1028+
if (pe_here() == pe(npes)) then
1029+
! assign all remaining cells to the last PE.
1030+
num_elim_cells_remaining = num_elim_cells_global - num_elim_cells_local * npes
1031+
allocate(gindex_elim(num_elim_cells_local+num_elim_cells_remaining))
1032+
else
1033+
allocate(gindex_elim(num_elim_cells_local))
1034+
endif
1035+
1036+
! Zero-based PE index.
1037+
pe_ix = pe_here() - pe(1)
1038+
1039+
k = 0
1040+
do jg = 1, nj
1041+
do ig = 1, ni
1042+
if (cell_mask(ig, jg) == 0) then
1043+
k = k + 1
1044+
if (k > pe_ix * num_elim_cells_local .and. &
1045+
k <= ((pe_ix+1) * num_elim_cells_local + num_elim_cells_remaining)) then
1046+
gindex_elim(k - pe_ix * num_elim_cells_local) = ni * (jg -1) + ig
1047+
endif
1048+
endif
1049+
enddo
1050+
enddo
1051+
1052+
allocate(gindex(lsize + num_elim_cells_local + num_elim_cells_remaining))
1053+
do k = 1, lsize
1054+
gindex(k) = gindex_ocn(k)
1055+
enddo
1056+
do k = 1, num_elim_cells_local + num_elim_cells_remaining
1057+
gindex(k+lsize) = gindex_elim(k)
1058+
enddo
1059+
1060+
deallocate(cell_mask)
1061+
deallocate(gindex_ocn)
1062+
deallocate(gindex_elim)
1063+
1064+
else ! no eliminated land blocks
1065+
1066+
! Create the global index space for the computational domain
1067+
allocate(gindex(lsize))
1068+
k = 0
1069+
do j = ocean_grid%jsc, ocean_grid%jec
1070+
jg = j + ocean_grid%jdg_offset
1071+
do i = ocean_grid%isc, ocean_grid%iec
1072+
ig = i + ocean_grid%idg_offset
1073+
k = k + 1 ! Increment position within gindex
1074+
gindex(k) = ni * (jg - 1) + ig
1075+
enddo
1076+
enddo
1077+
1078+
endif
9851079

9861080
DistGrid = ESMF_DistGridCreate(arbSeqIndexList=gindex, rc=rc)
9871081
if (ChkErr(rc,__LINE__,u_FILE_u)) return
@@ -1005,6 +1099,10 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
10051099
call ESMF_MeshGet(Emesh, spatialDim=spatialDim, numOwnedElements=numOwnedElements, rc=rc)
10061100
if (ChkErr(rc,__LINE__,u_FILE_u)) return
10071101

1102+
if (lsize /= numOwnedElements - num_elim_cells_local - num_elim_cells_remaining) then
1103+
call MOM_error(FATAL, "Discrepancy detected between ESMF mesh and internal MOM6 domain sizes. Check mask table.")
1104+
endif
1105+
10081106
allocate(ownedElemCoords(spatialDim*numOwnedElements))
10091107
allocate(lonMesh(numOwnedElements), lon(numOwnedElements))
10101108
allocate(latMesh(numOwnedElements), lat(numOwnedElements))
@@ -1036,7 +1134,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
10361134
end do
10371135

10381136
eps_omesh = get_eps_omesh(ocean_state)
1039-
do n = 1,numOwnedElements
1137+
do n = 1,lsize
10401138
diff_lon = abs(mod(lonMesh(n) - lon(n),360.0))
10411139
if (diff_lon > eps_omesh) then
10421140
frmt = "('ERROR: Difference between ESMF Mesh and MOM6 domain coords is "//&
@@ -1140,11 +1238,11 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
11401238

11411239
! generate delayout and dist_grid
11421240

1143-
allocate(deBlockList(2,2,ntiles))
1144-
allocate(petMap(ntiles))
1145-
allocate(deLabelList(ntiles))
1241+
allocate(deBlockList(2,2,npes))
1242+
allocate(petMap(npes))
1243+
allocate(deLabelList(npes))
11461244

1147-
do n = 1, ntiles
1245+
do n = 1, npes
11481246
deLabelList(n) = n
11491247
deBlockList(1,1,n) = xb(n)
11501248
deBlockList(1,2,n) = xe(n)
@@ -1727,7 +1825,7 @@ subroutine ModelAdvance(gcomp, rc)
17271825
rpointer_filename = 'rpointer.ocn'//trim(inst_suffix)
17281826

17291827
write(restartname,'(A,".mom6.r.",I4.4,"-",I2.2,"-",I2.2,"-",I5.5)') &
1730-
trim(casename), year, month, day, seconds
1828+
trim(casename), year, month, day, hour * 3600 + minute * 60 + seconds
17311829
call ESMF_LogWrite("MOM_cap: Writing restart : "//trim(restartname), ESMF_LOGMSG_INFO)
17321830
! write restart file(s)
17331831
call ocean_model_restart(ocean_state, restartname=restartname, num_rest_files=num_rest_files)

config_src/drivers/nuopc_cap/mom_cap_methods.F90

+8-1
Original file line numberDiff line numberDiff line change
@@ -853,7 +853,7 @@ subroutine State_SetExport(state, fldname, isc, iec, jsc, jec, input, ocean_grid
853853

854854
! local variables
855855
type(ESMF_StateItem_Flag) :: itemFlag
856-
integer :: n, i, j, i1, j1, ig,jg
856+
integer :: n, i, j, k, i1, j1, ig,jg
857857
integer :: lbnd1,lbnd2
858858
real(ESMF_KIND_R8), pointer :: dataPtr1d(:)
859859
real(ESMF_KIND_R8), pointer :: dataPtr2d(:,:)
@@ -889,6 +889,13 @@ subroutine State_SetExport(state, fldname, isc, iec, jsc, jec, input, ocean_grid
889889
enddo
890890
end if
891891

892+
! if a maskmap is provided, set exports of all eliminated cells to zero.
893+
if (associated(ocean_grid%Domain%maskmap)) then
894+
do k = n+1, size(dataPtr1d)
895+
dataPtr1d(k) = 0.0
896+
enddo
897+
endif
898+
892899
else if (geomtype == ESMF_GEOMTYPE_GRID) then
893900

894901
call state_getfldptr(state, trim(fldname), dataptr2d, rc)

config_src/infra/FMS1/MOM_domain_infra.F90

+13-2
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ module MOM_domain_infra
1616
use mpp_domains_mod, only : mpp_create_group_update, mpp_do_group_update
1717
use mpp_domains_mod, only : mpp_reset_group_update_field, mpp_group_update_initialized
1818
use mpp_domains_mod, only : mpp_start_group_update, mpp_complete_group_update
19-
use mpp_domains_mod, only : mpp_compute_block_extent
19+
use mpp_domains_mod, only : mpp_compute_block_extent, mpp_compute_extent
2020
use mpp_domains_mod, only : mpp_broadcast_domain, mpp_redistribute, mpp_global_field
2121
use mpp_domains_mod, only : AGRID, BGRID_NE, CGRID_NE, SCALAR_PAIR, BITWISE_EXACT_SUM
2222
use mpp_domains_mod, only : CYCLIC_GLOBAL_DOMAIN, FOLD_NORTH_EDGE
@@ -40,7 +40,7 @@ module MOM_domain_infra
4040
public :: domain2D, domain1D, group_pass_type
4141
! These interfaces are actually implemented or have explicit interfaces in this file.
4242
public :: create_MOM_domain, clone_MOM_domain, get_domain_components, get_domain_extent
43-
public :: deallocate_MOM_domain, get_global_shape, compute_block_extent
43+
public :: deallocate_MOM_domain, get_global_shape, compute_block_extent, compute_extent
4444
public :: pass_var, pass_vector, fill_symmetric_edges, rescale_comp_data
4545
public :: pass_var_start, pass_var_complete, pass_vector_start, pass_vector_complete
4646
public :: create_group_pass, do_group_pass, start_group_pass, complete_group_pass
@@ -1945,6 +1945,17 @@ subroutine compute_block_extent(isg, ieg, ndivs, ibegin, iend)
19451945
call mpp_compute_block_extent(isg, ieg, ndivs, ibegin, iend)
19461946
end subroutine compute_block_extent
19471947

1948+
!> Get the array ranges in one dimension for the divisions of a global index space
1949+
subroutine compute_extent(isg, ieg, ndivs, ibegin, iend)
1950+
integer, intent(in) :: isg !< The starting index of the global index space
1951+
integer, intent(in) :: ieg !< The ending index of the global index space
1952+
integer, intent(in) :: ndivs !< The number of divisions
1953+
integer, dimension(:), intent(out) :: ibegin !< The starting index of each division
1954+
integer, dimension(:), intent(out) :: iend !< The ending index of each division
1955+
1956+
call mpp_compute_extent(isg, ieg, ndivs, ibegin, iend)
1957+
end subroutine compute_extent
1958+
19481959
!> Broadcast a 2-d domain from the root PE to the other PEs
19491960
subroutine broadcast_domain(domain)
19501961
type(domain2d), intent(inout) :: domain !< The domain2d type that will be shared across PEs.

config_src/infra/FMS2/MOM_coms_infra.F90

+10
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ module MOM_coms_infra
4242
interface sum_across_PEs
4343
module procedure sum_across_PEs_int4_0d
4444
module procedure sum_across_PEs_int4_1d
45+
module procedure sum_across_PEs_int4_2d
4546
module procedure sum_across_PEs_int8_0d
4647
module procedure sum_across_PEs_int8_1d
4748
module procedure sum_across_PEs_int8_2d
@@ -357,6 +358,15 @@ subroutine sum_across_PEs_int4_1d(field, length, pelist)
357358
call mpp_sum(field, length, pelist)
358359
end subroutine sum_across_PEs_int4_1d
359360

361+
!> Find the sum of the values in corresponding positions of field across PEs, and return these sums in field.
362+
subroutine sum_across_PEs_int4_2d(field, length, pelist)
363+
integer(kind=int32), dimension(:,:), intent(inout) :: field !< The values to add, the sums upon return
364+
integer, intent(in) :: length !< Number of elements in field to add
365+
integer, optional, intent(in) :: pelist(:) !< List of PEs to work with
366+
367+
call mpp_sum(field, length, pelist)
368+
end subroutine sum_across_PEs_int4_2d
369+
360370
!> Find the sum of field across PEs, and return this sum in field.
361371
subroutine sum_across_PEs_int8_0d(field, pelist)
362372
integer(kind=int64), intent(inout) :: field !< Value on this PE, and the sum across PEs upon return

config_src/infra/FMS2/MOM_domain_infra.F90

+14-3
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ module MOM_domain_infra
1616
use mpp_domains_mod, only : mpp_create_group_update, mpp_do_group_update
1717
use mpp_domains_mod, only : mpp_reset_group_update_field, mpp_group_update_initialized
1818
use mpp_domains_mod, only : mpp_start_group_update, mpp_complete_group_update
19-
use mpp_domains_mod, only : mpp_compute_block_extent
19+
use mpp_domains_mod, only : mpp_compute_block_extent, mpp_compute_extent
2020
use mpp_domains_mod, only : mpp_broadcast_domain, mpp_redistribute, mpp_global_field
2121
use mpp_domains_mod, only : AGRID, BGRID_NE, CGRID_NE, SCALAR_PAIR, BITWISE_EXACT_SUM
2222
use mpp_domains_mod, only : CYCLIC_GLOBAL_DOMAIN, FOLD_NORTH_EDGE
@@ -38,7 +38,7 @@ module MOM_domain_infra
3838
public :: domain2D, domain1D, group_pass_type
3939
! These interfaces are actually implemented or have explicit interfaces in this file.
4040
public :: create_MOM_domain, clone_MOM_domain, get_domain_components, get_domain_extent
41-
public :: deallocate_MOM_domain, get_global_shape, compute_block_extent
41+
public :: deallocate_MOM_domain, get_global_shape, compute_block_extent, compute_extent
4242
public :: pass_var, pass_vector, fill_symmetric_edges, rescale_comp_data
4343
public :: pass_var_start, pass_var_complete, pass_vector_start, pass_vector_complete
4444
public :: create_group_pass, do_group_pass, start_group_pass, complete_group_pass
@@ -1936,7 +1936,7 @@ subroutine get_global_shape(domain, niglobal, njglobal)
19361936
njglobal = domain%njglobal
19371937
end subroutine get_global_shape
19381938

1939-
!> Get the array ranges in one dimension for the divisions of a global index space
1939+
!> Get the array ranges in one dimension for the divisions of a global index space (alternative to compute_extent)
19401940
subroutine compute_block_extent(isg, ieg, ndivs, ibegin, iend)
19411941
integer, intent(in) :: isg !< The starting index of the global index space
19421942
integer, intent(in) :: ieg !< The ending index of the global index space
@@ -1947,6 +1947,17 @@ subroutine compute_block_extent(isg, ieg, ndivs, ibegin, iend)
19471947
call mpp_compute_block_extent(isg, ieg, ndivs, ibegin, iend)
19481948
end subroutine compute_block_extent
19491949

1950+
!> Get the array ranges in one dimension for the divisions of a global index space
1951+
subroutine compute_extent(isg, ieg, ndivs, ibegin, iend)
1952+
integer, intent(in) :: isg !< The starting index of the global index space
1953+
integer, intent(in) :: ieg !< The ending index of the global index space
1954+
integer, intent(in) :: ndivs !< The number of divisions
1955+
integer, dimension(:), intent(out) :: ibegin !< The starting index of each division
1956+
integer, dimension(:), intent(out) :: iend !< The ending index of each division
1957+
1958+
call mpp_compute_extent(isg, ieg, ndivs, ibegin, iend)
1959+
end subroutine compute_extent
1960+
19501961
!> Broadcast a 2-d domain from the root PE to the other PEs
19511962
subroutine broadcast_domain(domain)
19521963
type(domain2d), intent(inout) :: domain !< The domain2d type that will be shared across PEs.

src/core/MOM.F90

+4-4
Original file line numberDiff line numberDiff line change
@@ -2539,12 +2539,12 @@ subroutine initialize_MOM(Time, Time_init, param_file, dirs, CS, &
25392539
G_in => CS%G_in
25402540
#ifdef STATIC_MEMORY_
25412541
call MOM_domains_init(G_in%domain, param_file, symmetric=symmetric, &
2542-
static_memory=.true., NIHALO=NIHALO_, NJHALO=NJHALO_, &
2543-
NIGLOBAL=NIGLOBAL_, NJGLOBAL=NJGLOBAL_, NIPROC=NIPROC_, &
2544-
NJPROC=NJPROC_)
2542+
static_memory=.true., NIHALO=NIHALO_, NJHALO=NJHALO_, &
2543+
NIGLOBAL=NIGLOBAL_, NJGLOBAL=NJGLOBAL_, NIPROC=NIPROC_, &
2544+
NJPROC=NJPROC_, US=US)
25452545
#else
25462546
call MOM_domains_init(G_in%domain, param_file, symmetric=symmetric, &
2547-
domain_name="MOM_in")
2547+
domain_name="MOM_in", US=US)
25482548
#endif
25492549

25502550
! Copy input grid (G_in) domain to active grid G

0 commit comments

Comments
 (0)