aboutsummaryrefslogtreecommitdiff
path: root/src/fpm_source_parsing.f90
diff options
context:
space:
mode:
authorLKedward <laurence.kedward@bristol.ac.uk>2021-06-05 14:20:45 +0100
committerLKedward <laurence.kedward@bristol.ac.uk>2021-06-05 14:20:45 +0100
commitc1a902d6556d25fe491c3ba8eed4999c9ee27372 (patch)
tree28e55a415cd75e224c1380be565d8fd31c2d6b9e /src/fpm_source_parsing.f90
parent5566c16f184a20080238fcc731a4d1f039d9d29c (diff)
downloadfpm-c1a902d6556d25fe491c3ba8eed4999c9ee27372.tar.gz
fpm-c1a902d6556d25fe491c3ba8eed4999c9ee27372.zip
Fix: module stmt parsing
Diffstat (limited to 'src/fpm_source_parsing.f90')
-rw-r--r--src/fpm_source_parsing.f9031
1 files changed, 17 insertions, 14 deletions
diff --git a/src/fpm_source_parsing.f90 b/src/fpm_source_parsing.f90
index dd9a4c5..6fa00d5 100644
--- a/src/fpm_source_parsing.f90
+++ b/src/fpm_source_parsing.f90
@@ -79,7 +79,7 @@ function parse_f_source(f_filename,error) result(f_source)
integer :: stat
integer :: fh, n_use, n_include, n_mod, i, j, ic, pass
type(string_t), allocatable :: file_lines(:)
- character(:), allocatable :: temp_string, mod_name
+ character(:), allocatable :: temp_string, mod_name, string_parts(:)
f_source%file_name = f_filename
@@ -191,22 +191,25 @@ function parse_f_source(f_filename,error) result(f_source)
! Extract name of module if is module
if (index(adjustl(lower(file_lines(i)%s)),'module ') == 1) then
- mod_name = lower(split_n(file_lines(i)%s,n=2,delims=' ',stat=stat))
- if (stat /= 0) then
- call file_parse_error(error,f_filename, &
- 'unable to find module name',i, &
- file_lines(i)%s)
- return
+ ! Remove any trailing comments
+ ic = index(file_lines(i)%s,'!')-1
+ if (ic < 1) then
+ ic = len(file_lines(i)%s)
+ end if
+ temp_string = trim(file_lines(i)%s(1:ic))
+
+ ! R1405 module-stmt := "MODULE" module-name
+ ! module-stmt has two space-delimited parts only
+ ! (no line continuations)
+ call split(temp_string,string_parts,' ')
+ if (size(string_parts) /= 2) then
+ cycle
end if
- if (mod_name == 'procedure' .or. &
- mod_name == 'subroutine' .or. &
- mod_name == 'function' .or. &
- scan(mod_name,'=(')>0 ) then
+ mod_name = lower(trim(adjustl(string_parts(2))))
+ if (scan(mod_name,'=(&')>0 ) then
! Ignore these cases:
- ! module procedure *
- ! module function *
- ! module subroutine *
+ ! module <something>&
! module =*
! module (i)
cycle