@@ -78,7 +78,7 @@ function parse_f_source(f_filename,error) result(f_source)
78
78
79
79
integer :: stat
80
80
integer :: fh, n_use, n_include, n_mod, i, j, ic, pass
81
- type (string_t), allocatable :: file_lines(:)
81
+ type (string_t), allocatable :: file_lines(:), file_lines_lower(:)
82
82
character (:), allocatable :: temp_string, mod_name, string_parts(:)
83
83
84
84
f_source% file_name = f_filename
@@ -87,62 +87,67 @@ function parse_f_source(f_filename,error) result(f_source)
87
87
file_lines = read_lines(fh)
88
88
close (fh)
89
89
90
- ! Ignore empty files, returned as FPM_UNIT_UNKNOW
91
- if (len_trim (file_lines) < 1 ) return
90
+ ! for efficiency in parsing make a lowercase left-adjusted copy of the file
91
+ ! Need a copy because INCLUDE (and #include) file arguments are case-sensitive
92
+ file_lines_lower= file_lines
93
+ do i= 1 ,size (file_lines_lower)
94
+ file_lines_lower(i)% s= adjustl (lower(file_lines_lower(i)% s))
95
+ enddo
96
+
97
+ ! Ignore empty files, returned as FPM_UNIT_UNKNOWN
98
+ if (len_trim (file_lines_lower) < 1 ) return
92
99
93
100
f_source% digest = fnv_1a(file_lines)
94
101
95
102
do pass = 1 ,2
96
103
n_use = 0
97
104
n_include = 0
98
105
n_mod = 0
99
- file_loop: do i= 1 ,size (file_lines )
106
+ file_loop: do i= 1 ,size (file_lines_lower )
100
107
101
108
! Skip lines that are continued: not statements
102
109
if (i > 1 ) then
103
- ic = index (file_lines (i-1 )% s,' !' )
110
+ ic = index (file_lines_lower (i-1 )% s,' !' )
104
111
if (ic < 1 ) then
105
- ic = len (file_lines (i-1 )% s)
112
+ ic = len (file_lines_lower (i-1 )% s)
106
113
end if
107
- temp_string = trim (file_lines (i-1 )% s(1 :ic))
114
+ temp_string = trim (file_lines_lower (i-1 )% s(1 :ic))
108
115
if (len (temp_string) > 0 .and. index (temp_string,' &' ) == len (temp_string)) then
109
116
cycle
110
117
end if
111
118
end if
112
119
113
120
! Process 'USE' statements
114
- if (index (adjustl (lower(file_lines( i)% s)) ,' use ' ) == 1 .or. &
115
- index (adjustl (lower(file_lines( i)% s)) ,' use::' ) == 1 ) then
121
+ if (index (file_lines_lower( i)% s,' use ' ) == 1 .or. &
122
+ index (file_lines_lower( i)% s,' use::' ) == 1 ) then
116
123
117
- if (index (file_lines (i)% s,' ::' ) > 0 ) then
124
+ if (index (file_lines_lower (i)% s,' ::' ) > 0 ) then
118
125
119
- temp_string = split_n(file_lines (i)% s,delims= ' :' ,n= 2 ,stat= stat)
126
+ temp_string = split_n(file_lines_lower (i)% s,delims= ' :' ,n= 2 ,stat= stat)
120
127
if (stat /= 0 ) then
121
128
call file_parse_error(error,f_filename, &
122
129
' unable to find used module name' ,i, &
123
- file_lines (i)% s,index (file_lines (i)% s,' ::' ))
130
+ file_lines_lower (i)% s,index (file_lines_lower (i)% s,' ::' ))
124
131
return
125
132
end if
126
133
127
134
mod_name = split_n(temp_string,delims= ' ,' ,n= 1 ,stat= stat)
128
135
if (stat /= 0 ) then
129
136
call file_parse_error(error,f_filename, &
130
137
' unable to find used module name' ,i, &
131
- file_lines (i)% s)
138
+ file_lines_lower (i)% s)
132
139
return
133
140
end if
134
- mod_name = lower(mod_name)
135
141
136
142
else
137
143
138
- mod_name = split_n(file_lines (i)% s,n= 2 ,delims= ' ,' ,stat= stat)
144
+ mod_name = split_n(file_lines_lower (i)% s,n= 2 ,delims= ' ,' ,stat= stat)
139
145
if (stat /= 0 ) then
140
146
call file_parse_error(error,f_filename, &
141
147
' unable to find used module name' ,i, &
142
- file_lines (i)% s)
148
+ file_lines_lower (i)% s)
143
149
return
144
150
end if
145
- mod_name = lower(mod_name)
146
151
147
152
end if
148
153
@@ -166,13 +171,12 @@ function parse_f_source(f_filename,error) result(f_source)
166
171
end if
167
172
168
173
! Process 'INCLUDE' statements
169
- ic = index (adjustl (lower(file_lines( i)% s)) ,' include' )
174
+ ic = index (file_lines_lower( i)% s,' include' )
170
175
if ( ic == 1 ) then
171
176
ic = index (lower(file_lines(i)% s),' include' )
172
177
if (index (adjustl (file_lines(i)% s(ic+7 :)),' "' ) == 1 .or. &
173
178
index (adjustl (file_lines(i)% s(ic+7 :))," '" ) == 1 ) then
174
179
175
-
176
180
n_include = n_include + 1
177
181
178
182
if (pass == 2 ) then
@@ -189,14 +193,14 @@ function parse_f_source(f_filename,error) result(f_source)
189
193
end if
190
194
191
195
! Extract name of module if is module
192
- if (index (adjustl (lower(file_lines( i)% s)) ,' module ' ) == 1 ) then
196
+ if (index (file_lines_lower( i)% s,' module ' ) == 1 ) then
193
197
194
198
! Remove any trailing comments
195
- ic = index (file_lines (i)% s,' !' )- 1
199
+ ic = index (file_lines_lower (i)% s,' !' )- 1
196
200
if (ic < 1 ) then
197
- ic = len (file_lines (i)% s)
201
+ ic = len (file_lines_lower (i)% s)
198
202
end if
199
- temp_string = trim (file_lines (i)% s(1 :ic))
203
+ temp_string = trim (file_lines_lower (i)% s(1 :ic))
200
204
201
205
! R1405 module-stmt := "MODULE" module-name
202
206
! module-stmt has two space-delimited parts only
@@ -206,7 +210,7 @@ function parse_f_source(f_filename,error) result(f_source)
206
210
cycle
207
211
end if
208
212
209
- mod_name = lower( trim (adjustl (string_parts(2 ) )))
213
+ mod_name = trim (adjustl (string_parts(2 )))
210
214
if (scan (mod_name,' =(&' )>0 ) then
211
215
! Ignore these cases:
212
216
! module <something>&
@@ -218,7 +222,7 @@ function parse_f_source(f_filename,error) result(f_source)
218
222
if (.not. is_fortran_name(mod_name)) then
219
223
call file_parse_error(error,f_filename, &
220
224
' empty or invalid name for module' ,i, &
221
- file_lines (i)% s, index (file_lines (i)% s,mod_name))
225
+ file_lines_lower (i)% s, index (file_lines_lower (i)% s,mod_name))
222
226
return
223
227
end if
224
228
@@ -233,29 +237,29 @@ function parse_f_source(f_filename,error) result(f_source)
233
237
end if
234
238
235
239
! Extract name of submodule if is submodule
236
- if (index (adjustl (lower(file_lines( i)% s)) ,' submodule' ) == 1 ) then
240
+ if (index (file_lines_lower( i)% s,' submodule' ) == 1 ) then
237
241
238
- mod_name = split_n(file_lines (i)% s,n= 3 ,delims= ' ()' ,stat= stat)
242
+ mod_name = split_n(file_lines_lower (i)% s,n= 3 ,delims= ' ()' ,stat= stat)
239
243
if (stat /= 0 ) then
240
244
call file_parse_error(error,f_filename, &
241
245
' unable to get submodule name' ,i, &
242
- file_lines (i)% s)
246
+ file_lines_lower (i)% s)
243
247
return
244
248
end if
245
249
if (.not. is_fortran_name(mod_name)) then
246
250
call file_parse_error(error,f_filename, &
247
251
' empty or invalid name for submodule' ,i, &
248
- file_lines (i)% s, index (file_lines (i)% s,mod_name))
252
+ file_lines_lower (i)% s, index (file_lines_lower (i)% s,mod_name))
249
253
return
250
254
end if
251
255
252
256
n_mod = n_mod + 1
253
257
254
- temp_string = split_n(file_lines (i)% s,n= 2 ,delims= ' ()' ,stat= stat)
258
+ temp_string = split_n(file_lines_lower (i)% s,n= 2 ,delims= ' ()' ,stat= stat)
255
259
if (stat /= 0 ) then
256
260
call file_parse_error(error,f_filename, &
257
261
' unable to get submodule ancestry' ,i, &
258
- file_lines (i)% s)
262
+ file_lines_lower (i)% s)
259
263
return
260
264
end if
261
265
@@ -274,23 +278,23 @@ function parse_f_source(f_filename,error) result(f_source)
274
278
if (.not. is_fortran_name(temp_string)) then
275
279
call file_parse_error(error,f_filename, &
276
280
' empty or invalid name for submodule parent' ,i, &
277
- file_lines (i)% s, index (file_lines (i)% s,temp_string))
281
+ file_lines_lower (i)% s, index (file_lines_lower (i)% s,temp_string))
278
282
return
279
283
end if
280
284
281
- f_source% modules_used(n_use)% s = lower( temp_string)
285
+ f_source% modules_used(n_use)% s = temp_string
282
286
283
- f_source% modules_provided(n_mod)% s = lower( mod_name)
287
+ f_source% modules_provided(n_mod)% s = mod_name
284
288
285
289
end if
286
290
287
291
end if
288
292
289
293
! Detect if contains a program
290
294
! (no modules allowed after program def)
291
- if (index (adjustl (lower(file_lines( i)% s)) ,' program ' ) == 1 ) then
295
+ if (index (file_lines_lower( i)% s,' program ' ) == 1 ) then
292
296
293
- temp_string = lower( split_n(file_lines (i)% s,n= 2 ,delims= ' ' ,stat= stat) )
297
+ temp_string = split_n(file_lines_lower (i)% s,n= 2 ,delims= ' ' ,stat= stat)
294
298
if (stat == 0 ) then
295
299
296
300
if (scan (temp_string,' =(' )>0 ) then
@@ -357,7 +361,7 @@ function parse_c_source(c_filename,error) result(c_source)
357
361
file_lines = read_lines(fh)
358
362
close (fh)
359
363
360
- ! Ignore empty files, returned as FPM_UNIT_UNKNOW
364
+ ! Ignore empty files, returned as FPM_UNIT_UNKNOWN
361
365
if (len_trim (file_lines) < 1 ) then
362
366
c_source% unit_type = FPM_UNIT_UNKNOWN
363
367
return
0 commit comments