TreeMig Code
Loading...
Searching...
No Matches
PrepareBioclimInput.f90
Go to the documentation of this file.
1!==============================================================================
2!
3! Name : PrepareBioclimInput
4!
5! Remarks: contains the SUBROUTINES
6!
7! PrepareBioclimInput (<TreeMig)
8! CheckDriverNames
9!==============================================================================
35! !==============================================================================
41
42
43 IMPLICIT NONE
44
45
46 INTEGER :: err
47 character(len=:), allocatable :: rest
48
49
50 !----- opens the bioclimate file
51 call openfiler(bioclimate_file, err)
52 if (err /= 0) then
53 call logerror("Could not open bioclimate file: "//bioclimate_file%path)
54 error stop
55 end if
56 !----- extracts the header column names
58 !print *, nDrivers, (trim(columnNamesOfDrivers(iread ) )//"," , iread=1, nDrivers)
59 !----- checks whether these header column names are allowed
60 call checkdrivernames()
61
62 !read (Bioclimate_File%unit, *) ! read header
63 write (logmessage, '(A)') "Read and checked header of "//bioclimate_file%path//", now reading first year"
65 ! read one year of the bioclimate
67
68end SUBROUTINE preparebiocliminput
69
70!==============================================================================
71! @brief CheckDriverNames
72! *****************************************
98!==============================================================================
99SUBROUTINE checkdrivernames()
102 use loggermodule, only: logerror
103 IMPLICIT NONE
104
105
106 INTEGER :: iallowed, iread, nAllowedNames
107 LOGICAL :: ok, innerok
108 character(len=:), allocatable :: allowedName, readName,allowedNamesString
109
110
111 nallowednames = size(alloweddrivernames)
112
113 !---- are all required names (lon, lat, year, DD, WiT, DrStr) present?
114 !---- note, the first 6 names in allowedDriverNames are the required, the additional ones are allowed
115 ok=.true.
116 iallowed=0
117 do while((iallowed < 6) .and. ok) ! only the first 6 must be present
118 iallowed = iallowed+1
119 allowedname = trim(alloweddrivernames(iallowed)) ! get one allowed name
120 innerok =.false.
121 iread=0
122 do while((iread < ndrivers) .and. (.not.innerok)) ! compare it to all column names
123 iread = iread + 1
124 readname= trim(columnnamesofdrivers(iread))
125 innerok = readname == allowedname ! check it against one allowed name
126 end do
127 ok = innerok
128 end do
129 if (ok ) then
130 ! print *, "All required column names are present."
131 else
132 call logerror("At least the required column "//trim(alloweddrivernames(iallowed))// &
133 " is missing in input file "//bioclimate_file%path)
134 error stop
135 end if
136
137 !---- are all read column names allowed (including required) ?
138
139 columnlocations(:) = 0
140 ok=.true.
141 iread=0
142 do while((iread < ndrivers) .and. ok)
143 iread = iread + 1
144 readname= trim(columnnamesofdrivers(iread) ) ! get the read in column name
145 innerok =.false.
146 iallowed=0
147 do while((iallowed < nallowednames) .and. (.not.innerok) ) ! compare it to all allowed names
148 iallowed = iallowed + 1
149 allowedname =trim(alloweddrivernames(iallowed))
150 innerok = readname == allowedname
151 end do
152 if (innerok) columnlocations(iallowed)=iread ! note, which column corresponds to the allowed name
153 ok=innerok
154 end do
155
156 if (ok) then
157 ! print *, "ok: all column names allowed "
158 else
159 !---- make a string out of the vector of allowed driver names, with "," as a separator; only for error message
160 allowednamesstring=""
161 do iallowed= 1,nallowednames-1
162 allowednamesstring = allowednamesstring//trim(alloweddrivernames(iallowed))//","
163 end do
164 allowednamesstring = allowednamesstring//trim(alloweddrivernames(nallowednames))
165 !---- log the error message
166 call logerror("At least the column "//readname// " in input file "//bioclimate_file%path &
167 //" is not within the allowed names "// allowednamesstring )
168 error stop
169 end if
170
171end SUBROUTINE checkdrivernames
172
173!done
174
175
subroutine preparebiocliminput()
PrepareBioclimInput
subroutine checkdrivernames()
subroutine readnewbioclim
ReadNewBioClim
character(len=30), dimension(nalloweddrivernames), parameter alloweddrivernames
Definition All_par.f90:109
character(len=30), dimension(1:50) columnnamesofdrivers
Definition All_par.f90:107
type(wroutp) true
Definition All_par.f90:143
integer, dimension(nalloweddrivernames) columnlocations
Definition All_par.f90:113
type(wroutp) false
Definition All_par.f90:143
integer ndrivers
Definition All_par.f90:106
subroutine openfiler(thefile, err)
openFileR
subroutine extractandcountwords(thefile, nwords, words, rest, err)
ExtractAndCountWords
type(file) bioclimate_file
LoggerModule.
subroutine loginfo(msg)
LogInfo
character(len=1024) logmessage
subroutine logerror(msg)
LogError