Skip to content

Commit

Permalink
Merge branch 'master' into support/HAFS
Browse files Browse the repository at this point in the history
  • Loading branch information
BinLiu-NOAA committed Jan 23, 2020
2 parents 904a433 + 3998189 commit 9648204
Show file tree
Hide file tree
Showing 79 changed files with 13,711 additions and 1,778 deletions.
17 changes: 12 additions & 5 deletions physics/GFS_DCNV_generic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -17,17 +17,17 @@ end subroutine GFS_DCNV_generic_pre_finalize
!! \htmlinclude GFS_DCNV_generic_pre_run.html
!!
#endif
subroutine GFS_DCNV_generic_pre_run (im, levs, ldiag3d, do_cnvgwd, do_ca, &
subroutine GFS_DCNV_generic_pre_run (im, levs, ldiag3d, do_cnvgwd, do_ca, cplchm,&
isppt_deep, gu0, gv0, gt0, gq0_water_vapor, &
save_u, save_v, save_t, save_qv, ca_deep, &
errmsg, errflg)
dqdti, errmsg, errflg)

use machine, only: kind_phys
use machine, only: kind_phys

implicit none

integer, intent(in) :: im, levs
logical, intent(in) :: ldiag3d, do_cnvgwd, do_ca, isppt_deep
logical, intent(in) :: ldiag3d, do_cnvgwd, do_ca, cplchm, isppt_deep
real(kind=kind_phys), dimension(im,levs), intent(in) :: gu0
real(kind=kind_phys), dimension(im,levs), intent(in) :: gv0
real(kind=kind_phys), dimension(im,levs), intent(in) :: gt0
Expand All @@ -37,9 +37,12 @@ subroutine GFS_DCNV_generic_pre_run (im, levs, ldiag3d, do_cnvgwd, do_ca,
real(kind=kind_phys), dimension(im,levs), intent(inout) :: save_t
real(kind=kind_phys), dimension(im,levs), intent(inout) :: save_qv
real(kind=kind_phys), dimension(im), intent(in) :: ca_deep
! dqdti only allocated if cplchm is .true.
real(kind=kind_phys), dimension(:,:), intent(inout) :: dqdti
character(len=*), intent(out) :: errmsg
integer, intent(out) :: errflg

real(kind=kind_phys), parameter :: zero = 0.0d0
integer :: i, k

! Initialize CCPP error handling variables
Expand Down Expand Up @@ -70,14 +73,18 @@ subroutine GFS_DCNV_generic_pre_run (im, levs, ldiag3d, do_cnvgwd, do_ca,
enddo
endif

if (ldiag3d .or. isppt_deep) then
if (ldiag3d .or. cplchm .or. isppt_deep) then
do k=1,levs
do i=1,im
save_qv(i,k) = gq0_water_vapor(i,k)
enddo
enddo
endif

if (cplchm) then
dqdti = zero
endif

end subroutine GFS_DCNV_generic_pre_run

end module GFS_DCNV_generic_pre
Expand Down
17 changes: 17 additions & 0 deletions physics/GFS_DCNV_generic.meta
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,14 @@
type = logical
intent = in
optional = F
[cplchm]
standard_name = flag_for_chemistry_coupling
long_name = flag controlling cplchm collection (default off)
units = flag
dimensions = ()
type = logical
intent = in
optional = F
[isppt_deep]
standard_name = flag_for_combination_of_sppt_with_isppt_deep
long_name = switch for combination with isppt_deep.
Expand Down Expand Up @@ -130,6 +138,15 @@
kind = kind_phys
intent = in
optional = F
[dqdti]
standard_name = instantaneous_water_vapor_specific_humidity_tendency_due_to_convection
long_name = instantaneous moisture tendency due to convection
units = kg kg-1 s-1
dimensions = (horizontal_dimension,vertical_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
64 changes: 57 additions & 7 deletions physics/GFS_GWD_generic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,6 @@ module GFS_GWD_generic_pre

contains

!> \section arg_table_GFS_GWD_generic_pre_init Argument Table
!!
subroutine GFS_GWD_generic_pre_init()
end subroutine GFS_GWD_generic_pre_init

Expand Down Expand Up @@ -105,12 +103,64 @@ subroutine GFS_GWD_generic_pre_run( &
end subroutine GFS_GWD_generic_pre_run
!> @}

! \ingroup GFS_ogwd
! \brief Brief description of the subroutine
!
!> \section arg_table_GFS_GWD_generic_pre_finalize Argument Table
!!
subroutine GFS_GWD_generic_pre_finalize()
end subroutine GFS_GWD_generic_pre_finalize

end module GFS_GWD_generic_pre

!> This module contains the CCPP-compliant orographic gravity wave drag post
!! interstitial codes.
module GFS_GWD_generic_post

contains


subroutine GFS_GWD_generic_post_init()
end subroutine GFS_GWD_generic_post_init

!! \section arg_table_GFS_GWD_generic_post_run Argument Table
!! \htmlinclude GFS_GWD_generic_post_run.html
!!
!! \section general General Algorithm
!! \section detailed Detailed Algorithm
!! @{
subroutine GFS_GWD_generic_post_run(lssav, ldiag3d, dtf, dusfcg, dvsfcg, dudt, dvdt, dtdt, &
& dugwd, dvgwd, du3dt, dv3dt, dt3dt, errmsg, errflg)

use machine, only : kind_phys
implicit none

logical, intent(in) :: lssav, ldiag3d

real(kind=kind_phys), intent(in) :: dusfcg(:), dvsfcg(:)
real(kind=kind_phys), intent(in) :: dudt(:,:), dvdt(:,:), dtdt(:,:)
real(kind=kind_phys), intent(in) :: dtf

real(kind=kind_phys), intent(inout) :: dugwd(:), dvgwd(:)
real(kind=kind_phys), intent(inout) :: du3dt(:,:), dv3dt(:,:), dt3dt(:,:)

character(len=*), intent(out) :: errmsg
integer, intent(out) :: errflg

! Initialize CCPP error handling variables
errmsg = ''
errflg = 0

if (lssav) then
dugwd(:) = dugwd(:) + dusfcg(:)*dtf
dvgwd(:) = dvgwd(:) + dvsfcg(:)*dtf

if (ldiag3d) then
du3dt(:,:) = du3dt(:,:) + dudt(:,:) * dtf
dv3dt(:,:) = dv3dt(:,:) + dvdt(:,:) * dtf
dt3dt(:,:) = dt3dt(:,:) + dtdt(:,:) * dtf
endif
endif

end subroutine GFS_GWD_generic_post_run
!> @}

subroutine GFS_GWD_generic_post_finalize()
end subroutine GFS_GWD_generic_post_finalize

end module GFS_GWD_generic_post
137 changes: 137 additions & 0 deletions physics/GFS_GWD_generic.meta
Original file line number Diff line number Diff line change
Expand Up @@ -167,3 +167,140 @@
[ccpp-arg-table]
name = GFS_GWD_generic_pre_finalize
type = scheme

########################################################################
[ccpp-arg-table]
name = GFS_GWD_generic_post_run
type = scheme
[lssav]
standard_name = flag_diagnostics
long_name = flag for calculating diagnostic fields
units = flag
dimensions = ()
type = logical
intent = in
optional = F
[ldiag3d]
standard_name = flag_diagnostics_3D
long_name = flag for calculating 3-D diagnostic fields
units = flag
dimensions = ()
type = logical
intent = in
optional = F
[dtf]
standard_name = time_step_for_dynamics
long_name = dynamics time step
units = s
dimensions = ()
type = real
kind = kind_phys
intent = in
optional = F
[dusfcg]
standard_name = instantaneous_x_stress_due_to_gravity_wave_drag
long_name = zonal surface stress due to orographic gravity wave drag
units = Pa
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[dvsfcg]
standard_name = instantaneous_y_stress_due_to_gravity_wave_drag
long_name = meridional surface stress due to orographic gravity wave drag
units = Pa
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[dudt]
standard_name = tendency_of_x_wind_due_to_model_physics
long_name = zonal wind tendency due to model physics
units = m s-2
dimensions = (horizontal_dimension,vertical_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[dvdt]
standard_name = tendency_of_y_wind_due_to_model_physics
long_name = meridional wind tendency due to model physics
units = m s-2
dimensions = (horizontal_dimension,vertical_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[dtdt]
standard_name = tendency_of_air_temperature_due_to_model_physics
long_name = air temperature tendency due to model physics
units = K s-1
dimensions = (horizontal_dimension,vertical_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[dugwd]
standard_name = time_integral_of_x_stress_due_to_gravity_wave_drag
long_name = integral over time of zonal stress due to gravity wave drag
units = Pa s
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dvgwd]
standard_name = time_integral_of_y_stress_due_to_gravity_wave_drag
long_name = integral over time of meridional stress due to gravity wave drag
units = Pa s
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[du3dt]
standard_name = cumulative_change_in_x_wind_due_to_orographic_gravity_wave_drag
long_name = cumulative change in zonal wind due to orographic gravity wave drag
units = m s-1
dimensions = (horizontal_dimension,vertical_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dv3dt]
standard_name = cumulative_change_in_y_wind_due_to_orographic_gravity_wave_drag
long_name = cumulative change in meridional wind due to orographic gravity wave drag
units = m s-1
dimensions = (horizontal_dimension,vertical_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[dt3dt]
standard_name = cumulative_change_in_temperature_due_to_orographic_gravity_wave_drag
long_name = cumulative change in temperature due to orographic gravity wave drag
units = K
dimensions = (horizontal_dimension,vertical_dimension)
type = real
kind = kind_phys
intent = inout
optional = F
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
units = none
dimensions = ()
type = character
kind = len=*
intent = out
optional = F
[errflg]
standard_name = ccpp_error_flag
long_name = error flag for error handling in CCPP
units = flag
dimensions = ()
type = integer
intent = out
optional = F
39 changes: 28 additions & 11 deletions physics/GFS_MP_generic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -81,19 +81,19 @@ end subroutine GFS_MP_generic_post_init
!> \section gfs_mp_gen GFS MP Generic Post General Algorithm
!> @{
subroutine GFS_MP_generic_post_run(im, ix, levs, kdt, nrcm, ncld, nncl, ntcw, ntrac, imp_physics, imp_physics_gfdl, &
imp_physics_thompson, imp_physics_mg, cal_pre, lssav, ldiag3d, cplflx, cplchm, con_g, dtf, frain, rainc, rain1, &
imp_physics_thompson, imp_physics_mg, imp_physics_fer_hires, cal_pre, lssav, ldiag3d, cplflx, cplchm, con_g, dtf, frain, rainc, rain1, &
rann, xlat, xlon, gt0, gq0, prsl, prsi, phii, tsfc, ice, snow, graupel, save_t, save_qv, rain0, ice0, snow0, &
graupel0, del, rain, domr_diag, domzr_diag, domip_diag, doms_diag, tprcp, srflag, sr, cnvprcp, totprcp, totice, &
totsnw, totgrp, cnvprcpb, totprcpb, toticeb, totsnwb, totgrpb, dt3dt, dq3dt, rain_cpl, rainc_cpl, snow_cpl, pwat, &
do_sppt, dtdtr, dtdtc, drain_cpl, dsnow_cpl, lsm, lsm_ruc, raincprv, rainncprv, iceprv, snowprv, graupelprv, &
dtp, errmsg, errflg)
do_sppt, dtdtr, dtdtc, drain_cpl, dsnow_cpl, lsm, lsm_ruc, lsm_noahmp, raincprv, rainncprv, iceprv, snowprv, &
graupelprv, draincprv, drainncprv, diceprv, dsnowprv, dgraupelprv, dtp, errmsg, errflg)
!
use machine, only: kind_phys

implicit none

integer, intent(in) :: im, ix, levs, kdt, nrcm, ncld, nncl, ntcw, ntrac
integer, intent(in) :: imp_physics, imp_physics_gfdl, imp_physics_thompson, imp_physics_mg
integer, intent(in) :: imp_physics, imp_physics_gfdl, imp_physics_thompson, imp_physics_mg, imp_physics_fer_hires
logical, intent(in) :: cal_pre, lssav, ldiag3d, cplflx, cplchm

real(kind=kind_phys), intent(in) :: dtf, frain, con_g
Expand All @@ -120,13 +120,18 @@ subroutine GFS_MP_generic_post_run(im, ix, levs, kdt, nrcm, ncld, nncl, ntcw, nt
real(kind=kind_phys), dimension(im), intent(inout) :: drain_cpl
real(kind=kind_phys), dimension(im), intent(inout) :: dsnow_cpl

! Rainfall variables previous time step (update for RUC LSM)
integer, intent(in) :: lsm, lsm_ruc
! Rainfall variables previous time step
integer, intent(in) :: lsm, lsm_ruc, lsm_noahmp
real(kind=kind_phys), dimension(im), intent(inout) :: raincprv
real(kind=kind_phys), dimension(im), intent(inout) :: rainncprv
real(kind=kind_phys), dimension(im), intent(inout) :: iceprv
real(kind=kind_phys), dimension(im), intent(inout) :: snowprv
real(kind=kind_phys), dimension(im), intent(inout) :: graupelprv
real(kind=kind_phys), dimension(im), intent(inout) :: draincprv
real(kind=kind_phys), dimension(im), intent(inout) :: drainncprv
real(kind=kind_phys), dimension(im), intent(inout) :: diceprv
real(kind=kind_phys), dimension(im), intent(inout) :: dsnowprv
real(kind=kind_phys), dimension(im), intent(inout) :: dgraupelprv

real(kind=kind_phys), intent(in) :: dtp

Expand All @@ -152,7 +157,7 @@ subroutine GFS_MP_generic_post_run(im, ix, levs, kdt, nrcm, ncld, nncl, ntcw, nt
errflg = 0

onebg = one/con_g

do i = 1, im
rain(i) = rainc(i) + frain * rain1(i) ! time-step convective plus explicit
enddo
Expand All @@ -179,15 +184,28 @@ subroutine GFS_MP_generic_post_run(im, ix, levs, kdt, nrcm, ncld, nncl, ntcw, nt
graupel = frain*graupel0 ! time-step graupel
ice = frain*ice0 ! time-step ice
snow = frain*snow0 ! time-step snow
end if

if (lsm==lsm_ruc) then
if (imp_physics == imp_physics_gfdl .or. imp_physics == imp_physics_thompson) then
else if (imp_physics == imp_physics_fer_hires) then
tprcp = max (0.,rain) ! time-step convective and explicit precip
ice = frain*rain1*sr ! time-step ice
end if

if (lsm==lsm_ruc .or. lsm==lsm_noahmp) then
raincprv(:) = rainc(:)
rainncprv(:) = frain * rain1(:)
iceprv(:) = ice(:)
snowprv(:) = snow(:)
graupelprv(:) = graupel(:)
!for NoahMP, calculate precipitation rates from liquid water equivalent thickness for use in next time step
!Note (GJF): Precipitation LWE thicknesses are multiplied by the frain factor, and are thus on the dynamics time step, but the conversion as written
! (with dtp in the denominator) assumes the rate is calculated on the physics time step. This only works as expected when dtf=dtp (i.e. when frain=1).
if (lsm == lsm_noahmp) then
tem = 1.0 / (dtp*con_p001) !GJF: This conversion was taken from GFS_physics_driver.F90, but should denominator also have the frain factor?
draincprv(:) = tem * raincprv(:)
drainncprv(:) = tem * rainncprv(:)
dsnowprv(:) = tem * snowprv(:)
dgraupelprv(:) = tem * graupelprv(:)
diceprv(:) = tem * iceprv(:)
end if
end if

Expand Down Expand Up @@ -296,7 +314,6 @@ subroutine GFS_MP_generic_post_run(im, ix, levs, kdt, nrcm, ncld, nncl, ntcw, nt
! if (snow0(i)+ice0(i)+graupel0(i)+csnow > 0.0) then
! Sfcprop%srflag(i) = 1. ! clu: set srflag to 'snow' (i.e. 1)
! endif
! compute fractional srflag
total_precip = snow0(i)+ice0(i)+graupel0(i)+rain0(i)+rainc(i)
if (total_precip > rainmin) then
srflag(i) = (snow0(i)+ice0(i)+graupel0(i)+csnow)/total_precip
Expand Down
Loading

0 comments on commit 9648204

Please sign in to comment.