Skip to content

Commit

Permalink
support one step s2s cold start (#168)
Browse files Browse the repository at this point in the history
* set up dycore_data at atmos_init
* fix syntax error in atmos_model.F90
* put in initial fields in fv3 export fields at init
* add state_diagnose from Denise
* fix state diagnose on write tasks


Co-authored-by: Jun Wang <junwang-noaa@users.noreply.github.com>
Co-authored-by: Denise.Worthen <denise.worthen@noaa.gov>
  • Loading branch information
3 people committed Sep 16, 2020
1 parent 3bceaff commit 6bc61df
Show file tree
Hide file tree
Showing 4 changed files with 154 additions and 34 deletions.
17 changes: 13 additions & 4 deletions atmos_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -743,6 +743,15 @@ subroutine atmos_model_init (Atmos, Time_init, Time, Time_step)
fv3Clock = mpp_clock_id( 'FV3 Dycore ', flags=clock_flag_default, grain=CLOCK_COMPONENT )
endif

!--- get bottom layer data from dynamical core for coupling
call atmosphere_get_bottom_layer (Atm_block, DYCORE_Data)

!if in coupled mode, set up coupled fields
if (IPD_Control%cplflx .or. IPD_Control%cplwav) then
if (mpp_pe() == mpp_root_pe()) print *,'COUPLING: IPD layer'
call setup_exportdata(ierr)
endif

#ifdef CCPP
! Set flag for first time step of time integration
IPD_Control%first_time_step = .true.
Expand Down Expand Up @@ -911,8 +920,6 @@ subroutine update_atmos_model_state (Atmos)

!if in coupled mode, set up coupled fields
if (IPD_Control%cplflx .or. IPD_Control%cplwav) then
! if (mpp_pe() == mpp_root_pe()) print *,'COUPLING: IPD layer'
!jw call setup_exportdata(IPD_Control, IPD_Data, Atm_block)
call setup_exportdata(rc)
endif

Expand Down Expand Up @@ -2016,7 +2023,7 @@ subroutine setup_exportdata (rc)
integer :: j, i, ix, nb, isc, iec, jsc, jec, idx
real(IPD_kind_phys) :: rtime, rtimek
!
! if (mpp_pe() == mpp_root_pe()) print *,'enter setup_exportdata'
if (mpp_pe() == mpp_root_pe()) print *,'enter setup_exportdata'

isc = IPD_control%isc
iec = IPD_control%isc+IPD_control%nx-1
Expand Down Expand Up @@ -2579,6 +2586,7 @@ subroutine setup_exportdata (rc)

! bottom layer temperature (t)
idx = queryfieldlist(exportFieldsList,'inst_temp_height_lowest')
if (mpp_pe() == mpp_root_pe()) print *,'cpl, in get inst_temp_height_lowest'
if (idx > 0 ) then
!$omp parallel do default(shared) private(i,j,nb,ix)
do j=jsc,jec
Expand All @@ -2592,6 +2600,7 @@ subroutine setup_exportdata (rc)
endif
enddo
enddo
if (mpp_pe() == mpp_root_pe()) print *,'cpl, in get inst_temp_height_lowest=',exportData(isc,jsc,idx)
endif

! bottom layer specific humidity (q)
Expand Down Expand Up @@ -2728,7 +2737,7 @@ subroutine setup_exportdata (rc)
IPD_Data(nb)%coupling%snow_cpl(ix) = zero
enddo
enddo
if (mpp_pe() == mpp_root_pe()) print *,'zeroing coupling fields at kdt= ',IPD_Control%kdt
if (mpp_pe() == mpp_root_pe()) print *,'zeroing coupling accumulated fields at kdt= ',IPD_Control%kdt
endif !cplflx
! if (mpp_pe() == mpp_root_pe()) print *,'end of setup_exportdata'

Expand Down
123 changes: 103 additions & 20 deletions cpl/module_cap_cpl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ module module_cap_cpl
public clock_cplIntval
public realizeConnectedInternCplField
public realizeConnectedCplFields
public Dump_cplFields
public diagnose_cplFields
!
contains

Expand Down Expand Up @@ -193,9 +193,11 @@ subroutine realizeConnectedCplFields(state, grid,
end select
call NUOPC_Realize(state, field=field, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

! -- zero out field
call ESMF_FieldFill(field, dataFillScheme="const", const1=0._ESMF_KIND_R8, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

! -- save field
fieldList(item) = field
call ESMF_LogWrite('realizeConnectedCplFields '//trim(state_tag)//' Field '//trim(fieldNames(item)) &
Expand All @@ -213,13 +215,14 @@ end subroutine realizeConnectedCplFields

!-----------------------------------------------------------------------------

subroutine Dump_cplFields(gcomp, importState, exportstate, clock_fv3, &
statewrite_flag, state_tag, timestr)
subroutine diagnose_cplFields(gcomp, importState, exportstate, clock_fv3, &
statewrite_flag, stdiagnose_flag, state_tag, timestr)

type(ESMF_GridComp), intent(in) :: gcomp
type(ESMF_State) :: importState, exportstate
type(ESMF_Clock),intent(in) :: clock_fv3
logical, intent(in) :: statewrite_flag
integer, intent(in) :: stdiagnose_flag
character(len=*), intent(in) :: state_tag !< Import or export.
character(len=*), intent(in) :: timestr !< Import or export.
integer :: timeslice = 1
Expand All @@ -241,32 +244,39 @@ subroutine Dump_cplFields(gcomp, importState, exportstate, clock_fv3, &
unit=nuopcMsg)
! call ESMF_LogWrite(nuopcMsg, ESMF_LOGMSG_INFO)

! Dumping Fields out
if (statewrite_flag) then
if(trim(state_tag) .eq. 'import')then
call ESMF_GridCompGet(gcomp, importState=importState, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

if(trim(state_tag) .eq. 'import')then
call ESMF_GridCompGet(gcomp, importState=importState, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
! replace with tiled field dumps
!call ESMFPP_RegridWriteState(importState, "fv3_cap_import_", timeslice, rc=rc)
write(filename,'(a,a,a)') 'fv3_cap_import_'//trim(timestr)//'_'
if(stdiagnose_flag > 0)then
call state_diagnose(importState, ':IS', rc=rc)
end if

! Dump Fields out
if (statewrite_flag) then
write(filename,'(A)') 'fv3_cap_import_'//trim(timestr)//'_'
call State_RWFields_tiles(importState,trim(filename), timeslice, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
end if
end if

if(trim(state_tag) .eq. 'export')then
call ESMF_GridCompGet(gcomp, exportState=exportState, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
! replace with tiled field dumps
!call ESMFPP_RegridWriteState(exportState, "fv3_cap_export_", timeslice, rc=rc)
write(filename,'(a,a,a)') 'fv3_cap_export_'//trim(timestr)//'_'
if(trim(state_tag) .eq. 'export')then
call ESMF_GridCompGet(gcomp, exportState=exportState, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

if(stdiagnose_flag > 0)then
call state_diagnose(exportState, ':ES', rc=rc)
end if

! Dump Fields out
if (statewrite_flag) then
write(filename,'(A)') 'fv3_cap_export_'//trim(timestr)//'_'
call State_RWFields_tiles(exportState,trim(filename), timeslice, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
end if
end if

endif
!
end subroutine Dump_cplFields
end subroutine diagnose_cplFields

!-----------------------------------------------------------------------------

Expand Down Expand Up @@ -457,4 +467,77 @@ end subroutine State_RWFields_tiles

!-----------------------------------------------------------------------------

subroutine state_diagnose(State,string, rc)
! ----------------------------------------------
! Diagnose status of state
! ----------------------------------------------
type(ESMF_State), intent(inout) :: State
character(len=*), intent(in), optional :: string
integer, intent(out), optional :: rc

! local variables
integer :: i,j,n
integer :: itemCount
character(len=64) ,pointer :: itemNameList(:)
character(len=64) :: lstring
character(len=256) :: tmpstr

type(ESMF_Field) :: lfield
type(ESMF_StateItem_Flag) :: itemType
real(ESMF_KIND_R8), pointer :: dataPtr2d(:,:)
real(ESMF_KIND_R8), pointer :: dataPtr3d(:,:,:)
integer :: lrc, dimCount
character(len=*),parameter :: subname='(FV3: state_diagnose)'

lstring = ''
if (present(string)) then
lstring = trim(string)
endif

call ESMF_LogWrite(subname//' called', ESMF_LOGMSG_INFO)

call ESMF_StateGet(State, itemCount=itemCount, rc=lrc)
if (ESMF_LogFoundError(rcToCheck=lrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
allocate(itemNameList(itemCount))

call ESMF_StateGet(State, itemNameList=itemNameList, rc=lrc)
if (ESMF_LogFoundError(rcToCheck=lrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

do n = 1, itemCount
call ESMF_StateGet(State, itemName=trim(itemNameList(n)), itemType=itemType, rc=lrc)
if (ESMF_LogFoundError(rcToCheck=lrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

if(itemType == ESMF_STATEITEM_FIELD)then
call ESMF_StateGet(State, itemName=trim(itemNameList(n)), field=lfield, rc=lrc)
if (ESMF_LogFoundError(rcToCheck=lrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

call ESMF_FieldGet(lfield, dimCount=dimcount, rc=lrc)
if (ESMF_LogFoundError(rcToCheck=lrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

if(dimcount == 2)then
call ESMF_FieldGet(lfield, farrayPtr=dataPtr2d, rc=lrc)
if (ESMF_LogFoundError(rcToCheck=lrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

write(tmpstr,'(A,3g14.7)') trim(subname)//' '//trim(lstring)//':'//trim(itemNameList(n))//' ', &
minval(dataPtr2d),maxval(dataPtr2d),sum(dataPtr2d)
call ESMF_LogWrite(trim(tmpstr), ESMF_LOGMSG_INFO, rc=lrc)
else
call ESMF_FieldGet(lfield, farrayPtr=dataPtr3d, rc=lrc)
if (ESMF_LogFoundError(rcToCheck=lrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

write(tmpstr,'(A,3g14.7)') trim(subname)//' '//trim(lstring)//':'//trim(itemNameList(n))//' ', &
minval(dataPtr3d),maxval(dataPtr3d),sum(dataPtr3d)
call ESMF_LogWrite(trim(tmpstr), ESMF_LOGMSG_INFO, rc=lrc)
end if
end if
enddo
deallocate(itemNameList)

if (present(rc)) rc = lrc
call ESMF_LogWrite(subname//' exit', ESMF_LOGMSG_INFO)

end subroutine state_diagnose

!-----------------------------------------------------------------------------

end module module_cap_cpl
4 changes: 3 additions & 1 deletion cpl/module_cplfields.F90
Original file line number Diff line number Diff line change
Expand Up @@ -201,6 +201,7 @@ subroutine fillExportFields(data_a2oi, rc)
integer :: n,dimCount
logical :: isCreated
type(ESMF_TypeKind_Flag) :: datatype
character(len=ESMF_MAXSTR) :: fieldName
real(kind=ESMF_KIND_R4), dimension(:,:), pointer :: datar42d
real(kind=ESMF_KIND_R8), dimension(:,:), pointer :: datar82d

Expand All @@ -212,8 +213,9 @@ subroutine fillExportFields(data_a2oi, rc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__, rcToReturn=rc)) return
if (isCreated) then
! set data
call ESMF_FieldGet(exportFields(n), dimCount=dimCount, typekind=datatype, rc=localrc)
call ESMF_FieldGet(exportFields(n), name=fieldname, dimCount=dimCount, typekind=datatype, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__, rcToReturn=rc)) return
!print *,'in fillExportFields, field created n=',n,size(exportFields),'name=', trim(fieldname)
if ( datatype == ESMF_TYPEKIND_R8) then
if ( dimCount == 2) then
call ESMF_FieldGet(exportFields(n),farrayPtr=datar82d,localDE=0, rc=localrc)
Expand Down
44 changes: 35 additions & 9 deletions fv3_cap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -60,9 +60,10 @@ module fv3gfs_cap_mod
nImportFields, importFields, &
importFieldsList, importFieldTypes, &
importFieldShare, importFieldsValid, &
queryFieldList
queryFieldList, fillExportFields, &
exportData
use module_cap_cpl, only: realizeConnectedCplFields, &
clock_cplIntval, Dump_cplFields
clock_cplIntval, diagnose_cplFields


implicit none
Expand Down Expand Up @@ -92,6 +93,7 @@ module fv3gfs_cap_mod
character(len=160) :: nuopcMsg
integer :: timeslice = 0
integer :: fcstmype
integer :: dbug = 0

!-----------------------------------------------------------------------

Expand Down Expand Up @@ -188,7 +190,7 @@ subroutine InitializeP0(gcomp, importState, exportState, clock, rc)

character(len=10) :: value
character(240) :: msgString

logical :: isPresent, isSet
character(len=*),parameter :: subname='(fv3gfs_cap:InitializeP0)'

rc = ESMF_SUCCESS
Expand All @@ -211,6 +213,15 @@ subroutine InitializeP0(gcomp, importState, exportState, clock, rc)
write(msgString,'(A,l6)') trim(subname)//' cplprint_flag = ',cplprint_flag
call ESMF_LogWrite(trim(msgString), ESMF_LOGMSG_INFO, rc=rc)

! Read in cap debug flag
call NUOPC_CompAttributeGet(gcomp, name='dbug_flag', value=value, isPresent=isPresent, isSet=isSet, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
if (isPresent .and. isSet) then
read(value,*) dbug
end if
write(msgString,'(A,i6)') trim(subname)//' dbug = ',dbug
call ESMF_LogWrite(trim(msgString), ESMF_LOGMSG_INFO, rc=rc)

end subroutine

!-----------------------------------------------------------------------------
Expand Down Expand Up @@ -549,6 +560,7 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
rsthour = CurrTime - StartTime
first_kdt = nint(rsthour/timeStep) + 1
endif

!
!#######################################################################
! set up fcst grid component
Expand All @@ -560,7 +572,11 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
! create fcst grid component

fcstpe = .false.
num_pes_fcst = petcount - write_groups * wrttasks_per_group
if( quilting ) then
num_pes_fcst = petcount - write_groups * wrttasks_per_group
else
num_pes_fcst = petcount
endif
allocate(fcstPetList(num_pes_fcst))
do j=1, num_pes_fcst
fcstPetList(j) = j - 1
Expand Down Expand Up @@ -937,6 +953,8 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
importFields, rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
end if
!jw
call fillExportFields(exportData)
endif

end subroutine InitializeRealize
Expand Down Expand Up @@ -1042,6 +1060,7 @@ subroutine ModelAdvance(gcomp, rc)
call ESMF_ClockGet(clock_fv3, currTime=currTime, timeStep=timeStep, rc=rc)
call ESMF_TimeGet(currTime, timestring=import_timestr, rc=rc)
call ESMF_TimeGet(currTime+timestep, timestring=export_timestr, rc=rc)

!
!-----------------------------------------------------------------------------
!*** integration loop
Expand All @@ -1066,8 +1085,12 @@ subroutine ModelAdvance(gcomp, rc)

if ( cpl ) then
! assign import_data called during phase=1
call Dump_cplFields(gcomp, importState, exportstate, clock_fv3, &
cplprint_flag, 'import', import_timestr)
if( dbug > 0 .or. cplprint_flag ) then
if( mype < num_pes_fcst ) then
call diagnose_cplFields(gcomp, importState, exportstate, clock_fv3, &
cplprint_flag, dbug, 'import', import_timestr)
endif
endif
endif

call ESMF_GridCompRun(fcstComp, exportState=fcstState, clock=clock_fv3, &
Expand Down Expand Up @@ -1191,8 +1214,12 @@ subroutine ModelAdvance(gcomp, rc)
!
!jw for coupled, check clock and dump import and export state
if ( cpl ) then
call Dump_cplFields(gcomp, importState, exportstate, clock_fv3, &
cplprint_flag, 'export', export_timestr)
if( dbug > 0 .or. cplprint_flag ) then
if( mype < num_pes_fcst ) then
call diagnose_cplFields(gcomp, importState, exportstate, clock_fv3, &
cplprint_flag, dbug, 'export', export_timestr)
endif
end if
endif

if (mype==0) print *,'fv3_cap,end integrate,na=',na,' time=',mpi_wtime()- timeri
Expand Down Expand Up @@ -1660,7 +1687,6 @@ subroutine atmos_model_finalize(gcomp, rc)


end subroutine atmos_model_finalize

!#######################################################################
!
!
Expand Down

0 comments on commit 6bc61df

Please sign in to comment.