Skip to content

Commit ed44775

Browse files
authored
Merge pull request #743 from scrasmussen/enhancement/liquidWaterFraction-rebase
Enhancement: liquid water fraction and forcing variable names
2 parents 7afc6b3 + c3f7998 commit ed44775

File tree

6 files changed

+463
-216
lines changed

6 files changed

+463
-216
lines changed

src/CPL/NoahMP_cpl/hrldas_drv_HYDRO.F

Lines changed: 18 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,9 @@ end subroutine hrldas_drv_HYDRO_ini
7474

7575
subroutine HYDRO_frocing_drv (indir,forc_typ, snow_assim,olddate, &
7676
ixs, ixe,jxs,jxe, &
77-
T2,Q2X,U,V,PRES,XLONG,SHORT,PRCP1,lai,fpar,snodep, kt, FORCING_TIMESTEP,pcp_old)
77+
forcing_name_T,forcing_name_Q,forcing_name_U,forcing_name_V,forcing_name_P, &
78+
forcing_name_LW,forcing_name_SW,forcing_name_PR,forcing_name_SN, forcing_name_LF,&
79+
T2,Q2X,U,V,PRES,XLONG,SHORT,PRCP1,lai,SNOWBL,fpar,snodep, kt, FORCING_TIMESTEP,pcp_old)
7880

7981
use module_lsm_forcing, only: read_hydro_forcing
8082
use config_base, only: nlst
@@ -83,19 +85,32 @@ subroutine HYDRO_frocing_drv (indir,forc_typ, snow_assim,olddate, &
8385
integer ix,jx, kt
8486
character(len=19) :: olddate
8587
character(len=*) :: indir
88+
character(len=256), intent(in) :: forcing_name_T
89+
character(len=256), intent(in) :: forcing_name_Q
90+
character(len=256), intent(in) :: forcing_name_U
91+
character(len=256), intent(in) :: forcing_name_V
92+
character(len=256), intent(in) :: forcing_name_P
93+
character(len=256), intent(in) :: forcing_name_LW
94+
character(len=256), intent(in) :: forcing_name_SW
95+
character(len=256), intent(in) :: forcing_name_PR
96+
character(len=256), intent(in) :: forcing_name_SN
97+
character(len=256), intent(in) :: forcing_name_LF
8698
real, dimension(ixs:ixe,jxs:jxe):: T2,Q2X,U,V,PRES,XLONG,SHORT,PRCP1, &
87-
lai, fpar,snodep, pcp_old
99+
lai, snowbl, fpar, snodep, pcp_old
88100
integer :: forc_typ, snow_assim, FORCING_TIMESTEP
89101

90102
ix = ixe-ixs+1
91103
jx = jxe-jxs+1
92104
did = 1
105+
93106
call read_hydro_forcing( &
94107
indir, olddate, &
95108
nlst(did)%hgrid,&
96109
ix,jx,forc_typ,snow_assim, &
110+
forcing_name_T,forcing_name_Q,forcing_name_U,forcing_name_V,forcing_name_P, &
111+
forcing_name_LW,forcing_name_SW,forcing_name_PR,forcing_name_SN, forcing_name_LF,&
97112
T2,q2x,u,v,pres,xlong,short,prcp1,&
98-
lai,fpar,snodep,FORCING_TIMESTEP*1.0,kt, pcp_old)
113+
lai,snowbl,fpar,snodep,FORCING_TIMESTEP*1.0,kt, pcp_old)
99114
end subroutine HYDRO_frocing_drv
100115

101116
subroutine get_greenfrac(inFile,greenfrac, idim, jdim, olddate,SHDMAX)

src/Land_models/NoahMP/IO_code/module_NoahMP_hrldas_driver.F

