aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm_source_parsing.f9024
-rw-r--r--fpm/test/fpm_test/test_source_parsing.f9061
2 files changed, 82 insertions, 3 deletions
diff --git a/fpm/src/fpm_source_parsing.f90 b/fpm/src/fpm_source_parsing.f90
index ea5b4f9..80b21fb 100644
--- a/fpm/src/fpm_source_parsing.f90
+++ b/fpm/src/fpm_source_parsing.f90
@@ -197,8 +197,14 @@ function parse_f_source(f_filename,error) result(f_source)
if (mod_name == 'procedure' .or. &
mod_name == 'subroutine' .or. &
- mod_name == 'function') then
- ! Ignore these cases
+ mod_name == 'function' .or. &
+ scan(mod_name,'=(')>0 ) then
+ ! Ignore these cases:
+ ! module procedure *
+ ! module function *
+ ! module subroutine *
+ ! module =*
+ ! module (i)
cycle
end if
@@ -275,7 +281,19 @@ function parse_f_source(f_filename,error) result(f_source)
! Detect if contains a program
! (no modules allowed after program def)
- if (index(adjustl(lower(file_lines(i)%s)),'program') == 1) then
+ if (index(adjustl(lower(file_lines(i)%s)),'program ') == 1) then
+
+ temp_string = lower(split_n(file_lines(i)%s,n=2,delims=' ',stat=stat))
+ if (stat == 0) then
+
+ if (scan(temp_string,'=(')>0 ) then
+ ! Ignore:
+ ! program =*
+ ! program (i) =*
+ cycle
+ end if
+
+ end if
f_source%unit_type = FPM_UNIT_PROGRAM
diff --git a/fpm/test/fpm_test/test_source_parsing.f90 b/fpm/test/fpm_test/test_source_parsing.f90
index 4463c07..79a4d7a 100644
--- a/fpm/test/fpm_test/test_source_parsing.f90
+++ b/fpm/test/fpm_test/test_source_parsing.f90
@@ -24,6 +24,7 @@ contains
& new_unittest("modules-used", test_modules_used), &
& new_unittest("intrinsic-modules-used", test_intrinsic_modules_used), &
& new_unittest("include-stmt", test_include_stmt), &
+ & new_unittest("program", test_program), &
& new_unittest("module", test_module), &
& new_unittest("program-with-module", test_program_with_module), &
& new_unittest("submodule", test_submodule), &
@@ -238,6 +239,61 @@ contains
end subroutine test_include_stmt
+ !> Try to parse a simple fortran program
+ subroutine test_program(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)') &
+ & 'program my_program', &
+ & 'use module_one', &
+ & 'implicit none', &
+ & 'integer :: module', &
+ & 'module = 1', &
+ & 'module= 1', &
+ & 'module =1', &
+ & 'module (i) =1', &
+ & 'contains', &
+ & 'subroutine f()', &
+ & 'end subroutine f', &
+ & 'end program 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) /= 0) then
+ call test_failed(error,'Unexpected modules_provided - expecting zero')
+ return
+ end if
+
+ if (size(f_source%modules_used) /= 1) then
+ call test_failed(error,'Incorrect number of modules_used - expecting one')
+ 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
+
+ end subroutine test_program
+
!> Try to parse fortran module
subroutine test_module(error)
@@ -258,6 +314,11 @@ contains
& 'interface', &
& ' module subroutine f()', &
& 'end interface', &
+ & 'integer :: program', &
+ & 'program = 1', &
+ & 'program= 1', &
+ & 'program =1', &
+ & 'program (i) =1', &
& 'contains', &
& 'module procedure f()', &
& 'end procedure f', &