Skip to content

Commit deffb94

Browse files
authored
Merge pull request #303 from LKedward/fix-parsing
Fixes to source parsing
2 parents 983d244 + 33ad2ce commit deffb94

File tree

2 files changed

+92
-4
lines changed

2 files changed

+92
-4
lines changed

fpm/src/fpm_source_parsing.f90

Lines changed: 31 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@
1616
!>
1717
module fpm_source_parsing
1818
use fpm_error, only: error_t, file_parse_error, fatal_error
19-
use fpm_strings, only: string_t, split, lower, str_ends_with, fnv_1a
19+
use fpm_strings, only: string_t, string_cat, split, lower, str_ends_with, fnv_1a
2020
use fpm_model, only: srcfile_t, &
2121
FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
2222
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
@@ -86,6 +86,9 @@ function parse_f_source(f_filename,error) result(f_source)
8686
file_lines = read_lines(fh)
8787
close(fh)
8888

89+
! Ignore empty files, returned as FPM_UNIT_UNKNOW
90+
if (len_trim(string_cat(file_lines,' ')) < 1) return
91+
8992
f_source%digest = fnv_1a(file_lines)
9093

9194
do pass = 1,2
@@ -197,8 +200,14 @@ function parse_f_source(f_filename,error) result(f_source)
197200

198201
if (mod_name == 'procedure' .or. &
199202
mod_name == 'subroutine' .or. &
200-
mod_name == 'function') then
201-
! Ignore these cases
203+
mod_name == 'function' .or. &
204+
scan(mod_name,'=(')>0 ) then
205+
! Ignore these cases:
206+
! module procedure *
207+
! module function *
208+
! module subroutine *
209+
! module =*
210+
! module (i)
202211
cycle
203212
end if
204213

@@ -275,7 +284,19 @@ function parse_f_source(f_filename,error) result(f_source)
275284

276285
! Detect if contains a program
277286
! (no modules allowed after program def)
278-
if (index(adjustl(lower(file_lines(i)%s)),'program') == 1) then
287+
if (index(adjustl(lower(file_lines(i)%s)),'program ') == 1) then
288+
289+
temp_string = lower(split_n(file_lines(i)%s,n=2,delims=' ',stat=stat))
290+
if (stat == 0) then
291+
292+
if (scan(temp_string,'=(')>0 ) then
293+
! Ignore:
294+
! program =*
295+
! program (i) =*
296+
cycle
297+
end if
298+
299+
end if
279300

280301
f_source%unit_type = FPM_UNIT_PROGRAM
281302

@@ -370,6 +391,12 @@ function parse_c_source(c_filename,error) result(c_source)
370391
file_lines = read_lines(fh)
371392
close(fh)
372393

394+
! Ignore empty files, returned as FPM_UNIT_UNKNOW
395+
if (len_trim(string_cat(file_lines,' ')) < 1) then
396+
c_source%unit_type = FPM_UNIT_UNKNOWN
397+
return
398+
end if
399+
373400
c_source%digest = fnv_1a(file_lines)
374401

375402
do pass = 1,2

fpm/test/fpm_test/test_source_parsing.f90

Lines changed: 61 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@ subroutine collect_source_parsing(testsuite)
2424
& new_unittest("modules-used", test_modules_used), &
2525
& new_unittest("intrinsic-modules-used", test_intrinsic_modules_used), &
2626
& new_unittest("include-stmt", test_include_stmt), &
27+
& new_unittest("program", test_program), &
2728
& new_unittest("module", test_module), &
2829
& new_unittest("program-with-module", test_program_with_module), &
2930
& new_unittest("submodule", test_submodule), &
@@ -238,6 +239,61 @@ subroutine test_include_stmt(error)
238239

239240
end subroutine test_include_stmt
240241

242+
!> Try to parse a simple fortran program
243+
subroutine test_program(error)
244+
245+
!> Error handling
246+
type(error_t), allocatable, intent(out) :: error
247+
248+
integer :: unit
249+
character(:), allocatable :: temp_file
250+
type(srcfile_t), allocatable :: f_source
251+
252+
allocate(temp_file, source=get_temp_filename())
253+
254+
open(file=temp_file, newunit=unit)
255+
write(unit, '(a)') &
256+
& 'program my_program', &
257+
& 'use module_one', &
258+
& 'implicit none', &
259+
& 'integer :: module', &
260+
& 'module = 1', &
261+
& 'module= 1', &
262+
& 'module =1', &
263+
& 'module (i) =1', &
264+
& 'contains', &
265+
& 'subroutine f()', &
266+
& 'end subroutine f', &
267+
& 'end program my_program'
268+
close(unit)
269+
270+
f_source = parse_f_source(temp_file,error)
271+
if (allocated(error)) then
272+
return
273+
end if
274+
275+
if (f_source%unit_type /= FPM_UNIT_PROGRAM) then
276+
call test_failed(error,'Wrong unit type detected - expecting FPM_UNIT_PROGRAM')
277+
return
278+
end if
279+
280+
if (size(f_source%modules_provided) /= 0) then
281+
call test_failed(error,'Unexpected modules_provided - expecting zero')
282+
return
283+
end if
284+
285+
if (size(f_source%modules_used) /= 1) then
286+
call test_failed(error,'Incorrect number of modules_used - expecting one')
287+
return
288+
end if
289+
290+
if (.not.('module_one' .in. f_source%modules_used)) then
291+
call test_failed(error,'Missing module in modules_used')
292+
return
293+
end if
294+
295+
end subroutine test_program
296+
241297

242298
!> Try to parse fortran module
243299
subroutine test_module(error)
@@ -258,6 +314,11 @@ subroutine test_module(error)
258314
& 'interface', &
259315
& ' module subroutine f()', &
260316
& 'end interface', &
317+
& 'integer :: program', &
318+
& 'program = 1', &
319+
& 'program= 1', &
320+
& 'program =1', &
321+
& 'program (i) =1', &
261322
& 'contains', &
262323
& 'module procedure f()', &
263324
& 'end procedure f', &

0 commit comments

Comments
 (0)