Skip to content

Commit

Permalink
Merge pull request #717 from mzhangw/redund_mzhang
Browse files Browse the repository at this point in the history
Redundant surface variable cleanup
  • Loading branch information
climbfuji authored Aug 17, 2021
2 parents 55e0814 + e5cdd22 commit 8e670b0
Show file tree
Hide file tree
Showing 16 changed files with 101 additions and 183 deletions.
12 changes: 6 additions & 6 deletions physics/GFS_suite_interstitial.meta
Original file line number Diff line number Diff line change
Expand Up @@ -611,26 +611,26 @@
intent = inout
optional = F
[adjsfculw_lnd]
standard_name = surface_upwelling_longwave_flux_over_land_interstitial
long_name = surface upwelling longwave flux at current time over land (temporary use as interstitial)
standard_name = surface_upwelling_longwave_flux_over_land
long_name = surface upwelling longwave flux at current time over land
units = W m-2
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
optional = F
[adjsfculw_ice]
standard_name = surface_upwelling_longwave_flux_over_ice_interstitial
long_name = surface upwelling longwave flux at current time over ice (temporary use as interstitial)
standard_name = surface_upwelling_longwave_flux_over_ice
long_name = surface upwelling longwave flux at current time over ice
units = W m-2
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
optional = F
[adjsfculw_wat]
standard_name = surface_upwelling_longwave_flux_over_water_interstitial
long_name = surface upwelling longwave flux at current time over water (temporary use as interstitial)
standard_name = surface_upwelling_longwave_flux_over_water
long_name = surface upwelling longwave flux at current time over water
units = W m-2
dimensions = (horizontal_loop_extent)
type = real
Expand Down
42 changes: 16 additions & 26 deletions physics/GFS_surface_composites.F90
Original file line number Diff line number Diff line change
Expand Up @@ -33,9 +33,9 @@ subroutine GFS_surface_composites_pre_run (im, flag_init, flag_restart, lkm, lsm
snowd, snowd_lnd, snowd_ice, tprcp, tprcp_wat, &
tprcp_lnd, tprcp_ice, uustar, uustar_wat, uustar_lnd, uustar_ice, &
weasd, weasd_lnd, weasd_ice, ep1d_ice, tsfc, tsfco, tsfcl, tsfc_wat, &
tsfc_lnd, tsfc_ice, tisfc, tice, tsurf_wat, tsurf_lnd, tsurf_ice, &
tsfc_ice, tisfc, tsurf_wat, tsurf_lnd, tsurf_ice, &
gflx_ice, tgice, islmsk, islmsk_cice, slmsk, semis_rad, semis_wat, semis_lnd, semis_ice, &
emis_lnd, emis_ice, qss, qss_wat, qss_lnd, qss_ice, hflx, hflx_wat, hflx_lnd, hflx_ice, &
emis_lnd, emis_ice, qss, qss_wat, qss_lnd, qss_ice, &
min_lakeice, min_seaice, kdt, errmsg, errflg)

