Skip to content

Commit

Permalink
Merge branch 'feature/timestamps' into feature/domb4b_update
Browse files Browse the repository at this point in the history
  • Loading branch information
DeniseWorthen committed Mar 26, 2020
2 parents 6f4cb56 + b1d9037 commit 03bdc3b
Show file tree
Hide file tree
Showing 6 changed files with 59 additions and 40 deletions.
4 changes: 2 additions & 2 deletions atmos_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2044,7 +2044,7 @@ subroutine setup_exportdata (rc)

if (IPD_Control%cplflx) then
! MEAN Zonal compt of momentum flux (N/m**2)
idx = queryfieldlist(exportFieldsList,'mean_zonal_moment_flx')
idx = queryfieldlist(exportFieldsList,'mean_zonal_moment_flx_atm')
if (idx > 0 ) then
!$omp parallel do default(shared) private(i,j,nb,ix)
do j=jsc,jec
Expand All @@ -2057,7 +2057,7 @@ subroutine setup_exportdata (rc)
endif

! MEAN Merid compt of momentum flux (N/m**2)
idx = queryfieldlist(exportFieldsList,'mean_merid_moment_flx')
idx = queryfieldlist(exportFieldsList,'mean_merid_moment_flx_atm')
if (idx > 0 ) then
!$omp parallel do default(shared) private(i,j,nb,ix)
do j=jsc,jec
Expand Down
34 changes: 21 additions & 13 deletions cpl/module_cap_cpl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -214,49 +214,57 @@ end subroutine realizeConnectedCplFields
!-----------------------------------------------------------------------------

subroutine Dump_cplFields(gcomp, importState, exportstate, clock_fv3, &
statewrite_flag, timeslice)
statewrite_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 :: timeslice
character(len=*), intent(in) :: state_tag !< Import or export.
character(len=*), intent(in) :: timestr !< Import or export.
integer :: timeslice = 1
!
type(ESMF_Time) :: currTime
type(ESMF_TimeInterval) :: timeStep

character(len=160) :: nuopcMsg
character(len=160) :: filename
integer :: rc
!
call ESMF_ClockPrint(clock_fv3, options="currTime", &
preString="leaving FV3_ADVANCE with clock_fv3 current: ", &
unit=nuopcMsg)
call ESMF_LogWrite(nuopcMsg, ESMF_LOGMSG_INFO)
!call ESMF_LogWrite(nuopcMsg, ESMF_LOGMSG_INFO)
call ESMF_ClockPrint(clock_fv3, options="startTime", &
preString="leaving FV3_ADVANCE with clock_fv3 start: ", &
unit=nuopcMsg)
call ESMF_LogWrite(nuopcMsg, ESMF_LOGMSG_INFO)
!call ESMF_LogWrite(nuopcMsg, ESMF_LOGMSG_INFO)
call ESMF_ClockPrint(clock_fv3, options="stopTime", &
preString="leaving FV3_ADVANCE with clock_fv3 stop: ", &
unit=nuopcMsg)
call ESMF_LogWrite(nuopcMsg, ESMF_LOGMSG_INFO)
!call ESMF_LogWrite(nuopcMsg, ESMF_LOGMSG_INFO)

