Skip to content

Commit

Permalink
Merge pull request #60 from NCAR/develop
Browse files Browse the repository at this point in the history
bring hard-coded tunable canopy heat capacity parameter to MPTABLE
  • Loading branch information
cenlinhe authored Dec 23, 2022
2 parents ba1699d + b1bdfe5 commit 4b7870f
Show file tree
Hide file tree
Showing 3 changed files with 12 additions and 4 deletions.
1 change: 1 addition & 0 deletions drivers/wrf/module_sf_noahmpdrv.F
Original file line number Diff line number Diff line change
Expand Up @@ -1481,6 +1481,7 @@ SUBROUTINE TRANSFER_MP_PARAMETERS(NSOIL,VEGTYPE,SOILTYPE,SLOPETYPE,SOILCOLOR,CRO
parameters%RC = RC_TABLE(VEGTYPE) !tree crown radius (m)
parameters%MFSNO = MFSNO_TABLE(VEGTYPE) !snowmelt m parameter ()
parameters%SCFFAC = SCFFAC_TABLE(VEGTYPE) !snow cover factor (m) (originally hard-coded 2.5*z0 in SCF formulation)
parameters%CBIOM = CBIOM_TABLE(VEGTYPE) !canopy biomass heat capacity parameter (m)
parameters%SAIM = SAIM_TABLE(VEGTYPE,:) !monthly stem area index, one-sided
parameters%LAIM = LAIM_TABLE(VEGTYPE,:) !monthly leaf area index, one-sided
parameters%SLA = SLA_TABLE(VEGTYPE) !single-side leaf area per Kg [m2/kg]
Expand Down
3 changes: 3 additions & 0 deletions parameters/MPTABLE.TBL
Original file line number Diff line number Diff line change
Expand Up @@ -66,6 +66,8 @@
MFSNO = 4.00, 3.00, 3.00, 3.00, 4.00, 4.00, 2.00, 2.00, 2.00, 2.00, 1.00, 1.00, 1.00, 1.00, 1.00, 3.00, 3.00, 3.00, 3.00, 3.50, 3.50, 3.50, 3.50, 2.50, 3.50, 3.50, 3.50,
! C. He 12/17/2020: optimized snow cover factor (m) in SCF formulation to replace original constant 2.5*z0,z0=0.002m, based on evaluation with SNOTEL SWE and MODIS SCF, surface albedo
SCFFAC= 0.042, 0.014, 0.014, 0.014, 0.026, 0.026, 0.020, 0.018, 0.016, 0.020, 0.008, 0.008, 0.008, 0.008, 0.008, 0.030, 0.020, 0.020, 0.016, 0.030, 0.030, 0.030, 0.030, 0.030, 0.030, 0.030, 0.030,
! C. He 12/23/2022: bring canopy heat capacity parameter from hard-coded to table value here.
CBIOM = 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02,

! Row 1: Vis
! Row 2: Near IR
Expand Down Expand Up @@ -221,6 +223,7 @@
MFSNO = 1.00, 1.00, 1.00, 1.00, 1.00, 2.00, 2.00, 2.00, 2.00, 2.00, 3.00, 3.00, 4.00, 4.00, 2.50, 3.00, 3.00, 3.50, 3.50, 3.50,
! C. He 12/17/2020: optimized snow cover factor (m) in SCF formulation to replace original constant 2.5*z0,z0=0.002m, based on evaluation with SNOTEL SWE and MODIS SCF, surface albedo
SCFFAC = 0.008, 0.008, 0.008, 0.008, 0.008, 0.016, 0.016, 0.020, 0.020, 0.020, 0.020, 0.014, 0.042, 0.026, 0.030, 0.016, 0.030, 0.030, 0.030, 0.030,
CBIOM = 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02,

! Row 1: Vis
! Row 2: Near IR
Expand Down
12 changes: 8 additions & 4 deletions src/module_sf_noahmplsm.F
Original file line number Diff line number Diff line change
Expand Up @@ -248,6 +248,7 @@ MODULE MODULE_SF_NOAHMPLSM
REAL :: RC !tree crown radius (m)
REAL :: MFSNO !snowmelt m parameter ()
REAL :: SCFFAC !snow cover factor (m) (originally hard-coded 2.5*z0 in SCF formulation)
REAL :: CBIOM !canopy biomass heat capacity parameter (m)
REAL :: SAIM(12) !monthly stem area index, one-sided
REAL :: LAIM(12) !monthly leaf area index, one-sided
REAL :: SLA !single-side leaf area per Kg [m2/kg]
Expand Down Expand Up @@ -4047,7 +4048,7 @@ SUBROUTINE VEGE_FLUX(parameters,NSNOW ,NSOIL ,ISNOW ,VEGTYP ,VEG , &
EVC = MIN(CANICE*LATHEAV/DT,EVC)
END IF
! canopy heat capacity
HCV = 0.02*VAIE*CWAT + CANLIQ*CWAT/DENH2O + CANICE*CICE/DENICE !j/m2/k
HCV = parameters%CBIOM*VAIE*CWAT + CANLIQ*CWAT/DENH2O + CANICE*CICE/DENICE !j/m2/k

B = SAV-IRC-SHC-EVC-TR+PAHV !additional w/m2
! A = FVEG*(4.0*CIR*TV**3 + CSH + (CEV+CTR)*DESTV) !volumetric heat capacity
Expand Down Expand Up @@ -11123,6 +11124,7 @@ MODULE NOAHMP_TABLES
REAL :: RC_TABLE(MVT) !tree crown radius (m)
REAL :: MFSNO_TABLE(MVT) !snowmelt curve parameter ()
REAL :: SCFFAC_TABLE(MVT) !snow cover factor (m) (replace original hard-coded 2.5*z0 in SCF formulation)
REAL :: CBIOM_TABLE(MVT) !canopy biomass heat capacity parameter (m)
REAL :: SAIM_TABLE(MVT,12) !monthly stem area index, one-sided
REAL :: LAIM_TABLE(MVT,12) !monthly leaf area index, one-sided
REAL :: SLA_TABLE(MVT) !single-side leaf area per Kg [m2/kg]
Expand Down Expand Up @@ -11414,15 +11416,15 @@ subroutine read_mp_veg_parameters(DATASET_IDENTIFIER)
LAI_JUL,LAI_AUG,LAI_SEP,LAI_OCT,LAI_NOV,LAI_DEC
REAL, DIMENSION(MVT) :: RHOL_VIS, RHOL_NIR, RHOS_VIS, RHOS_NIR, &
TAUL_VIS, TAUL_NIR, TAUS_VIS, TAUS_NIR
REAL, DIMENSION(MVT) :: CH2OP, DLEAF, Z0MVT, HVT, HVB, DEN, RC, MFSNO, SCFFAC, XL, CWPVT, C3PSN, KC25, AKC, KO25, AKO, &
REAL, DIMENSION(MVT) :: CH2OP, DLEAF, Z0MVT, HVT, HVB, DEN, RC, MFSNO, SCFFAC, CBIOM, XL, CWPVT, C3PSN, KC25, AKC, KO25, AKO, &
AVCMX, AQE, LTOVRC, DILEFC, DILEFW, RMF25 , SLA , FRAGR , TMIN , VCMX25, TDLEF , &
BP, MP, QE25, RMS25, RMR25, ARM, FOLNMX, WDPOOL, WRRAT, MRP, NROOT, RGL, RS, HS, TOPT, RSMAX, &
SLAREA, EPS1, EPS2, EPS3, EPS4, EPS5

NAMELIST / noahmp_usgs_veg_categories / VEG_DATASET_DESCRIPTION, NVEG
NAMELIST / noahmp_usgs_parameters / ISURBAN, ISWATER, ISBARREN, ISICE, ISCROP, EBLFOREST, NATURAL, &
LCZ_1,LCZ_2,LCZ_3,LCZ_4,LCZ_5,LCZ_6,LCZ_7,LCZ_8,LCZ_9,LCZ_10,LCZ_11,&
CH2OP, DLEAF, Z0MVT, HVT, HVB, DEN, RC, MFSNO, SCFFAC, XL, CWPVT, C3PSN, KC25, AKC, KO25, AKO, AVCMX, AQE, &
CH2OP, DLEAF, Z0MVT, HVT, HVB, DEN, RC, MFSNO, SCFFAC, CBIOM, XL, CWPVT, C3PSN, KC25, AKC, KO25, AKO, AVCMX, AQE, &
LTOVRC, DILEFC, DILEFW, RMF25 , SLA , FRAGR , TMIN , VCMX25, TDLEF , BP, MP, QE25, RMS25, RMR25, ARM, &
FOLNMX, WDPOOL, WRRAT, MRP, NROOT, RGL, RS, HS, TOPT, RSMAX, &
SAI_JAN, SAI_FEB, SAI_MAR, SAI_APR, SAI_MAY, SAI_JUN,SAI_JUL,SAI_AUG,SAI_SEP,SAI_OCT,SAI_NOV,SAI_DEC, &
Expand All @@ -11432,7 +11434,7 @@ subroutine read_mp_veg_parameters(DATASET_IDENTIFIER)
NAMELIST / noahmp_modis_veg_categories / VEG_DATASET_DESCRIPTION, NVEG
NAMELIST / noahmp_modis_parameters / ISURBAN, ISWATER, ISBARREN, ISICE, ISCROP, EBLFOREST, NATURAL, &
LCZ_1,LCZ_2,LCZ_3,LCZ_4,LCZ_5,LCZ_6,LCZ_7,LCZ_8,LCZ_9,LCZ_10,LCZ_11, &
CH2OP, DLEAF, Z0MVT, HVT, HVB, DEN, RC, MFSNO, SCFFAC, XL, CWPVT, C3PSN, KC25, AKC, KO25, AKO, AVCMX, AQE, &
CH2OP, DLEAF, Z0MVT, HVT, HVB, DEN, RC, MFSNO, SCFFAC, CBIOM, XL, CWPVT, C3PSN, KC25, AKC, KO25, AKO, AVCMX, AQE, &
LTOVRC, DILEFC, DILEFW, RMF25 , SLA , FRAGR , TMIN , VCMX25, TDLEF , BP, MP, QE25, RMS25, RMR25, ARM, &
FOLNMX, WDPOOL, WRRAT, MRP, NROOT, RGL, RS, HS, TOPT, RSMAX, &
SAI_JAN, SAI_FEB, SAI_MAR, SAI_APR, SAI_MAY, SAI_JUN,SAI_JUL,SAI_AUG,SAI_SEP,SAI_OCT,SAI_NOV,SAI_DEC, &
Expand All @@ -11449,6 +11451,7 @@ subroutine read_mp_veg_parameters(DATASET_IDENTIFIER)
RC_TABLE = -1.0E36
MFSNO_TABLE = -1.0E36
SCFFAC_TABLE = -1.0E36
CBIOM_TABLE = -1.0E36
RHOL_TABLE = -1.0E36
RHOS_TABLE = -1.0E36
TAUL_TABLE = -1.0E36
Expand Down Expand Up @@ -11561,6 +11564,7 @@ subroutine read_mp_veg_parameters(DATASET_IDENTIFIER)
RC_TABLE(1:NVEG) = RC(1:NVEG)
MFSNO_TABLE(1:NVEG) = MFSNO(1:NVEG)
SCFFAC_TABLE(1:NVEG) = SCFFAC(1:NVEG)
CBIOM_TABLE(1:NVEG) = CBIOM(1:NVEG)
XL_TABLE(1:NVEG) = XL(1:NVEG)
CWPVT_TABLE(1:NVEG) = CWPVT(1:NVEG)
C3PSN_TABLE(1:NVEG) = C3PSN(1:NVEG)
Expand Down

0 comments on commit 4b7870f

Please sign in to comment.