implicit none
Expand All @@ -49,14 +49,13 @@ subroutine GFS_surface_composites_pre_run (im, flag_init, flag_restart, lkm, lsm
real(kind=kind_phys), dimension(:), intent(in ) :: landfrac, lakefrac, lakedepth, oceanfrac
real(kind=kind_phys), dimension(:), intent(inout) :: cice, hice
real(kind=kind_phys), dimension(:), intent( out) :: frland
real(kind=kind_phys), dimension(:), intent(in ) :: snowd, tprcp, uustar, weasd, qss, hflx
real(kind=kind_phys), dimension(:), intent(in ) :: snowd, tprcp, uustar, weasd, qss

real(kind=kind_phys), dimension(:), intent(inout) :: tsfc, tsfco, tsfcl, tisfc
real(kind=kind_phys), dimension(:), intent(inout) :: snowd_lnd, snowd_ice, tprcp_wat, &
tprcp_lnd, tprcp_ice, tsfc_wat, tsfc_lnd, tsfc_ice, tsurf_wat,tsurf_lnd, tsurf_ice, &
tprcp_lnd, tprcp_ice, tsfc_wat, tsfc_ice, tsurf_wat,tsurf_lnd, tsurf_ice, &
uustar_wat, uustar_lnd, uustar_ice, weasd_lnd, weasd_ice, &
qss_wat, qss_lnd, qss_ice, hflx_wat, hflx_lnd, hflx_ice, ep1d_ice, gflx_ice
real(kind=kind_phys), dimension(:), intent( out) :: tice
qss_wat, qss_lnd, qss_ice, ep1d_ice, gflx_ice
real(kind=kind_phys), intent(in ) :: tgice
integer, dimension(:), intent(inout) :: islmsk, islmsk_cice
real(kind=kind_phys), dimension(:), intent(in ) :: semis_rad
Expand Down Expand Up @@ -229,7 +228,6 @@ subroutine GFS_surface_composites_pre_run (im, flag_init, flag_restart, lkm, lsm
if (dry(i)) then ! Land
uustar_lnd(i) = uustar(i)
weasd_lnd(i) = weasd(i)
tsfc_lnd(i) = tsfcl(i)
tsurf_lnd(i) = tsfcl(i)
if (iemsflg == 2 .and. .not. flag_init) then
!-- use land emissivity from the LSM
Expand All @@ -241,6 +239,8 @@ subroutine GFS_surface_composites_pre_run (im, flag_init, flag_restart, lkm, lsm
else
zorll(i) = huge
! *DH
!mjz
tsfcl(i) = huge
endif
if (icy(i)) then ! Ice
uustar_ice(i) = uustar(i)
Expand Down Expand Up @@ -315,11 +315,6 @@ subroutine GFS_surface_composites_pre_run (im, flag_init, flag_restart, lkm, lsm

! write(0,*)' minmax of ice snow=',minval(snowd_ice),maxval(snowd_ice)

! Assign sea ice temperature to interstitial variable
do i = 1, im
tice(i) = tisfc(i)
enddo

end subroutine GFS_surface_composites_pre_run

end module GFS_surface_composites_pre
Expand Down Expand Up @@ -437,7 +432,7 @@ subroutine GFS_surface_composites_post_run (
cmm, cmm_wat, cmm_lnd, cmm_ice, chh, chh_wat, chh_lnd, chh_ice, gflx, gflx_wat, gflx_lnd, gflx_ice, ep1d, ep1d_wat, &
ep1d_lnd, ep1d_ice, weasd, weasd_lnd, weasd_ice, snowd, snowd_lnd, snowd_ice, tprcp, tprcp_wat, &
tprcp_lnd, tprcp_ice, evap, evap_wat, evap_lnd, evap_ice, hflx, hflx_wat, hflx_lnd, hflx_ice, qss, qss_wat, qss_lnd, &
qss_ice, tsfc, tsfco, tsfcl, tsfc_wat, tsfc_lnd, tsfc_ice, tisfc, tice, hice, cice, min_seaice, tiice, &
qss_ice, tsfc, tsfco, tsfcl, tsfc_wat, tsfc_ice, tisfc, hice, cice, min_seaice, tiice, &
sigmaf, zvfun, lheatstrg, h0facu, h0facs, hflxq, hffac, stc, &
grav, prsik1, prslk1, prslki, z1, ztmax_wat, ztmax_lnd, ztmax_ice, errmsg, errflg)

Expand All @@ -454,12 +449,11 @@ subroutine GFS_surface_composites_post_run (
fm10_wat, fm10_lnd, fm10_ice, fh2_wat, fh2_lnd, fh2_ice, tsurf_wat, tsurf_lnd, tsurf_ice, cmm_wat, cmm_lnd, cmm_ice, &
chh_wat, chh_lnd, chh_ice, gflx_wat, gflx_lnd, gflx_ice, ep1d_wat, ep1d_lnd, ep1d_ice, weasd_lnd, weasd_ice, &
snowd_lnd, snowd_ice, tprcp_wat, tprcp_lnd, tprcp_ice, evap_wat, evap_lnd, evap_ice, hflx_wat, hflx_lnd, &
hflx_ice, qss_wat, qss_lnd, qss_ice, tsfc_wat, tsfc_lnd, tsfc_ice, zorlo, zorll, zorli, garea
hflx_ice, qss_wat, qss_lnd, qss_ice, tsfc_wat, tsfc_ice, zorlo, zorll, zorli, garea

real(kind=kind_phys), dimension(:), intent(inout) :: zorl, cd, cdq, rb, stress, ffmm, ffhh, uustar, fm10, &
fh2, cmm, chh, gflx, ep1d, weasd, snowd, tprcp, evap, hflx, qss, tsfc, tsfco, tsfcl, tisfc

real(kind=kind_phys), dimension(:), intent(in ) :: tice ! interstitial sea ice temperature
real(kind=kind_phys), dimension(:), intent(inout) :: hice, cice
real(kind=kind_phys), dimension(:), intent(inout) :: sigmaf, zvfun, hflxq, hffac
real(kind=kind_phys), intent(in ) :: h0facu, h0facs
Expand Down Expand Up @@ -537,8 +531,8 @@ subroutine GFS_surface_composites_post_run (
! layer parameterization being used - to be extended in the future !
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

tsfc(i) = ( txl * cdq_lnd(i) * tsfc_lnd(i) &
+ txi * cdq_ice(i) * tice(i) & ! DH* Ben had tsurf_ice(i), but GFS_surface_composites_post_run uses tice instead
tsfc(i) = ( txl * cdq_lnd(i) * tsfcl(i) &
+ txi * cdq_ice(i) * tisfc(i) & ! DH* Ben had tsurf_ice(i), but GFS_surface_composites_post_run uses tice instead
+ txo * cdq_wat(i) * tsfc_wat(i)) &
/ (txl * cdq_lnd(i) + txi * cdq_ice(i) + txo * cdq_wat(i) )
tsurf = ( txl * cdq_lnd(i) * tsurf_lnd(i) &
Expand Down Expand Up @@ -632,25 +626,24 @@ subroutine GFS_surface_composites_post_run (
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

if (dry(i)) then
tsfcl(i) = tsfc_lnd(i) ! over land
elseif (wet(i)) then
tsfcl(i) = tsfc_wat(i) ! over water
else
tsfcl(i) = tice(i) ! over ice
tsfcl(i) = tisfc(i) ! over ice
endif
if (wet(i)) then
tsfco(i) = tsfc_wat(i) ! over lake or ocean when uncoupled
elseif (icy(i)) then
tsfco(i) = tice(i) ! over lake or ocean ice when uncoupled
tsfco(i) = tisfc(i) ! over lake or ocean ice when uncoupled
else
tsfco(i) = tsfc_lnd(i) ! over land
tsfco(i) = tsfcl(i) ! over land
endif
if (icy(i)) then
tisfc(i) = tice(i) ! over lake or ocean ice when uncoupled
!tisfc(i) = tisfc(i) ! over lake or ocean ice when uncoupled
elseif (wet(i)) then
tisfc(i) = tsfc_wat(i) ! over lake or ocean when uncoupled
else
tisfc(i) = tsfc_lnd(i) ! over land
tisfc(i) = tsfcl(i) ! over land
endif
! for coupled model ocean will replace this
! if (icy(i)) tisfc(i) = tsfc_ice(i) ! over ice when uncoupled
Expand Down Expand Up @@ -690,7 +683,6 @@ subroutine GFS_surface_composites_post_run (
uustar(i) = uustar_lnd(i)
fm10(i) = fm10_lnd(i)
fh2(i) = fh2_lnd(i)
tsfcl(i) = tsfc_lnd(i) ! over land
tsfc(i) = tsfcl(i)
tsfco(i) = tsfc(i)
tisfc(i) = tsfc(i)
Expand Down Expand Up @@ -749,10 +741,8 @@ subroutine GFS_surface_composites_post_run (
weasd(i) = weasd_ice(i) * cice(i)
snowd(i) = snowd_ice(i) * cice(i)
qss(i) = qss_ice(i)
tsfc(i) = tsfc_ice(i)
evap(i) = evap_ice(i)
hflx(i) = hflx_ice(i)
tisfc(i) = tice(i) ! over lake ice (and sea ice when uncoupled)
tsfc(i) = tsfc_ice(i) ! over lake (and ocean when uncoupled)
!
if (flag_cice(i)) then
Expand Down
96 changes: 12 additions & 84 deletions physics/GFS_surface_composites.meta
Original file line number Diff line number Diff line change
Expand Up @@ -396,26 +396,17 @@
intent = inout
optional = F
[tsfc_wat]
standard_name = surface_skin_temperature_over_water_interstitial
long_name = surface skin temperature over water (temporary use as interstitial)
units = K
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = inout
optional = F
[tsfc_lnd]
standard_name = surface_skin_temperature_over_land_interstitial
long_name = surface skin temperature over land (temporary use as interstitial)
standard_name = surface_skin_temperature_over_water
long_name = surface skin temperature over water
units = K
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = inout
optional = F
[tsfc_ice]
standard_name = surface_skin_temperature_over_ice_interstitial
long_name = surface skin temperature over ice (temporary use as interstitial)
standard_name = surface_skin_temperature_over_ice
long_name = surface skin temperature over ice
units = K
dimensions = (horizontal_loop_extent)
type = real
Expand All @@ -431,15 +422,6 @@
kind = kind_phys
intent = inout
optional = F
[tice]
standard_name = sea_ice_temperature_interstitial
long_name = sea ice surface skin temperature use as interstitial
units = K
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
optional = F
[tsurf_wat]
standard_name = surface_skin_temperature_after_iteration_over_water
long_name = surface skin temperature after iteration over water
Expand Down Expand Up @@ -520,8 +502,8 @@
intent = in
optional = F
[semis_wat]
standard_name = surface_longwave_emissivity_over_water_interstitial
long_name = surface lw emissivity in fraction over water (temporary use as interstitial)
standard_name = surface_longwave_emissivity_over_water
long_name = surface lw emissivity in fraction over water
units = frac
dimensions = (horizontal_loop_extent)
type = real
Expand Down Expand Up @@ -600,42 +582,6 @@
kind = kind_phys
intent = inout
optional = F
[hflx]
standard_name = surface_upward_temperature_flux
long_name = kinematic surface upward sensible heat flux
units = K m s-1
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
optional = F
[hflx_wat]
standard_name = kinematic_surface_upward_sensible_heat_flux_over_water
long_name = kinematic surface upward sensible heat flux over water
units = K m s-1
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = inout
optional = F
[hflx_lnd]
standard_name = kinematic_surface_upward_sensible_heat_flux_over_land
long_name = kinematic surface upward sensible heat flux over land
units = K m s-1
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = inout
optional = F
[hflx_ice]
standard_name = kinematic_surface_upward_sensible_heat_flux_over_ice
long_name = kinematic surface upward sensible heat flux over ice
units = K m s-1
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = inout
optional = F
[min_lakeice]
standard_name = min_lake_ice_area_fraction
long_name = minimum lake ice value
Expand Down Expand Up @@ -723,8 +669,8 @@
intent = in
optional = F
[semis_wat]
standard_name = surface_longwave_emissivity_over_water_interstitial
long_name = surface lw emissivity in fraction over water (temporary use as interstitial)
standard_name = surface_longwave_emissivity_over_water
long_name = surface lw emissivity in fraction over water
units = frac
dimensions = (horizontal_loop_extent)
type = real
Expand Down Expand Up @@ -1774,26 +1720,17 @@
intent = inout
optional = F
[tsfc_wat]
standard_name = surface_skin_temperature_over_water_interstitial
long_name = surface skin temperature over water (temporary use as interstitial)
units = K
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
optional = F
[tsfc_lnd]
standard_name = surface_skin_temperature_over_land_interstitial
long_name = surface skin temperature over land (temporary use as interstitial)
standard_name = surface_skin_temperature_over_water
long_name = surface skin temperature over water
units = K
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
optional = F
[tsfc_ice]
standard_name = surface_skin_temperature_over_ice_interstitial
long_name = surface skin temperature over ice (temporary use as interstitial)
standard_name = surface_skin_temperature_over_ice
long_name = surface skin temperature over ice
units = K
dimensions = (horizontal_loop_extent)
type = real
Expand All @@ -1809,15 +1746,6 @@
kind = kind_phys
intent = inout
optional = F
[tice]
standard_name = sea_ice_temperature_interstitial
long_name = sea ice surface skin temperature use as interstitial
units = K
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
optional = F
[hice]
standard_name = sea_ice_thickness
long_name = sea ice thickness
Expand Down
8 changes: 4 additions & 4 deletions physics/GFS_surface_generic.meta
Original file line number Diff line number Diff line change
Expand Up @@ -627,8 +627,8 @@
intent = in
optional = F
[adjsfculw_wat]
standard_name = surface_upwelling_longwave_flux_over_water_interstitial
long_name = surface upwelling longwave flux at current time over water (temporary use as interstitial)
standard_name = surface_upwelling_longwave_flux_over_water
long_name = surface upwelling longwave flux at current time over water
units = W m-2
dimensions = (horizontal_loop_extent)
type = real
Expand Down Expand Up @@ -717,8 +717,8 @@
intent = in
optional = F
[tsfc_wat]
standard_name = surface_skin_temperature_over_water_interstitial
long_name = surface skin temperature over water (temporary use as interstitial)
standard_name = surface_skin_temperature_over_water
long_name = surface skin temperature over water
units = K
dimensions = (horizontal_loop_extent)
type = real
Expand Down
Loading

0 comments on commit 8e670b0

Please sign in to comment.