Skip to content

Commit

Permalink
Added code necessary for the generic deep convection interstitial sch…
Browse files Browse the repository at this point in the history
…emes

 - created GFS_DCNV_generic.f90 with modules for pre and post
 - moved code from GFS_physics_driver.f90 to this file
 - call the new subroutines from GFS_physics_driver.f90
 - edited makefile to compile new file
 - edits to sasasdeep_run table in mfdeepcnv.f
 - NOT TESTED YET (committing to test on Theia)
  • Loading branch information
grantfirl committed Nov 15, 2017
1 parent 82a1ca4 commit d06890a
Show file tree
Hide file tree
Showing 4 changed files with 179 additions and 51 deletions.
108 changes: 59 additions & 49 deletions GFS_layer/GFS_physics_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module module_physics_driver
use physcons, only: con_cp, con_fvirt, con_g, con_rd, &
con_rv, con_hvap, con_hfus, &
con_rerth, con_pi, rhc_max, dxmin,&
dxinv, pa2mb, rlapse
dxinv, pa2mb, rlapse
use cs_conv, only: cs_convr
use ozne_def, only: levozp, oz_coeff, oz_pres
use h2o_def, only: levh2o, h2o_coeff, h2o_pres
Expand All @@ -15,6 +15,9 @@ module module_physics_driver
GFS_control_type, GFS_grid_type, &
GFS_tbd_type, GFS_cldprop_type, &
GFS_radtend_type, GFS_diag_type
use sasas_deep, only: sasasdeep_run
use GFS_DCNV_generic_pre, only: GFS_DCNV_generic_pre_run
use GFS_DCNV_generic_post, only: GFS_DCNV_generic_post_run

implicit none

Expand All @@ -27,7 +30,7 @@ module module_physics_driver
real(kind=kind_phys), parameter :: hsub = con_hvap+con_hfus
real(kind=kind_phys), parameter :: czmin = 0.0001 ! cos(89.994)
real(kind=kind_phys), parameter :: onebg = 1.0/con_g
real(kind=kind_phys), parameter :: albdf = 0.06
real(kind=kind_phys), parameter :: albdf = 0.06
real(kind=kind_phys) tf, tcr, tcrf
parameter (tf=258.16, tcr=273.16, tcrf=1.0/(tcr-tf))

Expand Down Expand Up @@ -422,14 +425,14 @@ subroutine GFS_physics_driver &
flag_cice

logical, dimension(Model%ntrac-Model%ncld+2,2) :: &
otspt
otspt

!--- REAL VARIABLES
real(kind=kind_phys) :: &
dtf, dtp, rhbbot, rhbtop, rhpbl, frain, tem, tem1, tem2, &
xcosz_loc, zsea1, zsea2, eng0, eng1, dpshc, &
!--- experimental for shoc sub-stepping
dtshoc
!--- experimental for shoc sub-stepping
dtshoc

real(kind=kind_phys), dimension(size(Grid%xlon,1)) :: &
ccwfac, garea, dlength, cumabs, cice, zice, tice, gflx, &
Expand Down Expand Up @@ -460,15 +463,18 @@ subroutine GFS_physics_driver &
del, rhc, dtdt, dudt, dvdt, gwdcu, gwdcv, dtdtc, rainp, &
ud_mf, dd_mf, dt_mf, prnum, dkt, sigmatot, sigmafrac

!--- GFDL modification for FV3
real(kind=kind_phys), dimension(size(Grid%xlon,1),Model%levs) :: &
initial_u, initial_v, initial_t, initial_qv

!--- GFDL modification for FV3
real(kind=kind_phys), dimension(size(Grid%xlon,1),Model%levs+1) ::&
del_gz

real(kind=kind_phys), dimension(size(Grid%xlon,1),Model%levs,Model%ntrac) :: &
dqdt

real(kind=kind_phys), dimension(size(Grid%xlon,1),Model%levs,Model%nctp) :: &
sigmai, vverti
sigmai, vverti

real(kind=kind_phys), dimension(size(Grid%xlon,1),Model%levs,oz_coeff+5) :: &
dq3dt_loc
Expand All @@ -477,7 +483,7 @@ subroutine GFS_physics_driver &
!--- 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)
!--- Anning Cheng 9/21/2016 leave a hook here for diagnosed snow,
!--- Anning Cheng 9/21/2016 leave a hook here for diagnosed snow,
!--- rain, and their number
real(kind=kind_phys), allocatable :: &
clw(:,:,:), qpl(:,:), qpi(:,:), ncpl(:,:), ncpi(:,:), &
Expand Down Expand Up @@ -1012,7 +1018,7 @@ subroutine GFS_physics_driver &
Model%lsm, lprnt, ipr, &
! --- input/outputs:
zice, cice, tice, Sfcprop%weasd, Sfcprop%tsfc, &
Sfcprop%tprcp, stsoil, ep1d, &
Sfcprop%tprcp, stsoil, ep1d, &
! --- outputs:
Sfcprop%snowd, qss, snowmt, gflx, Diag%cmm, Diag%chh, evap, &
hflx)
Expand Down Expand Up @@ -1493,17 +1499,19 @@ subroutine GFS_physics_driver &
! &,' lat=',lat,' kdt=',kdt,' me=',me
! if (lprnt) write(7000,*)' bef convection gv0=',gv0(ipr,:)

