Skip to content

Commit

Permalink
Move canopy heat storage calculation of reduced latent/sensible heat …
Browse files Browse the repository at this point in the history
…flux from GFS_PBL_generic_pre to GFS_surface_generic_post and remove workaround in MYNNPBL wrapper
  • Loading branch information
climbfuji committed May 19, 2020
1 parent 6d2cdfb commit 6e4c787
Show file tree
Hide file tree
Showing 6 changed files with 141 additions and 182 deletions.
47 changes: 2 additions & 45 deletions physics/GFS_PBL_generic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -84,9 +84,8 @@ subroutine GFS_PBL_generic_pre_run (im, levs, nvdiff, ntrac,
ntwa, ntia, ntgl, ntoz, ntke, ntkev, nqrimef, trans_aero, ntchs, ntchm, &
imp_physics, imp_physics_gfdl, imp_physics_thompson, imp_physics_wsm6, &
imp_physics_zhao_carr, imp_physics_mg, imp_physics_fer_hires, cplchm, ltaerosol, &
hybedmf, do_shoc, satmedmf, qgrs, vdftra, lheatstrg, z0fac, e0fac, zorl, &
u10m, v10m, hflx, evap, hflxq, evapq, hffac, hefac, save_u, save_v, save_t, &
save_q, ldiag3d, qdiag3d, lssav, ugrs, vgrs, tgrs, errmsg, errflg)
hybedmf, do_shoc, satmedmf, qgrs, vdftra, save_u, save_v, save_t, save_q, &
ldiag3d, qdiag3d, lssav, ugrs, vgrs, tgrs, errmsg, errflg)

