TreeMig Code
Loading...
Searching...
No Matches
Allometries.f90
Go to the documentation of this file.
1!==============================================================================
2!
3! Module Allometries.f90!
4! Remarks: contains the functions BiomassFromDBH, DBHFromHeight, LAFromDBH
5!
6!==============================================================================
7
8!==============================================================================
23!===============================================================
24REAL FUNCTION biomassfromdbh(dbh, tb, stn) !,bm )
25 use all_par, only: a1, a2, c1
26
27IMPLICIT NONE
28 ! Passed variables>--------------------------------------------------------------------------------
29 real, intent(in) :: dbh ! tmp var to calculate diameters [=diam/nextDiam]
30 integer, intent(in) :: tb, stn ! tree species types [=diam/nextDiam]
31! real, intent(out) :: bm ! calculated biomas [=BioMassAtHeight(..)]
32
33 ! Local variables>---------------------------------------------------------------------------------
34 real :: bm ! calculated biomass [=BioMassAtHeight(..)]
35 real :: lndiam, & ! tmp var to calculate LA [=rLnDiam]
36 stmvol, & ! Stem volume [=stemvol]
37 stmwgt, & ! Stem weight [=stemW]
38 folwgt ! Foliage weight [=folW]
39
40 ! Here the subroutine starts>**********************************************************************
41 if (dbh .le. 0.0) then
42 lndiam = 0.0
43 folwgt = 0.0
44 stmvol = 0.0
45 else
46 lndiam = log(dbh*100.0)
47 folwgt = c1(tb) * a1(stn) * exp(lndiam * a2(stn))
48 stmvol = 0.12*exp(lndiam*2.4)
49 end if
50
51 !NZ: if output should only be stem volume (timber harvesting), comment next 2 lines out
52 ! and set bm = stmvol instead
53 stmwgt = 0.5*stmvol
54 bm = stmwgt + folwgt
56 return
57end FUNCTION biomassfromdbh
58
59!==============================================================================
72!===============================================================
73REAL FUNCTION dbhfromheight(height, birthheigth, maxheigth, maxdiam)
74IMPLICIT NONE
75REAL, intent(IN):: height,birthheigth, maxheigth, maxdiam
76REAL :: argmt
77 argmt = min(max(1.0 - ((height - birthheigth)/(real(maxheigth) - birthheigth)), 0.0), 1.0)
78 dbhfromheight = maxdiam * (1.0 - sqrt(argmt)) + 0.0127
79return
80END FUNCTION dbhfromheight
81
82!==============================================================================
97!===============================================================
98REAL FUNCTION lafromdbh(dbh, tb, stn)
99Use all_par, only: a1, a2, c2
100IMPLICIT NONE
101REAL, intent(IN) :: dbh
102INTEGER, intent(IN):: tb, stn
103REAL :: lndia
104if (dbh > 0.0) then
105 lndia = log(dbh * 100.0)
106else
107 lndia = 0
108end if
109lafromdbh = c2(tb) * a1(stn) * exp( lndia * a2(stn) )
110return
111END FUNCTION lafromdbh
112!==============================================================================
real function dbhfromheight(height, birthheigth, maxheigth, maxdiam)
DBHFromHeight.
real function lafromdbh(dbh, tb, stn)
LAFromDBH.
real function biomassfromdbh(dbh, tb, stn)
BiomassFromDBH.
real, dimension(5) a2
Definition All_par.f90:131
real stmvol
Definition All_par.f90:157
real, dimension(2) c1
Definition All_par.f90:132
real, dimension(5) a1
Definition All_par.f90:130
real, dimension(2) c2
Definition All_par.f90:133