Skip to content

Commit c1a902d

Browse files
committed
Fix: module stmt parsing
1 parent 5566c16 commit c1a902d

File tree

1 file changed

+17
-14
lines changed

1 file changed

+17
-14
lines changed

src/fpm_source_parsing.f90

Lines changed: 17 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -79,7 +79,7 @@ function parse_f_source(f_filename,error) result(f_source)
7979
integer :: stat
8080
integer :: fh, n_use, n_include, n_mod, i, j, ic, pass
8181
type(string_t), allocatable :: file_lines(:)
82-
character(:), allocatable :: temp_string, mod_name
82+
character(:), allocatable :: temp_string, mod_name, string_parts(:)
8383

8484
f_source%file_name = f_filename
8585

@@ -191,22 +191,25 @@ function parse_f_source(f_filename,error) result(f_source)
191191
! Extract name of module if is module
192192
if (index(adjustl(lower(file_lines(i)%s)),'module ') == 1) then
193193

194-
mod_name = lower(split_n(file_lines(i)%s,n=2,delims=' ',stat=stat))
195-
if (stat /= 0) then
196-
call file_parse_error(error,f_filename, &
197-
'unable to find module name',i, &
198-
file_lines(i)%s)
199-
return
194+
! Remove any trailing comments
195+
ic = index(file_lines(i)%s,'!')-1
196+
if (ic < 1) then
197+
ic = len(file_lines(i)%s)
198+
end if
199+
temp_string = trim(file_lines(i)%s(1:ic))
200+
201+
! R1405 module-stmt := "MODULE" module-name
202+
! module-stmt has two space-delimited parts only
203+
! (no line continuations)
204+
call split(temp_string,string_parts,' ')
205+
if (size(string_parts) /= 2) then
206+
cycle
200207
end if
201208

202-
if (mod_name == 'procedure' .or. &
203-
mod_name == 'subroutine' .or. &
204-
mod_name == 'function' .or. &
205-
scan(mod_name,'=(')>0 ) then
209+
mod_name = lower(trim(adjustl(string_parts(2))))
210+
if (scan(mod_name,'=(&')>0 ) then
206211
! Ignore these cases:
207-
! module procedure *
208-
! module function *
209-
! module subroutine *
212+
! module <something>&
210213
! module =*
211214
! module (i)
212215
cycle

0 commit comments

Comments
 (0)