Skip to content

Commit

Permalink
Merge pull request #729 from HelinWei-NOAA/main
Browse files Browse the repository at this point in the history
Noah MP updates for Prototype 8 (GFSv17)
  • Loading branch information
climbfuji authored Dec 2, 2021
2 parents aeef844 + 7ee1bf2 commit d9e6676
Show file tree
Hide file tree
Showing 11 changed files with 1,224 additions and 434 deletions.
24 changes: 18 additions & 6 deletions physics/GFS_surface_generic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -275,32 +275,34 @@ end subroutine GFS_surface_generic_post_finalize
!! \htmlinclude GFS_surface_generic_post_run.html
!!
subroutine GFS_surface_generic_post_run (im, cplflx, cplchm, cplwav, lssav, dry, icy, wet, &
dtf, ep1d, gflx, tgrs_1, qgrs_1, ugrs_1, vgrs_1, &
lsm, lsm_noahmp, dtf, ep1d, gflx, tgrs_1, qgrs_1, ugrs_1, vgrs_1, &
adjsfcdlw, adjsfcdsw, adjnirbmd, adjnirdfd, adjvisbmd, adjvisdfd, adjsfculw, adjsfculw_wat, adjnirbmu, adjnirdfu, &
adjvisbmu, adjvisdfu,t2m, q2m, u10m, v10m, tsfc, tsfc_wat, pgr, xcosz, evbs, evcw, trans, sbsno, snowc, snohf, &
adjvisbmu, adjvisdfu, t2m, q2m, u10m, v10m, tsfc, tsfc_wat, pgr, xcosz, evbs, evcw, trans, sbsno, snowc, snohf, pah, pahi, &
epi, gfluxi, t1, q1, u1, v1, dlwsfci_cpl, dswsfci_cpl, dlwsfc_cpl, dswsfc_cpl, dnirbmi_cpl, dnirdfi_cpl, dvisbmi_cpl, &
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, lheatstrg, h0facu, h0facs, zvfun, hflx, evap, hflxq, hffac, &
nnirdf_cpl, nvisbm_cpl, nvisdf_cpl, gflux, evbsa, evcwa, transa, sbsnoa, snowca, snohfa, paha, ep, ecan, etran, edir, waxy, &
runoff, srunoff, runof, drain, tecan, tetran, tedir, twa, lheatstrg, h0facu, h0facs, zvfun, hflx, evap, hflxq, hffac, &
isot, ivegsrc, islmsk, vtype, stype, slope, vtype_save, stype_save, slope_save, errmsg, errflg)

implicit none

integer, intent(in) :: im
logical, intent(in) :: cplflx, cplchm, cplwav, lssav
logical, dimension(:), intent(in) :: dry, icy, wet
integer, intent(in) :: lsm, lsm_noahmp
real(kind=kind_phys), intent(in) :: dtf

real(kind=kind_phys), dimension(:), intent(in) :: ep1d, gflx, tgrs_1, qgrs_1, ugrs_1, vgrs_1, adjsfcdlw, adjsfcdsw, &
adjnirbmd, adjnirdfd, adjvisbmd, adjvisdfd, adjsfculw, adjsfculw_wat, adjnirbmu, adjnirdfu, adjvisbmu, adjvisdfu, &
t2m, q2m, u10m, v10m, tsfc, tsfc_wat, pgr, xcosz, evbs, evcw, trans, sbsno, snowc, snohf
t2m, q2m, u10m, v10m, tsfc, tsfc_wat, pgr, xcosz, evbs, evcw, trans, sbsno, snowc, snohf, pah, ecan, etran, edir, &
waxy

real(kind=kind_phys), dimension(:), intent(inout) :: epi, gfluxi, t1, q1, u1, v1, dlwsfci_cpl, dswsfci_cpl, dlwsfc_cpl, &
dswsfc_cpl, dnirbmi_cpl, dnirdfi_cpl, dvisbmi_cpl, 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
evcwa, transa, sbsnoa, snowca, snohfa, ep, paha, tecan, tetran, tedir, twa, pahi

