Skip to content

Commit 13f9c85

Browse files
committed
Update: parsing with parse_sequence helper fcn
Adds a parse_sequence helper utility to parse sequences of tokens separated by zero or more spaces
1 parent 895f774 commit 13f9c85

File tree

1 file changed

+103
-21
lines changed

1 file changed

+103
-21
lines changed

src/fpm_source_parsing.f90

Lines changed: 103 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -123,7 +123,7 @@ function parse_f_source(f_filename,error) result(f_source)
123123

124124
! Detect exported C-API via bind(C)
125125
if (.not.inside_interface .and. &
126-
index(file_lines_lower(i)%s,'bind(c') > 0) then
126+
parse_subsequence(file_lines_lower(i)%s,'bind','(','c')) then
127127

128128
do j=i,1,-1
129129

@@ -172,15 +172,10 @@ function parse_f_source(f_filename,error) result(f_source)
172172
end if
173173

174174
! Detect end of interface block
175-
if (index(file_lines_lower(i)%s,'end') == 1 .and. &
176-
len(file_lines_lower(i)%s) > 3) then
175+
if (parse_sequence(file_lines_lower(i)%s,'end','interface')) then
177176

178-
if (index(adjustl(file_lines_lower(i)%s(4:)),'interface') == 1) then
179-
180-
inside_interface = .false.
181-
cycle
182-
183-
end if
177+
inside_interface = .false.
178+
cycle
184179

185180
end if
186181

@@ -407,18 +402,11 @@ function parse_f_source(f_filename,error) result(f_source)
407402

408403
! Parse end module statement
409404
! (to check for code outside of modules)
410-
if (index(file_lines_lower(i)%s,'end') == 1) then
411-
412-
temp_string = split_n(file_lines_lower(i)%s,n=2,delims=' ',stat=stat)
413-
414-
if (stat == 0) then
415-
if (temp_string == 'module' .or. temp_string == 'submodule') then
416-
417-
inside_module = .false.
418-
cycle
419-
420-
end if
421-
end if
405+
if (parse_sequence(file_lines_lower(i)%s,'end','module') .or. &
406+
parse_sequence(file_lines_lower(i)%s,'end','submodule')) then
407+
408+
inside_module = .false.
409+
cycle
422410

423411
end if
424412

@@ -567,4 +555,98 @@ function split_n(string,delims,n,stat) result(substring)
567555

568556
end function split_n
569557

558+
559+
!> Parse a subsequence of blank-separated tokens within a string
560+
!> (see parse_sequence)
561+
function parse_subsequence(string,t1,t2,t3,t4) result(found)
562+
character(*), intent(in) :: string
563+
character(*), intent(in) :: t1
564+
character(*), intent(in), optional :: t2, t3, t4
565+
logical :: found
566+
567+
integer :: offset, i
568+
569+
found = .false.
570+
offset = 1
571+
572+
do
573+
574+
i = index(string(offset:),t1)
575+
576+
if (i == 0) return
577+
578+
offset = offset + i - 1
579+
580+
found = parse_sequence(string(offset:),t1,t2,t3,t4)
581+
582+
if (found) return
583+
584+
offset = offset + len(t1)
585+
586+
if (offset > len(string)) return
587+
588+
end do
589+
590+
end function parse_subsequence
591+
592+
!> Helper utility to parse sequences of tokens
593+
!> that may be optionally separated by zero or more spaces
594+
function parse_sequence(string,t1,t2,t3,t4) result(found)
595+
character(*), intent(in) :: string
596+
character(*), intent(in) :: t1
597+
character(*), intent(in), optional :: t2, t3, t4
598+
logical :: found
599+
600+
integer :: post, n, incr, pos, token_n
601+
logical :: match
602+
603+
n = len(string)
604+
found = .false.
605+
pos = 1
606+
607+
do token_n=1,4
608+
609+
do while (pos <= n)
610+
if (string(pos:pos) /= ' ') then
611+
exit
612+
end if
613+
pos = pos + 1
614+
end do
615+
616+
select case(token_n)
617+
case(1)
618+
incr = len(t1)
619+
match = string(pos:pos+incr-1) == t1
620+
case(2)
621+
if (.not.present(t2)) exit
622+
incr = len(t2)
623+
if (pos+incr-1>n) return
624+
match = string(pos:pos+incr-1) == t2
625+
case(3)
626+
if (.not.present(t3)) exit
627+
incr = len(t3)
628+
if (pos+incr-1>n) return
629+
match = string(pos:pos+incr-1) == t3
630+
case(4)
631+
if (.not.present(t4)) exit
632+
incr = len(t4)
633+
if (pos+incr-1>n) return
634+
match = string(pos:pos+incr-1) == t4
635+
case default
636+
exit
637+
end select
638+
639+
if (.not.match) then
640+
return
641+
end if
642+
643+
pos = pos + incr
644+
645+
end do
646+
647+
found = .true.
648+
649+
end function parse_sequence
650+
570651
end module fpm_source_parsing
652+

0 commit comments

Comments
 (0)