Skip to content

Commit

Permalink
Merge pull request ESCOMP#129 from jedwards4b/backout_mask_changes
Browse files Browse the repository at this point in the history
  • Loading branch information
jedwards4b authored Oct 22, 2021
2 parents ce35b27 + 6994d8e commit 3e486d4
Show file tree
Hide file tree
Showing 3 changed files with 16 additions and 39 deletions.
3 changes: 1 addition & 2 deletions datm/datm_datamode_clmncep_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -348,7 +348,7 @@ subroutine datm_datamode_clmncep_advance(masterproc, logunit, mpicom, rc)
! determine tbotmax (see below for use)
rtmp = maxval(Sa_tbot(:))
call shr_mpi_max(rtmp, tbotmax, mpicom, 'datm_tbot', all=.true.)
write(logunit,*) trim(subname),' tbotmax = ',tbotmax
if (masterproc) write(logunit,*) trim(subname),' tbotmax = ',tbotmax
if(tbotmax <= 0) then
call shr_sys_abort(subname//'ERROR: bad value in tbotmax')
endif
Expand Down Expand Up @@ -418,7 +418,6 @@ subroutine datm_datamode_clmncep_advance(masterproc, logunit, mpicom, rc)
else
call shr_sys_abort(subname//'ERROR: cannot compute shum')
endif

!--- density ---
vp = (Sa_shum(n)*pbot) / (0.622_r8 + 0.378_r8 * Sa_shum(n))
Sa_dens(n) = (pbot - 0.378_r8 * vp) / (tbot*rdair)
Expand Down
7 changes: 4 additions & 3 deletions docn/ocn_comp_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ module cdeps_docn_comp
use ESMF , only : ESMF_Alarm, ESMF_MethodRemove, ESMF_MethodAdd
use ESMF , only : ESMF_GridCompSetEntryPoint, ESMF_ClockGetAlarm, ESMF_AlarmIsRinging
use ESMF , only : ESMF_StateGet, operator(+), ESMF_AlarmRingerOff, ESMF_LogWrite
use ESMF , only : ESMF_Field, ESMF_FieldGet
use ESMF , only : ESMF_Field, ESMF_FieldGet, ESMF_VmLogMemInfo
use NUOPC , only : NUOPC_CompDerive, NUOPC_CompSetEntryPoint, NUOPC_CompSpecialize
use NUOPC , only : NUOPC_Advertise, NUOPC_CompAttributeGet
use NUOPC_Model , only : model_routine_SS => SetServices
Expand Down Expand Up @@ -306,7 +306,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
!-------------------------------------------------------------------------------

rc = ESMF_SUCCESS

call ESMF_VMLogMemInfo("Entering "//trim(subname))
! Initialize model mesh, restart flag, logunit, model_mask and model_frac
call ESMF_TraceRegionEnter('docn_strdata_init')
call dshr_mesh_init(gcomp, sdat, nullstr, logunit, 'OCN', nx_global, ny_global, &
Expand Down Expand Up @@ -355,6 +355,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
! *******************
! *** RETURN HERE ***
! *******************
call ESMF_VMLogMemInfo("Leaving "//trim(subname))
RETURN
end if

Expand All @@ -374,7 +375,7 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
call dshr_state_SetScalar(dble(ny_global),flds_scalar_index_ny, exportState, flds_scalar_name, flds_scalar_num, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return

call ESMF_VMLogMemInfo("Leaving "//trim(subname))
end subroutine InitializeRealize

!===============================================================================
Expand Down
45 changes: 11 additions & 34 deletions streams/dshr_strdata_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ module dshr_strdata_mod
use ESMF , only : ESMF_FieldReGridStore, ESMF_FieldRedistStore, ESMF_UNMAPPEDACTION_IGNORE
use ESMF , only : ESMF_TERMORDER_SRCSEQ, ESMF_FieldRegrid, ESMF_FieldFill
use ESMF , only : ESMF_REGION_TOTAL, ESMF_FieldGet, ESMF_TraceRegionExit, ESMF_TraceRegionEnter
use ESMF , only : ESMF_LOGMSG_INFO, ESMF_LogWrite
use ESMF , only : ESMF_LOGMSG_INFO, ESMF_LogWrite, ESMF_RC_ARG_VALUE
use shr_kind_mod , only : r8=>shr_kind_r8, r4=>shr_kind_r4, i2=>shr_kind_I2
use shr_kind_mod , only : cs=>shr_kind_cs, cl=>shr_kind_cl, cxx=>shr_kind_cxx
use shr_sys_mod , only : shr_sys_abort
Expand Down Expand Up @@ -848,7 +848,6 @@ subroutine shr_strdata_advance(sdat, ymd, tod, logunit, istr, timers, rc)
integer :: nstreams
integer :: stream_index
integer :: lsize
integer ,allocatable :: mask(:)
real(r8) ,parameter :: solZenMin = 0.001_r8 ! minimum solar zenith angle
integer ,parameter :: tadj = 2
character(len=*) ,parameter :: timname = "_strd_adv"
Expand Down Expand Up @@ -984,12 +983,6 @@ subroutine shr_strdata_advance(sdat, ymd, tod, logunit, istr, timers, rc)
! ---------------------------------------------------------

do ns = 1,nstreams
call ESMF_MeshGet(sdat%model_mesh, elementCount=lsize)
if (chkerr(rc,__LINE__,u_FILE_u)) return
allocate(mask(lsize))
call ESMF_MeshGet(sdat%model_mesh, elementMask=mask)
if (chkerr(rc,__LINE__,u_FILE_u)) return

if (trim(sdat%stream(ns)%tinterpalgo) == 'coszen') then

! Determine stream lower bound index
Expand Down Expand Up @@ -1033,7 +1026,7 @@ subroutine shr_strdata_advance(sdat, ymd, tod, logunit, istr, timers, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
do i = 1,size(dataptr2d,dim=2)
if (coszen(i) > solZenMin) then
dataptr2d(:,i) = mask(i)*dataptr2d_lb(:,i)*coszen(i)/sdat%tavCoszen(i)
dataptr2d(:,i) = dataptr2d_lb(:,i)*coszen(i)/sdat%tavCoszen(i)
else
dataptr2d(:,i) = 0._r8
endif
Expand All @@ -1047,7 +1040,7 @@ subroutine shr_strdata_advance(sdat, ymd, tod, logunit, istr, timers, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
do i = 1,size(dataptr1d)
if (coszen(i) > solZenMin) then
dataptr1d(i) = mask(i)*dataptr1d_lb(i)*coszen(i)/sdat%tavCoszen(i)
dataptr1d(i) = dataptr1d_lb(i)*coszen(i)/sdat%tavCoszen(i)
else
dataptr1d(i) = 0._r8
endif
Expand Down Expand Up @@ -1085,7 +1078,7 @@ subroutine shr_strdata_advance(sdat, ymd, tod, logunit, istr, timers, rc)
sdat%pstrm(ns)%fldlist_model(nf), fldptr2=dataptr2d_ub, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
do lev = 1,sdat%pstrm(ns)%stream_nlev
dataptr2d(lev,:) = mask(:)*(dataptr2d_lb(lev,:) * flb + dataptr2d_ub(lev,:) * fub)
dataptr2d(lev,:) = dataptr2d_lb(lev,:) * flb + dataptr2d_ub(lev,:) * fub
end do
else
call dshr_fldbun_getfldptr(sdat%pstrm(ns)%fldbun_model, &
Expand All @@ -1097,7 +1090,7 @@ subroutine shr_strdata_advance(sdat, ymd, tod, logunit, istr, timers, rc)
call dshr_fldbun_getfldptr(sdat%pstrm(ns)%fldbun_data(sdat%pstrm(ns)%stream_ub), &
sdat%pstrm(ns)%fldlist_model(nf), fldptr1=dataptr1d_ub, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
dataptr1d(:) = mask(:)*(dataptr1d_lb(:) * flb + dataptr1d_ub(:) * fub)
dataptr1d(:) = dataptr1d_lb(:) * flb + dataptr1d_ub(:) * fub
end if
end do
call ESMF_TraceRegionExit(trim(lstr)//trim(timname)//'_tint')
Expand Down Expand Up @@ -1125,7 +1118,6 @@ subroutine shr_strdata_advance(sdat, ymd, tod, logunit, istr, timers, rc)
call ESMF_TraceRegionExit(trim(lstr)//trim(timname)//'_zero')

endif
deallocate(mask)
end do ! loop over ns (number of streams)

deallocate(newData)
Expand Down Expand Up @@ -1362,7 +1354,6 @@ subroutine shr_strdata_readstrm(sdat, per_stream, stream, fldbun_data, &
real(r8), allocatable :: data_dbl2d(:,:) ! stream input data
integer(i2), allocatable :: data_short1d(:) ! stream input data
integer(i2), allocatable :: data_short2d(:,:) ! stream input data
integer, allocatable :: mask(:)
integer :: lsize, n
integer :: spatialDim, numOwnedElements
integer :: pio_iovartype
Expand Down Expand Up @@ -1513,13 +1504,6 @@ subroutine shr_strdata_readstrm(sdat, per_stream, stream, fldbun_data, &

! read the data
call pio_setframe(pioid, varid, int(nt,kind=Pio_Offset_Kind))

call ESMF_MeshGet(per_stream%stream_mesh, elementCount=lsize)
if (chkerr(rc,__LINE__,u_FILE_u)) return
allocate(mask(lsize))
call ESMF_MeshGet(per_stream%stream_mesh, elementMask=mask)
if (chkerr(rc,__LINE__,u_FILE_u)) return

if (pio_iovartype == PIO_REAL) then
! -----------------------------
! pio_iovartype is PIO_REAL
Expand Down Expand Up @@ -1670,14 +1654,14 @@ subroutine shr_strdata_readstrm(sdat, per_stream, stream, fldbun_data, &
if(data_short2d(n,lev) .eq. fillvalue_i2) then
dataptr2d(lev,n) = r8fill
else
dataptr2d(lev,n) = mask(n)*(real(data_short2d(lev,n),r8) * scale_factor + add_offset)
dataptr2d(lev,n) = real(data_short2d(lev,n),r8) * scale_factor + add_offset
endif
enddo
end do
else
do lev = 1,stream_nlev
do n = 1,lsize
dataptr2d(lev,n) = mask(n)*(real(data_short2d(n,lev),r8) * scale_factor + add_offset)
dataptr2d(lev,n) = real(data_short2d(n,lev),r8) * scale_factor + add_offset
enddo
end do
end if
Expand All @@ -1695,12 +1679,12 @@ subroutine shr_strdata_readstrm(sdat, per_stream, stream, fldbun_data, &
if(data_short1d(n).eq.fillvalue_i2) then
dataptr1d(n) = r8fill
else
dataptr1d(n) = mask(n)*(real(data_short1d(n),r8) * scale_factor + add_offset)
dataptr1d(n) = real(data_short1d(n),r8) * scale_factor + add_offset
endif
enddo
else
do n=1,lsize
dataptr1d(n) = mask(n)*(real(data_short1d(n),r8) * scale_factor + add_offset)
dataptr1d(n) = real(data_short1d(n),r8) * scale_factor + add_offset
enddo
endif
end if
Expand Down Expand Up @@ -1731,16 +1715,10 @@ subroutine shr_strdata_readstrm(sdat, per_stream, stream, fldbun_data, &
call ESMF_FieldFill(field_dst, dataFillScheme="const", const1=dataptr1d(1), rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
endif
deallocate(mask)
enddo

! Both components of a vector stream must be in the same input stream file
if (associated(dataptr2d_src) .and. associated(dataptr1d)) then
call ESMF_MeshGet(per_stream%stream_mesh, elementCount=lsize)
if (chkerr(rc,__LINE__,u_FILE_u)) return
allocate(mask(lsize))
call ESMF_MeshGet(per_stream%stream_mesh, elementMask=mask)
if (chkerr(rc,__LINE__,u_FILE_u)) return

! get lon and lat of stream u and v fields
lsize = size(dataptr1d)
Expand All @@ -1763,8 +1741,8 @@ subroutine shr_strdata_readstrm(sdat, per_stream, stream, fldbun_data, &
lat = nu_coords(2*i)
sinlon = sin(lon*deg2rad); coslon = cos(lon*deg2rad)
sinlat = sin(lat*deg2rad); coslat = cos(lat*deg2rad)
dataptr2d_src(1,i) = mask(i)*(coslon * dataptr(i) - sinlon * dataptr2d_src(2,i))
dataptr2d_src(2,i) = mask(i)*(sinlon * dataptr(i) + coslon * dataptr2d_src(2,i))
dataptr2d_src(1,i) = (coslon * dataptr(i) - sinlon * dataptr2d_src(2,i))
dataptr2d_src(2,i) = (sinlon * dataptr(i) + coslon * dataptr2d_src(2,i))
enddo
vector_dst = ESMF_FieldCreate(sdat%model_mesh, ESMF_TYPEKIND_r8, name='vector_dst', &
ungriddedLbound=(/1/), ungriddedUbound=(/2/), gridToFieldMap=(/2/), meshloc=ESMF_MESHLOC_ELEMENT, rc=rc)
Expand All @@ -1789,7 +1767,6 @@ subroutine shr_strdata_readstrm(sdat, per_stream, stream, fldbun_data, &
data_u_dst(i) = coslon * dataptr2d_dst(1,i) + sinlon * dataptr2d_dst(2,i)
data_v_dst(i) = -sinlon * dataptr2d_dst(1,i) + coslon * dataptr2d_dst(2,i)
enddo
deallocate(mask)
deallocate(dataptr)
endif

Expand Down

0 comments on commit 3e486d4

Please sign in to comment.