TreeMig Code
Loading...
Searching...
No Matches
ReadNewBioClim.f90
Go to the documentation of this file.
1!==============================================================================
23!==============================================================================
26 use loggermodule
27
30 IMPLICIT NONE
31
32
33
34
35 INTEGER :: err, ilat, ilon, oldcctime, isite, ngridcells, newtime
36 REAL :: xr, yr, muDD, stdDD, muWiT, stdWiT, prop0DrStr, muDrStr, stdDrStr, distu, brwpr, germDrought, avnit
37 REAL :: drivervariables(nDrivers)
38 REAL :: AssignReadOrDefaultDriver
39
40! Here the SUBROUTINE starts>**********************************************************************
41 err = 0
42 oldcctime = 0
43 newbioclim%bc%muDD = -999.0 ! null value, later used for masking out
44
45 ngridcells = int(((latrealend - latrealstart)*unitofspatialdata/cellsidelength + 1) & ! the total number of grid cells; is the maximum number of lines per year in the bioclimate file
47!---- loop at least over so many lines as there are grid cells
48 do isite = 1, ngridcells
49 !---- read one line of drivers
50
51 read (bioclimate_file%unit, *, iostat=err) drivervariables
52
53 !---- These driver variables have to be present
54 xr = drivervariables(columnlocations(1))
55 yr = drivervariables(columnlocations(2))
56 newtime = drivervariables(columnlocations(3))
57 mudd = drivervariables(columnlocations(4))
58 muwit = drivervariables(columnlocations(5))
59 mudrstr = drivervariables(columnlocations(6))
60 !---- These optional driver variables are assigned to the correct variables
61 !---- Or they are set to default, if they are not present in the data set. The indices refer to the allowed drivers in All_par
62
63 distu = assignreadordefaultdriver(7, "Large scale disturbances (distu) " ,ndrivers, drivervariables)
64 brwpr = assignreadordefaultdriver(8, "Browsing pressure (brwpr) " ,ndrivers, drivervariables)
65 germdrought= assignreadordefaultdriver(9, "Germination drought (germDrought) " ,ndrivers, drivervariables)
66 avnit = assignreadordefaultdriver(10,"Nutrient availability (avnit) " ,ndrivers, drivervariables)
67
68 ! if germDrought is set to default -1, then the drought stress for the trees (muDrStr) is used
69 if (abs(germdrought - (-1.0)) < 1e-5) then
70 germdrought = mudrstr
71 end if
72!---- the standard deviations are set to very small values, because the standard case is yearly data
73!---- analogously the proportion of zero-drought years is set to 0
74!---- this is a legacy from before when these statistical parameters were used for longer periods of bioclimate
75!---- maybe the stdevs and prop0DrStr can completely be omitted. To be checked
76 stddd = 0.0000001
77 stdwit = 0.0000001
78 prop0drstr = 0
79 stddrstr = 0.0000001
80!---- if the read in year (newtime) was later than the last read in year (oldcctime), then all bioclimate data were read, and the loop can be left
81 if ((isite > 1) .AND. (newtime /= oldcctime)) then
82 backspace(bioclimate_file%unit)
83 exit
84 end if
85
86 ilat = 1 + nint((yr - latrealstart)*unitofspatialdata/cellsidelength)
87 ilon = 1 + nint((xr - lonrealstart)*unitofspatialdata/cellsidelength)
88!---- error handling if the bioclimate region is outside the simulation region.
89!---- if it is smaller, doesn't matter, then the non-read in cells are set to Null (dd= -999) and by this masked out
90 if ((ilat > maxlat) .or. (ilon > maxlon)) then
91 write (logmessage, "(A)") "Coordinates are outside domain in bioclimate"
93 write (logmessage, "(6A15)") "yr", "xr", "ilon", "ilat", "maxlon", "maxlat"
95 write (logmessage, "(2F8.7,4I15)") yr, xr, ilon, ilat, maxlon, maxlat
97 error stop
98 end if
99!---- Assign the read in values to the right places in newBioClim
100 newbioclim%cctime = newtime
101
102 newbioclim%bc(ilat, ilon)%muDD = mudd
103 newbioclim%bc(ilat, ilon)%stdDD = stddd
104 newbioclim%bc(ilat, ilon)%muWiT = muwit
105 newbioclim%bc(ilat, ilon)%stdWiT = stdwit
106 newbioclim%bc(ilat, ilon)%prop0DrStr = prop0drstr
107 newbioclim%bc(ilat, ilon)%muDrStr = mudrstr
108 newbioclim%bc(ilat, ilon)%stdDrStr = stddrstr
109 newbioclim%bc(ilat, ilon)%disturb = distu
110 newbioclim%bc(ilat, ilon)%brwpr = brwpr
111 newbioclim%bc(ilat, ilon)%germDrought= germdrought
112 newbioclim%bc(ilat, ilon)%avnit = avnit
113 if (err /= 0) then
114 exit
115 end if
116 oldcctime = newtime ! update the read in time
117 end do
118 end SUBROUTINE readnewbioclim
119
120!==============================================================================
135!==============================================================================
136 function assignreadordefaultdriver (idriver, drivertext, nDrivers, drivervariables) &
137 result(driver)
139 use loggermodule
140
141 IMPLICIT NONE
142
143 REAL, INTENT(in) :: drivervariables(ndrivers)
144 INTEGER, INTENT(in) :: idriver,ndrivers
145 character(len=35), INTENT(in) :: drivertext
146 REAL :: driver ,defaultvalue
147 character(len=: ), allocatable ::defaulttext
148
149 defaulttext = " not read in, set to default value "
150 !---- get the default value of this (idriver) driver
151 defaultvalue = driverdefault(idriver)
152 !---- if the driver was read in, i.e. it has a columnlocation, it is assigned to the corresponding drivervariable
153 if (columnlocations(idriver)>0) then
154 driver = drivervariables(columnlocations(idriver))
155 else ! otherwise it is set to its default value
156 driver = defaultvalue
157 ! write (LogMessage, "(A,A,F9.3)") drivertext,defaultText, defaultvalue
158 ! call LogInfo (LogMessage)
159 end if
160 end function
161!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
162
163!done
real function assignreadordefaultdriver(idriver, drivertext, ndrivers, drivervariables)
AssignReadOrDefaultDriver
subroutine readnewbioclim
ReadNewBioClim
real latrealend
Definition All_par.f90:50
real lonrealstart
Definition All_par.f90:50
real cellsidelength
Definition All_par.f90:63
real unitofspatialdata
Definition All_par.f90:53
real lonrealend
Definition All_par.f90:50
real, dimension(nalloweddrivernames) driverdefault
Definition All_par.f90:115
real latrealstart
Definition All_par.f90:50
character(len=:), allocatable e
Definition All_par.f90:93
integer maxlon
Definition All_par.f90:46
type(bioclimdata) newbioclim
Definition All_par.f90:351
integer, dimension(nalloweddrivernames) columnlocations
Definition All_par.f90:113
integer ndrivers
Definition All_par.f90:106
integer maxlat
Definition All_par.f90:45
type(file) bioclimate_file
LoggerModule.
character(len=1024) logmessage
subroutine logerror(msg)
LogError