Skip to content

Commit

Permalink
Merge pull request #259 from uturuncoglu/feature/mask_only
Browse files Browse the repository at this point in the history
Bring support for configurable source and destination mask
  • Loading branch information
jedwards4b committed Jan 26, 2024
2 parents 97a2da6 + 416b566 commit 28cc73e
Show file tree
Hide file tree
Showing 2 changed files with 54 additions and 23 deletions.
56 changes: 35 additions & 21 deletions streams/dshr_strdata_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -240,7 +240,8 @@ subroutine shr_strdata_init_from_inline(sdat, my_task, logunit, compname, &
stream_meshfile, stream_lev_dimname, stream_mapalgo, &
stream_filenames, stream_fldlistFile, stream_fldListModel, &
stream_yearFirst, stream_yearLast, stream_yearAlign, &
stream_offset, stream_taxmode, stream_dtlimit, stream_tintalgo, stream_name, rc)
stream_offset, stream_taxmode, stream_dtlimit, stream_tintalgo, &
stream_src_mask, stream_dst_mask, stream_name, rc)

! input/output variables
type(shr_strdata_type) , intent(inout) :: sdat ! stream data type
Expand All @@ -262,8 +263,14 @@ subroutine shr_strdata_init_from_inline(sdat, my_task, logunit, compname, &
character(*) , intent(in) :: stream_taxMode ! time axis mode
real(r8) , intent(in) :: stream_dtlimit ! ratio of max/min stream delta times
character(*) , intent(in) :: stream_tintalgo ! time interpolation algorithm
integer, optional , intent(in) :: stream_src_mask ! source mask value
integer, optional , intent(in) :: stream_dst_mask ! destination mask value
character(*), optional , intent(in) :: stream_name ! name of stream
integer , intent(out) :: rc ! error code
integer, optional , intent(out) :: rc ! error code

! local variables
integer :: src_mask = 0
integer :: dst_mask = 0
! ----------------------------------------------

rc = ESMF_SUCCESS
Expand All @@ -277,6 +284,10 @@ subroutine shr_strdata_init_from_inline(sdat, my_task, logunit, compname, &
sdat%io_format = shr_pio_getioformat(trim(compname))
#endif

! Check source and destination mask, defaults are 0
if (present(stream_src_mask)) src_mask = stream_src_mask
if (present(stream_dst_mask)) dst_mask = stream_dst_mask

! Initialize sdat%pstrm - ASSUME only 1 stream
allocate(sdat%pstrm(1))

Expand All @@ -292,7 +303,7 @@ subroutine shr_strdata_init_from_inline(sdat, my_task, logunit, compname, &
stream_yearFirst, stream_yearLast, stream_yearAlign, &
stream_offset, stream_taxmode, stream_tintalgo, stream_dtlimit, &
stream_fldlistFile, stream_fldListModel, stream_fileNames, &
logunit, trim(compname))
logunit, trim(compname), src_mask, dst_mask)

! Now finish initializing sdat
call shr_strdata_init(sdat, model_clock, stream_name, rc)
Expand Down Expand Up @@ -549,8 +560,8 @@ subroutine shr_strdata_init(sdat, model_clock, stream_name, rc)
regridmethod=ESMF_REGRIDMETHOD_BILINEAR, &
polemethod=ESMF_POLEMETHOD_ALLAVG, &
extrapMethod=ESMF_EXTRAPMETHOD_NEAREST_STOD, &
dstMaskValues = (/0/), & ! ignore destination points where the mask is 0
srcMaskValues = (/0/), & ! ignore source points where the mask is 0
dstMaskValues=(/sdat%stream(ns)%dst_mask_val/), &
srcMaskValues=(/sdat%stream(ns)%src_mask_val/), &
srcTermProcessing=srcTermProcessing_Value, ignoreDegenerate=.true., rc=rc)
if (chkerr(rc,__LINE__,u_FILE_u)) return
else if (trim(sdat%stream(ns)%mapalgo) == 'redist') then
Expand All @@ -562,26 +573,26 @@ subroutine shr_strdata_init(sdat, model_clock, stream_name, rc)
call ESMF_FieldReGridStore(sdat%pstrm(ns)%field_stream, lfield_dst, &
routehandle=sdat%pstrm(ns)%routehandle, &
regridmethod=ESMF_REGRIDMETHOD_NEAREST_STOD, &
dstMaskValues = (/0/), & ! ignore destination points where the mask is 0
srcMaskValues = (/0/), & ! ignore source points where the mask is 0
dstMaskValues=(/sdat%stream(ns)%dst_mask_val/), &
srcMaskValues=(/sdat%stream(ns)%src_mask_val/), &
srcTermProcessing=srcTermProcessing_Value, ignoreDegenerate=.true., &
unmappedaction=ESMF_UNMAPPEDACTION_IGNORE, rc=rc)
else if (trim(sdat%stream(ns)%mapalgo) == 'consf') then
call ESMF_FieldReGridStore(sdat%pstrm(ns)%field_stream, lfield_dst, &
routehandle=sdat%pstrm(ns)%routehandle, &
regridmethod=ESMF_REGRIDMETHOD_CONSERVE, &
normType=ESMF_NORMTYPE_FRACAREA, &
dstMaskValues = (/0/), & ! ignore destination points where the mask is 0
srcMaskValues = (/0/), & ! ignore source points where the mask is 0
dstMaskValues=(/sdat%stream(ns)%dst_mask_val/), &
srcMaskValues=(/sdat%stream(ns)%src_mask_val/), &
srcTermProcessing=srcTermProcessing_Value, ignoreDegenerate=.true., &
unmappedaction=ESMF_UNMAPPEDACTION_IGNORE, rc=rc)
else if (trim(sdat%stream(ns)%mapalgo) == 'consd') then
call ESMF_FieldReGridStore(sdat%pstrm(ns)%field_stream, lfield_dst, &
routehandle=sdat%pstrm(ns)%routehandle, &
regridmethod=ESMF_REGRIDMETHOD_CONSERVE, &
normType=ESMF_NORMTYPE_DSTAREA, &
dstMaskValues = (/0/), & ! ignore destination points where the mask is 0
srcMaskValues = (/0/), & ! ignore source points where the mask is 0
dstMaskValues=(/sdat%stream(ns)%dst_mask_val/), &
srcMaskValues=(/sdat%stream(ns)%src_mask_val/), &
srcTermProcessing=srcTermProcessing_Value, ignoreDegenerate=.true., &
unmappedaction=ESMF_UNMAPPEDACTION_IGNORE, rc=rc)
else if (trim(sdat%stream(ns)%mapalgo) == 'none') then
Expand Down Expand Up @@ -1235,9 +1246,10 @@ subroutine shr_strdata_print(sdat, name)
character(*),parameter :: F00 = "('(shr_strdata_print) ',8a)"
character(*),parameter :: F01 = "('(shr_strdata_print) ',a,i6,a)"
character(*),parameter :: F02 = "('(shr_strdata_print) ',a,es13.6)"
character(*),parameter :: F04 = "('(shr_strdata_print) ',a,i2,a,a)"
character(*),parameter :: F05 = "('(shr_strdata_print) ',a)"
character(*),parameter :: F07 = "('(shr_strdata_print) ',a,i2,a,es13.6)"
character(*),parameter :: F03 = "('(shr_strdata_print) ',a,i2,a,a)"
character(*),parameter :: F04 = "('(shr_strdata_print) ',a)"
character(*),parameter :: F05 = "('(shr_strdata_print) ',a,i2,a,es13.6)"
character(*),parameter :: F06 = "('(shr_strdata_print) ',a,i2,a,i1)"
character(*),parameter :: F90 = "('(shr_strdata_print) ',58('-'))"
!-------------------------------------------------------------------------------

