Skip to content

Commit

Permalink
Merge pull request #105 from grantfirl/ufs-dev-PR98
Browse files Browse the repository at this point in the history
UFS-dev PR#98
  • Loading branch information
grantfirl authored Jan 24, 2024
2 parents 84245dd + 6e75cfc commit c79c072
Show file tree
Hide file tree
Showing 18 changed files with 333 additions and 89 deletions.
2 changes: 1 addition & 1 deletion atmos_cubed_sphere
2 changes: 1 addition & 1 deletion atmos_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -748,7 +748,7 @@ subroutine atmos_model_init (Atmos, Time_init, Time, Time_step)
call fv3atm_restart_read (GFS_data, GFS_restart_var, Atm_block, GFS_control, Atmos%domain_for_read, &
Atm(mygrid)%flagstruct%warm_start, ignore_rst_cksum)
if(GFS_control%do_ca .and. Atm(mygrid)%flagstruct%warm_start)then
call read_ca_restart (Atmos%domain,GFS_control%ncells,GFS_control%nca,GFS_control%ncells_g,GFS_control%nca_g)
call read_ca_restart (Atmos%domain,3,GFS_control%ncells,GFS_control%nca,GFS_control%ncells_g,GFS_control%nca_g)
endif
! Populate the GFS_data%Statein container with the prognostic state
! in Atm_block, which contains the initial conditions/restart data.
Expand Down
13 changes: 11 additions & 2 deletions ccpp/data/GFS_typedefs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -612,6 +612,7 @@ module GFS_typedefs
real (kind=kind_phys), pointer :: spp_wts_mp (:,:) => null() ! spp-mp-perts
real (kind=kind_phys), pointer :: spp_wts_gwd (:,:) => null() ! spp-gwd-perts
real (kind=kind_phys), pointer :: spp_wts_rad (:,:) => null() ! spp-rad-perts
real (kind=kind_phys), pointer :: spp_wts_cu_deep (:,:) => null() ! spp-cu-deep-perts

!--- aerosol surface emissions for Thompson microphysics
real (kind=kind_phys), pointer :: nwfa2d (:) => null() !< instantaneous water-friendly sfc aerosol source
Expand Down Expand Up @@ -1328,6 +1329,7 @@ module GFS_typedefs
integer :: nseed !< cellular automata seed frequency
integer :: nseed_g !< cellular automata seed frequency
logical :: do_ca !< cellular automata main switch
logical :: ca_advect !< Advection of cellular automata
logical :: ca_sgs !< switch for sgs ca
logical :: ca_global !< switch for global ca
logical :: ca_smooth !< switch for gaussian spatial filter
Expand Down Expand Up @@ -1369,8 +1371,9 @@ module GFS_typedefs
integer :: spp_mp
integer :: spp_rad
integer :: spp_gwd
integer :: spp_cu_deep
integer :: n_var_spp
character(len=3) , pointer :: spp_var_list(:)
character(len=10) , pointer :: spp_var_list(:)
real(kind=kind_phys), pointer :: spp_prt_list(:)
real(kind=kind_phys), pointer :: spp_stddev_cutoff(:)

Expand Down Expand Up @@ -3120,6 +3123,8 @@ subroutine coupling_create (Coupling, IM, Model)
Coupling%spp_wts_gwd = clear_val
allocate (Coupling%spp_wts_rad (IM,Model%levs))
Coupling%spp_wts_rad = clear_val
allocate (Coupling%spp_wts_cu_deep (IM,Model%levs))
Coupling%spp_wts_cu_deep = clear_val
endif

!--- needed for Thompson's aerosol option
Expand Down Expand Up @@ -3765,6 +3770,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
integer :: iseed_ca = 1
integer :: nspinup = 1
logical :: do_ca = .false.
logical :: ca_advect = .false.
logical :: ca_sgs = .false.
logical :: ca_global = .false.
logical :: ca_smooth = .false.
Expand Down Expand Up @@ -3815,6 +3821,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
integer :: spp_mp = 0
integer :: spp_rad = 0
integer :: spp_gwd = 0
integer :: spp_cu_deep = 0
logical :: do_spp = .false.

