Skip to content

Commit acc33b9

Browse files
committed
Make sure we replace only modifiers
Edit regex and replace to consider word boundaries
1 parent 20f2e3d commit acc33b9

File tree

4 files changed

+41
-9
lines changed

4 files changed

+41
-9
lines changed

fortls/parse_fortran.py

Lines changed: 5 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -314,8 +314,7 @@ def read_fun_def(
314314
# Get all the keyword modifier mathces
315315
keywords = re.findall(SUB_MOD_REGEX, line)
316316
# remove modifiers from line
317-
for modifier in keywords:
318-
line = line.replace(modifier, "")
317+
line = re.sub(SUB_MOD_REGEX, "", line)
319318

320319
# Try and get the result type
321320
# Recursively will call read_var_def which will then call read_fun_def
@@ -353,12 +352,10 @@ def read_fun_def(
353352

354353
def read_sub_def(line: str, mod_flag: bool = False):
355354
"""Attempt to read SUBROUTINE definition line"""
356-
keywords: list[str] = []
357-
mod_match = SUB_MOD_REGEX.match(line)
358-
while mod_match is not None:
359-
line = line[mod_match.end(0) :]
360-
keywords.append(mod_match.group(1))
361-
mod_match = SUB_MOD_REGEX.match(line)
355+
# Get all the keyword modifier mathces
356+
keywords = re.findall(SUB_MOD_REGEX, line)
357+
# remove modifiers from line
358+
line = re.sub(SUB_MOD_REGEX, "", line)
362359
sub_match = SUB_REGEX.match(line)
363360
if sub_match is None:
364361
return None

fortls/regex_patterns.py

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@
1111
INCLUDE_REGEX = re.compile(r"[ ]*INCLUDE[ :]*[\'\"]([^\'\"]*)", re.I)
1212
CONTAINS_REGEX = re.compile(r"[ ]*(CONTAINS)[ ]*$", re.I)
1313
IMPLICIT_REGEX = re.compile(r"[ ]*IMPLICIT[ ]+([a-z]*)", re.I)
14-
SUB_MOD_REGEX = re.compile(r"[ ]*(PURE|IMPURE|ELEMENTAL|RECURSIVE)+", re.I)
14+
SUB_MOD_REGEX = re.compile(r"[ ]*\b(PURE|IMPURE|ELEMENTAL|RECURSIVE)\b", re.I)
1515
SUB_REGEX = re.compile(r"[ ]*SUBROUTINE[ ]+([a-z0-9_]+)", re.I)
1616
END_SUB_REGEX = re.compile(r"SUBROUTINE", re.I)
1717
FUN_REGEX = re.compile(r"[ ]*FUNCTION[ ]+([a-z0-9_]+)", re.I)

test/test_server.py

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -579,6 +579,8 @@ def check_return(result_array, checks):
579579
string += hover_req(file_path, 12, 12)
580580
string += hover_req(file_path, 18, 19)
581581
string += hover_req(file_path, 23, 34)
582+
file_path = test_dir / "hover" / "recursive.f90"
583+
string += hover_req(file_path, 9, 40)
582584
file_path = test_dir / "subdir" / "test_submod.F90"
583585
string += hover_req(file_path, 29, 24)
584586
string += hover_req(file_path, 34, 24)
@@ -615,6 +617,10 @@ def check_return(result_array, checks):
615617
# any modifiers before the type would be discarded
616618
"""INTEGER PURE ELEMENTAL FUNCTION fun5(arg) RESULT(retval)
617619
INTEGER, INTENT(IN) :: arg""",
620+
"""RECURSIVE SUBROUTINE recursive_assign_descending(node, vector, current_loc)
621+
TYPE(tree_inode), POINTER, INTENT(IN) :: node
622+
INTEGER, DIMENSION(:), INTENT(INOUT) :: vector
623+
INTEGER, INTENT(INOUT) :: current_loc""",
618624
# TODO: more tests to add from functions
619625
"""REAL FUNCTION point_dist(a, b) RESULT(distance)
620626
TYPE(point), INTENT(IN) :: a
@@ -746,6 +752,11 @@ def check_return(results, ref_results):
746752
string += write_rpc_notification(
747753
"textDocument/didOpen", {"textDocument": {"uri": file_path}}
748754
)
755+
# Test module procedure in submodules importing scopes
756+
file_path = str(test_dir / "subdir" / "test_submod.f90")
757+
string += write_rpc_notification(
758+
"textDocument/didOpen", {"textDocument": {"uri": file_path}}
759+
)
749760
errcode, results = run_request(string)
750761
assert errcode == 0
751762

@@ -815,6 +826,7 @@ def check_return(results, ref_results):
815826
[],
816827
[],
817828
[],
829+
[],
818830
[
819831
{
820832
"range": {
Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,23 @@
1+
module tree
2+
type tree_inode
3+
integer :: value = 0
4+
type (tree_inode), pointer :: left=>null()
5+
type (tree_inode), pointer :: right=>null()
6+
type (tree_inode), pointer :: parent=>null()
7+
end type tree_inode
8+
9+
contains
10+
recursive subroutine recursive_assign_descending(node, vector, current_loc)
11+
type(tree_inode), pointer, intent(in) :: node
12+
integer, dimension(:), intent(inout) :: vector
13+
integer, intent(inout) :: current_loc
14+
15+
if (associated(node)) then
16+
call recursive_assign_descending(node%right, vector, current_loc)
17+
vector(current_loc) = node%value
18+
current_loc = current_loc + 1
19+
call recursive_assign_descending(node%left, vector, current_loc)
20+
end if
21+
return
22+
end subroutine recursive_assign_descending
23+
end module tree

0 commit comments

Comments
 (0)