Skip to content
This repository has been archived by the owner on Nov 8, 2024. It is now read-only.

Commit

Permalink
More RUC LSM improvement in operational RAP and HRRR (#142)
Browse files Browse the repository at this point in the history
TYPE: enhancement

KEYWORDS: soil moisture hydraulic conductivity, snow dripping

SOURCE: Tanya Smirnova, NOAA/ESRL/GSD, CIRES.

DESCRIPTION OF CHANGES:

1. remove computation of accumulated snow, should be done in phys/module_diag_misc.F.
2. perturb soil moisture hydraulic conductivity rather than soil moisture itself.
3. bug fix in snow dripping from the canopy when "mosaic" snow is on.

LIST OF MODIFIED FILES:

modified:   phys/module_sf_ruclsm.F

TESTS CONDUCTED: Regtested. And the changes have been tested in the RAP/HRRR as well.
  • Loading branch information
weiwangncar committed Feb 17, 2017
1 parent 46825b0 commit 7f599c8
Showing 1 changed file with 40 additions and 51 deletions.
91 changes: 40 additions & 51 deletions phys/module_sf_ruclsm.F
Original file line number Diff line number Diff line change
Expand Up @@ -479,7 +479,6 @@ SUBROUTINE LSMRUC(spp_lsm, &
qsfc(i,j) = qvg(i,j)/(1.+qvg(i,j))
SMELT(i,j) = 0.
SNOM (i,j) = 0.
ACSNOW(i,j) = 0.
SNOWFALLAC(i,j) = 0.
PRECIPFR(i,j) = 0.
RHOSNF(i,j) = -1.e3 ! non-zero flag
Expand Down Expand Up @@ -804,7 +803,6 @@ SUBROUTINE LSMRUC(spp_lsm, &
SNOWC(I,J)=0.0
LMAVAIL(I,J)=1.0
! accumulated water equivalent of frozen precipitation over water [mm]
acsnow(i,j)=acsnow(i,j)+precipfr(i,j)

ILAND=iswater
! ILAND=16
Expand Down Expand Up @@ -1452,14 +1450,6 @@ SUBROUTINE SFCTMP (spp_lsm,rstochcol,fieldcol_sf, &
EMISSN = 0.98
EMISS_snowfree = LEMITBL(IVGTYP)
!beka stochastic pert of soil mositure
if(spp_lsm == 1) then
! stochastic perturbations for soil moisture
do k=1,nzs
soilm1d(k)=max(0.,min(soilm1d(k)*(1+rstochcol(k)),dqm))
enddo
endif
!--- sea ice properties
!--- N.N Zubov "Arctic Ice"
!--- no salinity dependence because we consider the ice pack
Expand Down Expand Up @@ -1505,7 +1495,6 @@ SUBROUTINE SFCTMP (spp_lsm,rstochcol,fieldcol_sf, &
newsn=newsnms*delt
!---- ACSNOW - run-total snowfall water [mm]
acsnow=acsnow+newsn*1.e3
IF(NEWSN.GT.0.) THEN
! IF(NEWSN.GE.1.E-8) THEN
Expand All @@ -1514,6 +1503,8 @@ SUBROUTINE SFCTMP (spp_lsm,rstochcol,fieldcol_sf, &
print *, 'THERE IS NEW SNOW, newsn', newsn
ENDIF
newsnowratio = min(1.,newsn/(snwe+newsn))
!*** Calculate fresh snow density (t > -15C, else MIN value)
!*** Eq. 10 from Koren et al. (1999)
!--- old formulation from Koren (1999)
Expand Down Expand Up @@ -1591,17 +1582,24 @@ SUBROUTINE SFCTMP (spp_lsm,rstochcol,fieldcol_sf, &
CST=SAT
DRIP=DD1-SAT
ENDIF
else
CST=0.
DRIP=0.
interw=0.
intersn=0.
infwater=PRCPMS
endif ! vegfrac > 0.01
else
CST=0.
DRIP=0.
interw=0.
intersn=0.
infwater=PRCPMS
endif ! vegfrac > 0.01

! SNHEI_CRIT is a threshold for fractional snow
SNHEI_CRIT=0.01601*1.e3/rhosn
SNHEI_CRIT_newsn=0.0005*1.e3/rhosn
! snowfrac from the previous time step
SNOWFRAC=MIN(1.,SNHEI/(2.*SNHEI_CRIT))
if(snowfrac < 0.75) snow_mosaic = 1.

IF(NEWSN.GT.0.) THEN
!Update snow on the ground
snwe=snwe+newsn-intersn
snwe=max(0.,snwe+newsn-intersn)
! if(drip > 0.) then
! if (snow_mosaic==1.) then
! dripsn = drip*snowfrac
Expand All @@ -1611,7 +1609,19 @@ SUBROUTINE SFCTMP (spp_lsm,rstochcol,fieldcol_sf, &
! snwe=snwe+drip
! endif
! endif
! newsnowratio = min(1.,newsn/snwe)
! Add drip to snow on the ground
if(drip > 0.) then
if (snow_mosaic==1.) then
dripliq=drip*intwratio
dripsn = drip - dripliq
snwe=snwe+dripsn
infwater=infwater+dripliq
dripliq=0.
dripsn = 0.
else
snwe=snwe+drip
endif
endif
snhei=snwe*rhowater/rhosn
NEWSN=NEWSN*rhowater/rhonewsn
ENDIF
Expand All @@ -1622,23 +1632,18 @@ SUBROUTINE SFCTMP (spp_lsm,rstochcol,fieldcol_sf, &
ILAND=ISICE
!24nov15 - based on field exp on Pleasant View soccer fields
! if(meltfactor > 1.5) then ! all veg. types, except forests
! SNHEI_CRIT is a threshold for fractional snow
! SNHEI_CRIT=0.01*1.e3/rhosn
SNHEI_CRIT=0.01601*1.e3/rhosn
! SNHEI_CRIT=0.01601*1.e3/rhosn
! Petzold - 1 cm of fresh snow overwrites effects from old snow.
! Need to test SNHEI_CRIT_newsn=0.01
! SNHEI_CRIT_newsn=0.01
SNHEI_CRIT_newsn=0.0005*1.e3/rhosn
! else ! forests
!24nov15
! SNHEI_CRIT=0.02*1.e3/rhosn
! SNHEI_CRIT_newsn=0.001*1.e3/rhosn
! endif

! SNOWFRAC=MIN(1.,SNHEI/SNHEI_CRIT)
SNOWFRAC=MIN(1.,SNHEI/(2.*SNHEI_CRIT))
!24nov15 - SNOWFRAC for urban category < 0.5
if(ivgtyp == urban) snowfrac=min(0.7,snowfrac)
!24nov15 - SNOWFRAC for urban category < 0.75
if(ivgtyp == urban) snowfrac=min(0.75,snowfrac)
! if(meltfactor > 1.5) then
! if(isltyp > 9 .and. isltyp < 13) then
!24nov15 clay soil types - SNOFRAC < 0.9
Expand All @@ -1652,7 +1657,7 @@ SUBROUTINE SFCTMP (spp_lsm,rstochcol,fieldcol_sf, &
! SNOWFRAC=MIN(1.,SNHEI/(2.*SNHEI_CRIT))
! elseif(snowfrac < 0.3 .and. tabs > 275.) then

if(snowfrac < 0.75) snow_mosaic = 1.
if(snowfrac < 0.75) snow_mosaic = 1.

if(newsn > 0. ) SNOWFRACnewsn=MIN(1.,SNHEI/SNHEI_CRIT_newsn)

Expand All @@ -1663,22 +1668,6 @@ SUBROUTINE SFCTMP (spp_lsm,rstochcol,fieldcol_sf, &
snow_mosaic=0. ! ???
ENDIF

! Add drip to snow on the ground
if(drip > 0.) then
if (snow_mosaic==1.) then
dripliq=drip*intwratio
dripsn = drip - dripliq
snwe=snwe+dripsn
infwater=infwater+dripliq
dripliq=0.
dripsn = 0.
else
snwe=snwe+drip
endif
endif
if (snwe.gt.0.0) newsnowratio = min(1.,newsn/snwe)
snhei=snwe*rhowater/rhosn

IF ( wrf_at_debug_level(LSMRUC_DBG_LVL) ) THEN
print *,'SNHEI_CRIT,SNOWFRAC,SNHEI_CRIT_newsn,SNOWFRACnewsn', &
SNHEI_CRIT,SNOWFRAC,SNHEI_CRIT_newsn,SNOWFRACnewsn
Expand Down Expand Up @@ -6367,12 +6356,12 @@ SUBROUTINE SOILPROP(spp_lsm,rstochcol,fieldcol_sf, &
ENDDO

! perturb hydrolic conductivity by 10-30%, not more than 50%
!beka if (spp_lsm==1) then
!beka DO K=1,NZS !lala
!beka fieldcol_sf(k)=hydro(k)*rstochcol(k)
!beka hydro(k)=hydro(k)*(1+rstochcol(k))
!beka ENDDO
!beka ENDIF
if (spp_lsm==1) then
DO K=1,NZS !lala
fieldcol_sf(k)=hydro(k)*rstochcol(k)
hydro(k)=hydro(k)*(1+rstochcol(k))
ENDDO
ENDIF

! RETURN
! END
Expand Down

0 comments on commit 7f599c8

Please sign in to comment.