Skip to content

Commit 17ac86b

Browse files
committed
Update parsing: to detect subprograms outside modules
Sources files are only designated as FPM_UNIT_MODULE if they only contain modules. Non-program sources that contain subprograms not in modules are designated as FPM_UNIT_SUBPROGRAM.
1 parent 20643a4 commit 17ac86b

File tree

3 files changed

+111
-14
lines changed

3 files changed

+111
-14
lines changed

src/fpm_model.f90

Lines changed: 21 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,23 @@
1414
!> __Source type:__ `FPM_UNIT_*`
1515
!> Describes the type of source file — determines build target generation
1616
!>
17+
!> The logical order of precedence for assigning `unit_type` is as follows:
18+
!>
19+
!>```
20+
!> if source-file contains program then
21+
!> unit_type = FPM_UNIT_PROGRAM
22+
!> else if source-file contains non-module subroutine/function then
23+
!> unit_type = FPM_UNIT_SUBPROGRAM
24+
!> else if source-file contains submodule then
25+
!> unit_type = FPM_UNIT_SUBMODULE
26+
!> else if source-file contains module then
27+
!> unit_type = FPM_UNIT_MODULE
28+
!> end if
29+
!>```
30+
!>
31+
!> @note A source file is only designated `FPM_UNIT_MODULE` if it **only** contains modules - no non-module subprograms.
32+
!> (This allows tree-shaking/pruning of build targets based on unused module dependencies.)
33+
!>
1734
!> __Source scope:__ `FPM_SCOPE_*`
1835
!> Describes the scoping rules for using modules — controls module dependency resolution
1936
!>
@@ -34,13 +51,13 @@ module fpm_model
3451

3552
!> Source type unknown
3653
integer, parameter :: FPM_UNIT_UNKNOWN = -1
37-
!> Source type is fortran program
54+
!> Source contains a fortran program
3855
integer, parameter :: FPM_UNIT_PROGRAM = 1
39-
!> Source type is fortran module
56+
!> Source **only** contains one or more fortran modules
4057
integer, parameter :: FPM_UNIT_MODULE = 2
41-
!> Source type is fortran submodule
58+
!> Source contains one or more fortran submodules
4259
integer, parameter :: FPM_UNIT_SUBMODULE = 3
43-
!> Source type is fortran subprogram
60+
!> Source contains one or more fortran subprogram not within modules
4461
integer, parameter :: FPM_UNIT_SUBPROGRAM = 4
4562
!> Source type is c source file
4663
integer, parameter :: FPM_UNIT_CSOURCE = 5

src/fpm_source_parsing.f90

Lines changed: 38 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -76,6 +76,7 @@ function parse_f_source(f_filename,error) result(f_source)
7676
type(srcfile_t) :: f_source
7777
type(error_t), allocatable, intent(out) :: error
7878

79+
logical :: inside_module
7980
integer :: stat
8081
integer :: fh, n_use, n_include, n_mod, i, j, ic, pass
8182
type(string_t), allocatable :: file_lines(:), file_lines_lower(:)
@@ -103,6 +104,7 @@ function parse_f_source(f_filename,error) result(f_source)
103104
n_use = 0
104105
n_include = 0
105106
n_mod = 0
107+
inside_module = .false.
106108
file_loop: do i=1,size(file_lines_lower)
107109

108110
! Skip comment lines
@@ -242,7 +244,11 @@ function parse_f_source(f_filename,error) result(f_source)
242244
f_source%modules_provided(n_mod) = string_t(mod_name)
243245
end if
244246

245-
f_source%unit_type = FPM_UNIT_MODULE
247+
if (f_source%unit_type == FPM_UNIT_UNKNOWN) then
248+
f_source%unit_type = FPM_UNIT_MODULE
249+
end if
250+
251+
inside_module = .true.
246252

247253
cycle
248254

@@ -274,11 +280,15 @@ function parse_f_source(f_filename,error) result(f_source)
274280
file_lines_lower(i)%s)
275281
return
276282
end if
277-
278-
f_source%unit_type = FPM_UNIT_SUBMODULE
283+
284+
if (f_source%unit_type /= FPM_UNIT_PROGRAM) then
285+
f_source%unit_type = FPM_UNIT_SUBMODULE
286+
end if
279287

280288
n_use = n_use + 1
281289

290+
inside_module = .true.
291+
282292
if (pass == 2) then
283293