Expand All @@ -1251,14 +1263,16 @@ subroutine shr_strdata_print(sdat, name)
write(sdat%stream(1)%logunit,F02) "obliqr = ",sdat%obliqr
write(sdat%stream(1)%logunit,F01) "pio_iotype = ",sdat%io_type
write(sdat%stream(1)%logunit,F01) "nstreams = ",shr_strdata_get_stream_count(sdat)
write(sdat%stream(1)%logunit,F05) "Per stream information "
write(sdat%stream(1)%logunit,F04) "Per stream information "
do ns = 1, shr_strdata_get_stream_count(sdat)
write(sdat%stream(1)%logunit,F04) " taxMode (",ns,") = ",trim(sdat%stream(ns)%taxmode)
write(sdat%stream(1)%logunit,F07) " dtlimit (",ns,") = ",sdat%stream(ns)%dtlimit
write(sdat%stream(1)%logunit,F04) " mapalgo (",ns,") = ",trim(sdat%stream(ns)%mapalgo)
write(sdat%stream(1)%logunit,F04) " tintalgo(",ns,") = ",trim(sdat%stream(ns)%tinterpalgo)
write(sdat%stream(1)%logunit,F04) " readmode(",ns,") = ",trim(sdat%stream(ns)%readmode)
write(sdat%stream(1)%logunit,F04) " vectors (",ns,") = ",trim(sdat%stream(ns)%stream_vectors)
write(sdat%stream(1)%logunit,F03) " taxMode (",ns,") = ",trim(sdat%stream(ns)%taxmode)
write(sdat%stream(1)%logunit,F05) " dtlimit (",ns,") = ",sdat%stream(ns)%dtlimit
write(sdat%stream(1)%logunit,F03) " mapalgo (",ns,") = ",trim(sdat%stream(ns)%mapalgo)
write(sdat%stream(1)%logunit,F03) " tintalgo(",ns,") = ",trim(sdat%stream(ns)%tinterpalgo)
write(sdat%stream(1)%logunit,F03) " readmode(",ns,") = ",trim(sdat%stream(ns)%readmode)
write(sdat%stream(1)%logunit,F03) " vectors (",ns,") = ",trim(sdat%stream(ns)%stream_vectors)
write(sdat%stream(1)%logunit,F06) " src_mask(",ns,") = ",sdat%stream(ns)%src_mask_val
write(sdat%stream(1)%logunit,F06) " dst_mask(",ns,") = ",sdat%stream(ns)%dst_mask_val
write(sdat%stream(1)%logunit,F01) " "
end do
write(sdat%stream(1)%logunit,F90)
Expand Down
21 changes: 19 additions & 2 deletions streams/dshr_stream_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -131,6 +131,8 @@ module dshr_stream_mod
type(file_desc_t) :: currpioid ! current pio file desc
type(shr_stream_file_type) , allocatable :: file(:) ! filenames of stream data files (full pathname)
type(shr_stream_data_variable), allocatable :: varlist(:) ! stream variable names (on file and in model)
integer :: src_mask_val = 0 ! mask value for src mesh
integer :: dst_mask_val = 0 ! mask value for dst mesh
end type shr_stream_streamType

