Skip to content

Commit f452d20

Browse files
committed
improve parsing speed by about 8.5/100
1 parent d13dfca commit f452d20

File tree

1 file changed

+41
-37
lines changed

1 file changed

+41
-37
lines changed

src/fpm_source_parsing.f90

Lines changed: 41 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -78,7 +78,7 @@ function parse_f_source(f_filename,error) result(f_source)
7878

7979
integer :: stat
8080
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(:)
8282
character(:), allocatable :: temp_string, mod_name, string_parts(:)
8383

8484
f_source%file_name = f_filename
@@ -87,62 +87,67 @@ function parse_f_source(f_filename,error) result(f_source)
8787
file_lines = read_lines(fh)
8888
close(fh)
8989

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
9299

93100
f_source%digest = fnv_1a(file_lines)
94101

95102
do pass = 1,2
96103
n_use = 0
97104
n_include = 0
98105
n_mod = 0
99-
file_loop: do i=1,size(file_lines)
106+
file_loop: do i=1,size(file_lines_lower)
100107

101108
! Skip lines that are continued: not statements
102109
if (i > 1) then
103-
ic = index(file_lines(i-1)%s,'!')
110+
ic = index(file_lines_lower(i-1)%s,'!')
104111
if (ic < 1) then
105-
ic = len(file_lines(i-1)%s)
112+
ic = len(file_lines_lower(i-1)%s)
106113
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))
108115
if (len(temp_string) > 0 .and. index(temp_string,'&') == len(temp_string)) then
109116
cycle
110117
end if
111118
end if
112119

113120
! 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
116123

117-
if (index(file_lines(i)%s,'::') > 0) then
124+
if (index(file_lines_lower(i)%s,'::') > 0) then
118125

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)
120127
if (stat /= 0) then
121128
call file_parse_error(error,f_filename, &
122129
'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,'::'))
124131
return
125132
end if
126133

127134
mod_name = split_n(temp_string,delims=' ,',n=1,stat=stat)
128135
if (stat /= 0) then
129136
call file_parse_error(error,f_filename, &
130137
'unable to find used module name',i, &
131-
file_lines(i)%s)
138+
file_lines_lower(i)%s)
132139
return
133140
end if
134-
mod_name = lower(mod_name)
135141

136142
else
137143

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)
139145
if (stat /= 0) then
140146
call file_parse_error(error,f_filename, &
141147
'unable to find used module name',i, &
142-
file_lines(i)%s)
148+
file_lines_lower(i)%s)
143149
return
144150
end if
145-
mod_name = lower(mod_name)
146151

147152
end if
148153

@@ -166,13 +171,12 @@ function parse_f_source(f_filename,error) result(f_source)
166171
end if
167172

168173
! Process 'INCLUDE' statements
169-
ic = index(adjustl(lower(file_lines(i)%s)),'include')
174+
ic = index(file_lines_lower(i)%s,'include')
170175
if ( ic == 1 ) then
171176
ic = index(lower(file_lines(i)%s),'include')
172177
if (index(adjustl(file_lines(i)%s(ic+7:)),'"') == 1 .or. &
173178
index(adjustl(file_lines(i)%s(ic+7:)),"'") == 1 ) then
174179

175-
176180
n_include = n_include + 1
177181

178182
if (pass == 2) then
@@ -189,14 +193,14 @@ function parse_f_source(f_filename,error) result(f_source)
189193
end if
190194

191195
! 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
193197

194198
! Remove any trailing comments
195-
ic = index(file_lines(i)%s,'!')-1
199+
ic = index(file_lines_lower(i)%s,'!')-1
196200
if (ic < 1) then
197-
ic = len(file_lines(i)%s)
201+
ic = len(file_lines_lower(i)%s)
198202
end if
199-
temp_string = trim(file_lines(i)%s(1:ic))
203+
temp_string = trim(file_lines_lower(i)%s(1:ic))
200204

201205
! R1405 module-stmt := "MODULE" module-name
202206
! module-stmt has two space-delimited parts only
@@ -206,7 +210,7 @@ function parse_f_source(f_filename,error) result(f_source)
206210
cycle
207211
end if
208212

209-
mod_name = lower(trim(adjustl(string_parts(2))))
213+
mod_name = trim(adjustl(string_parts(2)))
210214
if (scan(mod_name,'=(&')>0 ) then
211215
! Ignore these cases:
212216
! module <something>&
@@ -218,7 +222,7 @@ function parse_f_source(f_filename,error) result(f_source)
218222
if (.not.is_fortran_name(mod_name)) then
219223
call file_parse_error(error,f_filename, &
220224
'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))
222226
return
223227
end if
224228

@@ -233,29 +237,29 @@ function parse_f_source(f_filename,error) result(f_source)
233237
end if
234238

235239
! 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
237241

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)
239243
if (stat /= 0) then
240244
call file_parse_error(error,f_filename, &
241245
'unable to get submodule name',i, &
242-
file_lines(i)%s)
246+
file_lines_lower(i)%s)
243247
return
244248
end if
245249
if (.not.is_fortran_name(mod_name)) then
246250
call file_parse_error(error,f_filename, &
247251
'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))
249253
return
250254
end if
251255

252256
n_mod = n_mod + 1
253257

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)
255259
if (stat /= 0) then
256260
call file_parse_error(error,f_filename, &
257261
'unable to get submodule ancestry',i, &
258-
file_lines(i)%s)
262+
file_lines_lower(i)%s)
259263
return
260264
end if
261265

@@ -274,23 +278,23 @@ function parse_f_source(f_filename,error) result(f_source)
274278
if (.not.is_fortran_name(temp_string)) then
275279
call file_parse_error(error,f_filename, &
276280
'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))
278282
return
279283
end if
280284

281-
f_source%modules_used(n_use)%s = lower(temp_string)
285+
f_source%modules_used(n_use)%s = temp_string
282286

283-
f_source%modules_provided(n_mod)%s = lower(mod_name)
287+
f_source%modules_provided(n_mod)%s = mod_name
284288

285289
end if
286290

287291
end if
288292

289293
! Detect if contains a program
290294
! (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
292296

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)
294298
if (stat == 0) then
295299

296300
if (scan(temp_string,'=(')>0 ) then
@@ -357,7 +361,7 @@ function parse_c_source(c_filename,error) result(c_source)
357361
file_lines = read_lines(fh)
358362
close(fh)
359363

360-
! Ignore empty files, returned as FPM_UNIT_UNKNOW
364+
! Ignore empty files, returned as FPM_UNIT_UNKNOWN
361365
if (len_trim(file_lines) < 1) then
362366
c_source%unit_type = FPM_UNIT_UNKNOWN
363367
return

0 commit comments

Comments
 (0)