Skip to content

Commit

Permalink
Merge pull request #158 from gnikit:gnikit/issue157
Browse files Browse the repository at this point in the history
Erroneous diagnostic error with "recursive" argument in arg list
  • Loading branch information
gnikit authored Jun 30, 2022
2 parents a703bfd + 4ecc4ce commit 4f17ee4
Show file tree
Hide file tree
Showing 4 changed files with 50 additions and 1 deletion.
7 changes: 7 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,13 @@

## Unreleased

## 2.11.0

### Fixed

- Fixed bug thorowing diagnostic errors if arguments were named `pure`, `elemental`, etc.
([#157](https://github.com/gnikit/fortls/issues/157))

## 2.10.0

### Fixed
Expand Down
6 changes: 5 additions & 1 deletion fortls/regex_patterns.py
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,11 @@ class FortranRegularExpressions:
INCLUDE: Pattern = compile(r"[ ]*INCLUDE[ :]*[\'\"]([^\'\"]*)", I)
CONTAINS: Pattern = compile(r"[ ]*(CONTAINS)[ ]*$", I)
IMPLICIT: Pattern = compile(r"[ ]*IMPLICIT[ ]+([a-z]*)", I)
SUB_MOD: Pattern = compile(r"[ ]*\b(PURE|IMPURE|ELEMENTAL|RECURSIVE)\b", I)
#: Parse procedure keywords but not if they start with , or ( or end with , or )
#: This is to avoid parsing as keywords variables named pure, impure, etc.
SUB_MOD: Pattern = compile(
r"[ ]*(?!<[,\()][ ]*)\b(PURE|IMPURE|ELEMENTAL|RECURSIVE)\b(?![,\)][ ]*)", I
)
SUB: Pattern = compile(r"[ ]*SUBROUTINE[ ]+(\w+)", I)
END_SUB: Pattern = compile(r"SUBROUTINE", I)
FUN: Pattern = compile(r"[ ]*FUNCTION[ ]+(\w+)", I)
Expand Down
12 changes: 12 additions & 0 deletions test/test_server_diagnostics.py
Original file line number Diff line number Diff line change
Expand Up @@ -404,3 +404,15 @@ def test_submodule_scopes():
errcode, results = run_request(string, ["-n", "1"])
assert errcode == 0
assert results[1]["diagnostics"] == []


def test_keyword_arg_list_var_names():
"""Test argument list variables named as keywords are correctly parsed."""
string = write_rpc_request(1, "initialize", {"rootPath": str(test_dir / "diag")})
file_path = str(test_dir / "diag" / "test_function_arg_list.f90")
string += write_rpc_notification(
"textDocument/didOpen", {"textDocument": {"uri": file_path}}
)
errcode, results = run_request(string, ["-n", "1"])
assert errcode == 0
assert results[1]["diagnostics"] == []
26 changes: 26 additions & 0 deletions test/test_source/diag/test_function_arg_list.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
program test_arg_names_as_keywords
implicit none
integer, parameter :: impure = 8
contains
subroutine foo(recursive, ierr)
integer, intent(in) :: recursive
integer, intent(out) :: ierr
print*, recursive
end subroutine foo
real(8) impure elemental function foo2(recursive, elemental) result(pure)
integer, intent(in) :: recursive, elemental
end function foo2
real( kind = impure ) pure elemental function foo3(recursive) result(pure)
integer, intent(in) :: recursive
end function foo3
subroutine foo4(&
recursive, &
ierr)
integer, intent(in) :: recursive
integer, intent(out) :: ierr
print*, recursive
end subroutine foo4
pure real(impure) function foo5(recursive) result(val)
integer, intent(in) :: recursive
end function foo5
end program test_arg_names_as_keywords

0 comments on commit 4f17ee4

Please sign in to comment.