284294
if (index(temp_string,':') > 0) then
@@ -323,15 +333,34 @@ function parse_f_source(f_filename,error) result(f_source)
323333
f_source%unit_type = FPM_UNIT_PROGRAM
324334

325335
cycle
326-
336+
327337
end if
328338

329-
end do file_loop
339+
! Parse end module statement
340+
! (to check for code outside of modules)
341+
if (index(file_lines_lower(i)%s,'end') == 1) then
330342

331-
! Default to subprogram unit type
332-
if (f_source%unit_type == FPM_UNIT_UNKNOWN) then
333-
f_source%unit_type = FPM_UNIT_SUBPROGRAM
334-
end if
343+
temp_string = split_n(file_lines_lower(i)%s,n=2,delims=' ',stat=stat)
344+
345+
if (stat == 0) then
346+
if (temp_string == 'module' .or. temp_string == 'submodule') then
347+
348+
inside_module = .false.
349+
cycle
350+
351+
end if
352+
end if
353+
354+
end if
355+
356+
! Any statements not yet parsed are assumed to be other code statements
357+
if (.not.inside_module .and. f_source%unit_type /= FPM_UNIT_PROGRAM) then
358+
359+
f_source%unit_type = FPM_UNIT_SUBPROGRAM
360+
361+
end if
362+
363+
end do file_loop
335364

336365
if (pass == 1) then
337366
allocate(f_source%modules_used(n_use))

test/fpm_test/test_source_parsing.f90

Lines changed: 52 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,7 @@ subroutine collect_source_parsing(testsuite)
2626
& new_unittest("include-stmt", test_include_stmt), &
2727
& new_unittest("program", test_program), &
2828
& new_unittest("module", test_module), &
29+
& new_unittest("module-with-subprogram", test_module_with_subprogram), &
2930
& new_unittest("program-with-module", test_program_with_module), &
3031
& new_unittest("submodule", test_submodule), &
3132
& new_unittest("submodule-ancestor", test_submodule_ancestor), &
@@ -335,7 +336,8 @@ subroutine test_module(error)
335336
& 'string = " &', &
336337
& 'module name !"', &
337338
& 'end function i', &
338-
& 'end module test'
339+
& 'end module test', &
340+
& '! A trailing comment outside of module'
339341
close(unit)
340342

341343
f_source = parse_f_source(temp_file,error)
@@ -371,6 +373,55 @@ subroutine test_module(error)
371373
end subroutine test_module
372374

373375

376+
!> Try to parse fortran module with subroutine outside of module
377+
!> (this should be detected as FPM_UNIT_SUBPROGRAM not FPM_UNIT_MODULE)
378+
subroutine test_module_with_subprogram(error)
379+
380+
!> Error handling
381+
type(error_t), allocatable, intent(out) :: error
382+
383+
integer :: unit
384+
character(:), allocatable :: temp_file
385+
type(srcfile_t), allocatable :: f_source
386+
387+
allocate(temp_file, source=get_temp_filename())
388+
389+
open(file=temp_file, newunit=unit)
390+
write(unit, '(a)') &
391+
& 'module my_mod', &
392+
& 'contains', &
393+
& 'module subroutine f()', &
394+
& 'end subroutine f', &
395+
& 'module function g()', &
396+
& 'end function g', &
397+
& 'end module test',&
398+
& 'function h()', &
399+
& 'end function'
400+
close(unit)
401+
402+
f_source = parse_f_source(temp_file,error)
403+
if (allocated(error)) then
404+
return
405+
end if
406+
407+
if (f_source%unit_type /= FPM_UNIT_SUBPROGRAM) then
408+
call test_failed(error,'Wrong unit type detected - expecting FPM_UNIT_SUBPROGRAM')
409+
return
410+
end if
411+
412+
if (size(f_source%modules_provided) /= 1) then
413+
call test_failed(error,'Unexpected modules_provided - expecting one')
414+
return
415+
end if
416+
417+
if (size(f_source%modules_used) /= 0) then
418+
call test_failed(error,'Incorrect number of modules_used - expecting zero')
419+
return
420+
end if
421+
422+
end subroutine test_module_with_subprogram
423+
424+
374425
!> Try to parse combined fortran module and program
375426
!> Check that parsed unit type is FPM_UNIT_PROGRAM
376427
subroutine test_program_with_module(error)

0 commit comments

Comments
 (0)