if (Model%ldiag3d) then
dtdt(:,:) = Stateout%gt0(:,:)
dudt(:,:) = Stateout%gu0(:,:)
dvdt(:,:) = Stateout%gv0(:,:)
elseif (Model%cnvgwd) then
dtdt(:,:) = Stateout%gt0(:,:)
endif ! end if_ldiag3d/cnvgwd
! if (Model%ldiag3d) then
! dtdt(:,:) = Stateout%gt0(:,:)
! dudt(:,:) = Stateout%gu0(:,:)
! dvdt(:,:) = Stateout%gv0(:,:)
! elseif (Model%cnvgwd) then
! dtdt(:,:) = Stateout%gt0(:,:)
! endif ! end if_ldiag3d/cnvgwd
!
! if (Model%ldiag3d .or. Model%lgocart) then
! dqdt(:,:,1) = Stateout%gq0(:,:,1)
! endif ! end if_ldiag3d/lgocart

if (Model%ldiag3d .or. Model%lgocart) then
dqdt(:,:,1) = Stateout%gq0(:,:,1)
endif ! end if_ldiag3d/lgocart
call GFS_DCNV_generic_pre_run (Model, Stateout, Grid, initial_u, initial_v, initial_t, intial_qv)

#ifdef GFS_HYDRO
call get_phi(im, ix, levs, ntrac, Stateout%gt0, Stateout%gq0, &
Expand Down Expand Up @@ -1857,26 +1865,28 @@ subroutine GFS_physics_driver &
! write(0,*)' aftcnvgq1=',(gq0(ipr,k,ntcw),k=1,levs)
! endif
!
do i = 1, im
Diag%rainc(:) = frain * rain1(:)
enddo
! do i = 1, im
! Diag%rainc(:) = frain * rain1(:)
! enddo
! !
! if (Model%lssav) then
! Diag%cldwrk (:) = Diag%cldwrk (:) + cld1d(:) * dtf
! Diag%cnvprcp(:) = Diag%cnvprcp(:) + Diag%rainc(:)
!
if (Model%lssav) then
Diag%cldwrk (:) = Diag%cldwrk (:) + cld1d(:) * dtf
Diag%cnvprcp(:) = Diag%cnvprcp(:) + Diag%rainc(:)

if (Model%ldiag3d) then
Diag%dt3dt(:,:,4) = Diag%dt3dt(:,:,4) + (Stateout%gt0(:,:)-dtdt(:,:)) * frain
Diag%dq3dt(:,:,2) = Diag%dq3dt(:,:,2) + (Stateout%gq0(:,:,1)-dqdt(:,:,1)) * frain
Diag%du3dt(:,:,3) = Diag%du3dt(:,:,3) + (Stateout%gu0(:,:)-dudt(:,:)) * frain
Diag%dv3dt(:,:,3) = Diag%dv3dt(:,:,3) + (Stateout%gv0(:,:)-dvdt(:,:)) * frain

Diag%upd_mf(:,:) = Diag%upd_mf(:,:) + ud_mf(:,:) * (con_g*frain)
Diag%dwn_mf(:,:) = Diag%dwn_mf(:,:) + dd_mf(:,:) * (con_g*frain)
Diag%det_mf(:,:) = Diag%det_mf(:,:) + dt_mf(:,:) * (con_g*frain)
endif ! if (ldiag3d)
! if (Model%ldiag3d) then
! Diag%dt3dt(:,:,4) = Diag%dt3dt(:,:,4) + (Stateout%gt0(:,:)-dtdt(:,:)) * frain
! Diag%dq3dt(:,:,2) = Diag%dq3dt(:,:,2) + (Stateout%gq0(:,:,1)-dqdt(:,:,1)) * frain
! Diag%du3dt(:,:,3) = Diag%du3dt(:,:,3) + (Stateout%gu0(:,:)-dudt(:,:)) * frain
! Diag%dv3dt(:,:,3) = Diag%dv3dt(:,:,3) + (Stateout%gv0(:,:)-dvdt(:,:)) * frain
!
! Diag%upd_mf(:,:) = Diag%upd_mf(:,:) + ud_mf(:,:) * (con_g*frain)
! Diag%dwn_mf(:,:) = Diag%dwn_mf(:,:) + dd_mf(:,:) * (con_g*frain)
! Diag%det_mf(:,:) = Diag%det_mf(:,:) + dt_mf(:,:) * (con_g*frain)
! endif ! if (ldiag3d)
!
! endif ! end if_lssav

endif ! end if_lssav
call GFS_DCNV_generic_post_run (Grid, Model, Stateout, frain, rain1, cld1d, initial_u, intial_v, intial_t, initial_qv, ud_mf, dd_mf, dt_mf, Diag)
!
! update dqdt_v to include moisture tendency due to deep convection
if (Model%lgocart) then
Expand Down Expand Up @@ -1905,7 +1915,7 @@ subroutine GFS_physics_driver &

if (Model%cnvgwd) then ! call convective gravity wave drag

! --- ... calculate maximum convective heating rate
! --- ... calculate maximum convective heating rate
! cuhr = temperature change due to deep convection

cumabs(:) = 0.0
Expand Down Expand Up @@ -2239,7 +2249,7 @@ subroutine GFS_physics_driver &
Stateout%gq0(1,1,1), clw(1,1,1), clw(1,1,2), qpi, qpl,rhc, &
Model%sup, Tbd%phy_f3d(1,1,Model%ntot3d-2), &
Stateout%gq0(1,1,Model%ntke), hflx, evap, prnum, &
Tbd%phy_f3d(1,1,Model%ntot3d-1), Tbd%phy_f3d(1,1,Model%ntot3d),&
Tbd%phy_f3d(1,1,Model%ntot3d-1), Tbd%phy_f3d(1,1,Model%ntot3d),&
lprnt, ipr, ncpl, ncpi, kdt)