real(kind=kind_phys), dimension(:), intent(inout) :: runoff, srunoff
real(kind=kind_phys), dimension(:), intent(in) :: drain, runof
Expand Down Expand Up @@ -333,6 +335,9 @@ subroutine GFS_surface_generic_post_run (im, cplflx, cplchm, cplwav, lssav, dry,
do i=1,im
epi(i) = ep1d(i)
gfluxi(i) = gflx(i)
if (lsm == lsm_noahmp) then
pahi(i) = pah(i)
endif
t1(i) = tgrs_1(i)
q1(i) = qgrs_1(i)
u1(i) = ugrs_1(i)
Expand Down Expand Up @@ -426,6 +431,13 @@ subroutine GFS_surface_generic_post_run (im, cplflx, cplchm, cplwav, lssav, dry,
! runoff at the surface and is accumulated in unit of meters
runoff(i) = runoff(i) + (drain(i)+runof(i)) * dtf
srunoff(i) = srunoff(i) + runof(i) * dtf
tecan(i) = tecan(i) + ecan(i) * dtf
tetran(i) = tetran(i) + etran(i) * dtf
tedir(i) = tedir(i) + edir(i) * dtf
if (lsm == lsm_noahmp) then
paha(i) = paha(i) + pah(i) * dtf
twa(i) = waxy(i)
endif
enddo
endif

Expand Down
102 changes: 102 additions & 0 deletions physics/GFS_surface_generic.meta
Original file line number Diff line number Diff line change
Expand Up @@ -600,6 +600,20 @@
dimensions = (horizontal_loop_extent)
type = logical
intent = in
[lsm]
standard_name = control_for_land_surface_scheme
long_name = flag for land surface model
units = flag
dimensions = ()
type = integer
intent = in
[lsm_noahmp]
standard_name = identifier_for_noahmp_land_surface_scheme
long_name = flag for NOAH MP land surface model
units = flag
dimensions = ()
type = integer
intent = in
[dtf]
standard_name = timestep_for_dynamics
long_name = dynamics timestep
Expand Down Expand Up @@ -864,6 +878,22 @@
type = real
kind = kind_phys
intent = in
[pah]
standard_name = total_precipitation_advected_heat
long_name = precipitation advected heat - total
units = W m-2
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[pahi]
standard_name = instantaneous_total_precipitation_advected_heat
long_name = instantaneous precipitation advected heat - total
units = W m-2
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[epi]
standard_name = instantaneous_surface_potential_evaporation
long_name = instantaneous sfc potential evaporation
Expand Down Expand Up @@ -1208,6 +1238,14 @@
type = real
kind = kind_phys
intent = inout
[paha]
standard_name = cumulative_precipitation_advected_heat_flux_multiplied_by_timestep
long_name = cumulative precipitation advected heat flux multiplied by timestep
units = W m-2 s
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = inout
[ep]
standard_name = cumulative_surface_upward_potential_latent_heat_flux_multiplied_by_timestep
long_name = cumulative surface upward potential latent heat flux multiplied by timestep
Expand All @@ -1216,6 +1254,38 @@
type = real
kind = kind_phys
intent = inout
[ecan]
standard_name = evaporation_of_intercepted_water
long_name = evaporation of intercepted water
units = kg m-2 s-1
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[etran]
standard_name = transpiration_rate
long_name = transpiration rate
units = kg m-2 s-1
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[edir]
standard_name = soil_surface_evaporation_rate
long_name = soil surface evaporation rate
units = kg m-2 s-1
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[waxy]
standard_name = water_storage_in_aquifer
long_name = water storage in aquifer
units = mm
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[runoff]
standard_name = total_runoff
long_name = total water runoff
Expand Down Expand Up @@ -1248,6 +1318,38 @@
type = real
kind = kind_phys
intent = in
[tecan]
standard_name = total_evaporation_of_intercepted_water
long_name = total evaporation of intercepted water
units = kg m-2
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = inout
[tetran]
standard_name = total_transpiration_rate
long_name = total transpiration rate
units = kg m-2
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = inout
[tedir]
standard_name = total_soil_surface_evaporation_rate
long_name = total soil surface evaporation rate
units = kg m-2
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = inout
[twa]
standard_name = total_water_storage_in_aquifer
long_name = total water storage in aquifer
units = kg m-2
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = inout
[lheatstrg]
standard_name = flag_for_canopy_heat_storage_in_land_surface_scheme
long_name = flag for canopy heat storage parameterization
Expand Down
11 changes: 7 additions & 4 deletions physics/GFS_surface_loop_control.F90
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,8 @@ end subroutine GFS_surface_loop_control_part1_finalize
!! \section detailed Detailed Algorithm
!! @{

subroutine GFS_surface_loop_control_part1_run (im, iter, wind, flag_guess, errmsg, errflg)
subroutine GFS_surface_loop_control_part1_run (im, iter, &
wind, flag_guess, errmsg, errflg)

use machine, only: kind_phys

Expand Down Expand Up @@ -78,8 +79,8 @@ end subroutine GFS_surface_loop_control_part2_finalize
!! \section detailed Detailed Algorithm
!! @{

subroutine GFS_surface_loop_control_part2_run (im, iter, wind, &
flag_guess, flag_iter, dry, wet, icy, nstf_name1, errmsg, errflg)
subroutine GFS_surface_loop_control_part2_run (im, lsm, lsm_noahmp, iter,&
wind, flag_guess, flag_iter, dry, wet, icy, nstf_name1, errmsg, errflg)

use machine, only: kind_phys

Expand All @@ -88,6 +89,8 @@ subroutine GFS_surface_loop_control_part2_run (im, iter, wind, &
! Interface variables
integer, intent(in) :: im
integer, intent(in) :: iter
integer, intent(in) :: lsm
integer, intent(in) :: lsm_noahmp
real(kind=kind_phys), dimension(:), intent(in) :: wind
logical, dimension(:), intent(inout) :: flag_guess
logical, dimension(:), intent(inout) :: flag_iter
Expand All @@ -110,7 +113,7 @@ subroutine GFS_surface_loop_control_part2_run (im, iter, wind, &

if (iter == 1 .and. wind(i) < 2.0d0) then
!if (dry(i) .or. (wet(i) .and. .not.icy(i) .and. nstf_name1 > 0)) then
if (dry(i) .or. (wet(i) .and. nstf_name1 > 0)) then
if((dry(i) .and. lsm /= lsm_noahmp) .or. (wet(i) .and. nstf_name1 > 0)) then
flag_iter(i) = .true.
endif
endif
Expand Down
14 changes: 14 additions & 0 deletions physics/GFS_surface_loop_control.meta
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,20 @@
dimensions = ()
type = integer
intent = in
[lsm]
standard_name = control_for_land_surface_scheme
long_name = flag for land surface model
units = flag
dimensions = ()
type = integer
intent = in
[lsm_noahmp]
standard_name = identifier_for_noahmp_land_surface_scheme
long_name = flag for NOAH MP land surface model
units = flag
dimensions = ()
type = integer
intent = in
[iter]
standard_name = ccpp_loop_counter
long_name = loop counter for subcycling loops in CCPP
Expand Down
Loading

0 comments on commit d9e6676

Please sign in to comment.