use machine, only : kind_phys
use GFS_PBL_generic_common, only : set_aerosol_tracer_index
Expand All @@ -107,25 +106,12 @@ subroutine GFS_PBL_generic_pre_run (im, levs, nvdiff, ntrac,
real(kind=kind_phys), dimension(im, levs), intent(out) :: save_u, save_v, save_t
real(kind=kind_phys), dimension(im, levs, ntrac), intent(out) :: save_q

! For canopy heat storage
logical, intent(in) :: lheatstrg
real(kind=kind_phys), intent(in) :: z0fac, e0fac
real(kind=kind_phys), dimension(im), intent(in) :: zorl, u10m, v10m
real(kind=kind_phys), dimension(im), intent(in) :: hflx, evap
real(kind=kind_phys), dimension(im), intent(out) :: hflxq, evapq
real(kind=kind_phys), dimension(im), intent(out) :: hffac, hefac

! CCPP error handling variables
character(len=*), intent(out) :: errmsg
integer, intent(out) :: errflg

! Parameters for canopy heat storage parametrization
real (kind=kind_phys), parameter :: z0min=0.2, z0max=1.0
real (kind=kind_phys), parameter :: u10min=2.5, u10max=7.5

! Local variables
integer :: i, k, kk, k1, n
real(kind=kind_phys) :: tem, tem1, tem2

! Initialize CCPP error handling variables
errmsg = ''
Expand Down Expand Up @@ -281,35 +267,6 @@ subroutine GFS_PBL_generic_pre_run (im, levs, nvdiff, ntrac,
!
endif

! --- ... Boundary Layer and Free atmospheic turbulence parameterization
!
! in order to achieve heat storage within canopy layer, in the canopy heat
! storage parameterization the kinematic sensible and latent heat fluxes
! (hflx & evap) as surface boundary forcings to the pbl scheme are
! reduced as a function of surface roughness
!
do i=1,im
hflxq(i) = hflx(i)
evapq(i) = evap(i)
hffac(i) = 1.0
hefac(i) = 1.0
enddo
if (lheatstrg) then
do i=1,im
tem = 0.01 * zorl(i) ! change unit from cm to m
tem1 = (tem - z0min) / (z0max - z0min)
hffac(i) = z0fac * min(max(tem1, 0.0), 1.0)
tem = sqrt(u10m(i)**2+v10m(i)**2)
tem1 = (tem - u10min) / (u10max - u10min)
tem2 = 1.0 - min(max(tem1, 0.0), 1.0)
hffac(i) = tem2 * hffac(i)
hefac(i) = 1. + e0fac * hffac(i)
hffac(i) = 1. + hffac(i)
hflxq(i) = hflx(i) / hffac(i)
evapq(i) = evap(i) / hefac(i)
enddo
endif

if(ldiag3d .and. lssav) then
do k=1,levs
do i=1,im
Expand Down
107 changes: 0 additions & 107 deletions physics/GFS_PBL_generic.meta
Original file line number Diff line number Diff line change
Expand Up @@ -307,113 +307,6 @@
kind = kind_phys
intent = inout
optional = F
[lheatstrg]
standard_name = flag_for_canopy_heat_storage
long_name = flag for canopy heat storage parameterization
units = flag
dimensions = ()
type = logical
intent = in
optional = F
[z0fac]
standard_name = surface_roughness_fraction_factor
long_name = surface roughness fraction factor for canopy heat storage parameterization
units = none
dimensions = ()
type = real
kind = kind_phys
intent = in
optional = F
[e0fac]
standard_name = latent_heat_flux_fraction_factor_relative_to_sensible_heat_flux
long_name = latent heat flux fraction factor relative to sensible heat flux for canopy heat storage parameterization
units = none
dimensions = ()
type = real
kind = kind_phys
intent = in
optional = F
[zorl]
standard_name = surface_roughness_length
long_name = surface roughness length
units = cm
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[u10m]
standard_name = x_wind_at_10m
long_name = 10 meter u wind speed
units = m s-1
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[v10m]
standard_name = y_wind_at_10m
long_name = 10 meter v wind speed
units = m s-1
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[hflx]
standard_name = kinematic_surface_upward_sensible_heat_flux
long_name = kinematic surface upward sensible heat flux
units = K m s-1
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[evap]
standard_name = kinematic_surface_upward_latent_heat_flux
long_name = kinematic surface upward latent heat flux
units = kg kg-1 m s-1
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[hflxq]
standard_name = kinematic_surface_upward_sensible_heat_flux_reduced_by_surface_roughness
long_name = kinematic surface upward sensible heat flux reduced by surface roughness
units = K m s-1
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[evapq]
standard_name = kinematic_surface_upward_latent_heat_flux_reduced_by_surface_roughness
long_name = kinematic surface upward latent heat flux reduced by surface roughness
units = kg kg-1 m s-1
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[hefac]
standard_name = surface_upward_latent_heat_flux_reduction_factor
long_name = surface upward latent heat flux reduction factor from canopy heat storage
units = none
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[hffac]
standard_name = surface_upward_sensible_heat_flux_reduction_factor
long_name = surface upward sensible heat flux reduction factor from canopy heat storage
units = none
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[save_u]
standard_name = x_wind_save
long_name = x-wind before entering a physics scheme
Expand Down
48 changes: 47 additions & 1 deletion physics/GFS_surface_generic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -221,7 +221,8 @@ subroutine GFS_surface_generic_post_run (im, cplflx, cplwav, lssav, icy, wet, dt
dvisdfi_cpl, dnirbm_cpl, dnirdf_cpl, dvisbm_cpl, dvisdf_cpl, nlwsfci_cpl, nlwsfc_cpl, t2mi_cpl, q2mi_cpl, u10mi_cpl, &
v10mi_cpl, tsfci_cpl, psurfi_cpl, nnirbmi_cpl, nnirdfi_cpl, nvisbmi_cpl, nvisdfi_cpl, nswsfci_cpl, nswsfc_cpl, nnirbm_cpl, &
nnirdf_cpl, nvisbm_cpl, nvisdf_cpl, gflux, evbsa, evcwa, transa, sbsnoa, snowca, snohfa, ep, &
runoff, srunoff, runof, drain, errmsg, errflg)
runoff, srunoff, runof, drain, lheatstrg, z0fac, e0fac, zorl, hflx, evap, hflxq, evapq, hffac, hefac, &
errmsg, errflg)

implicit none

Expand All @@ -243,13 +244,29 @@ subroutine GFS_surface_generic_post_run (im, cplflx, cplwav, lssav, icy, wet, dt
real(kind=kind_phys), dimension(im), intent(inout) :: runoff, srunoff
real(kind=kind_phys), dimension(im), intent(in) :: drain, runof

! For canopy heat storage
logical, intent(in) :: lheatstrg
real(kind=kind_phys), intent(in) :: z0fac, e0fac
real(kind=kind_phys), dimension(im), intent(in) :: zorl
real(kind=kind_phys), dimension(im), intent(in) :: hflx, evap
real(kind=kind_phys), dimension(im), intent(out) :: hflxq, evapq
real(kind=kind_phys), dimension(im), intent(out) :: hffac, hefac

! CCPP error handling variables
character(len=*), intent(out) :: errmsg
integer, intent(out) :: errflg

! Local variables

real(kind=kind_phys), parameter :: albdf = 0.06d0

! Parameters for canopy heat storage parametrization
real(kind=kind_phys), parameter :: z0min=0.2, z0max=1.0
real(kind=kind_phys), parameter :: u10min=2.5, u10max=7.5

integer :: i
real(kind=kind_phys) :: xcosz_loc, ocalnirdf_cpl, ocalnirbm_cpl, ocalvisdf_cpl, ocalvisbm_cpl
real(kind=kind_phys) :: tem, tem1, tem2

! Initialize CCPP error handling variables
errmsg = ''
Expand Down Expand Up @@ -354,6 +371,35 @@ subroutine GFS_surface_generic_post_run (im, cplflx, cplwav, lssav, icy, wet, dt
enddo
endif

! --- ... Boundary Layer and Free atmospheic turbulence parameterization
!
! in order to achieve heat storage within canopy layer, in the canopy heat
! storage parameterization the kinematic sensible and latent heat fluxes
! (hflx & evap) as surface boundary forcings to the pbl scheme are
! reduced as a function of surface roughness
!
do i=1,im
hflxq(i) = hflx(i)
evapq(i) = evap(i)
hffac(i) = 1.0
hefac(i) = 1.0
enddo
if (lheatstrg) then
do i=1,im
tem = 0.01 * zorl(i) ! change unit from cm to m
tem1 = (tem - z0min) / (z0max - z0min)
hffac(i) = z0fac * min(max(tem1, 0.0), 1.0)
tem = sqrt(u10m(i)**2+v10m(i)**2)
tem1 = (tem - u10min) / (u10max - u10min)
tem2 = 1.0 - min(max(tem1, 0.0), 1.0)
hffac(i) = tem2 * hffac(i)
hefac(i) = 1. + e0fac * hffac(i)
hffac(i) = 1. + hffac(i)
hflxq(i) = hflx(i) / hffac(i)
evapq(i) = evap(i) / hefac(i)
enddo
endif

end subroutine GFS_surface_generic_post_run

end module GFS_surface_generic_post
89 changes: 89 additions & 0 deletions physics/GFS_surface_generic.meta
Original file line number Diff line number Diff line change
Expand Up @@ -1280,6 +1280,95 @@
kind = kind_phys
intent = in
optional = F
[lheatstrg]
standard_name = flag_for_canopy_heat_storage
long_name = flag for canopy heat storage parameterization
units = flag
dimensions = ()
type = logical
intent = in
optional = F
[z0fac]
standard_name = surface_roughness_fraction_factor
long_name = surface roughness fraction factor for canopy heat storage parameterization
units = none
dimensions = ()
type = real
kind = kind_phys
intent = in
optional = F
[e0fac]
standard_name = latent_heat_flux_fraction_factor_relative_to_sensible_heat_flux
long_name = latent heat flux fraction factor relative to sensible heat flux for canopy heat storage parameterization
units = none
dimensions = ()
type = real
kind = kind_phys
intent = in
optional = F
[zorl]
standard_name = surface_roughness_length
long_name = surface roughness length
units = cm
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[hflx]
standard_name = kinematic_surface_upward_sensible_heat_flux
long_name = kinematic surface upward sensible heat flux
units = K m s-1
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[evap]
standard_name = kinematic_surface_upward_latent_heat_flux
long_name = kinematic surface upward latent heat flux
units = kg kg-1 m s-1
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
optional = F
[hflxq]
standard_name = kinematic_surface_upward_sensible_heat_flux_reduced_by_surface_roughness
long_name = kinematic surface upward sensible heat flux reduced by surface roughness
units = K m s-1
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[evapq]
standard_name = kinematic_surface_upward_latent_heat_flux_reduced_by_surface_roughness
long_name = kinematic surface upward latent heat flux reduced by surface roughness
units = kg kg-1 m s-1
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[hefac]
standard_name = surface_upward_latent_heat_flux_reduction_factor
long_name = surface upward latent heat flux reduction factor from canopy heat storage
units = none
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[hffac]
standard_name = surface_upward_sensible_heat_flux_reduction_factor
long_name = surface upward sensible heat flux reduction factor from canopy heat storage
units = none
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = out
optional = F
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
10 changes: 1 addition & 9 deletions physics/module_MYNNPBL_wrapper.F90
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ SUBROUTINE mynnedmf_wrapper_run( &
& qgrs_ice_aer_num_conc, &
& prsl,exner, &
& slmsk,tsurf,qsfc,ps, &
& ust,ch,hflx,qflx,hflxq,qflxq, &
& ust,ch,hflx,qflx, &
& wspd,rb,dtsfc1,dqsfc1, &
& dtsfci_diag,dqsfci_diag, &
& dtsfc_diag,dqsfc_diag, &
Expand Down Expand Up @@ -268,8 +268,6 @@ SUBROUTINE mynnedmf_wrapper_run( &
real(kind=kind_phys), dimension(im), intent(in) :: &
& dx,zorl,slmsk,tsurf,qsfc,ps, &
& hflx,qflx,ust,wspd,rb,recmol
real(kind=kind_phys), dimension(im), intent(out) :: &
& hflxq, qflxq

real(kind=kind_phys), dimension(im), intent(inout) :: &
& pblh
Expand Down Expand Up @@ -306,12 +304,6 @@ SUBROUTINE mynnedmf_wrapper_run( &
!print*,"in MYNN, initflag=",initflag
endif

! Set "kinematic surface upward latent/sensible heat flux reduced by
! surface roughness" to kinematic surface upward latent/sensible heat flux,
! because the lheatstrg capability in GFS_PBL_generic_pre is not implemented
hflxq = hflx
qflxq = qflx

! Assign variables for each microphysics scheme
if (imp_physics == imp_physics_wsm6) then
! WSM6
Expand Down
Loading

0 comments on commit 6e4c787

Please sign in to comment.