Lines changed: 30 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -136,6 +136,7 @@ module module_NoahMP_hrldas_driver
136136
REAL, ALLOCATABLE, DIMENSION(:,:) :: GLW ! longwave down at surface [W m-2]
137137
REAL, ALLOCATABLE, DIMENSION(:,:,:) :: P8W ! 3D pressure, valid at interface [Pa]
138138
REAL, ALLOCATABLE, DIMENSION(:,:) :: RAINBL, RAINBL_tmp ! precipitation entering land model [mm]
139+
REAL, ALLOCATABLE, DIMENSION(:,:) :: SNOWBL ! snow entering land model [mm]
139140
REAL, ALLOCATABLE, DIMENSION(:,:) :: SR ! frozen precip ratio entering land model [-]
140141
REAL, ALLOCATABLE, DIMENSION(:,:) :: RAINCV ! convective precip forcing [mm]
141142
REAL, ALLOCATABLE, DIMENSION(:,:) :: RAINNCV ! non-convective precip forcing [mm]
@@ -762,6 +763,7 @@ subroutine land_driver_ini(NTIME_out, state, wrfits,wrfite,wrfjts,wrfjte)
762763
ALLOCATE ( GLW (XSTART:XEND,YSTART:YEND) ) ! longwave down at surface [W m-2]
763764
ALLOCATE ( P8W (XSTART:XEND,KDS:KDE,YSTART:YEND) ) ! 3D pressure, valid at interface [Pa]
764765
ALLOCATE ( RAINBL (XSTART:XEND,YSTART:YEND) ) ! total precipitation entering land model [mm]
766+
ALLOCATE ( SNOWBL (XSTART:XEND,YSTART:YEND) ) ! snow entering land model [mm]
765767
ALLOCATE ( RAINBL_tmp (XSTART:XEND,YSTART:YEND) ) ! precipitation entering land model [mm]
766768
ALLOCATE ( SR (XSTART:XEND,YSTART:YEND) ) ! frozen precip ratio entering land model [-]
767769
ALLOCATE ( RAINCV (XSTART:XEND,YSTART:YEND) ) ! convective precip forcing [mm]
@@ -1005,6 +1007,7 @@ subroutine land_driver_ini(NTIME_out, state, wrfits,wrfite,wrfjts,wrfjte)
10051007
GLW = undefined_real
10061008
P8W = undefined_real
10071009
RAINBL = undefined_real
1010+
SNOWBL = undefined_real
10081011
RAINBL_tmp = undefined_real
10091012
SR = undefined_real
10101013
RAINCV = undefined_real
@@ -1184,11 +1187,11 @@ subroutine land_driver_ini(NTIME_out, state, wrfits,wrfite,wrfjts,wrfjte)
11841187
!PSNOWAGEXY = undefined_real
11851188
11861189
! These should probably be kept initialized with an undefined value (above)
1187-
! to allow tracking of cells that fall through the cracks in value updates
1190+
! to allow tracking of cells that fall through the cracks in value updates
11881191
! (also worth noting that 0 is not a valid value for all of these variables).
1189-
! However, since restarts are not currently water-masking 2d reals, this makes
1192+
! However, since restarts are not currently water-masking 2d reals, this makes
11901193
! for odd value ranges in the LSM restarts so leaving as 0s for now.
1191-
! On quick tests, the only one of these that changes answers if NOT initialized
1194+
! On quick tests, the only one of these that changes answers if NOT initialized
11921195
! at 0 is PSNOWHISTXY so making sure that one is covered in value initialization
11931196
! loop below in case we go back to undefined_real for these.
11941197
PSNOWLIQXY = 0.
@@ -1724,15 +1727,26 @@ subroutine land_driver_exe(itime, state)
17241727
if(forc_typ .eq. 0) then
17251728
CALL READFORC_HRLDAS(INFLNM_TEMPLATE, noah_lsm%FORCING_TIMESTEP, OLDDATE, &
17261729
XSTART, XEND, YSTART, YEND, &
1730+
noah_lsm%forcing_name_T ,noah_lsm%forcing_name_Q ,noah_lsm%forcing_name_U , &
1731+
noah_lsm%forcing_name_V ,noah_lsm%forcing_name_P ,noah_lsm%forcing_name_LW, &
1732+
noah_lsm%forcing_name_SW,noah_lsm%forcing_name_PR,noah_lsm%forcing_name_SN, &
1733+
noah_lsm%forcing_name_LF, &
17271734
T_PHY(:,1,:),QV_CURR(:,1,:),U_PHY(:,1,:),V_PHY(:,1,:), &
1728-
P8W(:,1,:), GLW ,SWDOWN ,RAINBL_tmp, VEGFRA, update_veg, LAI, update_lai)
1735+
P8W(:,1,:), GLW ,SWDOWN ,RAINBL_tmp, &
1736+
SNOWBL, VEGFRA, update_veg, LAI, &
1737+
update_lai)
17291738
else
17301739
if(olddate == forcDate) then
1731-
CALL HYDRO_frocing_drv(trim(noah_lsm%indir), forc_typ, wrf_hydro%snow_assim,olddate, &
1740+
CALL HYDRO_frocing_drv(trim(noah_lsm%indir), forc_typ, wrf_hydro%snow_assim, olddate, &
17321741
xstart, xend, ystart, yend, &
1733-
T_PHY(:,1,:),QV_CURR(:,1,:),U_PHY(:,1,:),V_PHY(:,1,:),P8W(:,1,:), &
1734-
GLW,SWDOWN,RAINBL_tmp,LAI,VEGFRA,state%SNOWH,ITIME,noah_lsm%FORCING_TIMESTEP,prcp0)
1735-
1742+
noah_lsm%forcing_name_T ,noah_lsm%forcing_name_Q ,noah_lsm%forcing_name_U , &
1743+
noah_lsm%forcing_name_V ,noah_lsm%forcing_name_P ,noah_lsm%forcing_name_LW, &
1744+
noah_lsm%forcing_name_SW,noah_lsm%forcing_name_PR,noah_lsm%forcing_name_SN, &
1745+
noah_lsm%forcing_name_LF, &
1746+
T_PHY(:,1,:), QV_CURR(:,1,:), U_PHY(:,1,:), V_PHY(:,1,:), &
1747+
P8W(:,1,:), GLW, SWDOWN, RAINBL_tmp, &
1748+
LAI, SNOWBL, VEGFRA, state%SNOWH, &
1749+
ITIME, noah_lsm%FORCING_TIMESTEP, prcp0)
17361750
if(maxval(VEGFRA) .le. 1) VEGFRA = VEGFRA * 100
17371751

