Skip to content

Commit 10d835a

Browse files
committed
Fix: include statement parsing
Include statements must have a single or double quote immediately following 'include'
1 parent 7ca0ba2 commit 10d835a

File tree

2 files changed

+21
-16
lines changed

2 files changed

+21
-16
lines changed

fpm/src/fpm_sources.f90

Lines changed: 17 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -300,21 +300,26 @@ function parse_f_source(f_filename,error) result(f_source)
300300
end if
301301

302302
! Process 'INCLUDE' statements
303-
if (index(adjustl(lower(file_lines(i)%s)),'include') == 1) then
304-
305-
n_include = n_include + 1
303+
ic = index(adjustl(lower(file_lines(i)%s)),'include')
304+
if ( ic == 1 ) then
305+
ic = index(lower(file_lines(i)%s),'include')
306+
if (index(adjustl(file_lines(i)%s(ic+7:)),'"') == 1 .or. &
307+
index(adjustl(file_lines(i)%s(ic+7:)),"'") == 1 ) then
306308

307-
if (pass == 2) then
308-
f_source%include_dependencies(n_include)%s = &
309-
& split_n(file_lines(i)%s,n=2,delims="'"//'"',stat=stat)
310-
if (stat /= 0) then
311-
call file_parse_error(error,f_filename, &
312-
'unable to find include file name',i, &
313-
file_lines(i)%s)
314-
return
309+
310+
n_include = n_include + 1
311+
312+
if (pass == 2) then
313+
f_source%include_dependencies(n_include)%s = &
314+
& split_n(file_lines(i)%s,n=2,delims="'"//'"',stat=stat)
315+
if (stat /= 0) then
316+
call file_parse_error(error,f_filename, &
317+
'unable to find include file name',i, &
318+
file_lines(i)%s)
319+
return
320+
end if
315321
end if
316322
end if
317-
318323
end if
319324

320325
! Extract name of module if is module

fpm/test/fpm_test/test_source_parsing.f90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -198,11 +198,11 @@ subroutine test_include_stmt(error)
198198
write(unit, '(a)') &
199199
& 'program test', &
200200
& ' implicit none', &
201-
& ' include "included_file.f90"', &
202-
& ' logical :: include_comments', &
203-
& ' include_comments = .false.', &
201+
& ' include "included_file.f90"', &
202+
& ' character(*) :: include_comments', &
203+
& ' include_comments = "some comments"', &
204204
& ' contains ', &
205-
& ' include "second_include.f90"', &
205+
& ' include"second_include.f90"', &
206206
& 'end program test'
207207
close(unit)
208208

0 commit comments

Comments
 (0)