diff options
author | LKedward <laurence.kedward@bristol.ac.uk> | 2020-09-19 11:45:39 +0100 |
---|---|---|
committer | LKedward <laurence.kedward@bristol.ac.uk> | 2020-09-19 11:45:39 +0100 |
commit | db67194d936181916bcef873e9317b3cf5048c3d (patch) | |
tree | 0113fafbc10f7f52369e7b506bc3e9d29f28cb0d | |
parent | f2a51196aa33fca3ae19a02a601dfa190fe14d80 (diff) | |
download | fpm-db67194d936181916bcef873e9317b3cf5048c3d.tar.gz fpm-db67194d936181916bcef873e9317b3cf5048c3d.zip |
Add: parsing unit test for program with module case
-rw-r--r-- | fpm/test/test_source_parsing.f90 | 68 |
1 files changed, 66 insertions, 2 deletions
diff --git a/fpm/test/test_source_parsing.f90 b/fpm/test/test_source_parsing.f90 index eec92d7..0b92bef 100644 --- a/fpm/test/test_source_parsing.f90 +++ b/fpm/test/test_source_parsing.f90 @@ -25,6 +25,7 @@ contains & new_unittest("intrinsic-modules-used", test_intrinsic_modules_used), & & new_unittest("include-stmt", test_include_stmt), & & new_unittest("module", test_module), & + & new_unittest("program-with-module", test_program_with_module), & & new_unittest("submodule", test_submodule), & & new_unittest("submodule-ancestor", test_submodule_ancestor), & & new_unittest("subprogram", test_subprogram), & @@ -258,7 +259,7 @@ contains & 'contains', & & 'module procedure f()', & & 'end procedure f', & - & 'end submodule test' + & 'end module test' close(unit) f_source = parse_f_source(temp_file,error) @@ -287,13 +288,76 @@ contains end if if (.not.('module_one' .in. f_source%modules_used)) then - call test_failed(error,'Missing parent module in modules_used') + call test_failed(error,'Missing module in modules_used') return end if end subroutine test_module + !> Try to parse combined fortran module and program + !> Check that parsed unit type is FPM_UNIT_PROGRAM + subroutine test_program_with_module(error) + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + integer :: unit + character(:), allocatable :: temp_file + type(srcfile_t), allocatable :: f_source + + allocate(temp_file, source=get_temp_filename()) + + open(file=temp_file, newunit=unit) + write(unit, '(a)') & + & 'module my_mod', & + & 'use module_one', & + & 'interface', & + & ' module subroutine f()', & + & 'end interface', & + & 'contains', & + & 'module procedure f()', & + & 'end procedure f', & + & 'end module test', & + & 'program my_program', & + & 'use my_mod', & + & 'implicit none', & + & 'end my_program' + close(unit) + + f_source = parse_f_source(temp_file,error) + if (allocated(error)) then + return + end if + + if (f_source%unit_type /= FPM_UNIT_PROGRAM) then + call test_failed(error,'Wrong unit type detected - expecting FPM_UNIT_PROGRAM') + return + end if + + if (size(f_source%modules_provided) /= 1) then + call test_failed(error,'Unexpected modules_provided - expecting one') + return + end if + + if (.not.('my_mod' .in. f_source%modules_provided)) then + call test_failed(error,'Missing module in modules_provided') + return + end if + + if (.not.('module_one' .in. f_source%modules_used)) then + call test_failed(error,'Missing module in modules_used') + return + end if + + if (.not.('my_mod' .in. f_source%modules_used)) then + call test_failed(error,'Missing module in modules_used') + return + end if + + end subroutine test_program_with_module + + !> Try to parse fortran submodule for ancestry subroutine test_submodule(error) |