Skip to content

Commit

Permalink
FV3: this commits #refs 48136
Browse files Browse the repository at this point in the history
  • Loading branch information
junwang-noaa committed Jun 1, 2018
1 parent 42ea482 commit 867dc10
Show file tree
Hide file tree
Showing 8 changed files with 3,026 additions and 125 deletions.
116 changes: 71 additions & 45 deletions gfsphysics/GFS_layer/GFS_physics_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -226,7 +226,7 @@ module module_physics_driver
!! - determine the index of TKE (ntk) in the convectively transported tracer array (clw)
!! - allocate precipitation mixing ratio cloud droplet number concentration arrays
!! - Deep Convection:
!! - determine which tracers in the tracer input array undergo convective transport (valid only for the RAS and Chikira-Sugiyama schemes) and allocate a local convective transported tracer array (clw)
!! - determine which tracers in the tracer input array undergo convective transport (valid for the RAS and Chikira-Sugiyama, and SAMF schemes) and allocate a local convective transported tracer array (clw)
!! - apply an adjustment to the tracers from the dynamics
!! - calculate horizontal grid-related parameters needed for some parameterizations
!! - calculate the maxiumum cloud base updraft speed for the Chikira-Sugiyama scheme
Expand Down Expand Up @@ -257,7 +257,7 @@ module module_physics_driver
!! - finally, accumulate surface-related diagnostics and calculate the max/min values of T and q at 2 m height.
!! .
!! ## Calculate the state variable tendencies due to the PBL (vertical diffusion) scheme.
!! - Call the vertical diffusion scheme (PBL) based on the following logical flags: do_shoc, hybedmf, old_monin, mstrat
!! - Call the vertical diffusion scheme (PBL) based on the following logical flags: do_shoc, hybedmf, satmedmf, old_monin, mstrat
!! - the PBL scheme is expected to return tendencies of the state variables
!! - If A/O/I coupling and the surface is sea ice, overwrite some surface-related variables to their states before PBL was called
!! - For diagnostics, do the following:
Expand Down Expand Up @@ -448,9 +448,9 @@ subroutine GFS_physics_driver &
ims, ime, kms, kme, its, ite, kts, kte, imp_physics, &
ntwa, ntia

integer :: i, kk, ic, k, n, k1, iter, levshcm, tracers, &
tottracer, num2, num3, nshocm, nshoc, ntk, nn, nncl, &
seconds
integer :: i, kk, ic, k, n, k1, iter, levshcm, tracers, &
tottracer, nsamftrac, num2, num3, nshocm, nshoc, ntk, &
nn, nncl, seconds

