TreeMig Code
Loading...
Searching...
No Matches
ReadState.f90
Go to the documentation of this file.
1!==============================================================================
29!===============================================================
30
31SUBROUTINE readstate(stateyear, latstart, latend, lonstart, lonend, nspc)
36
37 IMPLICIT NONE
38
39 ! Passed variables>--------------------------------------------------------------------------------
40 INTEGER, INTENT(in) :: latStart, latEnd, lonStart, lonEnd ! start and end of simulation domain
41 INTEGER, INTENT(in) :: nspc ! number of species
42 INTEGER, INTENT(out) :: stateyear ! year of state output
43
44 ! Local variables>---------------------------------------------------------------------------------
45 INTEGER :: height, & ! loop-counter
46 isp, i, currentLine, & ! loop-counter
47 lat, lon, err, & ! format variable
48 latOffset, lonOffset, & ! offsets to correct for different extents of statefile and simulation file
49 nhtc ! number of hight classes
50 character(len=1024) :: lineBuffer
51 character(len=200) :: ioerrmsg
52 character(len=100) :: nameLong
53 ! Here the SUBROUTINE starts>**********************************************************************
54
55 !---- initialize the state variables on the simulation domain with 0
56 looplat: do lat = latstart, latend
57 looplon: do lon = lonstart, lonend
58 do i = 1, nspc
59 stategrid(lat, lon)%sp(i)%seedBank = 0.
60 stategrid(lat, lon)%sp(i)%antagonist = 0.
61 do height = 0, spec(i)%maxhtc
62 stategrid(lat, lon)%sp(i)%numin(height) = 0.
63 end do !height
64 end do ! i (species)
65 end do looplon
66 end do looplat
67
68 !---- set offsets ????
69 latoffset = 0
70 lonoffset = 0
71
72 ! Read values, correct coordinates with offsets
73 call openfiler(statein_file, err) !open the state file closed (this l. 98)
74 if (err /= 0) then
75 call logerror("[Statefile] Could not open statefile: "//statein_file%path)
76 error stop
77 end if
78 backspace(statein_file%unit) ! go back one line. Why? Maybe because the first line is automatically read (Why?)
79
80 currentline = 0
81 do while (err == 0) ! go through the lines of the state file
82 ! keep track of currentLine
83 currentline = currentline + 1
84
85 ! read in line to buffer
86 read (statein_file%unit, "(A)", iostat=err, iomsg=ioerrmsg) linebuffer
87
88 ! check for EOF/errors
89 if (err < 0) then ! EOF
90 exit;
91 else if (err > 0) then ! error
92 write (logmessage, "(A,I10)") "[Statfile] Could not read line in statefile. Line: ", currentline
94 call logerror("[Statfile][Details] io-msg: "//ioerrmsg)
95 write (logmessage, "(A,I3)") "[Statfile][Details] io-stat: ",err
97 call logerror("[Statfile][Details] statefile path: "//statein_file%path)
98 call logerror("[Statfile][Details] line: "//linebuffer)
99 error stop
100 end if
101
102 ! first read the species name (nameLong) to get get maxhtc (otherwise we dont know how many vars to read in)
103 ! also read lat lon for bounds check
104 read (linebuffer, *, iostat=err) namelong, stateyear, lat, lon;
105
106 ! error handling of read call
107 if(err /= 0) then
108 write (logmessage, "(A,I10)") "[Statfile] Could not parse line in statefile. Line: ", currentline
109 call logerror(logmessage)
110 call logerror("[Statfile][Details] line content: "//linebuffer)
111 error stop
112 end if
113
114 ! check bounds of lat and lon
115 if(lat+latoffset > maxlat .or. lat+latoffset < 0 .or. lon+lonoffset > maxlon .or. lon+lonoffset < 0) then
116 write (logmessage, "(A,I10)") "[Statfile] lat/lon are out of bounds in statefile. Line: ", currentline
117 call logerror(logmessage)
118 write (logmessage, "(A,I7,',',I7)") "[Statfile][Details] (latOffset, lonOffset): ", latoffset, lonoffset
119 call logerror(logmessage)
120 write (logmessage, "(A,I7,',',I7)") "[Statfile][Details] (lat,lon) inc. offset : ", lat+latoffset, lon+lonoffset
121 call logerror(logmessage)
122 write (logmessage, "(A,I7,',',I7)") "[Statfile][Details] (maxlat,maxlon) : ", maxlat, maxlon
123 call logerror(logmessage)
124 call logerror("[Statfile][Details] line content: "//linebuffer)
125 error stop
126 end if
127
128 ! find the species-idx
129 do isp = 1, nspc
130 if(namelong == spec(isp)%nl) exit; ! after exiting isp is the correct index
131 end do
132
133 ! check if we found the species-idx
134 if (isp > nspc) then
135 ! species does not exist in our species selection, skip
136 !write (LogMessage, "(A, I10)") "[Statfile] Ignoring species '"// trim(nameLong)// "' on line: ", currentLine
137 !call LogWarning(LogMessage)
138 continue
139 else
140 ! species is one of the selected species, load all values and store them to stateGrid, for species isp and in the different height classes
141 read (linebuffer, *, iostat=err) namelong, stateyear, lat, lon, &
142 stategrid(lat + latoffset, lon + lonoffset)%sp(isp)%seedBank, &
143 stategrid(lat + latoffset, lon + lonoffset)%sp(isp)%antagonist, &
144 nhtc, &
145 (stategrid(lat + latoffset, lon + lonoffset)%sp(isp)%numin(height), height=0, min(spec(isp)%maxhtc,nhtc))
146
147 ! error handling of read call
148 if (err /= 0) then
149 write (logmessage, "(A,I10)") "[Statfile] Could not parse line in statefile. Line: ", currentline
150 call logerror(logmessage)
151 call logerror("[Details] line content: "//linebuffer)
152 error stop
153 end if
154
155 end if
156 end do ! while (err==0)
157
158
159 write (logmessage, "(A,I7)") "[Statefile] Reading statefile complete. State year:",stateyear
160 call loginfo(logmessage)
161
163 if(stateyear-simustartyear < 0)then
164 write (logmessage, "(A,I6,A,I6,A)") "[Statfile] State-file year is smaller than the simulation start year."&
165 "State-file year will be set to start year. (",stateyear,"->",simustartyear,")"
167 stateyear = 0
168 else
169 stateyear = stateyear-simustartyear
170 end if
171
172end SUBROUTINE readstate
173!done
subroutine readstate(stateyear, latstart, latend, lonstart, lonend, nspc)
ReadState.
Definition ReadState.f90:32
integer simustartyear
Definition All_par.f90:27
integer, parameter maxhc
Definition All_par.f90:99
type(specproperties), dimension(maxspc) spec
Definition All_par.f90:345
type(currstateincell), dimension(:, :), allocatable stategrid
Definition All_par.f90:340
integer maxlon
Definition All_par.f90:46
real, dimension(t/ha), parameter biothreshold
Definition All_par.f90:57
integer maxlat
Definition All_par.f90:45
subroutine closefile(thefile)
closeFile
subroutine openfiler(thefile, err)
openFileR
type(file) statein_file
LoggerModule.
subroutine logwarning(msg)
LogError
subroutine loginfo(msg)
LogInfo
character(len=1024) logmessage
subroutine logerror(msg)
LogError