Skip to content

Commit

Permalink
Merge pull request NCAR#743 from scrasmussen/enhancement/liquidWaterF…
Browse files Browse the repository at this point in the history
…raction-rebase

Enhancement: liquid water fraction and forcing variable names
  • Loading branch information
rcabell authored Mar 27, 2024
2 parents 7afc6b3 + c3f7998 commit ed44775
Show file tree
Hide file tree
Showing 6 changed files with 463 additions and 216 deletions.
21 changes: 18 additions & 3 deletions src/CPL/NoahMP_cpl/hrldas_drv_HYDRO.F
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,9 @@ end subroutine hrldas_drv_HYDRO_ini

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

use module_lsm_forcing, only: read_hydro_forcing
use config_base, only: nlst
Expand All @@ -83,19 +85,32 @@ subroutine HYDRO_frocing_drv (indir,forc_typ, snow_assim,olddate, &
integer ix,jx, kt
character(len=19) :: olddate
character(len=*) :: indir
character(len=256), intent(in) :: forcing_name_T
character(len=256), intent(in) :: forcing_name_Q
character(len=256), intent(in) :: forcing_name_U
character(len=256), intent(in) :: forcing_name_V
character(len=256), intent(in) :: forcing_name_P
character(len=256), intent(in) :: forcing_name_LW
character(len=256), intent(in) :: forcing_name_SW
character(len=256), intent(in) :: forcing_name_PR
character(len=256), intent(in) :: forcing_name_SN
character(len=256), intent(in) :: forcing_name_LF
real, dimension(ixs:ixe,jxs:jxe):: T2,Q2X,U,V,PRES,XLONG,SHORT,PRCP1, &
lai, fpar,snodep, pcp_old
lai, snowbl, fpar, snodep, pcp_old
integer :: forc_typ, snow_assim, FORCING_TIMESTEP

ix = ixe-ixs+1
jx = jxe-jxs+1
did = 1

call read_hydro_forcing( &
indir, olddate, &
nlst(did)%hgrid,&
ix,jx,forc_typ,snow_assim, &
forcing_name_T,forcing_name_Q,forcing_name_U,forcing_name_V,forcing_name_P, &
forcing_name_LW,forcing_name_SW,forcing_name_PR,forcing_name_SN, forcing_name_LF,&
T2,q2x,u,v,pres,xlong,short,prcp1,&
lai,fpar,snodep,FORCING_TIMESTEP*1.0,kt, pcp_old)
lai,snowbl,fpar,snodep,FORCING_TIMESTEP*1.0,kt, pcp_old)
end subroutine HYDRO_frocing_drv