integer, dimension(size(Grid%xlon,1)) :: &
kbot, ktop, kcnv, soiltyp, vegtype, kpbl, slopetyp, kinver, &
Expand Down Expand Up @@ -534,7 +534,7 @@ subroutine GFS_physics_driver &
!--- ALLOCATABLE ELEMENTS
!--- in clw, the first two varaibles are cloud water and ice.
!--- from third to ntrac are convective transportable tracers,
!--- third being the ozone, when ntrac=3 (valid only with ras)
!--- third being the ozone, when ntrac=3 (valid with ras, csaw, or samf)
!--- Anning Cheng 9/21/2016 leave a hook here for diagnosed snow,
!--- rain, and their numbers
real(kind=kind_phys), allocatable :: &
Expand Down Expand Up @@ -579,6 +579,10 @@ subroutine GFS_physics_driver &
ntiw = Model%ntiw
ncld = Model%ncld
ntke = Model%ntke
!
! scal-aware TKE-based moist EDMF (satmedmfvdif) scheme is coded assuming
! ntke=ntrac. If ntrac > ntke, the code needs to be modified. (Jongil Han)
!
ntlnc = Model%ntlnc
ntinc = Model%ntinc
ntrw = Model%ntrw
Expand Down Expand Up @@ -1445,7 +1449,18 @@ subroutine GFS_physics_driver &
! if (lprnt) write(0,*)'aftmonshoc=',Statein%tgrs(ipr,:)
! if (lprnt) write(0,*)'aftmonshocdtdt=',dtdt(ipr,1:10)
else
if (Model%hybedmf) then
if (Model%satmedmf) then
call satmedmfvdif(ix, im, levs, nvdiff, ntcw, ntke, &
dvdt, dudt, dtdt, dqdt, &
Statein%ugrs, Statein%vgrs, Statein%tgrs, Statein%qgrs, &
Radtend%htrsw, Radtend%htrlw, xmu, garea, &
Statein%prsik(1,1), rb, Sfcprop%zorl, Diag%u10m, Diag%v10m, &
Sfcprop%ffmm, Sfcprop%ffhh, Sfcprop%tsfc, hflx, evap, &
stress, wind, kpbl, Statein%prsi, del, Statein%prsl, &
Statein%prslk, Statein%phii, Statein%phil, dtp, &
Model%dspheat, dusfc1, dvsfc1, dtsfc1, dqsfc1, Diag%hpbl, &
kinver, Model%xkzm_m, Model%xkzm_h, Model%xkzm_s)
elseif (Model%hybedmf) then
call moninedmf(ix, im, levs, nvdiff, ntcw, dvdt, dudt, dtdt, dqdt, &
Statein%ugrs, Statein%vgrs, Statein%tgrs, Statein%qgrs, &
Radtend%htrsw, Radtend%htrlw, xmu, Statein%prsik(1,1), &
Expand Down Expand Up @@ -1993,12 +2008,12 @@ subroutine GFS_physics_driver &
endif


! --- ... for convective tracer transport (while using ras or csaw)
! --- ... for convective tracer transport (while using ras, csaw, or samf)
! (the code here implicitly assumes that ntiw=ntcw+1)

ntk = 0
tottracer = 0
if (Model%cscnv .or. Model%trans_trac ) then
if (Model%cscnv .or. Model%satmedmf .or. Model%trans_trac ) then
otspt(:,:) = .true. ! otspt is used only for cscnv
otspt(1:3,:) = .false. ! this is for sp.hum, ice and liquid water
tracers = 2
Expand All @@ -2023,7 +2038,7 @@ subroutine GFS_physics_driver &
endif
enddo
tottracer = tracers - 2
endif ! end if_ras or cfscnv
endif ! end if_ras or cfscnv or samf

! if (kdt == 1 .and. me == 0) &
! write(0,*)' trans_trac=',Model%trans_trac,' tottracer=', &
Expand Down Expand Up @@ -2268,16 +2283,20 @@ subroutine GFS_physics_driver &
Model%evfact_deep, Model%evfactl_deep, &
Model%pgcon_deep)
elseif (Model%imfdeepcnv == 2) then
call samfdeepcnv(im, ix, levs, dtp, del, Statein%prsl, &
Statein%pgr, Statein%phil, clw(:,:,1:2), &
Stateout%gq0(:,:,1), &
Stateout%gt0, Stateout%gu0, Stateout%gv0, &
cld1d, rain1, kbot, ktop, kcnv, islmsk, &
garea, Statein%vvl, ncld, ud_mf, dd_mf, &
dt_mf, cnvw, cnvc, &
Model%clam_deep, Model%c0s_deep, &
Model%c1_deep, Model%betal_deep, Model%betas_deep,&
Model%evfact_deep, Model%evfactl_deep, &
if(.not. Model%satmedmf .and. .not. Model%trans_trac) then
nsamftrac = 0
else
nsamftrac = tottracer
endif
call samfdeepcnv(im, ix, levs, dtp, ntk, nsamftrac, del, &
Statein%prsl, Statein%pgr, Statein%phil, clw, &
Stateout%gq0(:,:,1), Stateout%gt0, &
Stateout%gu0, Stateout%gv0, &
cld1d, rain1, kbot, ktop, kcnv, islmsk, garea, &
Statein%vvl, ncld, ud_mf, dd_mf, dt_mf, cnvw, cnvc, &
Model%clam_deep, Model%c0s_deep, &
Model%c1_deep, Model%betal_deep, Model%betas_deep, &
Model%evfact_deep, Model%evfactl_deep, &
Model%pgcon_deep, Model%asolfac_deep)
! if (lprnt) print *,' rain1=',rain1(ipr)
elseif (Model%imfdeepcnv == 0) then ! random cloud top
Expand Down Expand Up @@ -2431,26 +2450,6 @@ subroutine GFS_physics_driver &
enddo
endif ! if (lgocart)

! --- ... update the tracers due to convective transport
! (except for suspended water and ice)

if (tottracer > 0) then
tracers = 2
do n=2,ntrac
! if ( n /= ntcw .and. n /= ntiw .and. n /= ntclamt) then
if ( n /= ntcw .and. n /= ntiw .and. n /= ntclamt .and. &
n /= ntrw .and. n /= ntsw .and. n /= ntrnc .and. &
n /= ntsnc .and. n /= ntgl .and. n /= ntgnc ) then
tracers = tracers + 1
do k=1,levs
do i=1,im
Stateout%gq0(i,k,n) = clw(i,k,tracers)
enddo
enddo
endif
enddo
endif

endif ! end if_not_ras
else ! no parameterized deep convection
cld1d = 0.
Expand Down Expand Up @@ -2779,10 +2778,15 @@ subroutine GFS_physics_driver &
endif

elseif (Model%imfshalcnv == 2) then
call samfshalcnv (im, ix, levs, dtp, del, Statein%prsl, &
Statein%pgr, Statein%phil, clw(:,:,1:2), &
Stateout%gq0(:,:,1:1), &
Stateout%gt0, Stateout%gu0, Stateout%gv0, &
if(.not. Model%satmedmf .and. .not. Model%trans_trac) then
nsamftrac = 0
else
nsamftrac = tottracer
endif
call samfshalcnv (im, ix, levs, dtp, ntk, nsamftrac, del, &
Statein%prsl, Statein%pgr, Statein%phil, clw, &
Stateout%gq0(:,:,1), Stateout%gt0, &
Stateout%gu0, Stateout%gv0, &
rain1, kbot, ktop, kcnv, islmsk, garea, &
Statein%vvl, ncld, DIag%hpbl, ud_mf, &
dt_mf, cnvw, cnvc, &
Expand Down Expand Up @@ -2977,7 +2981,29 @@ subroutine GFS_physics_driver &
! write(0,*) ' aftshgt0=',gt0(ipr,:)
! write(0,*) ' aftshgq0=',gq0(ipr,:,1)
! endif

!
!------------------------------------------------------------------------------
! --- update the tracers due to deep & shallow cumulus convective transport
! (except for suspended water and ice)
!
if (tottracer > 0) then
tracers = 2
do n=2,ntrac
! if ( n /= ntcw .and. n /= ntiw .and. n /= ntclamt) then
if ( n /= ntcw .and. n /= ntiw .and. n /= ntclamt .and. &
n /= ntrw .and. n /= ntsw .and. n /= ntrnc .and. &
n /= ntsnc .and. n /= ntgl .and. n /= ntgnc ) then
tracers = tracers + 1
do k=1,levs
do i=1,im
Stateout%gq0(i,k,n) = clw(i,k,tracers)
enddo
enddo
endif
enddo
endif
!-------------------------------------------------------------------------------
!
if (ntcw > 0) then

! for microphysics
Expand Down
14 changes: 11 additions & 3 deletions gfsphysics/GFS_layer/GFS_typedefs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -483,7 +483,7 @@ module GFS_typedefs
logical :: ras !< flag for ras convection scheme
logical :: flipv !< flag for vertical direction flip (ras)
!< .true. implies surface at k=1
logical :: trans_trac !< flag for convective transport of tracers (RAS only)
logical :: trans_trac !< flag for convective transport of tracers (RAS, CS, or SAMF)
logical :: old_monin !< flag for diff monin schemes
logical :: cnvgwd !< flag for conv gravity wave drag
logical :: mstrat !< flag for moorthi approach for stratus
Expand All @@ -502,6 +502,8 @@ module GFS_typedefs
logical :: shcnvcw !< flag for shallow convective cloud
logical :: redrag !< flag for reduced drag coeff. over sea
logical :: hybedmf !< flag for hybrid edmf pbl scheme
logical :: satmedmf !< flag for scale-aware TKE-based moist edmf
!< vertical turbulent mixing scheme
logical :: dspheat !< flag for tke dissipative heating
logical :: cnvcld
logical :: random_clds !< flag controls whether clouds are random
Expand Down Expand Up @@ -1545,7 +1547,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
logical :: ras = .false. !< flag for ras convection scheme
logical :: flipv = .true. !< flag for vertical direction flip (ras)
!< .true. implies surface at k=1
logical :: trans_trac = .false. !< flag for convective transport of tracers (RAS only)
logical :: trans_trac = .false. !< flag for convective transport of tracers (RAS, CS, or SAMF)
logical :: old_monin = .false. !< flag for diff monin schemes
logical :: cnvgwd = .false. !< flag for conv gravity wave drag
logical :: mstrat = .false. !< flag for moorthi approach for stratus
Expand All @@ -1563,6 +1565,8 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
logical :: shcnvcw = .false. !< flag for shallow convective cloud
logical :: redrag = .false. !< flag for reduced drag coeff. over sea
logical :: hybedmf = .false. !< flag for hybrid edmf pbl scheme
logical :: satmedmf = .false. !< flag for scale-aware TKE-based moist edmf
!< vertical turbulent mixing scheme
logical :: dspheat = .false. !< flag for tke dissipative heating
logical :: cnvcld = .false.
logical :: random_clds = .false. !< flag controls whether clouds are random
Expand Down Expand Up @@ -1702,7 +1706,8 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
!--- physical parameterizations
ras, trans_trac, old_monin, cnvgwd, mstrat, moist_adj, &
cscnv, cal_pre, do_aw, do_shoc, shocaftcnv, shoc_cld, &
h2o_phys, pdfcld, shcnvcw, redrag, hybedmf, dspheat, cnvcld, &
h2o_phys, pdfcld, shcnvcw, redrag, hybedmf, satmedmf, &
dspheat, cnvcld, &
random_clds, shal_cnv, imfshalcnv, imfdeepcnv, do_deep, jcap,&
cs_parm, flgmin, cgwf, ccwf, cdmbgwd, sup, ctei_rm, crtrh, &
dlqf, rbcr, shoc_parm, &
Expand Down Expand Up @@ -1899,6 +1904,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
Model%shcnvcw = shcnvcw
Model%redrag = redrag
Model%hybedmf = hybedmf
Model%satmedmf = satmedmf
Model%dspheat = dspheat
Model%cnvcld = cnvcld
Model%random_clds = random_clds
Expand Down Expand Up @@ -2060,6 +2066,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
Model%shal_cnv = .false.
Model%imfshalcnv = -1
Model%hybedmf = .false.
Model%satmedmf = .false.
if (Model%me == Model%master) print *,' Simplified Higher Order Closure Model used for', &
' Boundary layer and Shallow Convection', &
' nshoc_3d=',Model%nshoc_3d, &
Expand Down Expand Up @@ -2455,6 +2462,7 @@ subroutine control_print(Model)
print *, ' shcnvcw : ', Model%shcnvcw
print *, ' redrag : ', Model%redrag
print *, ' hybedmf : ', Model%hybedmf
print *, ' satmedmf : ', Model%satmedmf
print *, ' dspheat : ', Model%dspheat
print *, ' cnvcld : ', Model%cnvcld
print *, ' random_clds : ', Model%random_clds
Expand Down
7 changes: 5 additions & 2 deletions gfsphysics/makefile
Original file line number Diff line number Diff line change
Expand Up @@ -52,9 +52,9 @@ SRCS_f = \
./physics/iounitdef.f \
./physics/lrgsclr.f \
./physics/mersenne_twister.f \
./physics/samfdeepcnv.f \
./physics/mfpbl.f \
./physics/samfshalcnv.f \
./physics/mfpblt.f \
./physics/mfscu.f \
./physics/module_bfmicrophysics.f \
./physics/moninedmf.f \
./physics/moninp.f \
Expand Down Expand Up @@ -92,8 +92,11 @@ SRCS_f = \
./physics/rascnvv2.f \
./physics/rayleigh_damp.f \
./physics/rayleigh_damp_mesopause.f \
./physics/samfdeepcnv.f \
./physics/samfshalcnv.f \
./physics/sascnv.f \
./physics/sascnvn.f \
./physics/satmedmfvdif.f \
./physics/set_soilveg.f \
./physics/sfc_cice.f \
./physics/sfc_diag.f \
Expand Down
Loading

0 comments on commit 867dc10

Please sign in to comment.