17381752
call geth_newdate(newdate, forcDate, noah_lsm%FORCING_TIMESTEP)
@@ -1743,8 +1757,12 @@ subroutine land_driver_exe(itime, state)
17431757
#else
17441758
CALL READFORC_HRLDAS(INFLNM_TEMPLATE, noah_lsm%FORCING_TIMESTEP, OLDDATE, &
17451759
XSTART, XEND, YSTART, YEND, &
1760+
noah_lsm%forcing_name_T ,noah_lsm%forcing_name_Q ,noah_lsm%forcing_name_U , &
1761+
noah_lsm%forcing_name_V ,noah_lsm%forcing_name_P ,noah_lsm%forcing_name_LW, &
1762+
noah_lsm%forcing_name_SW,noah_lsm%forcing_name_PR,noah_lsm%forcing_name_SN, &
1763+
noah_lsm%forcing_name_LF, &
17461764
T_PHY(:,1,:),QV_CURR(:,1,:),U_PHY(:,1,:),V_PHY(:,1,:), &
1747-
P8W(:,1,:), GLW ,SWDOWN ,RAINBL_tmp, VEGFRA, update_veg, LAI, update_lai)
1765+
P8W(:,1,:), GLW ,SWDOWN ,RAINBL_tmp, SNOWBL, VEGFRA, update_veg, LAI, update_lai)
17481766
#endif
17491767

17501768
991 continue
@@ -1757,6 +1775,7 @@ subroutine land_driver_exe(itime, state)
17571775
where(XLAND > 1.5) GLW = 0.0
17581776
where(XLAND > 1.5) SWDOWN = 0.0
17591777
where(XLAND > 1.5) RAINBL_tmp = 0.0
1778+
where(XLAND > 1.5) SNOWBL = 0.0
17601779

17611780
QV_CURR(:,1,:) = QV_CURR(:,1,:)/(1.0 - QV_CURR(:,1,:)) ! Assuming input forcing are specific hum.;
17621781
! WRF wants mixing ratio at driver level
@@ -1766,11 +1785,12 @@ subroutine land_driver_exe(itime, state)
17661785
V_PHY(:,2,:) = V_PHY(:,1,:) !
17671786
QV_CURR(:,2,:) = QV_CURR(:,1,:) !
17681787
RAINBL = RAINBL_tmp * DTBL ! RAINBL in WRF is [mm]
1788+
SNOWBL = SNOWBL * DTBL !
17691789
SR = 0.0 ! Will only use component if opt_snf=4
17701790
RAINCV = 0.0
17711791
RAINNCV = RAINBL
17721792
RAINSHV = 0.0
1773-
SNOWNCV = 0.0
1793+
SNOWNCV = SNOWBL
17741794
GRAUPELNCV = 0.0
17751795
HAILNCV = 0.0
17761796
DZ8W = 2 * noah_lsm%ZLVL ! 2* to be consistent with WRF model level

0 commit comments

Comments
 (0)