subroutine get_greenfrac(inFile,greenfrac, idim, jdim, olddate,SHDMAX)
Expand Down
40 changes: 30 additions & 10 deletions src/Land_models/NoahMP/IO_code/module_NoahMP_hrldas_driver.F
Original file line number Diff line number Diff line change
Expand Up @@ -136,6 +136,7 @@ module module_NoahMP_hrldas_driver
REAL, ALLOCATABLE, DIMENSION(:,:) :: GLW ! longwave down at surface [W m-2]
REAL, ALLOCATABLE, DIMENSION(:,:,:) :: P8W ! 3D pressure, valid at interface [Pa]
REAL, ALLOCATABLE, DIMENSION(:,:) :: RAINBL, RAINBL_tmp ! precipitation entering land model [mm]
REAL, ALLOCATABLE, DIMENSION(:,:) :: SNOWBL ! snow entering land model [mm]
REAL, ALLOCATABLE, DIMENSION(:,:) :: SR ! frozen precip ratio entering land model [-]
REAL, ALLOCATABLE, DIMENSION(:,:) :: RAINCV ! convective precip forcing [mm]
REAL, ALLOCATABLE, DIMENSION(:,:) :: RAINNCV ! non-convective precip forcing [mm]
Expand Down Expand Up @@ -762,6 +763,7 @@ subroutine land_driver_ini(NTIME_out, state, wrfits,wrfite,wrfjts,wrfjte)
ALLOCATE ( GLW (XSTART:XEND,YSTART:YEND) ) ! longwave down at surface [W m-2]
ALLOCATE ( P8W (XSTART:XEND,KDS:KDE,YSTART:YEND) ) ! 3D pressure, valid at interface [Pa]
ALLOCATE ( RAINBL (XSTART:XEND,YSTART:YEND) ) ! total precipitation entering land model [mm]
ALLOCATE ( SNOWBL (XSTART:XEND,YSTART:YEND) ) ! snow entering land model [mm]
ALLOCATE ( RAINBL_tmp (XSTART:XEND,YSTART:YEND) ) ! precipitation entering land model [mm]
ALLOCATE ( SR (XSTART:XEND,YSTART:YEND) ) ! frozen precip ratio entering land model [-]
ALLOCATE ( RAINCV (XSTART:XEND,YSTART:YEND) ) ! convective precip forcing [mm]
Expand Down Expand Up @@ -1005,6 +1007,7 @@ subroutine land_driver_ini(NTIME_out, state, wrfits,wrfite,wrfjts,wrfjte)
GLW = undefined_real
P8W = undefined_real
RAINBL = undefined_real
SNOWBL = undefined_real
RAINBL_tmp = undefined_real
SR = undefined_real
RAINCV = undefined_real
Expand Down Expand Up @@ -1184,11 +1187,11 @@ subroutine land_driver_ini(NTIME_out, state, wrfits,wrfite,wrfjts,wrfjte)
!PSNOWAGEXY = undefined_real
! These should probably be kept initialized with an undefined value (above)
! to allow tracking of cells that fall through the cracks in value updates
! to allow tracking of cells that fall through the cracks in value updates
! (also worth noting that 0 is not a valid value for all of these variables).
! However, since restarts are not currently water-masking 2d reals, this makes
! However, since restarts are not currently water-masking 2d reals, this makes
! for odd value ranges in the LSM restarts so leaving as 0s for now.
! On quick tests, the only one of these that changes answers if NOT initialized
! On quick tests, the only one of these that changes answers if NOT initialized
! at 0 is PSNOWHISTXY so making sure that one is covered in value initialization
! loop below in case we go back to undefined_real for these.
PSNOWLIQXY = 0.
Expand Down Expand Up @@ -1724,15 +1727,26 @@ subroutine land_driver_exe(itime, state)
if(forc_typ .eq. 0) then
CALL READFORC_HRLDAS(INFLNM_TEMPLATE, noah_lsm%FORCING_TIMESTEP, OLDDATE, &
XSTART, XEND, YSTART, YEND, &
noah_lsm%forcing_name_T ,noah_lsm%forcing_name_Q ,noah_lsm%forcing_name_U , &
noah_lsm%forcing_name_V ,noah_lsm%forcing_name_P ,noah_lsm%forcing_name_LW, &
noah_lsm%forcing_name_SW,noah_lsm%forcing_name_PR,noah_lsm%forcing_name_SN, &
noah_lsm%forcing_name_LF, &
T_PHY(:,1,:),QV_CURR(:,1,:),U_PHY(:,1,:),V_PHY(:,1,:), &
P8W(:,1,:), GLW ,SWDOWN ,RAINBL_tmp, VEGFRA, update_veg, LAI, update_lai)
P8W(:,1,:), GLW ,SWDOWN ,RAINBL_tmp, &
SNOWBL, VEGFRA, update_veg, LAI, &
update_lai)
else
if(olddate == forcDate) then
CALL HYDRO_frocing_drv(trim(noah_lsm%indir), forc_typ, wrf_hydro%snow_assim,olddate, &
CALL HYDRO_frocing_drv(trim(noah_lsm%indir), forc_typ, wrf_hydro%snow_assim, olddate, &
xstart, xend, ystart, yend, &
T_PHY(:,1,:),QV_CURR(:,1,:),U_PHY(:,1,:),V_PHY(:,1,:),P8W(:,1,:), &
GLW,SWDOWN,RAINBL_tmp,LAI,VEGFRA,state%SNOWH,ITIME,noah_lsm%FORCING_TIMESTEP,prcp0)

noah_lsm%forcing_name_T ,noah_lsm%forcing_name_Q ,noah_lsm%forcing_name_U , &
noah_lsm%forcing_name_V ,noah_lsm%forcing_name_P ,noah_lsm%forcing_name_LW, &
noah_lsm%forcing_name_SW,noah_lsm%forcing_name_PR,noah_lsm%forcing_name_SN, &
noah_lsm%forcing_name_LF, &
T_PHY(:,1,:), QV_CURR(:,1,:), U_PHY(:,1,:), V_PHY(:,1,:), &
P8W(:,1,:), GLW, SWDOWN, RAINBL_tmp, &
LAI, SNOWBL, VEGFRA, state%SNOWH, &
ITIME, noah_lsm%FORCING_TIMESTEP, prcp0)
if(maxval(VEGFRA) .le. 1) VEGFRA = VEGFRA * 100

