Skip to content

Commit

Permalink
merge NOAA-GSL#148
Browse files Browse the repository at this point in the history
  • Loading branch information
SamuelTrahanNOAA committed Dec 19, 2023
2 parents 407db6b + c61295f commit 111d273
Show file tree
Hide file tree
Showing 5 changed files with 29 additions and 4 deletions.
4 changes: 3 additions & 1 deletion physics/GFS_surface_composites_pre.F90
Original file line number Diff line number Diff line change
Expand Up @@ -241,8 +241,10 @@ subroutine GFS_surface_composites_pre_run (im, lkm, frac_grid, iopt_lake, iopt_l
!mjz
tsfcl(i) = huge
endif
if (icy(i) .or. wet(i)) then ! init uustar_ice for all water/ice grids
uustar_ice(i) = uustar(i)
endif
if (icy(i)) then ! Ice
uustar_ice(i) = uustar(i)
is_clm = lkm>0 .and. iopt_lake==iopt_lake_clm .and. use_lake_model(i)>0
if(lsm /= lsm_ruc .and. .not.is_clm) then
weasd_ice(i) = weasd(i)
Expand Down
11 changes: 9 additions & 2 deletions physics/clm_lake.f90
Original file line number Diff line number Diff line change
Expand Up @@ -270,8 +270,8 @@ SUBROUTINE clm_lake_run( &

! Atmospheric model state inputs:
tg3, pgr, zlvl, gt0, prsi, phii, qvcurr, gu0, gv0, xlat_d, xlon_d, &
ch, cm, dlwsfci, dswsfci, oro_lakedepth, wind, tsfc, &
flag_iter, ISLTYP, rainncprv, raincprv, &
ch, cm, dlwsfci, dswsfci, oro_lakedepth, wind, rho0, tsfc, &
flag_iter, flag_lakefreeze, ISLTYP, rainncprv, raincprv, &

! Feedback to atmosphere:
evap_wat, evap_ice, hflx_wat, hflx_ice, gflx_wat, gflx_ice, &
Expand Down Expand Up @@ -328,6 +328,8 @@ SUBROUTINE clm_lake_run( &
rainncprv, raincprv, t1, qv1, prsl1
REAL(KIND_PHYS), DIMENSION(:,:), INTENT(in) :: gu0, gv0, prsi, gt0, phii
LOGICAL, DIMENSION(:), INTENT(IN) :: flag_iter
LOGICAL, DIMENSION(:), INTENT(INOUT) :: flag_lakefreeze

INTEGER, DIMENSION(:), INTENT(IN) :: ISLTYP

!
Expand Down Expand Up @@ -759,6 +761,11 @@ SUBROUTINE clm_lake_run( &
weasd(i) = weasdi(i)
snowd(i) = snodi(c) ! surface_snow_thickness_water_equivalent_over_ice


if (.not. icy(i)) then
flag_lakefreeze(i)=.true.
end if

! Ice points are icy:
icy(i)=.true. ! flag_nonzero_sea_ice_surface_fraction
ice_points = ice_points+1
Expand Down
7 changes: 7 additions & 0 deletions physics/clm_lake.meta
Original file line number Diff line number Diff line change
Expand Up @@ -320,6 +320,13 @@
dimensions = (horizontal_loop_extent)
type = logical
intent = in
[flag_lakefreeze]
standard_name = flag_for_lake_water_freeze
long_name = flag for lake water freeze
units = flag
dimensions = (horizontal_loop_extent)
type = logical
intent = inout
[isltyp]
standard_name = soil_type_classification
long_name = soil type at each grid cell
Expand Down
4 changes: 3 additions & 1 deletion physics/sfc_diff.f
Original file line number Diff line number Diff line change
Expand Up @@ -60,6 +60,7 @@ subroutine sfc_diff_run (im,rvrdm1,eps,epsm1,grav, & !intent(in)
& sigmaf,vegtype,shdmax,ivegsrc, & !intent(in)
& z0pert,ztpert, & ! mg, sfc-perts !intent(in)
& flag_iter,redrag, & !intent(in)
& flag_lakefreeze, & !intent(in)
& u10m,v10m,sfc_z0_type, & !hafs,z0 type !intent(in)
& wet,dry,icy, & !intent(in)
& thsfc_loc, & !intent(in)
Expand Down Expand Up @@ -90,6 +91,7 @@ subroutine sfc_diff_run (im,rvrdm1,eps,epsm1,grav, & !intent(in)
logical, intent(in) :: redrag ! reduced drag coeff. flag for high wind over sea (j.han)
logical, dimension(:), intent(in) :: flag_iter, dry, icy
logical, dimension(:), intent(in) :: flag_lakefreeze
logical, dimension(:), intent(inout) :: wet
logical, intent(in) :: thsfc_loc ! Flag for reference pressure in theta calculation
Expand Down Expand Up @@ -168,7 +170,7 @@ subroutine sfc_diff_run (im,rvrdm1,eps,epsm1,grav, & !intent(in)
! write(0,*)'in sfc_diff, sfc_z0_type=',sfc_z0_type
do i=1,im
if(flag_iter(i)) then
if(flag_iter(i) .or. flag_lakefreeze(i)) then
! Need to initialize ztmax arrays
ztmax_lnd(i) = 1. ! log(1) = 0
Expand Down
7 changes: 7 additions & 0 deletions physics/sfc_diff.meta
Original file line number Diff line number Diff line change
Expand Up @@ -194,6 +194,13 @@
dimensions = ()
type = logical
intent = in
[flag_lakefreeze]
standard_name = flag_for_lake_water_freeze
long_name = flag for lake water freeze
units = flag
dimensions = (horizontal_loop_extent)
type = logical
intent = in
[u10m]
standard_name = x_wind_at_10m
long_name = 10 meter u wind speed
Expand Down

0 comments on commit 111d273

Please sign in to comment.