integer :: ichoice = 0 !< flag for closure of C3/GF deep convection
Expand Down Expand Up @@ -3974,7 +3981,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
h0facu, h0facs, &
!--- cellular automata
nca, ncells, nlives, nca_g, ncells_g, nlives_g, nfracseed, &
nseed, nseed_g, nthresh, do_ca, &
nseed, nseed_g, nthresh, do_ca, ca_advect, &
ca_sgs, ca_global,iseed_ca,ca_smooth, &
nspinup,ca_amplitude,nsmooth,ca_closure,ca_entr,ca_trigger, &
!--- IAU
Expand Down Expand Up @@ -4943,6 +4950,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
Model%nseed_g = nseed_g
Model%ca_global = ca_global
Model%do_ca = do_ca
Model%ca_advect = ca_advect
Model%ca_sgs = ca_sgs
Model%iseed_ca = iseed_ca
Model%ca_smooth = ca_smooth
Expand Down Expand Up @@ -6705,6 +6713,7 @@ subroutine control_print(Model)
print *, ' ca_global : ', Model%ca_global
print *, ' ca_sgs : ', Model%ca_sgs
print *, ' do_ca : ', Model%do_ca
print *, ' ca_advect : ', Model%ca_advect
print *, ' iseed_ca : ', Model%iseed_ca
print *, ' ca_smooth : ', Model%ca_smooth
print *, ' nspinup : ', Model%nspinup
Expand Down
22 changes: 21 additions & 1 deletion ccpp/data/GFS_typedefs.meta
Original file line number Diff line number Diff line change
Expand Up @@ -2938,6 +2938,14 @@
type = real
kind = kind_phys
active = (do_stochastically_perturbed_parameterizations)
[spp_wts_cu_deep]
standard_name = spp_weights_for_cu_deep_scheme
long_name = spp weights for cu deep scheme
units = 1
dimensions = (horizontal_loop_extent,vertical_layer_dimension)
type = real
kind = kind_phys
active = (do_stochastically_perturbed_parameterizations)
[sfc_wts]
standard_name = surface_stochastic_weights_from_coupled_process
long_name = weights for stochastic surface physics perturbation
Expand Down Expand Up @@ -5698,6 +5706,12 @@
units = flag
dimensions = ()
type = logical
[ca_advect]
standard_name = flag_for_cellular_automata_advection
long_name = cellular automata main switch
units = flag
dimensions = ()
type = logical
[ca_sgs]
standard_name = flag_for_sgs_cellular_automata
long_name = switch for sgs ca
Expand Down Expand Up @@ -5853,7 +5867,7 @@
units = none
dimensions = (number_of_perturbed_spp_schemes)
type = character
kind = len=3
kind = len=10
active = (do_stochastically_perturbed_parameterizations)
[spp_pbl]
standard_name = control_for_pbl_spp_perturbations
Expand Down Expand Up @@ -5885,6 +5899,12 @@
units = count
dimensions = ()
type = integer
[spp_cu_deep]
standard_name = control_for_deep_convection_spp_perturbations
long_name = control for deep convection spp perturbations
units = count
dimensions = ()
type = integer
[ntrac]
standard_name = number_of_tracers
long_name = number of tracers
Expand Down
13 changes: 13 additions & 0 deletions ccpp/driver/GFS_diagnostics.F90
Original file line number Diff line number Diff line change
Expand Up @@ -2510,6 +2510,19 @@ subroutine GFS_externaldiag_populate (ExtDiag, Model, Statein, Stateout, Sfcprop
enddo
endif

if (Model%do_spp) then
idx = idx + 1
ExtDiag(idx)%axes = 3
ExtDiag(idx)%name = 'spp_wts_cu_deep'
ExtDiag(idx)%desc = 'spp cu deep perturbation wts'
ExtDiag(idx)%unit = 'm/s'
ExtDiag(idx)%mod_name = 'gfs_phys'
allocate (ExtDiag(idx)%data(nblks))
do nb = 1,nblks
ExtDiag(idx)%data(nb)%var3 => Coupling(nb)%spp_wts_cu_deep(:,:)
enddo
endif

if (Model%lndp_type /= 0) then
idx = idx + 1
ExtDiag(idx)%axes = 3
Expand Down
2 changes: 1 addition & 1 deletion ccpp/suites/suite_FV3_HRRR_c3.xml
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@
<scheme>mynnsfc_wrapper</scheme>
<scheme>GFS_surface_loop_control_part1</scheme>
<scheme>lsm_ruc</scheme>
<scheme>flake_driver</scheme>
<scheme>clm_lake</scheme>
<scheme>GFS_surface_loop_control_part2</scheme>
</subcycle>
<!-- End of surface iteration loop -->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@
<scheme>mynnsfc_wrapper</scheme>
<scheme>GFS_surface_loop_control_part1</scheme>
<scheme>lsm_ruc</scheme>
<scheme>flake_driver</scheme>
<scheme>clm_lake</scheme>
<scheme>GFS_surface_loop_control_part2</scheme>
</subcycle>
<!-- End of surface iteration loop -->
Expand Down
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
Loading

0 comments on commit c79c072

Please sign in to comment.