Skip to content

Commit

Permalink
rename module; use check_esmf_error routine
Browse files Browse the repository at this point in the history
	renamed:    src/utils/esmf_zm_mod.F90 -> src/utils/esmf_zonal_ops.F90
	modified:   src/physics/cam/physpkg.F90
	modified:   src/physics/cam7/physpkg.F90
	modified:   src/utils/esmf_zonal_ops.F90
	modified:   src/utils/zm_test_mod.F90
  • Loading branch information
fvitt committed Dec 9, 2024
1 parent 88f8f00 commit c844d62
Show file tree
Hide file tree
Showing 4 changed files with 40 additions and 70 deletions.
4 changes: 2 additions & 2 deletions src/physics/cam/physpkg.F90
Original file line number Diff line number Diff line change
Expand Up @@ -159,7 +159,7 @@ subroutine phys_register
use offline_driver, only: offline_driver_reg
use hemco_interface, only: HCOI_Chunk_Init
use upper_bc, only: ubc_fixed_conc
use esmf_zm_mod, only: esmf_zm_init
use esmf_zonal_ops, only: esmf_zonal_ops_init
use zm_test_mod, only: zm_test_reg

!---------------------------Local variables-----------------------------
Expand Down Expand Up @@ -357,7 +357,7 @@ subroutine phys_register
call pbuf_cam_snapshot_register()
end if

call esmf_zm_init()
call esmf_zonal_ops_init()
call zm_test_reg()

end subroutine phys_register
Expand Down
4 changes: 2 additions & 2 deletions src/physics/cam7/physpkg.F90
Original file line number Diff line number Diff line change
Expand Up @@ -154,7 +154,7 @@ subroutine phys_register
use dyn_comp, only: dyn_register
use offline_driver, only: offline_driver_reg
use hemco_interface, only: HCOI_Chunk_Init
use esmf_zm_mod, only: esmf_zm_init
use esmf_zonal_ops, only: esmf_zonal_ops_init
use zm_test_mod, only: zm_test_reg

!---------------------------Local variables-----------------------------
Expand Down Expand Up @@ -345,7 +345,7 @@ subroutine phys_register
call pbuf_cam_snapshot_register()
end if

call esmf_zm_init()
call esmf_zonal_ops_init()
call zm_test_reg()

end subroutine phys_register
Expand Down
90 changes: 30 additions & 60 deletions src/utils/esmf_zm_mod.F90 → src/utils/esmf_zonal_ops.F90
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module esmf_zm_mod
module esmf_zonal_ops
use shr_kind_mod, only: r8 => shr_kind_r8, cl=>SHR_KIND_CL
use ppgrid, only: pcols, pver, begchunk, endchunk
use phys_grid, only: get_ncols_p
Expand Down Expand Up @@ -27,7 +27,7 @@ module esmf_zm_mod
real(r8), allocatable :: glats(:)
real(r8), allocatable :: glons(:)

integer, parameter :: minlats_per_pe = 1
integer, parameter :: minlats_per_pe = 2
integer, parameter :: minlons_per_pe = 2
integer :: ntasks_lat = -1
integer :: ntasks_lon = -1
Expand Down Expand Up @@ -56,7 +56,7 @@ module esmf_zm_mod

!------------------------------------------------------------------------------
!------------------------------------------------------------------------------
subroutine esmf_zm_init(nlats_in)
subroutine esmf_zonal_ops_init(nlats_in)
use phys_grid, only: get_grid_dims
use mpi, only: mpi_comm_size, mpi_comm_rank, MPI_PROC_NULL, MPI_INTEGER

Expand All @@ -71,7 +71,7 @@ subroutine esmf_zm_init(nlats_in)
integer :: n
integer :: lons_per_task, lons_overflow, lats_per_task, lats_overflow
integer :: task_cnt
character(len=*), parameter :: subname = 'esmf_zm_init'
character(len=*), parameter :: subname = 'esmf_zonal_ops_init'

