Skip to content

Commit

Permalink
Added PAVD condition if ZK (at max GEDI PAVD height) > GEDI FCH.
Browse files Browse the repository at this point in the history
  • Loading branch information
drnimbusrain committed Jan 3, 2024
1 parent a74b94b commit c507035
Show file tree
Hide file tree
Showing 2 changed files with 9 additions and 5 deletions.
5 changes: 2 additions & 3 deletions src/canopy_calcs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -140,7 +140,6 @@ SUBROUTINE canopy_calcs(nn)
pai, zcanmax, sigmau, sigma1)

! ... Choose between prescribed canopy/foliate shape profile or observed GEDI PAVD profile

if (pavd_opt .eq. 0) then
! ... calculate canopy/foliage distribution shape profile - bottom up total in-canopy and fraction at z
call canopy_foliage(modlays, zhc, zcanmax, sigmau, sigma1, &
Expand All @@ -149,7 +148,7 @@ SUBROUTINE canopy_calcs(nn)
! ... derive canopy/foliage distribution shape profile from interpolated GEDI PAVD profile - bottom up total in-canopy and fraction at z
if (variables_2d(i,j)%lat .gt. (-1.0_rk*pavd_set) .and. &
variables_2d(i,j)%lat .lt. pavd_set) then !use GEDI PAVD
call canopy_pavd2fafrac(sigmau, sigma1, hcmref, zhc, &
call canopy_pavd2fafrac(zcanmax, sigmau, sigma1, hcmref, zhc, &
variables_3d(i,j,:)%pavd, variables_1d%lev, fafraczInt)
!check if there is observed canopy height but no PAVD profile
if (hcmref .gt. 0.0 .and. maxval(fafraczInt) .le. 0.0) then !revert to prescribed shape profile
Expand Down Expand Up @@ -555,7 +554,7 @@ SUBROUTINE canopy_calcs(nn)
! ... derive canopy/foliage distribution shape profile from interpolated GEDI PAVD profile - bottom up total in-canopy and fraction at z
if (variables(loc)%lat .gt. (-1.0_rk*pavd_set) .and. &
variables(loc)%lat .lt. pavd_set) then !use GEDI PAVD
call canopy_pavd2fafrac(sigmau, sigma1, hcmref, zhc, &
call canopy_pavd2fafrac(zcanmax, sigmau, sigma1, hcmref, zhc, &
pavd_arr, lev_arr, fafraczInt)
!check if there is observed canopy height but no PAVD profile
if (hcmref .gt. 0.0 .and. maxval(fafraczInt) .le. 0.0) then !revert to prescribed shape profile
Expand Down
9 changes: 7 additions & 2 deletions src/canopy_var3din_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@ module canopy_var3din_mod
contains

!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
SUBROUTINE CANOPY_PAVD2FAFRAC ( SIGMAU, SIGMA1, FCH, ZHC, &
PAVD_IN, PAVD_LEVS, FAFRACZINT )
SUBROUTINE CANOPY_PAVD2FAFRAC ( ZCANMAX_IN, SIGMAU, SIGMA1, FCH, &
ZHC, PAVD_IN, PAVD_LEVS, FAFRACZINT )


!-----------------------------------------------------------------------
Expand All @@ -31,6 +31,7 @@ SUBROUTINE CANOPY_PAVD2FAFRAC ( SIGMAU, SIGMA1, FCH, ZHC, &
! Arguments:
! IN/OUT
REAL(RK), INTENT( IN ) :: FCH ! Grid cell canopy height (m) !From GEDI
REAL(RK), INTENT( IN ) :: ZCANMAX_IN ! Input height of maximum foliage area density (z/h) (nondimensional)
REAL(RK), INTENT( IN ) :: SIGMAU ! Standard deviation of shape function above zcanmax (z/h)
REAL(RK), INTENT( IN ) :: SIGMA1 ! Standard deviation of shape function below zcanmax (z/h)
REAL(RK), INTENT( IN ) :: ZHC(:) ! z/h (dimensionless)
Expand Down Expand Up @@ -71,6 +72,9 @@ SUBROUTINE CANOPY_PAVD2FAFRAC ( SIGMAU, SIGMA1, FCH, ZHC, &
do i=2, SIZE(ZK)
if (PAVD_INTERP(i) .ge. maxval(PAVD_INTERP) ) then
ZCANMAX = ZK(i)/FCH
if(ZCANMAX .gt. 1.0_rk) then !if ZK (at max GEDI PAVD height) > GEDI FCH (inconsistent!)
ZCANMAX = ZCANMAX_IN !override with Massman Input ZCANMAX
end if
exit
end if
end do
Expand All @@ -86,6 +90,7 @@ SUBROUTINE CANOPY_PAVD2FAFRAC ( SIGMAU, SIGMA1, FCH, ZHC, &

! ... calculate canopy/foliage distribution shape profile - bottom up total in-canopy and fraction at z
do i=1, SIZE(ZK)
! print*, 'ZK=',ZK(i), 'ZHC=',ZHC(i),'ZCANMAX=',ZCANMAX
if (ZHC(i) >= ZCANMAX .and. ZHC(i) <= 1.0) then
fainc(i) = exp((-1.0*((ZHC(i)-ZCANMAX)**2.0))/SIGMAU**2.0)
else if (ZHC(i) >= 0.0 .and. ZHC(i) <= ZCANMAX) then
Expand Down

0 comments on commit c507035

Please sign in to comment.