Skip to content

Commit 4c05a6f

Browse files
committed
Add: parsing test case where we can't detect end module statement
If we can't detect the end of a module, then we can't assume that there aren't non-module subprograms present, hence unit type becomes FPM_UNIT_SUBPROGRAM
1 parent 4eedd3a commit 4c05a6f

File tree

1 file changed

+66
-0
lines changed

1 file changed

+66
-0
lines changed

test/fpm_test/test_source_parsing.f90

Lines changed: 66 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,7 @@ subroutine collect_source_parsing(testsuite)
2727
& new_unittest("program", test_program), &
2828
& new_unittest("module", test_module), &
2929
& new_unittest("module-with-subprogram", test_module_with_subprogram), &
30+
& new_unittest("module-end-stmt", test_module_end_stmt), &
3031
& new_unittest("program-with-module", test_program_with_module), &
3132
& new_unittest("submodule", test_submodule), &
3233
& new_unittest("submodule-ancestor", test_submodule_ancestor), &
@@ -422,6 +423,71 @@ subroutine test_module_with_subprogram(error)
422423
end subroutine test_module_with_subprogram
423424

424425

426+
!> Try to parse fortran modules without the full end module statement
427+
!> This should be detected as FPM_UNIT_SUBPROGRAM not FPM_UNIT_MODULE
428+
!> because we cannot guarantee if non-module subprograms are present
429+
subroutine test_module_end_stmt(error)
430+
431+
!> Error handling
432+
type(error_t), allocatable, intent(out) :: error
433+
434+
integer :: unit
435+
character(:), allocatable :: temp_file
436+
type(srcfile_t), allocatable :: f_source
437+
438+
allocate(temp_file, source=get_temp_filename())
439+
440+
open(file=temp_file, newunit=unit)
441+
write(unit, '(a)') &
442+
& 'module mod1', &
443+
& 'contains', &
444+
& 'module subroutine f()', &
445+
& 'end subroutine f', &
446+
& 'module function g()', &
447+
& 'end function g', &
448+
& 'end', &
449+
& 'module mod2', &
450+
& 'contains', &
451+
& 'module subroutine f()', &
452+
& 'end subroutine f', &
453+
& 'module function g()', &
454+
& 'end function g', &
455+
& 'end module mod2'
456+
close(unit)
457+
458+
f_source = parse_f_source(temp_file,error)
459+
if (allocated(error)) then
460+
return
461+
end if
462+
463+
if (f_source%unit_type /= FPM_UNIT_SUBPROGRAM) then
464+
call test_failed(error,'Wrong unit type detected - expecting FPM_UNIT_SUBPROGRAM')
465+
return
466+
end if
467+
468+
if (size(f_source%modules_provided) /= 2) then
469+
call test_failed(error,'Unexpected modules_provided - expecting two')
470+
return
471+
end if
472+
473+
if (size(f_source%modules_used) /= 0) then
474+
call test_failed(error,'Incorrect number of modules_used - expecting zero')
475+
return
476+
end if
477+
478+
if (.not.('mod1' .in. f_source%modules_provided)) then
479+
call test_failed(error,'Missing module in modules_provided')
480+
return
481+
end if
482+
483+
if (.not.('mod2' .in. f_source%modules_provided)) then
484+
call test_failed(error,'Missing module in modules_provided')
485+
return
486+
end if
487+
488+
end subroutine test_module_end_stmt
489+
490+
425491
!> Try to parse combined fortran module and program
426492
!> Check that parsed unit type is FPM_UNIT_PROGRAM
427493
subroutine test_program_with_module(error)

0 commit comments

Comments
 (0)