integer, allocatable :: petmap(:,:,:)
integer :: petcnt
Expand Down Expand Up @@ -321,25 +321,19 @@ subroutine esmf_zm_init(nlats_in)
countsPerDEDim1=nlons_task, coordDep1=(/1/), &
countsPerDEDim2=nlats_task, coordDep2=(/2/), petmap=petmap, &
indexflag=ESMF_INDEX_GLOBAL,minIndex=(/1,1/), rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_GridCreate1PeriDim ERROR')
end if
call check_esmf_error(ierr, subname//'ESMF_GridCreate1PeriDim ERROR')


! Set coordinates:

call ESMF_GridAddCoord(lonlat_grid, staggerloc=ESMF_STAGGERLOC_CENTER, rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_GridAddCoord ERROR')
end if
call check_esmf_error(ierr, subname//'ESMF_GridAddCoord ERROR')

if (mytid<npes) then
call ESMF_GridGetCoord(lonlat_grid, coordDim=1, &
computationalLBound=lbnd, computationalUBound=ubnd, &
farrayPtr=coordX, staggerloc=ESMF_STAGGERLOC_CENTER, rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_GridGetCoord for longitude coords ERROR')
end if
call check_esmf_error(ierr, subname//'ESMF_GridGetCoord for longitude coords ERROR')

lbnd_lon = lbnd(1)
ubnd_lon = ubnd(1)
Expand All @@ -350,9 +344,7 @@ subroutine esmf_zm_init(nlats_in)
call ESMF_GridGetCoord(lonlat_grid, coordDim=2, &
computationalLBound=lbnd, computationalUBound=ubnd, &
farrayPtr=coordY, staggerloc=ESMF_STAGGERLOC_CENTER, rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_GridGetCoord for latitude coords ERROR')
end if
call check_esmf_error(ierr, subname//'ESMF_GridGetCoord for latitude coords ERROR')

lbnd_lat = lbnd(1)
ubnd_lat = ubnd(1)
Expand All @@ -365,52 +357,35 @@ subroutine esmf_zm_init(nlats_in)

! 3D phys fld
call ESMF_ArraySpecSet(arrayspec, 2, ESMF_TYPEKIND_R8, rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_ArraySpecSet 3D phys fld ERROR')
end if
call check_esmf_error(ierr, subname//'ESMF_ArraySpecSet 3D phys fld ERROR')

physfld_3d = ESMF_FieldCreate(physics_grid_mesh, arrayspec, &
gridToFieldMap=(/2/), meshloc=ESMF_MESHLOC_ELEMENT, &
ungriddedLBound=(/1/), ungriddedUBound=(/pver/), rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_FieldCreate 3D phys fld ERROR')
end if
gridToFieldMap=(/2/), meshloc=ESMF_MESHLOC_ELEMENT, &
ungriddedLBound=(/1/), ungriddedUBound=(/pver/), rc=ierr)
call check_esmf_error(ierr, subname//'ESMF_FieldCreate 3D phys fld ERROR')

! 2D phys fld
call ESMF_ArraySpecSet(arrayspec, 1, ESMF_TYPEKIND_R8, rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_ArraySpecSet 2D phys fld ERROR')
end if
call check_esmf_error(ierr, subname//'ESMF_ArraySpecSet 2D phys fld ERROR')

physfld_2d = ESMF_FieldCreate(physics_grid_mesh, arrayspec, &
meshloc=ESMF_MESHLOC_ELEMENT, rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_FieldCreate 2D phys fld ERROR')
end if
meshloc=ESMF_MESHLOC_ELEMENT, rc=ierr)
call check_esmf_error(ierr, subname//'ESMF_FieldCreate 2D phys fld ERROR')

! 3D lon/lat grid
call ESMF_ArraySpecSet(arrayspec, 3, ESMF_TYPEKIND_R8, rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_ArraySpecSet 3D lonlat fld ERROR')
end if
call check_esmf_error(ierr, subname//'ESMF_ArraySpecSet 3D lonlat fld ERROR')

lonlatfld_3d = ESMF_FieldCreate( lonlat_grid, arrayspec, staggerloc=ESMF_STAGGERLOC_CENTER, &
ungriddedLBound=(/1/), ungriddedUBound=(/pver/), rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_FieldCreate 3D lonlat fld ERROR')
end if
ungriddedLBound=(/1/), ungriddedUBound=(/pver/), rc=ierr)
call check_esmf_error(ierr, subname//'ESMF_FieldCreate 3D lonlat fld ERROR')

! 2D lon/lat grid
call ESMF_ArraySpecSet(arrayspec, 2, ESMF_TYPEKIND_R8, rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_ArraySpecSet 2D lonlat fld ERROR')
end if
call check_esmf_error(ierr, subname//'ESMF_ArraySpecSet 2D lonlat fld ERROR')

lonlatfld_2d = ESMF_FieldCreate( lonlat_grid, arrayspec, staggerloc=ESMF_STAGGERLOC_CENTER, &
rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_FieldCreate 2D lonlat fld ERROR')
end if
lonlatfld_2d = ESMF_FieldCreate( lonlat_grid, arrayspec, staggerloc=ESMF_STAGGERLOC_CENTER, rc=ierr)
call check_esmf_error(ierr, subname//'ESMF_FieldCreate 2D lonlat fld ERROR')


! route handles -- phys --> lonlat mapping
Expand All @@ -427,9 +402,7 @@ subroutine esmf_zm_init(nlats_in)
routeHandle=rh_phys2lonlat_3D, factorIndexList=factorIndexList, &
factorList=factorList, srcTermProcessing=smm_srctermproc, &
pipelineDepth=smm_pipelinedep, rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_FieldRegridStore 3D routehandle ERROR')
end if
call check_esmf_error(ierr, subname//'ESMF_FieldRegridStore 3D routehandle ERROR')

! 2D

Expand All @@ -440,17 +413,14 @@ subroutine esmf_zm_init(nlats_in)
routeHandle=rh_phys2lonlat_2D, factorIndexList=factorIndexList, &
factorList=factorList, srcTermProcessing=smm_srctermproc, &
pipelineDepth=smm_pipelinedep, rc=ierr)
if (ierr/=ESMF_SUCCESS) then
call endrun(subname//'ESMF_FieldRegridStore 2D routehandle ERROR')
end if

call check_esmf_error(ierr, subname//'ESMF_FieldRegridStore 2D routehandle ERROR')

end subroutine esmf_zm_init
end subroutine esmf_zonal_ops_init


!------------------------------------------------------------------------------
!------------------------------------------------------------------------------
function esmf_zm_calc_2d(physfld) result(zmfld)
function esmf_zonal_mean_2d(physfld) result(zmfld)

real(r8),intent(in) :: physfld(pcols,begchunk:endchunk)

Expand Down Expand Up @@ -494,11 +464,11 @@ function esmf_zm_calc_2d(physfld) result(zmfld)
zmfld(ilat) = gsum(1)/nlons
end do

end function esmf_zm_calc_2d
end function esmf_zonal_mean_2d

!------------------------------------------------------------------------------
!------------------------------------------------------------------------------
function esmf_zm_calc_3d(physfld) result(zmfld)
function esmf_zonal_mean_3d(physfld) result(zmfld)

real(r8),intent(in) :: physfld(pver,pcols,begchunk:endchunk)

Expand Down Expand Up @@ -547,7 +517,7 @@ function esmf_zm_calc_3d(physfld) result(zmfld)
zmfld(ilat,:) = gsum(:)/nlons
end do

end function esmf_zm_calc_3d
end function esmf_zonal_mean_3d

!------------------------------------------------------------------------------
!------------------------------------------------------------------------------
Expand All @@ -558,7 +528,7 @@ subroutine check_esmf_error( rc, errmsg )
character(len=cl) :: errstr

if (rc /= ESMF_SUCCESS) then
write(errstr,'(a,i6)') 'esmf_zm_mod::'//trim(errmsg)//' -- ESMF ERROR code: ',rc
write(errstr,'(a,i6)') 'esmf_zonal_ops::'//trim(errmsg)//' -- ESMF ERROR code: ',rc
if (masterproc) write(iulog,*) trim(errstr)
call endrun(trim(errstr))
end if
Expand All @@ -567,4 +537,4 @@ end subroutine check_esmf_error



end module esmf_zm_mod
end module esmf_zonal_ops
12 changes: 6 additions & 6 deletions src/utils/zm_test_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@ module zm_test_mod
use spmd_utils, only: masterproc
use cam_history, only: horiz_only, addfld, outfld

use esmf_zm_mod, only: lon_beg, lon_end, lat_beg, lat_end, esmf_zm_calc_2d, esmf_zm_calc_3d
use esmf_zm_mod, only: nlats, glats
use esmf_zonal_ops, only: lon_beg, lon_end, lat_beg, lat_end, esmf_zonal_mean_2d, esmf_zonal_mean_3d
use esmf_zonal_ops, only: nlats, glats

implicit none

Expand Down Expand Up @@ -96,11 +96,11 @@ subroutine zm_test_run(phys_state)
end do
end do

t_zm = esmf_zm_calc_3d(tfld)
u_zm = esmf_zm_calc_3d(ufld)
v_zm = esmf_zm_calc_3d(vfld)
t_zm = esmf_zonal_mean_3d(tfld)
u_zm = esmf_zonal_mean_3d(ufld)
v_zm = esmf_zonal_mean_3d(vfld)

ps_zm = esmf_zm_calc_2d(psfld)
ps_zm = esmf_zonal_mean_2d(psfld)

do icol = lat_beg, lat_end
call outfld('PS_emsfzm',ps_zm(icol),1,icol)
Expand Down

0 comments on commit c844d62

Please sign in to comment.