if ((Model%ntlnc > 0) .and. (Model%ntinc > 0) .and. (Model%ncld >= 2)) then
Expand Down Expand Up @@ -2429,13 +2439,13 @@ subroutine GFS_physics_driver &
ncpr(:,:) = 0.
ncps(:,:) = 0.
Tbd%phy_f3d(:,:,1) = Tbd%phy_f3d(:,:,Model%ntot3d-2) ! clouds from shoc
else
else
clw(:,:,1) = Stateout%gq0(:,:,Model%ntiw) ! ice
clw(:,:,2) = Stateout%gq0(:,:,Model%ntcw) ! water
qrn(:,:) = Stateout%gq0(:,:,Model%ntrw)
qsnw(:,:) = Stateout%gq0(:,:,Model%ntsw)
ncpr(:,:) = Stateout%gq0(:,:,Model%ntrnc)
ncps(:,:) = Stateout%gq0(:,:,Model%ntsnc)
qrn(:,:) = Stateout%gq0(:,:,Model%ntrw)
qsnw(:,:) = Stateout%gq0(:,:,Model%ntsw)
ncpr(:,:) = Stateout%gq0(:,:,Model%ntrnc)
ncps(:,:) = Stateout%gq0(:,:,Model%ntsnc)
Tbd%phy_f3d(:,:,1) = Tbd%phy_f3d(:,:,Model%ntot3d-2) ! clouds from shoc
end if
elseif ((Model%imfdeepcnv >= 0) .or. (Model%imfshalcnv > 0)) then
Expand Down Expand Up @@ -2471,10 +2481,10 @@ subroutine GFS_physics_driver &
else
clw(:,:,1) = Stateout%gq0(:,:,Model%ntiw) ! ice
clw(:,:,2) = Stateout%gq0(:,:,Model%ntcw) ! water
qrn(:,:) = Stateout%gq0(:,:,Model%ntrw)
qsnw(:,:) = Stateout%gq0(:,:,Model%ntsw)
ncpr(:,:) = Stateout%gq0(:,:,Model%ntrnc)
ncps(:,:) = Stateout%gq0(:,:,Model%ntsnc)
qrn(:,:) = Stateout%gq0(:,:,Model%ntrw)
qsnw(:,:) = Stateout%gq0(:,:,Model%ntsw)
ncpr(:,:) = Stateout%gq0(:,:,Model%ntrnc)
ncps(:,:) = Stateout%gq0(:,:,Model%ntsnc)
Tbd%phy_f3d(:,:,1) = min(1.0, Tbd%phy_f3d(:,:,1)+cnvc(:,:))
endif
endif
Expand Down Expand Up @@ -2813,7 +2823,7 @@ subroutine moist_bud(im,ix,ix2,levs,me,kdt,grav,dtp,delp,rain, &
! endif
enddo
return

end subroutine moist_bud
!> @}

Expand Down
2 changes: 1 addition & 1 deletion makefile
Original file line number Diff line number Diff line change
Expand Up @@ -119,6 +119,7 @@ SRCS_f90 = \
./physics/gcm_shoc.f90 \
./physics/gcycle.f90 \
./physics/get_prs_fv3.f90 \
./physics/GFS_DCNV_generic.f90 \
./physics/h2ointerp.f90 \
./physics/m_micro_driver.f90 \
./physics/module_nst_model.f90 \
Expand Down Expand Up @@ -190,4 +191,3 @@ include ./depend
ifneq (clean,$(findstring clean,$(MAKECMDGOALS)))
-include depend
endif

Loading

0 comments on commit d06890a

Please sign in to comment.