Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 3 additions & 1 deletion .coveragerc
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
[run]
dynamic_context = test_function
omit =
fortls/__init__.py
fortls/version.py
Expand All @@ -10,3 +9,6 @@ exclude_lines =
log.debug
except:
if not PY3K:

[html]
show_contexts = True
5 changes: 5 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,11 @@
- Redesigned the `fortls` website to be more aesthetically pleasing and user-friendly
([#112](https://github.com/gnikit/fortls/issues/112))

### Fixed

- Fixed bug where submodule procedure scopes would terminate early if keyword modifiers were used
([#119](https://github.com/gnikit/fortls/issues/119))

## 2.5.0

### Added
Expand Down
13 changes: 11 additions & 2 deletions fortls/parse_fortran.py
Original file line number Diff line number Diff line change
Expand Up @@ -532,7 +532,12 @@ def read_generic_def(line: str):


def read_mod_def(line: str):
"""Attempt to read MODULE and MODULE PROCEDURE definition lines"""
"""Attempt to read MODULE and MODULE PROCEDURE, MODULE FUNCTION definition lines"""
# Get all the keyword modifier mathces
keywords = re.findall(FRegex.SUB_MOD, line)
# remove modifiers from line
line = re.sub(FRegex.SUB_MOD, "", line)

mod_match = FRegex.MOD.match(line)
if mod_match is None:
return None
Expand All @@ -547,15 +552,19 @@ def read_mod_def(line: str):
return "int_pro", pro_names
# Check for submodule definition
trailing_line = line[mod_match.start(1) :]
# module procedure
sub_res = read_sub_def(trailing_line, mod_flag=True)
if sub_res is not None:
return sub_res
# module function
fun_res = read_var_def(trailing_line, fun_only=True)
if fun_res is not None:
fun_res[1].mod_flag = True
return fun_res[0], fun_res[1]
fun_res[1].keywords = keywords
return fun_res
fun_res = read_fun_def(trailing_line, mod_flag=True)
if fun_res is not None:
fun_res[1].keywords = keywords
return fun_res
return "mod", name

Expand Down
13 changes: 13 additions & 0 deletions test/test_server_diagnostics.py
Original file line number Diff line number Diff line change
Expand Up @@ -391,3 +391,16 @@ def test_function():
"severity": 1,
}
]


def test_submodule_scopes():
"""Test that submodule procedures and functions with modifier keywords are correctly
parsed and their scopes correctly closed."""
string = write_rpc_request(1, "initialize", {"rootPath": str(test_dir / "diag")})
file_path = str(test_dir / "diag" / "test_scope_overreach.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"] == []
21 changes: 21 additions & 0 deletions test/test_server_hover.py
Original file line number Diff line number Diff line change
Expand Up @@ -327,3 +327,24 @@ def test_hover_block():
assert errcode == 0
ref_results = ["REAL, DIMENSION(5)", "REAL"]
validate_hover(results, ref_results)


def test_hover_submodule_procedure():
"""Test that submodule procedures and functions with modifier keywords
are correctly displayed when hovering.
"""
string = write_rpc_request(1, "initialize", {"rootPath": str(test_dir / "diag")})
file_path = test_dir / "diag" / "test_scope_overreach.f90"
string += hover_req(file_path, 18, 37)
string += hover_req(file_path, 23, 37)
errcode, results = run_request(string, fortls_args=["-n", "1"])
assert errcode == 0
ref_results = [
"""PURE RECURSIVE FUNCTION foo_sp(x) RESULT(fi)
REAL(sp), INTENT(IN) :: x
REAL(sp) :: fi""",
"""PURE RECURSIVE FUNCTION foo_dp(x) RESULT(fi)
REAL(dp), INTENT(IN) :: x
REAL(dp) :: fi""",
]
validate_hover(results, ref_results)
28 changes: 28 additions & 0 deletions test/test_source/diag/test_scope_overreach.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
module m
interface
module subroutine sub(arg)
integer :: arg
end subroutine
end interface
end module m

submodule (m) n

use, intrinsic :: iso_fortran_env, only: int8, int16, int32, int64
implicit none

integer, parameter :: sp = selected_real_kind(6)
integer, parameter :: dp = selected_real_kind(15)

contains

pure recursive module function foo_sp(x) result(fi)
real(sp), intent(in) :: x
real(sp) :: fi
end function foo_sp

pure recursive module function foo_dp(x) result(fi)
real(dp), intent(in) :: x
real(dp) :: fi
end function foo_dp
end submodule n