From e865100660a999a158e9a94714c917e36332a136 Mon Sep 17 00:00:00 2001 From: gnikit Date: Fri, 26 Apr 2024 19:22:49 +0100 Subject: [PATCH 01/13] refactor: adds custom exceptions This is a first attempt at the problem. Slowly I will have to remove the levels of nested handling of certain errors and allow them to bubble up. --- fortls/debug.py | 13 +++-- fortls/langserver.py | 46 ++++++++++------ fortls/parsers/internal/parser.py | 91 ++++++++++++++++--------------- test/test_parser.py | 15 +++-- 4 files changed, 94 insertions(+), 71 deletions(-) diff --git a/fortls/debug.py b/fortls/debug.py index 4a3c8c97..7e7a5e48 100644 --- a/fortls/debug.py +++ b/fortls/debug.py @@ -10,7 +10,7 @@ from .helper_functions import only_dirs, resolve_globs from .jsonrpc import JSONRPC2Connection, ReadWriter, path_from_uri from .langserver import LangServer -from .parsers.internal.parser import FortranFile, preprocess_file +from .parsers.internal.parser import FortranFile, ParserError, preprocess_file class DebugError(Exception): @@ -421,13 +421,16 @@ def debug_parser(args): separator() ensure_file_accessible(args.debug_filepath) - pp_suffixes, pp_defs, include_dirs = read_config(args.debug_rootpath, args.config) + pp_suffixes, pp_defs, include_dirs = read_config(args.debug_rootpath) print(f' File = "{args.debug_filepath}"') file_obj = FortranFile(args.debug_filepath, pp_suffixes) - err_str, _ = file_obj.load_from_disk() - if err_str: - raise DebugError(f"Reading file failed: {err_str}") + try: + file_obj.load_from_disk() + except ParserError as exc: + msg = f"Reading file {args.debug_filepath} failed: {str(exc)}" + raise DebugError(msg) from exc + print(f' File = "{args.debug_filepath}"') print(f" Detected format: {'fixed' if file_obj.fixed else 'free'}") print("\n" + "=" * 80 + "\nParser Output\n" + "=" * 80 + "\n") file_ast = file_obj.parse(debug=True, pp_defs=pp_defs, include_dirs=include_dirs) diff --git a/fortls/langserver.py b/fortls/langserver.py index 8ecbce1c..7fdcf295 100644 --- a/fortls/langserver.py +++ b/fortls/langserver.py @@ -51,7 +51,7 @@ load_intrinsics, set_lowercase_intrinsics, ) -from fortls.parsers.internal.parser import FortranFile, get_line_context +from fortls.parsers.internal.parser import FortranFile, ParserError, get_line_context from fortls.parsers.internal.scope import Scope from fortls.parsers.internal.use import Use from fortls.parsers.internal.utilities import ( @@ -1313,9 +1313,10 @@ def serve_onChange(self, request: dict): return # Parse newly updated file if reparse_req: - _, err_str = self.update_workspace_file(path, update_links=True) - if err_str is not None: - self.post_message(f"Change request failed for file '{path}': {err_str}") + try: + self.update_workspace_file(path, update_links=True) + except LSPError as e: + self.post_message(f"Change request failed for file '{path}': {str(e)}") return # Update include statements linking to this file for _, tmp_file in self.workspace.items(): @@ -1350,11 +1351,12 @@ def serve_onSave( for key in ast_old.global_dict: self.obj_tree.pop(key, None) return - did_change, err_str = self.update_workspace_file( - filepath, read_file=True, allow_empty=did_open - ) - if err_str is not None: - self.post_message(f"Save request failed for file '{filepath}': {err_str}") + try: + did_change = self.update_workspace_file( + filepath, read_file=True, allow_empty=did_open + ) + except LSPError as e: + self.post_message(f"Save request failed for file '{filepath}': {str(e)}") return if did_change: # Update include statements linking to this file @@ -1390,12 +1392,14 @@ def update_workspace_file( return False, None else: return False, "File does not exist" # Error during load - err_string, file_changed = file_obj.load_from_disk() - if err_string: - log.error("%s : %s", err_string, filepath) - return False, err_string # Error during file read - if not file_changed: - return False, None + try: + file_changed = file_obj.load_from_disk() + if not file_changed: + return False, None + except ParserError as exc: + log.error("%s : %s", str(exc), filepath) + raise LSPError from exc + ast_new = file_obj.parse( pp_defs=self.pp_defs, include_dirs=self.include_dirs ) @@ -1452,9 +1456,11 @@ def file_init( A Fortran file object or a string containing the error message """ file_obj = FortranFile(filepath, pp_suffixes) - err_str, _ = file_obj.load_from_disk() - if err_str: - return err_str + # TODO: allow to bubble up the error message + try: + file_obj.load_from_disk() + except ParserError as e: + return str(e) try: # On Windows multiprocess does not propagate global variables in a shell. # Windows uses 'spawn' while Unix uses 'fork' which propagates globals. @@ -1844,6 +1850,10 @@ def update_recursion_limit(limit: int) -> None: sys.setrecursionlimit(limit) +class LSPError(Exception): + """Base class for Language Server Protocol errors""" + + class JSONRPC2Error(Exception): def __init__(self, code, message, data=None): self.code = code diff --git a/fortls/parsers/internal/parser.py b/fortls/parsers/internal/parser.py index 1cab8d11..6912ebb4 100644 --- a/fortls/parsers/internal/parser.py +++ b/fortls/parsers/internal/parser.py @@ -870,41 +870,44 @@ def copy(self) -> FortranFile: copy_obj.set_contents(self.contents_split) return copy_obj - def load_from_disk(self) -> tuple[str | None, bool | None]: + def load_from_disk(self) -> bool: """Read file from disk or update file contents only if they have changed A MD5 hash is used to determine that Returns ------- - tuple[str|None, bool|None] - ``str`` : string containing IO error message else None - ``bool``: boolean indicating if the file has changed + bool + boolean indicating if the file has changed + + Raises + ------ + FileReadDecodeError + If the file could not be read or decoded """ contents: str try: with open(self.path, encoding="utf-8", errors="replace") as f: contents = re.sub(r"\t", r" ", f.read()) - except OSError: - return "Could not read/decode file", None - else: - # Check if files are the same - try: - hash = hashlib.md5( - contents.encode("utf-8"), usedforsecurity=False - ).hexdigest() - # Python <=3.8 does not have the `usedforsecurity` option - except TypeError: - hash = hashlib.md5(contents.encode("utf-8")).hexdigest() - - if hash == self.hash: - return None, False - - self.hash = hash - self.contents_split = contents.splitlines() - self.fixed = detect_fixed_format(self.contents_split) - self.contents_pp = self.contents_split - self.nLines = len(self.contents_split) - return None, True + except OSError as exc: + raise FileReadDecodeError("Could not read/decode file") from exc + # Check if files are the same + try: + hash = hashlib.md5( + contents.encode("utf-8"), usedforsecurity=False + ).hexdigest() + # Python <=3.8 does not have the `usedforsecurity` option + except TypeError: + hash = hashlib.md5(contents.encode("utf-8")).hexdigest() + + if hash == self.hash: + return False + + self.hash = hash + self.contents_split = contents.splitlines() + self.fixed = detect_fixed_format(self.contents_split) + self.contents_pp = self.contents_split + self.nLines = len(self.contents_split) + return True def apply_change(self, change: dict) -> bool: """Apply a change to the file.""" @@ -2261,24 +2264,18 @@ def append_multiline_macro(def_value: str | tuple, line: str): if include_path is not None: try: include_file = FortranFile(include_path) - err_string, _ = include_file.load_from_disk() - if err_string is None: - log.debug("\n!!! Parsing include file '%s'", include_path) - _, _, _, defs_tmp = preprocess_file( - include_file.contents_split, - file_path=include_path, - pp_defs=defs_tmp, - include_dirs=include_dirs, - debug=debug, - ) - log.debug("!!! Completed parsing include file\n") - - else: - log.debug("!!! Failed to parse include file: %s", err_string) - - except: - log.debug("!!! Failed to parse include file: exception") - + include_file.load_from_disk() + log.debug("\n!!! Parsing include file '%s'", include_path) + _, _, _, defs_tmp = preprocess_file( + include_file.contents_split, + file_path=include_path, + pp_defs=defs_tmp, + include_dirs=include_dirs, + debug=debug, + ) + log.debug("!!! Completed parsing include file") + except ParserError as e: + log.debug("!!! Failed to parse include file: %s", str(e)) else: log.debug( "%s !!! Could not locate include file (%d)", line.strip(), i + 1 @@ -2313,3 +2310,11 @@ def append_multiline_macro(def_value: str | tuple, line: str): line = line_new output_file.append(line) return output_file, pp_skips, pp_defines, defs_tmp + + +class ParserError(Exception): + """Parser base class exception""" + + +class FileReadDecodeError(ParserError): + """File could not be read/decoded""" diff --git a/test/test_parser.py b/test/test_parser.py index 2478638b..2a311d3d 100644 --- a/test/test_parser.py +++ b/test/test_parser.py @@ -1,13 +1,13 @@ +import pytest from setup_tests import test_dir -from fortls.parsers.internal.parser import FortranFile +from fortls.parsers.internal.parser import FileReadDecodeError, FortranFile def test_line_continuations(): file_path = test_dir / "parse" / "line_continuations.f90" file = FortranFile(str(file_path)) - err_str, _ = file.load_from_disk() - assert err_str is None + file.load_from_disk() try: file.parse() assert True @@ -19,8 +19,7 @@ def test_line_continuations(): def test_submodule(): file_path = test_dir / "parse" / "submodule.f90" file = FortranFile(str(file_path)) - err_str, _ = file.load_from_disk() - assert err_str is None + file.load_from_disk() try: ast = file.parse() assert True @@ -48,3 +47,9 @@ def test_end_scopes_semicolon(): ast = file.parse() assert err_str is None assert not ast.end_errors + + +def test_load_from_disk_exception(): + file = FortranFile("/path/to/nonexistent/file.f90") + with pytest.raises(FileReadDecodeError): + file.load_from_disk() From 68b15f5501b3d0f1bf70270768f6156f25a75776 Mon Sep 17 00:00:00 2001 From: gnikit Date: Sun, 28 Apr 2024 16:30:38 +0100 Subject: [PATCH 02/13] refactor: use more specific exceptions for not found files --- fortls/langserver.py | 10 +++++++--- fortls/parsers/internal/parser.py | 15 ++++++++------- test/test_parser.py | 4 ++-- 3 files changed, 17 insertions(+), 12 deletions(-) diff --git a/fortls/langserver.py b/fortls/langserver.py index 7fdcf295..d388ce3e 100644 --- a/fortls/langserver.py +++ b/fortls/langserver.py @@ -51,7 +51,11 @@ load_intrinsics, set_lowercase_intrinsics, ) -from fortls.parsers.internal.parser import FortranFile, ParserError, get_line_context +from fortls.parsers.internal.parser import ( + FortranFile, + FortranFileNotFoundError, + get_line_context, +) from fortls.parsers.internal.scope import Scope from fortls.parsers.internal.use import Use from fortls.parsers.internal.utilities import ( @@ -1396,7 +1400,7 @@ def update_workspace_file( file_changed = file_obj.load_from_disk() if not file_changed: return False, None - except ParserError as exc: + except FortranFileNotFoundError as exc: log.error("%s : %s", str(exc), filepath) raise LSPError from exc @@ -1459,7 +1463,7 @@ def file_init( # TODO: allow to bubble up the error message try: file_obj.load_from_disk() - except ParserError as e: + except FortranFileNotFoundError as e: return str(e) try: # On Windows multiprocess does not propagate global variables in a shell. diff --git a/fortls/parsers/internal/parser.py b/fortls/parsers/internal/parser.py index 6912ebb4..25e22b08 100644 --- a/fortls/parsers/internal/parser.py +++ b/fortls/parsers/internal/parser.py @@ -881,15 +881,16 @@ def load_from_disk(self) -> bool: Raises ------ - FileReadDecodeError - If the file could not be read or decoded + FortranFileNotFoundError + If the file could not be found """ contents: str try: + # errors="replace" prevents UnicodeDecodeError being raised with open(self.path, encoding="utf-8", errors="replace") as f: contents = re.sub(r"\t", r" ", f.read()) - except OSError as exc: - raise FileReadDecodeError("Could not read/decode file") from exc + except FileNotFoundError as exc: + raise FortranFileNotFoundError(exc) from exc # Check if files are the same try: hash = hashlib.md5( @@ -2274,7 +2275,7 @@ def append_multiline_macro(def_value: str | tuple, line: str): debug=debug, ) log.debug("!!! Completed parsing include file") - except ParserError as e: + except FortranFileNotFoundError as e: log.debug("!!! Failed to parse include file: %s", str(e)) else: log.debug( @@ -2316,5 +2317,5 @@ class ParserError(Exception): """Parser base class exception""" -class FileReadDecodeError(ParserError): - """File could not be read/decoded""" +class FortranFileNotFoundError(ParserError, FileNotFoundError): + """File not found""" diff --git a/test/test_parser.py b/test/test_parser.py index 2a311d3d..ef40b2f0 100644 --- a/test/test_parser.py +++ b/test/test_parser.py @@ -1,7 +1,7 @@ import pytest from setup_tests import test_dir -from fortls.parsers.internal.parser import FileReadDecodeError, FortranFile +from fortls.parsers.internal.parser import FortranFile, FortranFileNotFoundError def test_line_continuations(): @@ -51,5 +51,5 @@ def test_end_scopes_semicolon(): def test_load_from_disk_exception(): file = FortranFile("/path/to/nonexistent/file.f90") - with pytest.raises(FileReadDecodeError): + with pytest.raises(FortranFileNotFoundError): file.load_from_disk() From 254ac6c90681851a6babcce6d79006c928827e27 Mon Sep 17 00:00:00 2001 From: gnikit Date: Sun, 28 Apr 2024 17:52:46 +0100 Subject: [PATCH 03/13] refactor: remove intermediate steps fom eval_pp_if --- fortls/parsers/internal/parser.py | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/fortls/parsers/internal/parser.py b/fortls/parsers/internal/parser.py index 25e22b08..4b93be2d 100644 --- a/fortls/parsers/internal/parser.py +++ b/fortls/parsers/internal/parser.py @@ -2074,10 +2074,8 @@ def replace_vars(line: str): if defs is None: defs = {} - out_line = replace_defined(text) - out_line = replace_vars(out_line) try: - line_res = eval(replace_ops(out_line)) + line_res = eval(replace_ops(replace_vars(replace_defined(text)))) except: return False else: From e3c2ff340c430a125841cf5217cf28b52d83f3e8 Mon Sep 17 00:00:00 2001 From: gnikit Date: Sun, 28 Apr 2024 18:00:51 +0100 Subject: [PATCH 04/13] refactor: improve error handling in preprocessor IF statement evaluation Now throws fortls exception --- fortls/parsers/internal/parser.py | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/fortls/parsers/internal/parser.py b/fortls/parsers/internal/parser.py index 4b93be2d..0ea9e202 100644 --- a/fortls/parsers/internal/parser.py +++ b/fortls/parsers/internal/parser.py @@ -2075,11 +2075,10 @@ def replace_vars(line: str): if defs is None: defs = {} try: - line_res = eval(replace_ops(replace_vars(replace_defined(text)))) - except: - return False - else: - return line_res + return eval(replace_ops(replace_vars(replace_defined(text)))) + except Exception as exc: + log.error("Error evaluating preprocessor IF statement: %s", exc) + raise ParserError(exc) from exc def expand_func_macro(def_name: str, def_value: tuple[str, str]): def_args, sub = def_value From caf2a6c48d3451965de190dced2adbdec1c243da Mon Sep 17 00:00:00 2001 From: gnikit Date: Sun, 28 Apr 2024 19:03:49 +0100 Subject: [PATCH 05/13] refactor: improve error handling in preprocessor include statement --- fortls/parsers/internal/parser.py | 53 ++++++++++++++----------------- test/test_parser.py | 10 +++++- 2 files changed, 33 insertions(+), 30 deletions(-) diff --git a/fortls/parsers/internal/parser.py b/fortls/parsers/internal/parser.py index 0ea9e202..e0aebdbd 100644 --- a/fortls/parsers/internal/parser.py +++ b/fortls/parsers/internal/parser.py @@ -9,9 +9,9 @@ # Python < 3.8 does not have typing.Literals try: - from typing import Literal + from typing import Iterable, Literal except ImportError: - from typing_extensions import Literal + from typing_extensions import Literal, Iterable from re import Match, Pattern @@ -2097,6 +2097,14 @@ def append_multiline_macro(def_value: str | tuple, line: str): return (def_args, def_value) return def_value + line + def find_file_in_directories(directories: Iterable[str], filename: str) -> str: + for include_dir in directories: + file = os.path.join(include_dir, filename) + if os.path.isfile(file): + return file + msg = f"Could not locate include file: {filename} in {directories}" + raise FortranFileNotFoundError(msg) + if pp_defs is None: pp_defs = {} if include_dirs is None: @@ -2250,34 +2258,21 @@ def append_multiline_macro(def_value: str | tuple, line: str): if (match is not None) and ((len(pp_stack) == 0) or (pp_stack[-1][0] < 0)): log.debug("%s !!! Include statement(%d)", line.strip(), i + 1) include_filename = match.group(1).replace('"', "") - include_path = None - # Intentionally keep this as a list and not a set. There are cases - # where projects play tricks with the include order of their headers - # to get their codes to compile. Using a set would not permit that. - for include_dir in include_dirs: - include_path_tmp = os.path.join(include_dir, include_filename) - if os.path.isfile(include_path_tmp): - include_path = os.path.abspath(include_path_tmp) - break - if include_path is not None: - try: - include_file = FortranFile(include_path) - include_file.load_from_disk() - log.debug("\n!!! Parsing include file '%s'", include_path) - _, _, _, defs_tmp = preprocess_file( - include_file.contents_split, - file_path=include_path, - pp_defs=defs_tmp, - include_dirs=include_dirs, - debug=debug, - ) - log.debug("!!! Completed parsing include file") - except FortranFileNotFoundError as e: - log.debug("!!! Failed to parse include file: %s", str(e)) - else: - log.debug( - "%s !!! Could not locate include file (%d)", line.strip(), i + 1 + try: + include_path = find_file_in_directories(include_dirs, include_filename) + include_file = FortranFile(include_path) + include_file.load_from_disk() + log.debug("\n!!! Parsing include file '%s'", include_path) + _, _, _, defs_tmp = preprocess_file( + include_file.contents_split, + file_path=include_path, + pp_defs=defs_tmp, + include_dirs=include_dirs, + debug=debug, ) + log.debug("!!! Completed parsing include file") + except FortranFileNotFoundError as e: + log.debug("%s !!! %s - Ln:%d", line.strip(), str(e), i + 1) # Substitute (if any) read in preprocessor macros for def_tmp, value in defs_tmp.items(): diff --git a/test/test_parser.py b/test/test_parser.py index ef40b2f0..7c84ebd9 100644 --- a/test/test_parser.py +++ b/test/test_parser.py @@ -1,7 +1,11 @@ import pytest from setup_tests import test_dir -from fortls.parsers.internal.parser import FortranFile, FortranFileNotFoundError +from fortls.parsers.internal.parser import ( + FortranFile, + FortranFileNotFoundError, + preprocess_file, +) def test_line_continuations(): @@ -53,3 +57,7 @@ def test_load_from_disk_exception(): file = FortranFile("/path/to/nonexistent/file.f90") with pytest.raises(FortranFileNotFoundError): file.load_from_disk() + + +def test_preprocess_missing_includes_exception(): + preprocess_file(["#include 'nonexistent_file.f90'"]) From 5a6a322ccd5e665ce7132a1e616ba5d1d9d853e3 Mon Sep 17 00:00:00 2001 From: gnikit Date: Sun, 28 Apr 2024 20:48:58 +0100 Subject: [PATCH 06/13] refactor: drop without error the AST preproc node --- fortls/parsers/internal/parser.py | 6 +++--- test/test_parser.py | 4 ++++ 2 files changed, 7 insertions(+), 3 deletions(-) diff --git a/fortls/parsers/internal/parser.py b/fortls/parsers/internal/parser.py index e0aebdbd..094a15c5 100644 --- a/fortls/parsers/internal/parser.py +++ b/fortls/parsers/internal/parser.py @@ -2076,9 +2076,9 @@ def replace_vars(line: str): defs = {} try: return eval(replace_ops(replace_vars(replace_defined(text)))) - except Exception as exc: - log.error("Error evaluating preprocessor IF statement: %s", exc) - raise ParserError(exc) from exc + # This needs to catch all possible exceptions thrown by eval() + except Exception: + return False def expand_func_macro(def_name: str, def_value: tuple[str, str]): def_args, sub = def_value diff --git a/test/test_parser.py b/test/test_parser.py index 7c84ebd9..302a30cf 100644 --- a/test/test_parser.py +++ b/test/test_parser.py @@ -61,3 +61,7 @@ def test_load_from_disk_exception(): def test_preprocess_missing_includes_exception(): preprocess_file(["#include 'nonexistent_file.f90'"]) + + +def test_preprocess_eval_if_exception(): + preprocess_file(["#if (1=and=1)", 'print*, "1==1"', "#endif"]) From a149662c1f7077121767281bee60fa211d8c0d7a Mon Sep 17 00:00:00 2001 From: gnikit Date: Sun, 28 Apr 2024 20:50:50 +0100 Subject: [PATCH 07/13] chore: fix import order --- fortls/parsers/internal/parser.py | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/fortls/parsers/internal/parser.py b/fortls/parsers/internal/parser.py index 094a15c5..d48a0dac 100644 --- a/fortls/parsers/internal/parser.py +++ b/fortls/parsers/internal/parser.py @@ -11,7 +11,7 @@ try: from typing import Iterable, Literal except ImportError: - from typing_extensions import Literal, Iterable + from typing_extensions import Iterable, Literal from re import Match, Pattern From 26e742b08faeb267f50338cf780b4e03ae498b25 Mon Sep 17 00:00:00 2001 From: gnikit Date: Tue, 7 May 2024 15:21:58 +0100 Subject: [PATCH 08/13] chore: add .venv/ to .gitignore --- .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index b4ef0c0a..08cc07b5 100644 --- a/.gitignore +++ b/.gitignore @@ -2,6 +2,7 @@ .vscode *.egg-info venv/ +.venv/ dist/ build/ docs/_build/ From 3580286f57eca22efb2d47fdc23f53fca618530f Mon Sep 17 00:00:00 2001 From: gnikit Date: Tue, 7 May 2024 17:04:54 +0100 Subject: [PATCH 09/13] refactor(exceptions): move DebugError, ParameterError, and ParserError to separate module --- fortls/debug.py | 1 + fortls/exceptions.py | 17 +++++++++++++++++ fortls/parsers/internal/parser.py | 9 +-------- 3 files changed, 19 insertions(+), 8 deletions(-) create mode 100644 fortls/exceptions.py diff --git a/fortls/debug.py b/fortls/debug.py index 7e7a5e48..3e8dbc07 100644 --- a/fortls/debug.py +++ b/fortls/debug.py @@ -7,6 +7,7 @@ import json5 +from .exceptions import DebugError, ParameterError, ParserError from .helper_functions import only_dirs, resolve_globs from .jsonrpc import JSONRPC2Connection, ReadWriter, path_from_uri from .langserver import LangServer diff --git a/fortls/exceptions.py b/fortls/exceptions.py new file mode 100644 index 00000000..654788b2 --- /dev/null +++ b/fortls/exceptions.py @@ -0,0 +1,17 @@ +from __future__ import annotations + + +class DebugError(Exception): + """Base class for debug CLI.""" + + +class ParameterError(DebugError): + """Exception raised for errors in the parameters.""" + + +class ParserError(Exception): + """Parser base class exception""" + + +class FortranFileNotFoundError(ParserError, FileNotFoundError): + """File not found""" diff --git a/fortls/parsers/internal/parser.py b/fortls/parsers/internal/parser.py index d48a0dac..56c54146 100644 --- a/fortls/parsers/internal/parser.py +++ b/fortls/parsers/internal/parser.py @@ -24,6 +24,7 @@ Severity, log, ) +from fortls.exceptions import FortranFileNotFoundError from fortls.ftypes import ( ClassInfo, FunSig, @@ -2303,11 +2304,3 @@ def find_file_in_directories(directories: Iterable[str], filename: str) -> str: line = line_new output_file.append(line) return output_file, pp_skips, pp_defines, defs_tmp - - -class ParserError(Exception): - """Parser base class exception""" - - -class FortranFileNotFoundError(ParserError, FileNotFoundError): - """File not found""" From 3f4b08560d84a6581e78ae1b94f9b66e90540642 Mon Sep 17 00:00:00 2001 From: gnikit Date: Wed, 15 May 2024 19:57:39 +0100 Subject: [PATCH 10/13] refactor: move DebugError, ParameterError, and ParserError to separate module --- fortls/debug.py | 10 +--------- 1 file changed, 1 insertion(+), 9 deletions(-) diff --git a/fortls/debug.py b/fortls/debug.py index 3e8dbc07..365c21bc 100644 --- a/fortls/debug.py +++ b/fortls/debug.py @@ -11,15 +11,7 @@ from .helper_functions import only_dirs, resolve_globs from .jsonrpc import JSONRPC2Connection, ReadWriter, path_from_uri from .langserver import LangServer -from .parsers.internal.parser import FortranFile, ParserError, preprocess_file - - -class DebugError(Exception): - """Base class for debug CLI.""" - - -class ParameterError(DebugError): - """Exception raised for errors in the parameters.""" +from .parsers.internal.parser import FortranFile, preprocess_file def is_debug_mode(args): From 590c29e735fb41252c3a733f3dfa8b285a8a8ade Mon Sep 17 00:00:00 2001 From: gnikit Date: Wed, 15 May 2024 21:33:33 +0100 Subject: [PATCH 11/13] chore: update tests to use new function signature --- test/test_parser.py | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/test/test_parser.py b/test/test_parser.py index 302a30cf..b6b5f458 100644 --- a/test/test_parser.py +++ b/test/test_parser.py @@ -39,17 +39,15 @@ def test_submodule(): def test_private_visibility_interfaces(): file_path = test_dir / "vis" / "private.f90" file = FortranFile(str(file_path)) - err_str, _ = file.load_from_disk() + file.load_from_disk() file.parse() - assert err_str is None def test_end_scopes_semicolon(): file_path = test_dir / "parse" / "trailing_semicolon.f90" file = FortranFile(str(file_path)) - err_str, _ = file.load_from_disk() + file.load_from_disk() ast = file.parse() - assert err_str is None assert not ast.end_errors From d830498827eb1cdef579f305461461282d6ef3ac Mon Sep 17 00:00:00 2001 From: gnikit Date: Wed, 15 May 2024 21:35:49 +0100 Subject: [PATCH 12/13] chore: modernised parser tests --- test/test_parser.py | 22 ++++++---------------- 1 file changed, 6 insertions(+), 16 deletions(-) diff --git a/test/test_parser.py b/test/test_parser.py index b6b5f458..ad49867c 100644 --- a/test/test_parser.py +++ b/test/test_parser.py @@ -12,28 +12,18 @@ def test_line_continuations(): file_path = test_dir / "parse" / "line_continuations.f90" file = FortranFile(str(file_path)) file.load_from_disk() - try: - file.parse() - assert True - except Exception as e: - print(e) - assert False + file.parse() def test_submodule(): file_path = test_dir / "parse" / "submodule.f90" file = FortranFile(str(file_path)) file.load_from_disk() - try: - ast = file.parse() - assert True - assert ast.scope_list[0].name == "val" - assert ast.scope_list[0].ancestor_name == "p1" - assert ast.scope_list[1].name == "" - assert ast.scope_list[1].ancestor_name == "p2" - except Exception as e: - print(e) - assert False + ast = file.parse() + assert ast.scope_list[0].name == "val" + assert ast.scope_list[0].ancestor_name == "p1" + assert ast.scope_list[1].name == "" + assert ast.scope_list[1].ancestor_name == "p2" def test_private_visibility_interfaces(): From 2c4273d92fa0a163f56b5caf0e9892ea9ea6fcc5 Mon Sep 17 00:00:00 2001 From: gnikit Date: Wed, 15 May 2024 21:43:49 +0100 Subject: [PATCH 13/13] fix: incorrect arguments passed at read_config debug fucntion signature --- fortls/debug.py | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/fortls/debug.py b/fortls/debug.py index 365c21bc..242585be 100644 --- a/fortls/debug.py +++ b/fortls/debug.py @@ -414,7 +414,7 @@ def debug_parser(args): separator() ensure_file_accessible(args.debug_filepath) - pp_suffixes, pp_defs, include_dirs = read_config(args.debug_rootpath) + pp_suffixes, pp_defs, include_dirs = read_config(args.debug_rootpath, args.config) print(f' File = "{args.debug_filepath}"') file_obj = FortranFile(args.debug_filepath, pp_suffixes)