Skip to content

Commit

Permalink
Merge pull request NCAR#45 from HelinWei-NOAA/flake.v9
Browse files Browse the repository at this point in the history
Updated Flake physics and modified related files
  • Loading branch information
HelinWei-NOAA authored Aug 10, 2022
2 parents ee43baf + cbbc106 commit a343c92
Show file tree
Hide file tree
Showing 25 changed files with 656 additions and 208 deletions.
21 changes: 20 additions & 1 deletion physics/GFS_phys_time_vary.fv3.F90
Original file line number Diff line number Diff line change
Expand Up @@ -82,7 +82,7 @@ subroutine GFS_phys_time_vary_init (
zwtxy, xlaixy, xsaixy, lfmassxy, stmassxy, rtmassxy, woodxy, stblcpxy, fastcpxy, &
smcwtdxy, deeprechxy, rechxy, snowxy, snicexy, snliqxy, tsnoxy , smoiseq, zsnsoxy, &
slc, smc, stc, tsfcl, snowd, canopy, tg3, stype, con_t0c, lsm_cold_start, nthrds, &
errmsg, errflg)
lkm, use_flake, lakefrac, lakedepth, errmsg, errflg)

implicit none

Expand All @@ -93,6 +93,10 @@ subroutine GFS_phys_time_vary_init (
real(kind_phys), intent(in) :: fhour
real(kind_phys), intent(in) :: xlat_d(:), xlon_d(:)

integer, intent(in) :: lkm
integer, intent(inout) :: use_flake(:)
real(kind=kind_phys), intent(in ) :: lakefrac(:), lakedepth(:)

integer, intent(inout) :: jindx1_o3(:), jindx2_o3(:), jindx1_h(:), jindx2_h(:)
real(kind_phys), intent(inout) :: ddy_o3(:), ddy_h(:)
real(kind_phys), intent(in) :: ozpl(:,:,:), h2opl(:,:,:)
Expand Down Expand Up @@ -672,6 +676,21 @@ subroutine GFS_phys_time_vary_init (
endif noahmp_init
endif lsm_init

!Flake
do i = 1, im
if (lakefrac(i) > 0.0 .and. lakedepth(i) > 1.0 ) then
if (lkm == 1 ) then
use_flake(i) = 1
elseif (lkm == 2 ) then
use_flake(i) = 2
else
use_flake(i) = 0
endif
else
use_flake(i) = 0
endif
enddo

is_initialized = .true.

contains
Expand Down
30 changes: 30 additions & 0 deletions physics/GFS_phys_time_vary.fv3.meta
Original file line number Diff line number Diff line change
Expand Up @@ -895,6 +895,36 @@
dimensions = ()
type = integer
intent = in
[lkm]
standard_name = control_for_lake_surface_scheme
long_name = flag for lake surface model
units = flag
dimensions = ()
type = integer
intent = in
[use_flake]
standard_name = flag_for_using_flake
long_name = flag indicating lake points using flake model
units = flag
dimensions = (horizontal_dimension)
type = integer
intent = inout
[lakefrac]
standard_name = lake_area_fraction
long_name = fraction of horizontal grid area occupied by lake
units = frac
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
[lakedepth]
standard_name = lake_depth
long_name = lake depth
units = m
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
3 changes: 2 additions & 1 deletion physics/GFS_radiation_surface.F90
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,8 @@ subroutine GFS_radiation_surface_run ( &
logical, intent(in) :: frac_grid, lslwr, lsswr, use_cice_alb, cplice
integer, intent(in) :: lsm, lsm_noahmp, lsm_ruc, lndp_type, n_var_lndp
real(kind=kind_phys), intent(in) :: min_seaice, min_lakeice
logical, dimension(:), intent(in) :: use_flake

integer, dimension(:), intent(in) :: use_flake

real(kind=kind_phys), dimension(:), intent(in) :: xlat, xlon, slmsk, &
sfc_alb_pert, lndp_prt_list, &
Expand Down
2 changes: 1 addition & 1 deletion physics/GFS_radiation_surface.meta
Original file line number Diff line number Diff line change
Expand Up @@ -291,7 +291,7 @@
long_name = flag indicating lake points using flake model
units = flag
dimensions = (horizontal_loop_extent)
type = logical
type = integer
intent = inout
[alvsf]
standard_name = vis_albedo_strong_cosz
Expand Down
9 changes: 6 additions & 3 deletions physics/GFS_surface_composites_inter.F90
Original file line number Diff line number Diff line change
Expand Up @@ -18,17 +18,19 @@ module GFS_surface_composites_inter
!!
subroutine GFS_surface_composites_inter_run (im, dry, icy, wet, semis_wat, semis_lnd, semis_ice, &
adjsfcdlw, gabsbdlw_lnd, gabsbdlw_ice, gabsbdlw_wat,&
adjsfcusw, adjsfcdsw, adjsfcnsw, errmsg, errflg)
adjsfcusw, adjsfcdsw, adjsfcnsw, use_flake, errmsg, errflg)

implicit none

! Interface variables
integer, intent(in ) :: im
logical, dimension(:), intent(in ) :: dry, icy, wet
logical, dimension(:), intent(in ) :: dry, icy
logical, dimension(:), intent(inout) :: wet
real(kind=kind_phys), dimension(:), intent(in ) :: semis_wat, semis_lnd, semis_ice, &
adjsfcdlw, adjsfcdsw, adjsfcnsw
real(kind=kind_phys), dimension(:), intent(inout) :: gabsbdlw_lnd, gabsbdlw_ice, gabsbdlw_wat
real(kind=kind_phys), dimension(:), intent(out) :: adjsfcusw
integer, dimension(:), intent(in) :: use_flake

! CCPP error handling
character(len=*), intent(out) :: errmsg
Expand Down Expand Up @@ -60,6 +62,7 @@ subroutine GFS_surface_composites_inter_run (im, dry, icy, wet, semis_wat, semis

! --- ... define the downward lw flux absorbed by ground
do i=1,im
if(use_flake(i)>0.0) wet(i)=.true.
if (dry(i)) gabsbdlw_lnd(i) = semis_lnd(i) * adjsfcdlw(i)
if (icy(i)) gabsbdlw_ice(i) = semis_ice(i) * adjsfcdlw(i)
if (wet(i)) gabsbdlw_wat(i) = semis_wat(i) * adjsfcdlw(i)
Expand All @@ -68,4 +71,4 @@ subroutine GFS_surface_composites_inter_run (im, dry, icy, wet, semis_wat, semis

end subroutine GFS_surface_composites_inter_run

end module GFS_surface_composites_inter
end module GFS_surface_composites_inter
11 changes: 9 additions & 2 deletions physics/GFS_surface_composites_inter.meta
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@
units = flag
dimensions = (horizontal_loop_extent)
type = logical
intent = in
intent = inout
[semis_wat]
standard_name = surface_longwave_emissivity_over_water
long_name = surface lw emissivity in fraction over water
Expand Down Expand Up @@ -116,6 +116,13 @@
type = real
kind = kind_phys
intent = in
[use_flake]
standard_name = flag_for_using_flake
long_name = flag indicating lake points using flake model
units = flag
dimensions = (horizontal_loop_extent)
type = integer
intent = in
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand All @@ -130,4 +137,4 @@
units = 1
dimensions = ()
type = integer
intent = out
intent = out
14 changes: 11 additions & 3 deletions physics/GFS_surface_composites_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,8 @@ subroutine GFS_surface_composites_post_run (
integer, intent(in) :: im, kice, km
logical, intent(in) :: cplflx, frac_grid, cplwav2atm
logical, intent(in) :: lheatstrg
logical, dimension(:), intent(in) :: flag_cice, dry, wet, icy
logical, dimension(:), intent(in) :: flag_cice, dry, icy
logical, dimension(:), intent(inout) :: wet
integer, dimension(:), intent(in) :: islmsk
real(kind=kind_phys), dimension(:), intent(in) :: wind, t1, q1, prsl1, landfrac, lakefrac, oceanfrac, &
cd_wat, cd_lnd, cd_ice, cdq_wat, cdq_lnd, cdq_ice, rb_wat, rb_lnd, rb_ice, stress_wat, &
Expand Down Expand Up @@ -87,6 +88,11 @@ subroutine GFS_surface_composites_post_run (
errflg = 0

! --- generate ocean/land/ice composites
do i=1, im
if(lakefrac(i)>0.0) then
wet(i) = .true.
endif
enddo

if (frac_grid) then

Expand Down Expand Up @@ -263,7 +269,8 @@ subroutine GFS_surface_composites_post_run (
else

do i=1,im
if (islmsk(i) == 1) then
! if (islmsk(i) == 1) then
if (dry(i)) then
!-- land
zorl(i) = zorll(i)
cd(i) = cd_lnd(i)
Expand All @@ -289,7 +296,8 @@ subroutine GFS_surface_composites_post_run (
qss(i) = qss_lnd(i)
hice(i) = zero
cice(i) = zero
elseif (islmsk(i) == 0) then
! elseif (islmsk(i) == 0) then
elseif (wet(i)) then
!-- water
zorl(i) = zorlo(i)
cd(i) = cd_wat(i)
Expand Down
23 changes: 8 additions & 15 deletions physics/GFS_surface_composites_pre.F90
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,8 @@ subroutine GFS_surface_composites_pre_run (im, lkm, frac_grid,
integer, intent(in ) :: im, lkm, kdt, lsm, lsm_ruc
logical, intent(in ) :: cplflx, cplice, cplwav2atm, frac_grid
logical, dimension(:), intent(inout) :: flag_cice
logical, dimension(:), intent(inout) :: dry, icy, lake, use_flake, wet
logical, dimension(:), intent(inout) :: dry, icy, lake, wet
integer, dimension(:), intent(inout) :: use_flake
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
Expand Down Expand Up @@ -71,6 +72,12 @@ subroutine GFS_surface_composites_pre_run (im, lkm, frac_grid,
errmsg = ''
errflg = 0

do i=1,im
if(use_flake(i) > 0.0) then
wet(i) = .true.
endif
enddo

if (frac_grid) then ! cice is ice fraction wrt water area
do i=1,im
frland(i) = landfrac(i)
Expand Down Expand Up @@ -239,20 +246,6 @@ subroutine GFS_surface_composites_pre_run (im, lkm, frac_grid,
if (nint(slmsk(i)) /= 1) slmsk(i) = islmsk(i)
enddo

! to prepare to separate lake from ocean under water category
do i = 1, im
if ((wet(i) .or. icy(i)) .and. lakefrac(i) > zero) then
lake(i) = .true.
if (lkm == 1 .and. lakefrac(i) >= 0.15 .and. lakedepth(i) > one) then
use_flake(i) = .true.
else
use_flake(i) = .false.
endif
else
lake(i) = .false.
use_flake(i) = .false.
endif
enddo
!
if (frac_grid) then
do i=1,im
Expand Down
4 changes: 2 additions & 2 deletions physics/GFS_surface_composites_pre.meta
Original file line number Diff line number Diff line change
Expand Up @@ -136,7 +136,7 @@
long_name = flag indicating lake points using flake model
units = flag
dimensions = (horizontal_loop_extent)
type = logical
type = integer
intent = inout
[wet]
standard_name = flag_nonzero_wet_surface_fraction
Expand Down Expand Up @@ -484,4 +484,4 @@
units = 1
dimensions = ()
type = integer
intent = out
intent = out
Loading

0 comments on commit a343c92

Please sign in to comment.