Skip to content

Commit

Permalink
Add run time info and upp (#678)
Browse files Browse the repository at this point in the history
* update missing value

* adding timing information

* add write_runtimelog option

* update upp and not include dycore updates that change results
  • Loading branch information
junwang-noaa authored Sep 7, 2023
1 parent 379ef21 commit a9fa26e
Show file tree
Hide file tree
Showing 4 changed files with 64 additions and 17 deletions.
41 changes: 37 additions & 4 deletions fv3_cap.F90
Original file line number Diff line number Diff line change
Expand Up @@ -70,11 +70,14 @@ module fv3atm_cap_mod
logical, allocatable :: is_moving_FB(:)

logical :: profile_memory = .true.
logical :: write_runtimelog = .false.
logical :: lprint = .false.

integer :: mype = -1
integer :: dbug = 0
integer :: frestart(999) = -1

real(kind=8) :: timere, timep2re
!-----------------------------------------------------------------------

contains
Expand Down Expand Up @@ -246,6 +249,11 @@ subroutine InitializeAdvertise(gcomp, rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
profile_memory = (trim(value)/="false")

call ESMF_AttributeGet(gcomp, name="RunTimeLog", value=value, defaultValue="false", &
convention="NUOPC", purpose="Instance", rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
write_runtimelog = (trim(value)=="true")

call ESMF_AttributeGet(gcomp, name="DumpFields", value=value, defaultValue="false", &
convention="NUOPC", purpose="Instance", rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
Expand Down Expand Up @@ -347,6 +355,7 @@ subroutine InitializeAdvertise(gcomp, rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return

first_kdt = 1
if( mype == 0) lprint = .true.
!
!#######################################################################
! set up fcst grid component
Expand Down Expand Up @@ -486,6 +495,7 @@ subroutine InitializeAdvertise(gcomp, rc)
enddo
k = k + wrttasks_per_group_from_parent
last_wrttask(i) = k - 1
if( mype == lead_wrttask(i) ) lprint = .true.
! if(mype==0)print *,'af wrtComp(i)=',i,'k=',k

! prepare name of the wrtComp(i)
Expand Down Expand Up @@ -971,8 +981,7 @@ subroutine InitializeAdvertise(gcomp, rc)

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

if(mype==0) print *,'in fv3_cap, aft import, export fields in atmos'
if(mype==0) print *,'in fv3_cap, init time=',MPI_Wtime()-timeis
if(write_runtimelog .and. lprint) print *,'in fv3_cap, init time=',MPI_Wtime()-timeis,mype
!-----------------------------------------------------------------------
!
end subroutine InitializeAdvertise
Expand All @@ -989,7 +998,10 @@ subroutine InitializeRealize(gcomp, rc)
type(ESMF_State) :: importState, exportState
integer :: urc

real(8) :: MPI_Wtime, timeirs

rc = ESMF_SUCCESS
timeirs = MPI_Wtime()

! query for importState and exportState
call NUOPC_ModelGet(gcomp, driverClock=clock, importState=importState, exportState=exportState, rc=rc)
Expand All @@ -1004,6 +1016,11 @@ subroutine InitializeRealize(gcomp, rc)

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

timere = 0.
timep2re = 0.

if(write_runtimelog .and. lprint) print *,'in fv3_cap, initirealz time=',MPI_Wtime()-timeirs,mype

end subroutine InitializeRealize

!-----------------------------------------------------------------------------
Expand All @@ -1012,10 +1029,13 @@ subroutine ModelAdvance(gcomp, rc)

type(ESMF_GridComp) :: gcomp
integer, intent(out) :: rc
real(kind=8) :: MPI_Wtime, timers

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

rc = ESMF_SUCCESS
timers = MPI_Wtime()
if(write_runtimelog .and. timere>0. .and. lprint) print *,'in fv3_cap, time between fv3 run step=', timers-timere,mype

if (profile_memory) call ESMF_VMLogMemInfo("Entering FV3 ModelAdvance: ")

Expand All @@ -1027,6 +1047,9 @@ subroutine ModelAdvance(gcomp, rc)

if (profile_memory) call ESMF_VMLogMemInfo("Leaving FV3 ModelAdvance: ")

timere = MPI_Wtime()
if(write_runtimelog .and. lprint) print *,'in fv3_cap, time in fv3 run step=', timere-timers, mype

end subroutine ModelAdvance

!-----------------------------------------------------------------------------
Expand All @@ -1041,10 +1064,13 @@ subroutine ModelAdvance_phase1(gcomp, rc)
logical :: fcstpe
character(len=*),parameter :: subname='(fv3_cap:ModelAdvance_phase1)'
character(240) :: msgString
real(kind=8) :: MPI_Wtime, timep1rs, timep1re

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

rc = ESMF_SUCCESS
timep1rs = MPI_Wtime()
if(write_runtimelog .and. timep2re>0. .and. lprint) print *,'in fv3_cap, time between fv3 run phase2 and phase1 ', timep1rs-timep2re,mype

if(profile_memory) call ESMF_VMLogMemInfo("Entering FV3 ModelAdvance_phase1: ")

Expand Down Expand Up @@ -1074,6 +1100,8 @@ subroutine ModelAdvance_phase1(gcomp, rc)
call diagnose_cplFields(gcomp, clock, fcstpe, cplprint_flag, dbug, 'import')
endif

timep1re = MPI_Wtime()
if(write_runtimelog .and. lprint) print *,'in fv3_cap,modeladvance phase1 time ', timep1re-timep1rs,mype
if (profile_memory) call ESMF_VMLogMemInfo("Leaving FV3 ModelAdvance_phase1: ")

end subroutine ModelAdvance_phase1
Expand All @@ -1100,9 +1128,12 @@ subroutine ModelAdvance_phase2(gcomp, rc)
type(ESMF_Clock) :: clock, clock_out
integer :: fieldCount

real(kind=8) :: MPI_Wtime, timep2rs

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

rc = ESMF_SUCCESS
timep2rs = MPI_Wtime()

if(profile_memory) call ESMF_VMLogMemInfo("Entering FV3 ModelAdvance_phase2: ")

Expand Down Expand Up @@ -1206,6 +1237,8 @@ subroutine ModelAdvance_phase2(gcomp, rc)
call diagnose_cplFields(gcomp, clock_out, fcstpe, cplprint_flag, dbug, 'export')
end if

timep2re = MPI_Wtime()
if(write_runtimelog .and. lprint) print *,'in fv3_cap,modeladvance phase2 time ', timep2re-timep2rs, mype
if(profile_memory) call ESMF_VMLogMemInfo("Leaving FV3 ModelAdvance_phase2: ")

end subroutine ModelAdvance_phase2
Expand Down Expand Up @@ -1380,8 +1413,8 @@ subroutine ModelFinalize(gcomp, rc)
!-----------------------------------------------------------------------------
!*** finialize forecast

timeffs = MPI_Wtime()
rc = ESMF_SUCCESS
timeffs = MPI_Wtime()
!
call ESMF_GridCompGet(gcomp,vm=vm,rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
Expand Down Expand Up @@ -1414,7 +1447,7 @@ subroutine ModelFinalize(gcomp, rc)
call ESMF_GridCompDestroy(fcstComp, rc=rc)
if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, line=__LINE__, file=__FILE__)) return
!
if(mype==0)print *,' wrt grid comp destroy time=',MPI_Wtime()-timeffs
if(write_runtimelog .and. lprint) print *,'in fv3_cap, finalize time=',MPI_Wtime()-timeffs, mype

end subroutine ModelFinalize
!
Expand Down
10 changes: 7 additions & 3 deletions io/module_wrt_grid_comp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2090,7 +2090,9 @@ subroutine wrt_run(wrt_comp, imp_state_write, exp_state_write,clock,rc)
if (mype == lead_write_task) then
!** write out inline post log file
open(newunit=nolog,file='log.atm.inlinepost.f'//trim(cfhour),form='FORMATTED')
write(nolog,"(' completed fv3atm fhour=',f10.3,2x,6(i4,2x))") nfhour, idate(1:6)
write(nolog,"('completed: fv3atm')")
write(nolog,"('forecast hour: ',f10.3)") nfhour
write(nolog,"('valid time: ',6(i4,2x))") wrt_int_state%fdate(1:6)
close(nolog)
endif
if (lprnt) then
Expand Down Expand Up @@ -2224,7 +2226,7 @@ subroutine wrt_run(wrt_comp, imp_state_write, exp_state_write,clock,rc)
endif
call mpi_bcast(kchunk3d(grid_id),1,mpi_integer,0,wrt_mpi_comm,rc)
endif
if (wrt_int_state%mype == 0) then
if (lprnt) then
print *,'ichunk2d,jchunk2d',ichunk2d(grid_id),jchunk2d(grid_id)
print *,'ichunk3d,jchunk3d,kchunk3d',ichunk3d(grid_id),jchunk3d(grid_id),kchunk3d(grid_id)
endif
Expand Down Expand Up @@ -2393,7 +2395,9 @@ subroutine wrt_run(wrt_comp, imp_state_write, exp_state_write,clock,rc)
if (out_phase == 1 .and. mype == lead_write_task) then
!** write out log file
open(newunit=nolog,file='log.atm.f'//trim(cfhour),form='FORMATTED')
write(nolog,"(' completed fv3atm fhour=',f10.3,2x,6(i4,2x))") nfhour, idate(1:6)
write(nolog,"('completed: fv3atm')")
write(nolog,"('forecast hour: ',f10.3)") nfhour
write(nolog,"('valid time: ',6(i4,2x))") wrt_int_state%fdate(1:6)
close(nolog)
endif
enddo two_phase_loop
Expand Down
28 changes: 19 additions & 9 deletions io/post_fv3.F90
Original file line number Diff line number Diff line change
Expand Up @@ -93,7 +93,7 @@ subroutine post_run_fv3(wrt_int_state,grid_id,mype,mpicomp,lead_write, &
its = wrt_int_state%out_grid_info(grid_id)%i_start !<-- Starting I of this write task's subsection
ite = wrt_int_state%out_grid_info(grid_id)%i_end !<-- Ending I of this write task's subsection

if(mype==0) print *,'in post_run,jts=',jts,'jte=',jte,'nwtpg=',nwtpg, &
if(mype==0) print *,'in post_run, numx=',numx,'its=',its,'ite=',ite,'nwtpg=',nwtpg, &
'jts=',jts,'jte=',jte,'maptype=',maptype,'wrt_int_state%FBCount=',wrt_int_state%FBCount

!
Expand Down Expand Up @@ -508,7 +508,7 @@ subroutine set_postvars_fv3(wrt_int_state,grid_id,mype,mpicomp)
use vrbls3d, only: t, q, uh, vh, wh, alpint, dpres, zint, zmid, o3, &
qqr, qqs, cwm, qqi, qqw, qqg, omga, cfr, pmid, &
q2, rlwtt, rswtt, tcucn, tcucns, train, el_pbl, &
pint, exch_h, ref_10cm, qqni, qqnr, qqnwfa, &
pint, exch_h, ref_10cm, qqni, qqnr, qqnw, qqnwfa, &
qqnifa, effri, effrl, effrs, aextc55, taod5503d, &
duem, dusd, dudp, duwt, dusv, ssem, sssd, ssdp, &
sswt, sssv, bcem, bcsd, bcdp, bcwt, bcsv, ocem, &
Expand Down Expand Up @@ -3642,8 +3642,8 @@ subroutine set_postvars_fv3(wrt_int_state,grid_id,mype,mpicomp)
endif

if(imp_physics == 8) then
! model level rain number
if(trim(fieldname)=='ncrain') then
! model level rain water number
if(trim(fieldname)=='rain_nc') then
!$omp parallel do default(none) private(i,j,l) shared(lm,jsta,jend,ista,iend,qqnr,arrayr43d,spval,fillvalue)
do l=1,lm
do j=jsta,jend
Expand All @@ -3655,8 +3655,8 @@ subroutine set_postvars_fv3(wrt_int_state,grid_id,mype,mpicomp)
enddo
endif

! model level rain number
if(trim(fieldname)=='ncice') then
! model level cloud ice number
if(trim(fieldname)=='nicp') then
!$omp parallel do default(none) private(i,j,l) shared(lm,jsta,jend,ista,iend,qqni,arrayr43d,spval,fillvalue)
do l=1,lm
do j=jsta,jend
Expand All @@ -3668,6 +3668,19 @@ subroutine set_postvars_fv3(wrt_int_state,grid_id,mype,mpicomp)
enddo
endif

! model level cloud water number
if(trim(fieldname)=='water_nc') then
!$omp parallel do default(none) private(i,j,l) shared(lm,jsta,jend,ista,iend,qqnw,arrayr43d,spval,fillvalue)
do l=1,lm
do j=jsta,jend
do i=ista, iend
qqnw(i,j,l)=arrayr43d(i,j,l)
if(abs(arrayr43d(i,j,l)-fillvalue)<small) qqnw(i,j,l) = spval
enddo
enddo
enddo
endif

! model level rain number
if(trim(fieldname)=='nwfa') then
!$omp parallel do default(none) private(i,j,l) shared(lm,jsta,jend,ista,iend,qqnwfa,arrayr43d,spval,fillvalue)
Expand Down Expand Up @@ -3699,7 +3712,6 @@ subroutine set_postvars_fv3(wrt_int_state,grid_id,mype,mpicomp)
endif !if(imp_physics == 11 .or. imp_physics == 8) then

! model level ref3d
if(modelname == 'GFS') then
if(trim(fieldname)=='ref3D') then
!$omp parallel do default(none) private(i,j,l) shared(lm,jsta,jend,ista,iend,ref_10cm,arrayr43d,fillvalue,spval)
do l=1,lm
Expand All @@ -3712,7 +3724,6 @@ subroutine set_postvars_fv3(wrt_int_state,grid_id,mype,mpicomp)
enddo
endif
! if(mype==0) print *,'in gfs_post, get ref_10cm=',maxval(ref_10cm), minval(ref_10cm)
else
if(trim(fieldname)=='refl_10cm') then
!$omp parallel do default(none) private(i,j,l) shared(lm,jsta,jend,ista,iend,ref_10cm,arrayr43d,fillvalue,spval)
do l=1,lm
Expand All @@ -3725,7 +3736,6 @@ subroutine set_postvars_fv3(wrt_int_state,grid_id,mype,mpicomp)
enddo
! if(mype==0) print *,'in gfs_post, get ref_10cm=',maxval(ref_10cm), minval(ref_10cm),'ibdl=',ibdl
endif
endif

! model level tke
if(trim(fieldname)=='qke') then
Expand Down
2 changes: 1 addition & 1 deletion upp
Submodule upp updated 49 files
+1 −125 docs/Doxyfile.in
+72 −0 modulefiles/hercules.lua
+2 −2 parm/README.make_flatfile
+0 −3,447 parm/fv3lam.xml
+0 −5,739 parm/fv3lam_post_avblflds.xml
+27 −0 parm/fv3lam_rrfs.xml
+32 −41 parm/makefile
+0 −1,254 parm/params_grib2_tbl_new_dtc
+2 −2 parm/post_avblflds.xml
+0 −959 parm/postcntrl.xml
+30 −13 parm/postcntrl_gefs.xml
+0 −465 parm/postcntrl_gefs_anl.xml
+30 −13 parm/postcntrl_gefs_f00.xml
+0 −695 parm/postcntrl_wrf.xml
+0 −2,905 parm/postxconfig-NT-GEFS-ANL.txt
+113 −39 parm/postxconfig-NT-GEFS-F00.txt
+113 −39 parm/postxconfig-NT-GEFS.txt
+0 −3,644 parm/postxconfig-NT-WRF.txt
+0 −18,091 parm/postxconfig-NT-fv3lam.txt
+114 −3 parm/postxconfig-NT-fv3lam_rrfs.txt
+0 −3,681 parm/postxconfig-NT.txt
+7 −16 sorc/ncep_post.fd/CALHEL2.f
+7 −14 sorc/ncep_post.fd/CALHEL3.f
+46 −14 sorc/ncep_post.fd/CALMICT.f
+8 −3 sorc/ncep_post.fd/CALPBL.f
+9 −4 sorc/ncep_post.fd/CALPBLREGIME.f
+8 −0 sorc/ncep_post.fd/CALPW.f
+40 −1 sorc/ncep_post.fd/CALRAD_WCLOUD_newcrtm.f
+12 −2 sorc/ncep_post.fd/CLDRAD.f
+7 −1 sorc/ncep_post.fd/COLLECT.f
+11 −0 sorc/ncep_post.fd/COLLECT_LOC.f
+217 −101 sorc/ncep_post.fd/CTLBLK.f
+12 −0 sorc/ncep_post.fd/EXCH.f
+15 −1 sorc/ncep_post.fd/FDLVL.f
+40 −7 sorc/ncep_post.fd/GFIP3.f
+34 −11 sorc/ncep_post.fd/GPVS.f
+32 −9 sorc/ncep_post.fd/GRIDSPEC.f
+49 −2 sorc/ncep_post.fd/INITPOST_GFS_NEMS_MPIIO.f
+9 −2 sorc/ncep_post.fd/INITPOST_NEMS.f
+62 −10 sorc/ncep_post.fd/INITPOST_NETCDF.f
+7 −2 sorc/ncep_post.fd/MDL2P.f
+23 −12 sorc/ncep_post.fd/MPI_FIRST.f
+127 −22 sorc/ncep_post.fd/PMICRPH.f
+9 −0 sorc/ncep_post.fd/PROCESS.f
+18 −4 sorc/ncep_post.fd/SELECT_CHANNELS.f
+3 −3 sorc/ncep_post.fd/SMOOTH.f
+5 −1 sorc/ncep_post.fd/WRFPOST.f
+31 −10 sorc/ncep_post.fd/xml_perl_data.f
+5 −34 tests/detect_machine.sh

0 comments on commit a9fa26e

Please sign in to comment.