From 3b717556ddfb259e4a0fb5714bfd7e2848112f50 Mon Sep 17 00:00:00 2001 From: gnikit Date: Sun, 20 Feb 2022 19:36:57 +0000 Subject: [PATCH 01/11] Fixed function hovering showing up as result type Closes Type prefixed functions display wrong signature upon hover gnikit/fortls#22 --- CHANGELOG.md | 7 +++++++ fortls/langserver.py | 4 +++- fortls/objects.py | 21 +++++++++++++++++++-- test/test_server.py | 8 ++++++++ test/test_source/hover/functions.f90 | 10 ++++++++++ 5 files changed, 47 insertions(+), 3 deletions(-) create mode 100644 test/test_source/hover/functions.f90 diff --git a/CHANGELOG.md b/CHANGELOG.md index bb09b643..db91734b 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -1,5 +1,12 @@ # CHANGELONG +## 2.2.2 + +### Fixed + +- Fixed hovering over functions displaying as theire result types + ([gnikit/fortls#22](https://github.com/gnikit/fortls/issues/22)) + ## 2.2.1 ### Changed diff --git a/fortls/langserver.py b/fortls/langserver.py index a6a477a5..21bed521 100644 --- a/fortls/langserver.py +++ b/fortls/langserver.py @@ -740,7 +740,9 @@ def get_definition( ) ): curr_scope = curr_scope.parent - var_obj = find_in_scope(curr_scope, def_name, self.obj_tree) + var_obj = find_in_scope( + curr_scope, def_name, self.obj_tree, var_line_number=def_line + 1 + ) # Search in global scope if var_obj is None: if is_member: diff --git a/fortls/objects.py b/fortls/objects.py index cada90b2..1bbaedac 100644 --- a/fortls/objects.py +++ b/fortls/objects.py @@ -165,9 +165,13 @@ def find_in_scope( obj_tree: dict, interface: bool = False, local_only: bool = False, + var_line_number: int = None, ): def check_scope( - local_scope: fortran_scope, var_name_lower: str, filter_public: bool = False + local_scope: fortran_scope, + var_name_lower: str, + filter_public: bool = False, + var_line_number: int = None, ): for child in local_scope.get_children(): if child.name.startswith("#GEN_INT"): @@ -178,6 +182,19 @@ def check_scope( if (child.vis < 0) or ((local_scope.def_vis < 0) and (child.vis <= 0)): continue if child.name.lower() == var_name_lower: + # For functions with an implicit result() variable the name + # of the function is used. If we are hovering over the function + # definition, we do not want the implicit result() to be returned. + # If scope is from a function and child's name is same as functions name + # and start of scope i.e. function definition is equal to the request ln + # then we are need to skip this child + if ( + isinstance(local_scope, fortran_function) + and local_scope.name.lower() == child.name.lower() + and local_scope.sline == var_line_number + ): + return None + return child return None @@ -186,7 +203,7 @@ def check_scope( # Check local scope if scope is None: return None - tmp_var = check_scope(scope, var_name_lower) + tmp_var = check_scope(scope, var_name_lower, var_line_number=var_line_number) if local_only or (tmp_var is not None): return tmp_var # Check INCLUDE statements diff --git a/test/test_server.py b/test/test_server.py index c6ae6e6e..3f62cfd1 100644 --- a/test/test_server.py +++ b/test/test_server.py @@ -573,6 +573,10 @@ def check_return(result_array, checks): string += hover_req(file_path, 7, 55) file_path = test_dir / "hover" / "pointers.f90" string += hover_req(file_path, 1, 26) + file_path = test_dir / "hover" / "functions.f90" + string += hover_req(file_path, 1, 11) + string += hover_req(file_path, 7, 19) + errcode, results = run_request( string, fortls_args=["--variable_hover", "--sort_keywords"] ) @@ -590,6 +594,10 @@ def check_return(result_array, checks): "DOUBLE PRECISION, PARAMETER :: somevar = 23.12", "DOUBLE PRECISION, PARAMETER :: some = 1e-19", "INTEGER, POINTER", + """FUNCTION fun1(arg) + INTEGER, INTENT(IN) :: arg""", + """INTEGER FUNCTION fun2(arg) + INTEGER, INTENT(IN) :: arg""", ) assert len(ref_results) == len(results) - 1 check_return(results[1:], ref_results) diff --git a/test/test_source/hover/functions.f90 b/test/test_source/hover/functions.f90 new file mode 100644 index 00000000..ec02d6e3 --- /dev/null +++ b/test/test_source/hover/functions.f90 @@ -0,0 +1,10 @@ +! simple function +function fun1(arg) + integer, intent(in) :: arg + integer :: fun1 +end function fun1 + +! function with type on definition, implied result +integer function fun2(arg) + integer, intent(in) :: arg +end function fun2 From 25e0f3df07c89127af0512f17bde8e8fea7814ab Mon Sep 17 00:00:00 2001 From: gnikit Date: Mon, 21 Feb 2022 00:06:36 +0000 Subject: [PATCH 02/11] Improves hover of functions Functions now all display the same signature: `type` `keywords` `function` `name(args)` `result(val)` - Submodule module procedure functions now display like so - functions without an explicit type or result now display like so - Nested functions i.e. using functions as args displays like so Closes Add support for Fortran scope/block snippets #47 Adds a series of hover unittests. Also renamed the result variables --- CHANGELOG.md | 2 + fortls/intrinsics.py | 2 +- fortls/objects.py | 60 +++++++++++++------------ fortls/parse_fortran.py | 48 ++++++++++++++------ test/test_server.py | 21 ++++++++- test/test_source/hover/functions.f90 | 11 +++++ test/test_source/subdir/test_submod.F90 | 6 +-- 7 files changed, 102 insertions(+), 48 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index db91734b..35a3a2f5 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -6,6 +6,8 @@ - Fixed hovering over functions displaying as theire result types ([gnikit/fortls#22](https://github.com/gnikit/fortls/issues/22)) +- Fixed function hovering signature now standardised + ([#47](https://github.com/hansec/fortran-language-server/issues/47)) ## 2.2.1 diff --git a/fortls/intrinsics.py b/fortls/intrinsics.py index fed1fc7d..aa27fbb5 100644 --- a/fortls/intrinsics.py +++ b/fortls/intrinsics.py @@ -117,7 +117,7 @@ def create_object(json_obj, enc_obj=None): 0, name, args=args, - return_type=[json_obj["return"], keywords, keyword_info], + result_type=[json_obj["return"], keywords, keyword_info], ) elif json_obj["type"] == 3: return fortran_var( diff --git a/fortls/objects.py b/fortls/objects.py index 1bbaedac..bcb47c1b 100644 --- a/fortls/objects.py +++ b/fortls/objects.py @@ -1087,8 +1087,8 @@ def __init__( args: str = "", mod_flag: bool = False, keywords: list = None, - return_type=None, - result_var=None, + result_type: list[str] = None, # TODO: make this a string + result_name: str = None, ): super().__init__(file_ast, line_number, name, args, mod_flag, keywords) self.args: str = args.replace(" ", "").lower() @@ -1097,17 +1097,21 @@ def __init__( self.in_children: list = [] self.missing_args: list = [] self.mod_scope: bool = mod_flag - self.result_var = result_var - self.result_obj = None - self.return_type = None - if return_type is not None: - self.return_type = return_type[0] + self.result_name: str = result_name + self.result_type: str = None + self.result_obj: fortran_var = None + if result_type: + self.result_type = result_type[0] + # Set the implicit result() name to be the function name + if self.result_name is None: + self.result_name = self.name def copy_interface(self, copy_source: fortran_function): # Call the parent class method child_names = super().copy_interface(copy_source) # Return specific options - self.result_var = copy_source.result_var + self.result_name = copy_source.result_name + self.result_type = copy_source.result_type self.result_obj = copy_source.result_obj if copy_source.result_obj is not None: if copy_source.result_obj.name.lower() not in child_names: @@ -1115,20 +1119,20 @@ def copy_interface(self, copy_source: fortran_function): def resolve_link(self, obj_tree): self.resolve_arg_link(obj_tree) - if self.result_var is not None: - result_var_lower = self.result_var.lower() - for child in self.children: - if child.name.lower() == result_var_lower: - self.result_obj = child + result_var_lower = self.result_name.lower() + for child in self.children: + if child.name.lower() == result_var_lower: + self.result_obj = child + # Update result value and type + self.result_name = child.name + self.result_type = child.get_desc() def get_type(self, no_link=False): return FUNCTION_TYPE_ID def get_desc(self): - if self.result_obj is not None: - return self.result_obj.get_desc() + " FUNCTION" - if self.return_type is not None: - return self.return_type + " FUNCTION" + if self.result_type: + return self.result_type + " FUNCTION" return "FUNCTION" def is_callable(self): @@ -1136,26 +1140,26 @@ def is_callable(self): def get_hover(self, long=False, include_doc=True, drop_arg=-1): fun_sig, _ = self.get_snippet(drop_arg=drop_arg) - fun_return = "" - if self.result_obj is not None: - fun_return, _ = self.result_obj.get_hover(include_doc=False) - if self.return_type is not None: - fun_return = self.return_type - keyword_list = get_keywords(self.keywords) + fun_sig += f" RESULT({self.result_name})" + keyword_list = [] + if self.result_type: + keyword_list.append(self.result_type) + keyword_list += get_keywords(self.keywords) keyword_list.append("FUNCTION") - hover_array = [f"{fun_return} {' '.join(keyword_list)} {fun_sig}"] + + hover_array = [f"{' '.join(keyword_list)} {fun_sig}"] self.get_docs_full(hover_array, long, include_doc, drop_arg) return "\n ".join(hover_array), long def get_interface(self, name_replace=None, change_arg=-1, change_strings=None): fun_sig, _ = self.get_snippet(name_replace=name_replace) + fun_sig += f" RESULT({self.result_name})" keyword_list = [] - if self.return_type is not None: - keyword_list.append(self.return_type) - if self.result_obj is not None: - fun_sig += f" RESULT({self.result_obj.name})" + if self.result_type: + keyword_list.append(self.result_type) keyword_list += get_keywords(self.keywords) keyword_list.append("FUNCTION ") + interface_array = self.get_interface_array( keyword_list, fun_sig, change_arg, change_strings ) diff --git a/fortls/parse_fortran.py b/fortls/parse_fortran.py index 5e463dfe..ca354d2b 100644 --- a/fortls/parse_fortran.py +++ b/fortls/parse_fortran.py @@ -287,8 +287,23 @@ def read_var_def(line: str, type_word: str = None, fun_only: bool = False): return "var", VAR_info(type_word, keywords, var_words) -def read_fun_def(line: str, return_type=None, mod_flag: bool = False): - """Attempt to read FUNCTION definition line""" +def read_fun_def(line: str, result_type=None, mod_flag: bool = False): + """Attempt to read FUNCTION definition line + + Parameters + ---------- + line : str + file line + result_type : str, optional + type of function e.g. INTEGER, REAL, etc., by default None + mod_flag : bool, optional + flag for module and module procedure parsing, by default False + + Returns + ------- + tuple[Literal['fun'], FUN_info] + a named tuple + """ mod_match = SUB_MOD_REGEX.match(line) mods_found = False keywords: list[str] = [] @@ -317,14 +332,14 @@ def read_fun_def(line: str, return_type=None, mod_flag: bool = False): word_match = [word for word in word_match] args = ",".join(word_match) trailing_line = trailing_line[paren_match.end(0) :] - # - return_var = None - if return_type is None: - trailing_line = trailing_line.strip() - results_match = RESULT_REGEX.match(trailing_line) - if results_match is not None: - return_var = results_match.group(1).strip().lower() - return "fun", FUN_info(name, args, return_type, return_var, mod_flag, keywords) + + # Extract if possible the variable name of the result() + result_name = None + trailing_line = trailing_line.strip() + results_match = RESULT_REGEX.match(trailing_line) + if results_match: + result_name = results_match.group(1).strip().lower() + return "fun", FUN_info(name, args, result_type, result_name, mod_flag, keywords) def read_sub_def(line: str, mod_flag: bool = False): @@ -1772,16 +1787,21 @@ def parser_debug_msg(msg: str, line: str, ln: int): args=obj_info.args, mod_flag=obj_info.mod_flag, keywords=keywords, - return_type=obj_info.return_type, - result_var=obj_info.return_var, + result_type=obj_info.return_type, + result_name=obj_info.return_var, ) file_ast.add_scope(new_fun, END_FUN_REGEX) - if obj_info.return_type is not None: + # function type is present without result(), register the automatic + # result() variable that is the function name + if obj_info.return_type: + result_name = obj_info.name + if obj_info.return_var: + result_name = obj_info.return_var keywords, keyword_info = map_keywords(obj_info.return_type[1]) new_obj = fortran_var( file_ast, line_number, - obj_info.name, + result_name, obj_info.return_type[0], keywords, keyword_info, diff --git a/test/test_server.py b/test/test_server.py index 3f62cfd1..52002c7a 100644 --- a/test/test_server.py +++ b/test/test_server.py @@ -576,6 +576,12 @@ def check_return(result_array, checks): file_path = test_dir / "hover" / "functions.f90" string += hover_req(file_path, 1, 11) string += hover_req(file_path, 7, 19) + string += hover_req(file_path, 12, 12) + string += hover_req(file_path, 18, 19) + file_path = test_dir / "subdir" / "test_submod.F90" + string += hover_req(file_path, 29, 24) + file_path = test_dir / "test_diagnostic_int.f90" + string += hover_req(file_path, 19, 14) errcode, results = run_request( string, fortls_args=["--variable_hover", "--sort_keywords"] @@ -594,10 +600,21 @@ def check_return(result_array, checks): "DOUBLE PRECISION, PARAMETER :: somevar = 23.12", "DOUBLE PRECISION, PARAMETER :: some = 1e-19", "INTEGER, POINTER", - """FUNCTION fun1(arg) + """INTEGER FUNCTION fun1(arg) RESULT(fun1) + INTEGER, INTENT(IN) :: arg""", + """INTEGER FUNCTION fun2(arg) RESULT(fun2) + INTEGER, INTENT(IN) :: arg""", + """INTEGER FUNCTION fun3(arg) RESULT(retval) INTEGER, INTENT(IN) :: arg""", - """INTEGER FUNCTION fun2(arg) + """INTEGER FUNCTION fun4(arg) RESULT(retval) INTEGER, INTENT(IN) :: arg""", + """REAL FUNCTION point_dist(a, b) RESULT(distance) + TYPE(point), INTENT(IN) :: a + TYPE(point), INTENT(IN) :: b""", + """REAL FUNCTION foo2(f, g, h) RESULT(arg3) + REAL FUNCTION f(x) RESULT(z) :: f + REAL FUNCTION g(x) RESULT(z) :: g + REAL FUNCTION h(x) RESULT(z) :: h""", ) assert len(ref_results) == len(results) - 1 check_return(results[1:], ref_results) diff --git a/test/test_source/hover/functions.f90 b/test/test_source/hover/functions.f90 index ec02d6e3..efd02f55 100644 --- a/test/test_source/hover/functions.f90 +++ b/test/test_source/hover/functions.f90 @@ -8,3 +8,14 @@ end function fun1 integer function fun2(arg) integer, intent(in) :: arg end function fun2 + +! function with return +function fun3(arg) result(retval) + integer, intent(in) :: arg + integer :: retval +end function fun3 + +! function with type on definition and return +integer function fun4(arg) result(retval) + integer, intent(in) :: arg +end function fun4 diff --git a/test/test_source/subdir/test_submod.F90 b/test/test_source/subdir/test_submod.F90 index fa8ff1af..1eb22004 100644 --- a/test/test_source/subdir/test_submod.F90 +++ b/test/test_source/subdir/test_submod.F90 @@ -27,8 +27,8 @@ end module points #define __PARENT_MOD__ points submodule (__PARENT_MOD__) points_a contains - module function point_dist - type(point) :: c + module function point_dist(a, b) + type(point), intent(in) :: a, b distance = sqrt((a%x - b%x)**2 + (a%y - b%y)**2) end function point_dist @@ -40,5 +40,5 @@ end function point_dist module procedure is_point_equal_sub type(point) :: c test = is_point_equal(a,b) - end module procedure is_point_equal_sub + end procedure is_point_equal_sub end submodule points_a From 0f87e6a57e7e04cdd6afa7e9c4c2a4aeb99ed7de Mon Sep 17 00:00:00 2001 From: gnikit Date: Mon, 21 Feb 2022 00:07:26 +0000 Subject: [PATCH 03/11] Escape function implicit result for both start and end of scope --- fortls/objects.py | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/fortls/objects.py b/fortls/objects.py index bcb47c1b..2448d9f5 100644 --- a/fortls/objects.py +++ b/fortls/objects.py @@ -191,7 +191,7 @@ def check_scope( if ( isinstance(local_scope, fortran_function) and local_scope.name.lower() == child.name.lower() - and local_scope.sline == var_line_number + and var_line_number in (local_scope.sline, local_scope.eline) ): return None @@ -1649,6 +1649,7 @@ def get_hover(self, long=False, include_doc=True, drop_arg=-1): hover_str = ", ".join( [self.desc] + get_keywords(self.keywords, self.keyword_info) ) + # TODO: at this stage we can mae this lowercase # Add parameter value in the output if self.is_parameter() and self.param_val: hover_str += f" :: {self.name} = {self.param_val}" From 20f2e3d577eead46933f43496e52df66ea55b180 Mon Sep 17 00:00:00 2001 From: gnikit Date: Mon, 21 Feb 2022 16:02:34 +0000 Subject: [PATCH 04/11] Fixes function modifiers not displaying on hover It required major rewrite of the function definition parsing Closes Functions with multiple keywords display incorrect hover gnikit/fortls#48 TODO: 1. Add tests about intrinsic functions 2. Add tests about functions returning arrays (this is actually a big deal) 2. touches on if hover should be displaying FORTRAN abiding code. I am leaning towards yes, so displaying ```fortran real dimension(10,10) function foo(arg) result(val) real, intent(in) :: arg ``` Does not seem the right thing for me to do. I think the hover request should return instead ```fortran real function foo(arg) result(val) real, intent(in) :: arg real, dimension(10,10) :: val ``` This way syntax highlighting in VSCode will not complain --- CHANGELOG.md | 2 + fortls/constants.py | 23 ++++++++++ fortls/intrinsics.py | 4 +- fortls/objects.py | 6 +-- fortls/parse_fortran.py | 69 +++++++++++++++------------- test/test_server.py | 11 +++++ test/test_source/hover/functions.f90 | 6 +++ 7 files changed, 85 insertions(+), 36 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 35a3a2f5..f5942acf 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -8,6 +8,8 @@ ([gnikit/fortls#22](https://github.com/gnikit/fortls/issues/22)) - Fixed function hovering signature now standardised ([#47](https://github.com/hansec/fortran-language-server/issues/47)) +- Fixed function modifiers not displaying upon hover + ([gnikit/fortls#48](https://github.com/gnikit/fortls/issues/48)) ## 2.2.1 diff --git a/fortls/constants.py b/fortls/constants.py index df0cbfa5..adf0f886 100644 --- a/fortls/constants.py +++ b/fortls/constants.py @@ -1,5 +1,8 @@ +from __future__ import annotations + import logging import sys +from dataclasses import dataclass, field PY3K = sys.version_info >= (3, 0) @@ -58,3 +61,23 @@ # it cannot also be a comment that requires !, c, d # and ^= (xor_eq) operator is invalid in Fortran C++ preproc FORTRAN_LITERAL = "0^=__LITERAL_INTERNAL_DUMMY_VAR_" + + +@dataclass +class RESULT_sig: + name: str = field(default=None) + type: str = field(default=None) + keywords: list[str] = field(default_factory=list) + + +@dataclass +class FUN_sig: + name: str + args: str + keywords: list[str] = field(default_factory=list) + mod_flag: bool = field(default=False) + result: RESULT_sig = field(default_factory=RESULT_sig) + + def __post_init__(self): + if not self.result.name: + self.result.name = self.name diff --git a/fortls/intrinsics.py b/fortls/intrinsics.py index aa27fbb5..16f89f2d 100644 --- a/fortls/intrinsics.py +++ b/fortls/intrinsics.py @@ -117,7 +117,9 @@ def create_object(json_obj, enc_obj=None): 0, name, args=args, - result_type=[json_obj["return"], keywords, keyword_info], + result_type=json_obj["return"], + keywords=keywords, + # keyword_info=keyword_info, ) elif json_obj["type"] == 3: return fortran_var( diff --git a/fortls/objects.py b/fortls/objects.py index 2448d9f5..de3dc109 100644 --- a/fortls/objects.py +++ b/fortls/objects.py @@ -1087,7 +1087,7 @@ def __init__( args: str = "", mod_flag: bool = False, keywords: list = None, - result_type: list[str] = None, # TODO: make this a string + result_type: str = None, result_name: str = None, ): super().__init__(file_ast, line_number, name, args, mod_flag, keywords) @@ -1098,10 +1098,8 @@ def __init__( self.missing_args: list = [] self.mod_scope: bool = mod_flag self.result_name: str = result_name - self.result_type: str = None + self.result_type: str = result_type self.result_obj: fortran_var = None - if result_type: - self.result_type = result_type[0] # Set the implicit result() name to be the function name if self.result_name is None: self.result_name = self.name diff --git a/fortls/parse_fortran.py b/fortls/parse_fortran.py index ca354d2b..801c1bdb 100644 --- a/fortls/parse_fortran.py +++ b/fortls/parse_fortran.py @@ -5,6 +5,7 @@ import os import re import sys +from typing import Literal from fortls.constants import ( DO_TYPE_ID, @@ -12,6 +13,8 @@ PY3K, SELECT_TYPE_ID, SUBMODULE_TYPE_ID, + FUN_sig, + RESULT_sig, log, ) from fortls.helper_functions import ( @@ -27,7 +30,6 @@ ) from fortls.objects import ( CLASS_info, - FUN_info, GEN_info, INT_info, SELECT_info, @@ -266,8 +268,8 @@ def read_var_def(line: str, type_word: str = None, fun_only: bool = False): return None # keywords, trailing_line = parse_var_keywords(trailing_line) - # Check if function - fun_def = read_fun_def(trailing_line, [type_word, keywords]) + # Check if this is a function definition + fun_def = read_fun_def(trailing_line, RESULT_sig(type=type_word, keywords=keywords)) if (fun_def is not None) or fun_only: return fun_def # @@ -287,34 +289,42 @@ def read_var_def(line: str, type_word: str = None, fun_only: bool = False): return "var", VAR_info(type_word, keywords, var_words) -def read_fun_def(line: str, result_type=None, mod_flag: bool = False): +def read_fun_def( + line: str, result: RESULT_sig = RESULT_sig(), mod_flag: bool = False +) -> tuple[Literal["fun"], FUN_sig] | None: """Attempt to read FUNCTION definition line + To infer the `result` `type` and `name` the variable definition is called + with the function only flag + Parameters ---------- line : str file line - result_type : str, optional - type of function e.g. INTEGER, REAL, etc., by default None + result : RESULT_sig, optional + a dataclass containing the result signature of the function mod_flag : bool, optional flag for module and module procedure parsing, by default False Returns ------- - tuple[Literal['fun'], FUN_info] + tuple[Literal["fun"], FUN_sig] | None a named tuple """ - mod_match = SUB_MOD_REGEX.match(line) - mods_found = False - keywords: list[str] = [] - while mod_match is not None: - mods_found = True - line = line[mod_match.end(0) :] - keywords.append(mod_match.group(1)) - mod_match = SUB_MOD_REGEX.match(line) - if mods_found: + # Get all the keyword modifier mathces + keywords = re.findall(SUB_MOD_REGEX, line) + # remove modifiers from line + for modifier in keywords: + line = line.replace(modifier, "") + + # Try and get the result type + # Recursively will call read_var_def which will then call read_fun_def + # with the variable result having been populated + if keywords: tmp_var = read_var_def(line, fun_only=True) if tmp_var is not None: + # Update keywords for function into dataclass + tmp_var[1].keywords = keywords return tmp_var fun_match = FUN_REGEX.match(line) if fun_match is None: @@ -334,12 +344,11 @@ def read_fun_def(line: str, result_type=None, mod_flag: bool = False): trailing_line = trailing_line[paren_match.end(0) :] # Extract if possible the variable name of the result() - result_name = None trailing_line = trailing_line.strip() results_match = RESULT_REGEX.match(trailing_line) if results_match: - result_name = results_match.group(1).strip().lower() - return "fun", FUN_info(name, args, result_type, result_name, mod_flag, keywords) + result.name = results_match.group(1).strip().lower() + return "fun", FUN_sig(name, args, keywords, mod_flag, result=result) def read_sub_def(line: str, mod_flag: bool = False): @@ -548,7 +557,8 @@ def read_mod_def(line: str): return sub_res fun_res = read_var_def(trailing_line, fun_only=True) if fun_res is not None: - return fun_res[0], fun_res[1]._replace(mod_flag=True) + fun_res[1].mod_flag = True + return fun_res[0], fun_res[1] fun_res = read_fun_def(trailing_line, mod_flag=True) if fun_res is not None: return fun_res @@ -1787,24 +1797,21 @@ def parser_debug_msg(msg: str, line: str, ln: int): args=obj_info.args, mod_flag=obj_info.mod_flag, keywords=keywords, - result_type=obj_info.return_type, - result_name=obj_info.return_var, + result_type=obj_info.result.type, + result_name=obj_info.result.name, ) file_ast.add_scope(new_fun, END_FUN_REGEX) # function type is present without result(), register the automatic # result() variable that is the function name - if obj_info.return_type: - result_name = obj_info.name - if obj_info.return_var: - result_name = obj_info.return_var - keywords, keyword_info = map_keywords(obj_info.return_type[1]) + if obj_info.result.type: + keywords, keyword_info = map_keywords(obj_info.result.keywords) new_obj = fortran_var( file_ast, line_number, - result_name, - obj_info.return_type[0], - keywords, - keyword_info, + name=obj_info.result.name, + var_desc=obj_info.result.type, + keywords=keywords, + keyword_info=keyword_info, ) file_ast.add_variable(new_obj) parser_debug_msg("FUNCTION", line, line_number) diff --git a/test/test_server.py b/test/test_server.py index 52002c7a..ed809d5e 100644 --- a/test/test_server.py +++ b/test/test_server.py @@ -578,8 +578,10 @@ def check_return(result_array, checks): string += hover_req(file_path, 7, 19) string += hover_req(file_path, 12, 12) string += hover_req(file_path, 18, 19) + string += hover_req(file_path, 23, 34) file_path = test_dir / "subdir" / "test_submod.F90" string += hover_req(file_path, 29, 24) + string += hover_req(file_path, 34, 24) file_path = test_dir / "test_diagnostic_int.f90" string += hover_req(file_path, 19, 14) @@ -608,8 +610,17 @@ def check_return(result_array, checks): INTEGER, INTENT(IN) :: arg""", """INTEGER FUNCTION fun4(arg) RESULT(retval) INTEGER, INTENT(IN) :: arg""", + # Notice that the order of the modifiers does not match the source code + # This is part of the test, ideally they would be identical but previously + # any modifiers before the type would be discarded + """INTEGER PURE ELEMENTAL FUNCTION fun5(arg) RESULT(retval) + INTEGER, INTENT(IN) :: arg""", + # TODO: more tests to add from functions """REAL FUNCTION point_dist(a, b) RESULT(distance) TYPE(point), INTENT(IN) :: a + TYPE(point), INTENT(IN) :: b""", + """LOGICAL FUNCTION is_point_equal_a(a, b) RESULT(is_point_equal_a) + TYPE(point), INTENT(IN) :: a TYPE(point), INTENT(IN) :: b""", """REAL FUNCTION foo2(f, g, h) RESULT(arg3) REAL FUNCTION f(x) RESULT(z) :: f diff --git a/test/test_source/hover/functions.f90 b/test/test_source/hover/functions.f90 index efd02f55..63e30d9d 100644 --- a/test/test_source/hover/functions.f90 +++ b/test/test_source/hover/functions.f90 @@ -19,3 +19,9 @@ end function fun3 integer function fun4(arg) result(retval) integer, intent(in) :: arg end function fun4 + +! function with type on definition, return and keywords +pure integer elemental function fun5(arg) result(retval) + integer, intent(in) :: arg +end function fun5 + From acc33b9c7d982d1f87a85f5e75c195d64f09cc39 Mon Sep 17 00:00:00 2001 From: gnikit Date: Mon, 21 Feb 2022 18:34:44 +0000 Subject: [PATCH 05/11] Make sure we replace only modifiers Edit regex and replace to consider word boundaries --- fortls/parse_fortran.py | 13 +++++-------- fortls/regex_patterns.py | 2 +- test/test_server.py | 12 ++++++++++++ test/test_source/hover/recursive.f90 | 23 +++++++++++++++++++++++ 4 files changed, 41 insertions(+), 9 deletions(-) create mode 100644 test/test_source/hover/recursive.f90 diff --git a/fortls/parse_fortran.py b/fortls/parse_fortran.py index 801c1bdb..29b2aa7e 100644 --- a/fortls/parse_fortran.py +++ b/fortls/parse_fortran.py @@ -314,8 +314,7 @@ def read_fun_def( # Get all the keyword modifier mathces keywords = re.findall(SUB_MOD_REGEX, line) # remove modifiers from line - for modifier in keywords: - line = line.replace(modifier, "") + line = re.sub(SUB_MOD_REGEX, "", line) # Try and get the result type # Recursively will call read_var_def which will then call read_fun_def @@ -353,12 +352,10 @@ def read_fun_def( def read_sub_def(line: str, mod_flag: bool = False): """Attempt to read SUBROUTINE definition line""" - keywords: list[str] = [] - mod_match = SUB_MOD_REGEX.match(line) - while mod_match is not None: - line = line[mod_match.end(0) :] - keywords.append(mod_match.group(1)) - mod_match = SUB_MOD_REGEX.match(line) + # Get all the keyword modifier mathces + keywords = re.findall(SUB_MOD_REGEX, line) + # remove modifiers from line + line = re.sub(SUB_MOD_REGEX, "", line) sub_match = SUB_REGEX.match(line) if sub_match is None: return None diff --git a/fortls/regex_patterns.py b/fortls/regex_patterns.py index 10df02d1..f384b7a5 100644 --- a/fortls/regex_patterns.py +++ b/fortls/regex_patterns.py @@ -11,7 +11,7 @@ INCLUDE_REGEX = re.compile(r"[ ]*INCLUDE[ :]*[\'\"]([^\'\"]*)", re.I) CONTAINS_REGEX = re.compile(r"[ ]*(CONTAINS)[ ]*$", re.I) IMPLICIT_REGEX = re.compile(r"[ ]*IMPLICIT[ ]+([a-z]*)", re.I) -SUB_MOD_REGEX = re.compile(r"[ ]*(PURE|IMPURE|ELEMENTAL|RECURSIVE)+", re.I) +SUB_MOD_REGEX = re.compile(r"[ ]*\b(PURE|IMPURE|ELEMENTAL|RECURSIVE)\b", re.I) SUB_REGEX = re.compile(r"[ ]*SUBROUTINE[ ]+([a-z0-9_]+)", re.I) END_SUB_REGEX = re.compile(r"SUBROUTINE", re.I) FUN_REGEX = re.compile(r"[ ]*FUNCTION[ ]+([a-z0-9_]+)", re.I) diff --git a/test/test_server.py b/test/test_server.py index ed809d5e..40d15120 100644 --- a/test/test_server.py +++ b/test/test_server.py @@ -579,6 +579,8 @@ def check_return(result_array, checks): string += hover_req(file_path, 12, 12) string += hover_req(file_path, 18, 19) string += hover_req(file_path, 23, 34) + file_path = test_dir / "hover" / "recursive.f90" + string += hover_req(file_path, 9, 40) file_path = test_dir / "subdir" / "test_submod.F90" string += hover_req(file_path, 29, 24) string += hover_req(file_path, 34, 24) @@ -615,6 +617,10 @@ def check_return(result_array, checks): # any modifiers before the type would be discarded """INTEGER PURE ELEMENTAL FUNCTION fun5(arg) RESULT(retval) INTEGER, INTENT(IN) :: arg""", + """RECURSIVE SUBROUTINE recursive_assign_descending(node, vector, current_loc) + TYPE(tree_inode), POINTER, INTENT(IN) :: node + INTEGER, DIMENSION(:), INTENT(INOUT) :: vector + INTEGER, INTENT(INOUT) :: current_loc""", # TODO: more tests to add from functions """REAL FUNCTION point_dist(a, b) RESULT(distance) TYPE(point), INTENT(IN) :: a @@ -746,6 +752,11 @@ def check_return(results, ref_results): string += write_rpc_notification( "textDocument/didOpen", {"textDocument": {"uri": file_path}} ) + # Test module procedure in submodules importing scopes + file_path = str(test_dir / "subdir" / "test_submod.f90") + string += write_rpc_notification( + "textDocument/didOpen", {"textDocument": {"uri": file_path}} + ) errcode, results = run_request(string) assert errcode == 0 @@ -815,6 +826,7 @@ def check_return(results, ref_results): [], [], [], + [], [ { "range": { diff --git a/test/test_source/hover/recursive.f90 b/test/test_source/hover/recursive.f90 new file mode 100644 index 00000000..50730816 --- /dev/null +++ b/test/test_source/hover/recursive.f90 @@ -0,0 +1,23 @@ +module tree + type tree_inode + integer :: value = 0 + type (tree_inode), pointer :: left=>null() + type (tree_inode), pointer :: right=>null() + type (tree_inode), pointer :: parent=>null() + end type tree_inode + +contains + recursive subroutine recursive_assign_descending(node, vector, current_loc) + type(tree_inode), pointer, intent(in) :: node + integer, dimension(:), intent(inout) :: vector + integer, intent(inout) :: current_loc + + if (associated(node)) then + call recursive_assign_descending(node%right, vector, current_loc) + vector(current_loc) = node%value + current_loc = current_loc + 1 + call recursive_assign_descending(node%left, vector, current_loc) + end if + return + end subroutine recursive_assign_descending +end module tree \ No newline at end of file From 8c2460b5bbfbf153692f8bf7466e9f789478de71 Mon Sep 17 00:00:00 2001 From: gnikit Date: Tue, 22 Feb 2022 10:18:32 +0000 Subject: [PATCH 06/11] Standardises function hover - Makes hover more robust - Adds extensive unittests for hover support of functions - Improves documentation of function hover --- CHANGELOG.md | 9 +++- fortls/objects.py | 58 +++++++++++++++++++++---- fortls/parse_fortran.py | 6 ++- test/test_server.py | 63 +++++++++++++++++++--------- test/test_source/hover/functions.f90 | 30 +++++++++++++ 5 files changed, 135 insertions(+), 31 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index f5942acf..e35db5a5 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -2,14 +2,19 @@ ## 2.2.2 +### Changed + +- Changed the way function hover messages are displayed, now signatures are standardised + ([gnikit/fortls#47](https://github.com/gnikit/fortls/issues/47)) + ### Fixed - Fixed hovering over functions displaying as theire result types ([gnikit/fortls#22](https://github.com/gnikit/fortls/issues/22)) -- Fixed function hovering signature now standardised - ([#47](https://github.com/hansec/fortran-language-server/issues/47)) - Fixed function modifiers not displaying upon hover ([gnikit/fortls#48](https://github.com/gnikit/fortls/issues/48)) +- Fixed function hover when returning arrays + ([gnikit/fortls#50](https://github.com/gnikit/fortls/issues/50)) ## 2.2.1 diff --git a/fortls/objects.py b/fortls/objects.py index de3dc109..742e6c1e 100644 --- a/fortls/objects.py +++ b/fortls/objects.py @@ -976,7 +976,7 @@ def get_hover(self, long=False, include_doc=True, drop_arg=-1): keyword_list = get_keywords(self.keywords) keyword_list.append(f"{self.get_desc()} ") hover_array = [" ".join(keyword_list) + sub_sig] - self.get_docs_full(hover_array, long, include_doc, drop_arg) + hover_array = self.get_docs_full(hover_array, long, include_doc, drop_arg) return "\n ".join(hover_array), long def get_docs_full( @@ -994,6 +994,7 @@ def get_docs_full( doc_str = arg_obj.get_documentation() if include_doc and (doc_str is not None): hover_array += doc_str.splitlines() + return hover_array def get_signature(self, drop_arg=-1): arg_sigs = [] @@ -1136,22 +1137,63 @@ def get_desc(self): def is_callable(self): return False - def get_hover(self, long=False, include_doc=True, drop_arg=-1): + def get_hover( + self, long: bool = False, include_doc: bool = True, drop_arg: int = -1 + ) -> tuple[str, bool]: + """Construct the hover message for a FUNCTION. + Two forms are produced here the `long` i.e. the normal for hover requests + + ``` + [MODIFIERS] FUNCTION NAME([ARGS]) RESULT(RESULT_VAR) + TYPE, [ARG_MODIFIERS] :: [ARGS] + TYPE, [RESULT_MODIFIERS] :: RESULT_VAR + ``` + + note: intrinsic functions will display slightly different, + `RESULT_VAR` and its `TYPE` might not always be present + + short form, used when functions are arguments in functions and subroutines: + + ``` + FUNCTION NAME([ARGS]) :: ARG_LIST_NAME + ``` + + Parameters + ---------- + long : bool, optional + toggle between long and short hover results, by default False + include_doc : bool, optional + if to include any documentation, by default True + drop_arg : int, optional + Ignore argument at position `drop_arg` in the argument list, by default -1 + + Returns + ------- + tuple[str, bool] + String representative of the hover message and the `long` flag used + """ fun_sig, _ = self.get_snippet(drop_arg=drop_arg) - fun_sig += f" RESULT({self.result_name})" - keyword_list = [] - if self.result_type: - keyword_list.append(self.result_type) - keyword_list += get_keywords(self.keywords) + # short hover messages do not include the result() + fun_sig += f" RESULT({self.result_name})" if long else "" + keyword_list = get_keywords(self.keywords) keyword_list.append("FUNCTION") hover_array = [f"{' '.join(keyword_list)} {fun_sig}"] - self.get_docs_full(hover_array, long, include_doc, drop_arg) + hover_array = self.get_docs_full(hover_array, long, include_doc, drop_arg) + # Only append the return value if using long form + if self.result_obj and long: + arg_doc, _ = self.result_obj.get_hover(include_doc=False) + hover_array.append(f"{arg_doc} :: {self.result_obj.name}") + # intrinsic functions, where the return type is missing but can be inferred + elif self.result_type and long: + # prepend type to function signature + hover_array[0] = f"{self.result_type} {hover_array[0]}" return "\n ".join(hover_array), long def get_interface(self, name_replace=None, change_arg=-1, change_strings=None): fun_sig, _ = self.get_snippet(name_replace=name_replace) fun_sig += f" RESULT({self.result_name})" + # XXX: keyword_list = [] if self.result_type: keyword_list.append(self.result_type) diff --git a/fortls/parse_fortran.py b/fortls/parse_fortran.py index 29b2aa7e..ac8853e3 100644 --- a/fortls/parse_fortran.py +++ b/fortls/parse_fortran.py @@ -290,7 +290,7 @@ def read_var_def(line: str, type_word: str = None, fun_only: bool = False): def read_fun_def( - line: str, result: RESULT_sig = RESULT_sig(), mod_flag: bool = False + line: str, result: RESULT_sig = None, mod_flag: bool = False ) -> tuple[Literal["fun"], FUN_sig] | None: """Attempt to read FUNCTION definition line @@ -345,9 +345,11 @@ def read_fun_def( # Extract if possible the variable name of the result() trailing_line = trailing_line.strip() results_match = RESULT_REGEX.match(trailing_line) + if result is None: + result = RESULT_sig() if results_match: result.name = results_match.group(1).strip().lower() - return "fun", FUN_sig(name, args, keywords, mod_flag, result=result) + return "fun", FUN_sig(name, args, keywords, mod_flag, result) def read_sub_def(line: str, mod_flag: bool = False): diff --git a/test/test_server.py b/test/test_server.py index 40d15120..ec0712d7 100644 --- a/test/test_server.py +++ b/test/test_server.py @@ -579,6 +579,11 @@ def check_return(result_array, checks): string += hover_req(file_path, 12, 12) string += hover_req(file_path, 18, 19) string += hover_req(file_path, 23, 34) + string += hover_req(file_path, 28, 11) + string += hover_req(file_path, 34, 21) + string += hover_req(file_path, 46, 11) + string += hover_req(file_path, 51, 11) + string += hover_req(file_path, 55, 11) file_path = test_dir / "hover" / "recursive.f90" string += hover_req(file_path, 9, 40) file_path = test_dir / "subdir" / "test_submod.F90" @@ -604,34 +609,54 @@ def check_return(result_array, checks): "DOUBLE PRECISION, PARAMETER :: somevar = 23.12", "DOUBLE PRECISION, PARAMETER :: some = 1e-19", "INTEGER, POINTER", - """INTEGER FUNCTION fun1(arg) RESULT(fun1) - INTEGER, INTENT(IN) :: arg""", - """INTEGER FUNCTION fun2(arg) RESULT(fun2) - INTEGER, INTENT(IN) :: arg""", - """INTEGER FUNCTION fun3(arg) RESULT(retval) - INTEGER, INTENT(IN) :: arg""", - """INTEGER FUNCTION fun4(arg) RESULT(retval) - INTEGER, INTENT(IN) :: arg""", + """FUNCTION fun1(arg) RESULT(fun1) + INTEGER, INTENT(IN) :: arg + INTEGER :: fun1""", + """FUNCTION fun2(arg) RESULT(fun2) + INTEGER, INTENT(IN) :: arg + INTEGER :: fun2""", + """FUNCTION fun3(arg) RESULT(retval) + INTEGER, INTENT(IN) :: arg + INTEGER :: retval""", + """FUNCTION fun4(arg) RESULT(retval) + INTEGER, INTENT(IN) :: arg + INTEGER :: retval""", # Notice that the order of the modifiers does not match the source code # This is part of the test, ideally they would be identical but previously # any modifiers before the type would be discarded - """INTEGER PURE ELEMENTAL FUNCTION fun5(arg) RESULT(retval) - INTEGER, INTENT(IN) :: arg""", + """PURE ELEMENTAL FUNCTION fun5(arg) RESULT(retval) + INTEGER, INTENT(IN) :: arg + INTEGER :: retval""", + """FUNCTION fun6(arg) RESULT(retval) + INTEGER, INTENT(IN) :: arg + INTEGER, DIMENSION(10,10) :: retval""", + """PURE FUNCTION outer_product(x, y) RESULT(outer_product) + REAL, DIMENSION(:), INTENT(IN) :: x + REAL, DIMENSION(:), INTENT(IN) :: y + REAL, DIMENSION(SIZE(X), SIZE(Y)) :: outer_product""", + """FUNCTION dlamch(cmach) RESULT(dlamch) + CHARACTER :: CMACH""", + """FUNCTION fun7() RESULT(val) + TYPE(c_ptr) :: val""", + """TYPE(c_ptr) FUNCTION c_loc(x) RESULT(c_loc)""", """RECURSIVE SUBROUTINE recursive_assign_descending(node, vector, current_loc) TYPE(tree_inode), POINTER, INTENT(IN) :: node INTEGER, DIMENSION(:), INTENT(INOUT) :: vector INTEGER, INTENT(INOUT) :: current_loc""", - # TODO: more tests to add from functions - """REAL FUNCTION point_dist(a, b) RESULT(distance) + """FUNCTION point_dist(a, b) RESULT(distance) TYPE(point), INTENT(IN) :: a - TYPE(point), INTENT(IN) :: b""", - """LOGICAL FUNCTION is_point_equal_a(a, b) RESULT(is_point_equal_a) + TYPE(point), INTENT(IN) :: b + REAL :: distance""", + """FUNCTION is_point_equal_a(a, b) RESULT(is_point_equal_a) TYPE(point), INTENT(IN) :: a - TYPE(point), INTENT(IN) :: b""", - """REAL FUNCTION foo2(f, g, h) RESULT(arg3) - REAL FUNCTION f(x) RESULT(z) :: f - REAL FUNCTION g(x) RESULT(z) :: g - REAL FUNCTION h(x) RESULT(z) :: h""", + TYPE(point), INTENT(IN) :: b + LOGICAL :: is_point_equal_a""", + # Could be subject to change + """FUNCTION foo2(f, g, h) RESULT(arg3) + FUNCTION f(x) :: f + FUNCTION g(x) :: g + FUNCTION h(x) :: h + REAL :: arg3""", ) assert len(ref_results) == len(results) - 1 check_return(results[1:], ref_results) diff --git a/test/test_source/hover/functions.f90 b/test/test_source/hover/functions.f90 index 63e30d9d..38f21916 100644 --- a/test/test_source/hover/functions.f90 +++ b/test/test_source/hover/functions.f90 @@ -25,3 +25,33 @@ pure integer elemental function fun5(arg) result(retval) integer, intent(in) :: arg end function fun5 +! function with type on definition and return +function fun6(arg) result(retval) + integer, intent(in) :: arg + integer, dimension(10,10) :: retval +end function fun6 + +! functions with complex result type +pure function outer_product(x, y) + real, dimension(:), intent(in) :: x, y + real, dimension(size(x), size(y)) :: outer_product + integer :: i, j + forall (i=1:size(x)) + forall (j=1:size(y)) + outer_product(i, j) = x(i) * y(j) + end forall + end forall +end function outer_product + +! functions with no result type, common in interfaces +function dlamch(CMACH) + character :: CMACH +end function dlamch + +! intrinsic functions like c_loc display a return type +function fun7() result(val) + use, intrinsic :: iso_c_binding + integer, dimension(1), target :: ar + type(c_ptr) :: val + val = c_loc(ar) +end function fun7 From 87d7202e5d124525bb805fd8b3494676606a32c2 Mon Sep 17 00:00:00 2001 From: gnikit Date: Tue, 22 Feb 2022 11:22:29 +0000 Subject: [PATCH 07/11] Fixes references for semi-implicit function result functions that do not use the word `result` but do define a variable that is the same as the function name previously failed to get refs A unittest has been added for this case --- fortls/langserver.py | 51 +++++++++++++++++++++----------------------- test/test_server.py | 4 ++++ 2 files changed, 28 insertions(+), 27 deletions(-) diff --git a/fortls/langserver.py b/fortls/langserver.py index 21bed521..f262fddb 100644 --- a/fortls/langserver.py +++ b/fortls/langserver.py @@ -907,34 +907,31 @@ def get_all_references(self, def_obj, type_mem, file_obj=None): continue for match in NAME_REGEX.finditer(line): var_def = self.get_definition(file_obj, i, match.start(1) + 1) - if var_def is not None: - ref_match = False - if (def_fqsn == var_def.FQSN) or ( - var_def.FQSN in override_cache + if var_def is None: + continue + ref_match = False + if def_fqsn == var_def.FQSN or var_def.FQSN in override_cache: + ref_match = True + elif var_def.parent and var_def.parent.get_type() == CLASS_TYPE_ID: + if type_mem: + for inherit_def in var_def.parent.get_overridden(def_name): + if def_fqsn == inherit_def.FQSN: + ref_match = True + override_cache.append(var_def.FQSN) + break + if ( + (var_def.sline - 1 == i) + and (var_def.file_ast.path == filename) + and (line.count("=>") == 0) ): - ref_match = True - elif var_def.parent.get_type() == CLASS_TYPE_ID: - if type_mem: - for inherit_def in var_def.parent.get_overridden( - def_name - ): - if def_fqsn == inherit_def.FQSN: - ref_match = True - override_cache.append(var_def.FQSN) - break - if ( - (var_def.sline - 1 == i) - and (var_def.file_ast.path == filename) - and (line.count("=>") == 0) - ): - try: - if var_def.link_obj is def_obj: - ref_objs.append(var_def) - ref_match = True - except: - pass - if ref_match: - file_refs.append([i, match.start(1), match.end(1)]) + try: + if var_def.link_obj is def_obj: + ref_objs.append(var_def) + ref_match = True + except: + pass + if ref_match: + file_refs.append([i, match.start(1), match.end(1)]) if len(file_refs) > 0: refs[filename] = file_refs return refs, ref_objs diff --git a/test/test_server.py b/test/test_server.py index ec0712d7..07772eac 100644 --- a/test/test_server.py +++ b/test/test_server.py @@ -463,6 +463,8 @@ def def_request(file_path, line, char): file_path = test_dir / "subdir" / "test_rename.F90" string += def_request(file_path, 13, 5) string += def_request(file_path, 14, 5) + file_path = test_dir / "hover" / "functions.f90" + string += def_request(file_path, 3, 17) errcode, results = run_request(string) assert errcode == 0 # @@ -488,6 +490,8 @@ def def_request(file_path, line, char): # subdir/test_rename.F90 [6, 6, str(test_dir / "subdir" / "test_rename.F90")], [1, 1, str(test_dir / "subdir" / "test_rename.F90")], + # hover/functions.f90 + [3, 3, str(test_dir / "hover" / "functions.f90")], ) assert len(exp_results) + 1 == len(results) for i in range(len(exp_results)): From 8420e98e15337bbd362a318ba28116e37ec27b0a Mon Sep 17 00:00:00 2001 From: gnikit Date: Tue, 22 Feb 2022 11:23:12 +0000 Subject: [PATCH 08/11] Improves typing --- fortls/langserver.py | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/fortls/langserver.py b/fortls/langserver.py index f262fddb..0cd1f4fa 100644 --- a/fortls/langserver.py +++ b/fortls/langserver.py @@ -883,16 +883,21 @@ def check_optional(arg, params): req_dict = {"signatures": [signature], "activeParameter": param_num} return req_dict - def get_all_references(self, def_obj, type_mem, file_obj=None): + def get_all_references( + self, + def_obj, + type_mem: bool, + file_obj: fortran_file = None, + ): # Search through all files - def_name = def_obj.name.lower() - def_fqsn = def_obj.FQSN + def_name: str = def_obj.name.lower() + def_fqsn: str = def_obj.FQSN NAME_REGEX = re.compile(rf"(?:\W|^)({def_name})(?:\W|$)", re.I) if file_obj is None: file_set = self.workspace.items() else: file_set = ((file_obj.path, file_obj),) - override_cache = [] + override_cache: list[str] = [] refs = {} ref_objs = [] for filename, file_obj in file_set: From 8ff561356918944d489baf1e886ddea834d25175 Mon Sep 17 00:00:00 2001 From: gnikit Date: Tue, 22 Feb 2022 11:23:42 +0000 Subject: [PATCH 09/11] Improves typing --- fortls/helper_functions.py | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/fortls/helper_functions.py b/fortls/helper_functions.py index f6b86aac..b1434c48 100644 --- a/fortls/helper_functions.py +++ b/fortls/helper_functions.py @@ -311,7 +311,7 @@ def set_keyword_ordering(sorted): sort_keywords = sorted -def map_keywords(keywords): +def map_keywords(keywords: list[str]): mapped_keywords = [] keyword_info = {} for keyword in keywords: From 6f93fd3d78818064da01a45577b842fd579121c0 Mon Sep 17 00:00:00 2001 From: gnikit Date: Tue, 22 Feb 2022 11:47:43 +0000 Subject: [PATCH 10/11] Add typing literals for older Python versions --- fortls/parse_fortran.py | 7 ++++++- setup.cfg | 1 + 2 files changed, 7 insertions(+), 1 deletion(-) diff --git a/fortls/parse_fortran.py b/fortls/parse_fortran.py index ac8853e3..8569c419 100644 --- a/fortls/parse_fortran.py +++ b/fortls/parse_fortran.py @@ -5,7 +5,12 @@ import os import re import sys -from typing import Literal + +# Python < 3.8 does not have typing.Literals +try: + from typing import Literal +except ImportError: + from typing_extensions import Literal from fortls.constants import ( DO_TYPE_ID, diff --git a/setup.cfg b/setup.cfg index 5ba20e0b..b8094f47 100644 --- a/setup.cfg +++ b/setup.cfg @@ -33,6 +33,7 @@ packages = find: python_requires = >= 3.7 install_requires = importlib-metadata; python_version < "3.8" + typing-extensions; python_version < "3.8" [options.package_data] fortls = *.json From 8aa64782be167a18ed0a12c6a2e8220f4c542b9d Mon Sep 17 00:00:00 2001 From: gnikit Date: Tue, 22 Feb 2022 12:51:20 +0000 Subject: [PATCH 11/11] Fixes test for windows --- test/test_server.py | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/test_server.py b/test/test_server.py index 07772eac..bf150bd2 100644 --- a/test/test_server.py +++ b/test/test_server.py @@ -782,7 +782,7 @@ def check_return(results, ref_results): "textDocument/didOpen", {"textDocument": {"uri": file_path}} ) # Test module procedure in submodules importing scopes - file_path = str(test_dir / "subdir" / "test_submod.f90") + file_path = str(test_dir / "subdir" / "test_submod.F90") string += write_rpc_notification( "textDocument/didOpen", {"textDocument": {"uri": file_path}} )