call geth_newdate(newdate, forcDate, noah_lsm%FORCING_TIMESTEP)
Expand All @@ -1743,8 +1757,12 @@ subroutine land_driver_exe(itime, state)
#else
CALL READFORC_HRLDAS(INFLNM_TEMPLATE, noah_lsm%FORCING_TIMESTEP, OLDDATE, &
XSTART, XEND, YSTART, YEND, &
noah_lsm%forcing_name_T ,noah_lsm%forcing_name_Q ,noah_lsm%forcing_name_U , &
noah_lsm%forcing_name_V ,noah_lsm%forcing_name_P ,noah_lsm%forcing_name_LW, &
noah_lsm%forcing_name_SW,noah_lsm%forcing_name_PR,noah_lsm%forcing_name_SN, &
noah_lsm%forcing_name_LF, &
T_PHY(:,1,:),QV_CURR(:,1,:),U_PHY(:,1,:),V_PHY(:,1,:), &
P8W(:,1,:), GLW ,SWDOWN ,RAINBL_tmp, VEGFRA, update_veg, LAI, update_lai)
P8W(:,1,:), GLW ,SWDOWN ,RAINBL_tmp, SNOWBL, VEGFRA, update_veg, LAI, update_lai)
#endif

991 continue
Expand All @@ -1757,6 +1775,7 @@ subroutine land_driver_exe(itime, state)
where(XLAND > 1.5) GLW = 0.0
where(XLAND > 1.5) SWDOWN = 0.0
where(XLAND > 1.5) RAINBL_tmp = 0.0
where(XLAND > 1.5) SNOWBL = 0.0

QV_CURR(:,1,:) = QV_CURR(:,1,:)/(1.0 - QV_CURR(:,1,:)) ! Assuming input forcing are specific hum.;
! WRF wants mixing ratio at driver level
Expand All @@ -1766,11 +1785,12 @@ subroutine land_driver_exe(itime, state)
V_PHY(:,2,:) = V_PHY(:,1,:) !
QV_CURR(:,2,:) = QV_CURR(:,1,:) !
RAINBL = RAINBL_tmp * DTBL ! RAINBL in WRF is [mm]
SNOWBL = SNOWBL * DTBL !
SR = 0.0 ! Will only use component if opt_snf=4
RAINCV = 0.0
RAINNCV = RAINBL
RAINSHV = 0.0
SNOWNCV = 0.0
SNOWNCV = SNOWBL
GRAUPELNCV = 0.0
HAILNCV = 0.0
DZ8W = 2 * noah_lsm%ZLVL ! 2* to be consistent with WRF model level
Expand Down
Loading

0 comments on commit ed44775

Please sign in to comment.