! Dumping Fields out
if (statewrite_flag) then
timeslice = timeslice + 1
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,i6.6)') 'fv3_cap_import_',timeslice
call State_RWFields_tiles(importState,trim(filename), timeslice, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
write(filename,'(a,a,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

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,i6.6)') 'fv3_cap_export_',timeslice
call State_RWFields_tiles(exportState,trim(filename), timeslice, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
write(filename,'(a,a,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
endif
!
end subroutine Dump_cplFields
Expand Down
4 changes: 2 additions & 2 deletions cpl/module_cplfields.F90
Original file line number Diff line number Diff line change
Expand Up @@ -39,8 +39,8 @@ module module_cplfields
"vegetation_type ", &
"inst_vegetation_area_frac ", &
"inst_surface_roughness ", &
"mean_zonal_moment_flx ", &
"mean_merid_moment_flx ", &
"mean_zonal_moment_flx_atm ", &
"mean_merid_moment_flx_atm ", &
"mean_sensi_heat_flx ", &
"mean_laten_heat_flx ", &
"mean_down_lw_flx ", &
Expand Down
15 changes: 13 additions & 2 deletions fv3_cap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -703,7 +703,7 @@ subroutine InitializeAdvertise(gcomp, importState, exportState, clock, rc)
call ESMF_StateGet(wrtState(i), &
itemName="mirror_"//trim(fcstItemNameList(j)), &
fieldbundle=wrtFB(j,i), rc=rc)
if(mype == 0) print *,'af get wrtfb=',"mirror_"//trim(fcstItemNameList(j)),'rc=',rc
if(mype == 0) print *,'af get wrtfb=',"mirror_"//trim(fcstItemNameList(j)),' rc=',rc
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

! determine regridmethod
Expand Down Expand Up @@ -949,6 +949,7 @@ subroutine ModelAdvance(gcomp, rc)
logical :: isAlarmEnabled, isAlarmRinging, lalarm, reconcileFlag
character(len=*),parameter :: subname='(fv3_cap:ModelAdvance)'
character(240) :: msgString
character(240) :: import_timestr, export_timestr
!jw debug
character(ESMF_MAXSTR) :: name
integer :: mype,date(6), fieldcount, fcst_nfld
Expand Down Expand Up @@ -1027,6 +1028,10 @@ subroutine ModelAdvance(gcomp, rc)
! if(mype==0) print *,'af clock,timestep date=',date
! if(mype==lead_wrttask(1)) print *,'on wrt lead,af clock,timestep date=',date
!
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 @@ -1046,6 +1051,12 @@ subroutine ModelAdvance(gcomp, rc)
phase=1, userRc=urc, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

if ( cpl ) then
! assign import_data called during phase=1
call Dump_cplFields(gcomp, importState, exportstate, clock_fv3, &
cplprint_flag, 'import', import_timestr)
endif

if (ESMF_LogFoundError(rcToCheck=urc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__, rcToReturn=rc)) return

call ESMF_GridCompRun(fcstComp, exportState=fcstState, clock=clock_fv3, &
Expand Down Expand Up @@ -1164,7 +1175,7 @@ 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, timeslice)
cplprint_flag, 'export', export_timestr)
endif

if (mype==0) print *,'fv3_cap,end integrate,na=',na,' time=',mpi_wtime()- timeri
Expand Down
38 changes: 19 additions & 19 deletions gfsphysics/physics/ugwp_driver_v0.f
Original file line number Diff line number Diff line change
Expand Up @@ -90,13 +90,13 @@ subroutine cires_ugwp_driver_v0(me, master,
! switches for GW-effects: pogw=1 (OGWs) pngw=1 (NGWs) pked=1 (eddy mixing)
!
if (me == master .and. kdt < 2) then
print *
write(6,*) 'FV3GFS execute ugwp_driver_v0 '
! print *
! write(6,*) 'FV3GFS execute ugwp_driver_v0 '
! write(6,*) 'FV3GFS execute ugwp_driver_v0 nmtvr=', nmtvr
write(6,*) ' COORDE EXPER pogw = ' , pogw
write(6,*) ' COORDE EXPER pgwd = ' , pgwd
write(6,*) ' COORDE EXPER pgwd4 = ', pgwd4
print *
! write(6,*) ' COORDE EXPER pogw = ' , pogw
! write(6,*) ' COORDE EXPER pgwd = ' , pgwd
! write(6,*) ' COORDE EXPER pgwd4 = ', pgwd4
! print *
endif

do i=1,im
Expand All @@ -119,10 +119,10 @@ subroutine cires_ugwp_driver_v0(me, master,
& du3dt_mtb, du3dt_ogw, du3dt_tms)
!
if (me == master .and. kdt < 2) then
print *
write(6,*) 'FV3GFS finished gwdps_v0 in ugwp_driver_v0 '
print *
endif
!print *
!write(6,*) 'FV3GFS finished gwdps_v0 in ugwp_driver_v0 '
!print *
endif
else ! calling old GFS gravity wave drag as is
do k=1,levs
do i=1,im
Expand Down Expand Up @@ -191,10 +191,10 @@ subroutine cires_ugwp_driver_v0(me, master,
& tau_ngw, me, master, kdt)

if (me == master .and. kdt < 2) then
print *
write(6,*)'FV3GFS finished fv3_ugwp_v0 in ugwp_driver_v0 '
write(6,*) ' non-stationary GWs with GMAO/MERRA GW-forcing '
print *
!print *
!write(6,*)'FV3GFS finished fv3_ugwp_v0 in ugwp_driver_v0 '
!write(6,*) ' non-stationary GWs with GMAO/MERRA GW-forcing '
!print *
endif
do k=1,levs
do i=1,im
Expand Down Expand Up @@ -1831,12 +1831,12 @@ subroutine fv3_ugwp_solv2_v0(klon, klev, dtime,
!---------------------------------------------------------------------------
!
if (kdt == 1 .and. mpi_id == master) then
print *, 'vgw done '
!print *, 'vgw done '
!
print *, maxval(pdudt)*86400., minval(pdudt)*86400, 'vgw ax'
print *, maxval(pdvdt)*86400., minval(pdvdt)*86400, 'vgw ay'
print *, maxval(dked)*1., minval(dked)*1, 'vgw keddy m2/sec'
print *, maxval(pdtdt)*86400., minval(pdtdt)*86400,'vgw eps'
!print *, maxval(pdudt)*86400., minval(pdudt)*86400, 'vgw ax'
!print *, maxval(pdvdt)*86400., minval(pdvdt)*86400, 'vgw ay'
!print *, maxval(dked)*1., minval(dked)*1, 'vgw keddy m2/sec'
!print *, maxval(pdtdt)*86400., minval(pdtdt)*86400,'vgw eps'
!
! print *, ' ugwp -heating rates '
endif
Expand Down
4 changes: 2 additions & 2 deletions module_fcst_grid_comp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -532,8 +532,8 @@ subroutine fcst_initialize(fcst_comp, importState, exportState, clock, rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
! print *,'call addLsmask2grid after fcstGrid, rc=',rc
if( cplprint_flag ) then
call ESMF_GridWriteVTK(fcstGrid, staggerloc=ESMF_STAGGERLOC_CENTER, &
filename='fv3cap_fv3Grid', rc=rc)
!call ESMF_GridWriteVTK(fcstgrid, staggerloc=ESMF_STAGGERLOC_CENTER, &
! filename='fv3cap_fv3Grid', rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
endif
endif
Expand Down

0 comments on commit 03bdc3b

Please sign in to comment.