Skip to content

Commit

Permalink
Having skinsst to operate on ocean points, while nsst on lake points
Browse files Browse the repository at this point in the history
  • Loading branch information
ShanSunNOAA committed Jul 25, 2024
1 parent 9687537 commit 4e998d6
Show file tree
Hide file tree
Showing 5 changed files with 63 additions and 114 deletions.
70 changes: 13 additions & 57 deletions physics/SFC_Layer/UFS/sfc_nst.f90
Original file line number Diff line number Diff line change
Expand Up @@ -28,8 +28,8 @@ subroutine sfc_nst_run &
( im, hvap, cp, hfus, jcal, eps, epsm1, rvrdm1, rd, rhw0, & ! --- inputs:
pi, tgice, sbc, ps, u1, v1, usfco, vsfco, icplocn2atm, t1, &
q1, tref, cm, ch, lseaspray, fm, fm10, &
prsl1, prslki, prsik1, prslk1, wet, use_lake_model, xlon, &
xlat, sinlat, stress, &
prsl1, prslki, prsik1, prslk1, wet, oceanfrac, &
use_lake_model, xlon, sinlat, stress, &
sfcemis, dlwflx, sfcnsw, rain, timestep, kdt, solhr,xcosz, &
wind, flag_iter, flag_guess, nstf_name1, nstf_name4, &
nstf_name5, lprnt, ipr, thsfc_loc, &
Expand All @@ -51,7 +51,7 @@ subroutine sfc_nst_run &
! prsl1, prslki, wet, use_lake_model, xlon, sinlat, stress, !
! sfcemis, dlwflx, sfcnsw, rain, timestep, kdt,solhr,xcosz, !
! wind, flag_iter, flag_guess, nstf_name1, nstf_name4, !
! nstf_name5, lprnt, ipr, thsfc_loc, xlat !
! nstf_name5, lprnt, ipr, thsfc_loc, !
! input/outputs: !
! tskin, tsurf, xt, xs, xu, xv, xz, zm, xtts, xzts, dt_cool, !
! z_c, c_0, c_d, w_0, w_d, d_conv, ifd, qrain, !
Expand Down Expand Up @@ -104,7 +104,6 @@ subroutine sfc_nst_run &
! use_lake_model- logical, =T if flake model is used for lake im !
! icy - logical, =T if any ice im !
! xlon - real, longitude (radians) im !
! xlat - real, latitude (radians) im !
! sinlat - real, sin of latitude im !
! stress - real, wind stress (n/m**2) im !
! sfcemis - real, sfc lw emissivity (fraction) im !
Expand Down Expand Up @@ -176,8 +175,8 @@ subroutine sfc_nst_run &
real (kind=kind_phys), intent(in) :: hvap, cp, hfus, jcal, eps, &
epsm1, rvrdm1, rd, rhw0, sbc, pi, tgice
real (kind=kind_phys), dimension(:), intent(in) :: ps, u1, v1, &
usfco, vsfco, t1, q1, cm, ch, fm, fm10, &
prsl1, prslki, prsik1, prslk1, xlon, xlat,xcosz, &
usfco, vsfco, t1, q1, cm, ch, fm, fm10, oceanfrac, &
prsl1, prslki, prsik1, prslk1, xlon, xcosz, &
sinlat, stress, sfcemis, dlwflx, sfcnsw, rain, wind
real (kind=kind_phys), dimension(:), intent(in), optional :: &
tref
Expand Down Expand Up @@ -231,9 +230,9 @@ subroutine sfc_nst_run &
real(kind=kind_phys) :: le,fc,dwat,dtmp,wetc,alfac,ustar_a,rich
real(kind=kind_phys) :: rnl_ts,hs_ts,hl_ts,rf_ts,q_ts
real(kind=kind_phys) :: fw,q_warm
real(kind=kind_phys) :: t12,alon,alat,tsea,sstc,dta,dtz
real(kind=kind_phys) :: t12,alon,tsea,sstc,dta,dtz
real(kind=kind_phys) :: zsea1,zsea2,soltim
logical :: do_nst, doprint
logical :: do_nst
!
! parameters for sea spray effect
!
Expand All @@ -246,16 +245,8 @@ subroutine sfc_nst_run &
real (kind=kind_phys), parameter :: alps=0.75,bets=0.75,gams=0.15, &
ws10cr=30., conlf=7.2e-9, consf=6.4e-8
real (kind=kind_phys) :: windrel

real(kind=kind_phys) :: frz=273.15, small=.05, testlon, testlat
doprint(alon,alat)=abs(testlon-alon).lt.small .and. &
abs(testlat-alat).lt.small
!
!======================================================================================================
call get_testpt(testlon,testlat)
! --- temporary
! print '(a,2f8.2)','entering sfc_nst_run, testpt =',testlon,testlat

! Initialize CCPP error handling variables
errmsg = ''
errflg = 0
Expand All @@ -273,43 +264,19 @@ subroutine sfc_nst_run &
do_nst = .false.
do i = 1, im
! flag(i) = wet(i) .and. .not.icy(i) .and. flag_iter(i)
flag(i) = wet(i) .and. flag_iter(i) .and. use_lake_model(i)/=1
flag(i) = wet(i) .and. flag_iter(i) .and. use_lake_model(i)/=1 &
.and. oceanfrac(i)==0.
do_nst = do_nst .or. flag(i)

alon=xlon(i)*rad2deg
alat=xlat(i)*rad2deg
if (doprint(alon,alat)) then
print 99,'entering sfc_nst_run lon,lat=',alon,alat, &
'xt',xt(i), &
'xs',xs(i), &
'xu',xu(i), &
'xv',xv(i), &
'xz',xz(i), &
'xtts',xtts(i), &
'xzts',xzts(i), &
'wind',wind(i), & ! wind speed
'prsl11',prsl1(i)*.01, & ! atmo layer 1 presure (mb)
't1',t1(i)-frz, & ! atmo layer 1 air temp
'q1',q1(i)*1.e3, & ! atmo layer 1 humidity (g/kg)
'tskin',tskin(i)-frz, & ! ocean skin temperature
'dtcool',dt_cool(i), & ! cool-skin correction
'tref',tref(i)-frz
print '(5(a13,"=",l2))', &
'flag_iter',flag_iter(i), &
'flag_guess',flag_guess(i), &
'flag',flag(i)
end if
99 format (/a,2f7.2/(5(a8,"=",f7.2)))
98 format (/a,2f7.2/(4(a8,"=",es11.4)))

enddo
if (.not. do_nst) return
!
! save nst-related prognostic fields for guess run
!
do i=1, im
! if(wet(i) .and. .not.icy(i) .and. flag_guess(i)) then
if(wet(i) .and. flag_guess(i) .and. use_lake_model(i)/=1) then
if(wet(i) .and. flag_guess(i) .and. use_lake_model(i)/=1 .and. &
oceanfrac(i)==0.) then
xt_old(i) = xt(i)
xs_old(i) = xs(i)
xu_old(i) = xu(i)
Expand Down Expand Up @@ -626,7 +593,8 @@ subroutine sfc_nst_run &
! restore nst-related prognostic fields for guess run
do i=1, im
! if (wet(i) .and. .not.icy(i)) then
if (wet(i) .and. use_lake_model(i)/=1) then
if (wet(i) .and. use_lake_model(i)/=1 .and. oceanfrac(i)==0.) &
then
if (flag_guess(i)) then ! when it is guess of
xt(i) = xt_old(i)
xs(i) = xs_old(i)
Expand Down Expand Up @@ -702,18 +670,6 @@ subroutine sfc_nst_run &
enddo
!
do i=1,im

alon=xlon(i)*rad2deg
alat=xlat(i)*rad2deg
if (doprint(alon,alat)) &
print 99,'exiting sfc_nst_run lon,lat=',alon,alat, &
'evap',evap(i), &
'hflx',hflx(i), &
'tsurf',tsurf(i)-frz, &
'tskin',tskin(i)-frz, &
'xt',xt(i), &
'xz',xz(i)

if ( flag(i) ) then
tem = one / rho_a(i)
hflx(i) = hflx(i) * tem * cpinv
Expand Down
16 changes: 8 additions & 8 deletions physics/SFC_Layer/UFS/sfc_nst.meta
Original file line number Diff line number Diff line change
Expand Up @@ -260,6 +260,14 @@
dimensions = (horizontal_loop_extent)
type = logical
intent = in
[oceanfrac]
standard_name = sea_area_fraction
long_name = fraction of horizontal grid area occupied by ocean
units = frac
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[use_lake_model]
standard_name = flag_for_using_lake_model
long_name = flag indicating lake points using a lake model
Expand All @@ -275,14 +283,6 @@
type = real
kind = kind_phys
intent = in
[xlat]
standard_name = latitude
long_name = latitude
units = radian
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[sinlat]
standard_name = sine_of_latitude
long_name = sine of latitude
Expand Down
9 changes: 5 additions & 4 deletions physics/SFC_Layer/UFS/sfc_nst_post.f90
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,8 @@ module sfc_nst_post
! \section NSST_detailed_post_algorithm Detailed Algorithm
! @{
subroutine sfc_nst_post_run &
( im, kdt, rlapse, tgice, wet, use_lake_model, icy, oro, &
oro_uf, nstf_name1, &
( im, kdt, rlapse, tgice, wet, oceanfrac, use_lake_model, &
icy, oro, oro_uf, nstf_name1, &
nstf_name4, nstf_name5, xt, xz, dt_cool, z_c, tref, xlon, &
tsurf_wat, tsfc_wat, nthreads, dtzm, errmsg, errflg &
)
Expand All @@ -32,7 +32,7 @@ subroutine sfc_nst_post_run &
real (kind=kind_phys), intent(in) :: rlapse, tgice
real (kind=kind_phys), dimension(:), intent(in) :: oro, oro_uf
integer, intent(in) :: nstf_name1, nstf_name4, nstf_name5
real (kind=kind_phys), dimension(:), intent(in) :: xlon
real (kind=kind_phys), dimension(:), intent(in) :: xlon, oceanfrac
real (kind=kind_phys), dimension(:), intent(in), optional :: xt, xz, dt_cool, z_c, tref

! --- input/outputs:
Expand Down Expand Up @@ -71,7 +71,8 @@ subroutine sfc_nst_post_run &
do i = 1, im
! if (wet(i) .and. .not.icy(i)) then
! if (wet(i) .and. (frac_grid .or. .not. icy(i))) then
if (wet(i) .and. use_lake_model(i) /=1) then
if (wet(i) .and. use_lake_model(i) /=1 .and. oceanfrac(i)==0.)&
then
tsfc_wat(i) = max(tgice, tref(i) + dtzm(i))
! tsfc_wat(i) = max(271.2, tref(i) + dtzm(i)) - &
! (oro(i)-oro_uf(i))*rlapse
Expand Down
8 changes: 8 additions & 0 deletions physics/SFC_Layer/UFS/sfc_nst_post.meta
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,14 @@
dimensions = (horizontal_loop_extent)
type = logical
intent = in
[oceanfrac]
standard_name = sea_area_fraction
long_name = fraction of horizontal grid area occupied by ocean
units = frac
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[use_lake_model]
standard_name = flag_for_using_lake_model
long_name = flag indicating lake points using a lake model
Expand Down
Loading

0 comments on commit 4e998d6

Please sign in to comment.