!----- parameters -----
Expand Down Expand Up @@ -445,7 +447,7 @@ subroutine shr_stream_init_from_inline(streamdat, &
stream_yearFirst, stream_yearLast, stream_yearAlign, &
stream_offset, stream_taxmode, stream_tintalgo, stream_dtlimit, &
stream_fldlistFile, stream_fldListModel, stream_fileNames, &
logunit, compname)
logunit, compname, stream_src_mask_val, stream_dst_mask_val)

! --------------------------------------------------------
! set values of stream datatype independent of a reading in a stream text file
Expand All @@ -472,6 +474,8 @@ subroutine shr_stream_init_from_inline(streamdat, &
character(*) ,intent(in) :: stream_filenames(:) ! stream data filenames (full pathnamesa)
integer ,intent(in) :: logunit ! stdout unit
character(len=*) ,intent(in) :: compname ! component name (e.g. ATM, OCN...)
integer ,optional, intent(in) :: stream_src_mask_val ! source mask value
integer ,optional, intent(in) :: stream_dst_mask_val ! destination mask value

! local variables
integer :: n
Expand Down Expand Up @@ -534,10 +538,15 @@ subroutine shr_stream_init_from_inline(streamdat, &

! Initialize logunit
streamdat(:)%logunit = logunit

! Get stream calendar
call shr_stream_getCalendar(streamdat(1), 1, calendar)
streamdat(1)%calendar = trim(calendar)

! Set source and destination mask
if (present(stream_src_mask_val)) streamdat(1)%src_mask_val = stream_src_mask_val
if (present(stream_dst_mask_val)) streamdat(1)%dst_mask_val = stream_dst_mask_val

! Initialize flag that stream has been set
streamdat(1)%init = .true.

Expand Down Expand Up @@ -571,6 +580,8 @@ subroutine shr_stream_init_from_esmfconfig(streamfilename, streamdat, logunit,
!! stream_data_files:
!! stream_data_variables:
!! stream_offset:
!! stream_src_mask:
!! stream_dst_mask:
!!---------------------------------------------------------------------

! input/output variables
Expand Down Expand Up @@ -606,7 +617,6 @@ subroutine shr_stream_init_from_esmfconfig(streamfilename, streamdat, logunit,
call ESMF_ConfigLoadFile(config=CF ,filename=trim(streamfilename), rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return


! get number of streams
nstrms = ESMF_ConfigGetLen(config=CF, label='stream_info:', rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
Expand Down Expand Up @@ -720,6 +730,13 @@ subroutine shr_stream_init_from_esmfconfig(streamfilename, streamdat, logunit,

call shr_stream_getCalendar(streamdat(i), 1, streamdat(i)%calendar)

! Get source and destination mask, 0 by default
call ESMF_ConfigGetAttribute(CF,value=streamdat(i)%src_mask_val,label="stream_src_mask"//mystrm//':', default=0, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return

call ESMF_ConfigGetAttribute(CF,value=streamdat(i)%dst_mask_val,label="stream_dst_mask"//mystrm//':', default=0, rc=rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return

! Error check
if (trim(streamdat(i)%taxmode) == shr_stream_taxis_extend .and. streamdat(i)%dtlimit < 1.e10) then
call shr_sys_abort(trim(subName)//" ERROR: if taxmode value is extend set dtlimit to 1.e30")
Expand Down

0 comments on commit 28cc73e

Please sign in to comment.