fortls.parsers.internal package

Submodules

fortls.parsers.internal.associate module

class fortls.parsers.internal.associate.Associate(file_ast, line_number, name)

Bases: Block

create_binding_variable(file_ast, line_number, bind_name, link_name)

Create a new variable to be linked upon resolution to the real variable that contains the information of the mapping from the parent scope to the ASSOCIATE block scope.

Parameters:
  • file_ast (fortran_ast) – AST file

  • line_number (int) – Line number

  • bind_name (str) – Name of the ASSOCIATE block variable

  • link_name (str) – Name of the parent scope variable

Returns:

Variable object holding the ASSOCIATE block variable, pending resolution

Return type:

fortran_var

get_desc()
get_type(no_link=False)
class fortls.parsers.internal.associate.AssociateMap(var, bind_name, link_name)

Bases: object

bind_name: str
var: Variable

fortls.parsers.internal.ast module

class fortls.parsers.internal.ast.FortranAST(file_obj=None)

Bases: object

add_doc(doc_string, forward=False)
add_error(msg, sev, ln, sch, ech=None)

Add a Diagnostic error, encountered during parsing, for a range in the document.

Parameters:
  • msg (str) – Error message

  • sev (int) – Severity, Error, Warning, Notification

  • ln (int) – Line number

  • sch (int) – Start character

  • ech (int) – End character

add_include(path, line_number)
add_int_member(key)
add_private(name)
add_public(name)
add_scope(new_scope, END_SCOPE_REGEX, exportable=True, req_container=False)
add_use(use_mod)
add_variable(new_var)
check_file(obj_tree)
close_file(line_number)
create_none_scope()

Create empty scope to hold non-module contained items

end_ppif(line_number)
end_scope(line_number, check=True)
get_enc_scope_name()

Get current enclosing scope name

get_inner_scope(line_number)
get_object(FQSN)
get_scopes(line_number=None)

Get a list of all the scopes present in the line number provided.

Parameters:

line_number (int, optional) – Document line number, if None return all document scopes, by default None

Returns:

A list of scopes

Return type:

Variable,Type,Function,Subroutine,Module,Program,Interface,BlockData

resolve_includes(workspace, path=None)
start_ppif(line_number)

fortls.parsers.internal.base module

class fortls.parsers.internal.base.FortranObj

Bases: object

add_doc(doc_str)
check_definition(obj_tree, known_types=None, interface=False)
check_valid_parent()
end(line_number)
get_actions(sline, eline)
get_ancestors()
get_children(public_only=False)
get_desc()
get_diagnostics()
get_documentation()
get_hover(long=False, drop_arg=-1)
Return type:

tuple[str | None, str | None]

get_hover_md(long=False, drop_arg=-1)
Return type:

str

get_implicit()
get_interface(name_replace=None, drop_arg=-1, change_strings=None)
get_signature(drop_arg=-1)
get_snippet(name_replace=None, drop_arg=-1)
get_type(no_link=False)
get_type_obj(obj_tree)
is_abstract()
is_callable()
is_external_int()
is_mod_scope()
is_optional()
req_named_end()
require_inherit()
resolve_inherit(obj_tree, inherit_version)
set_default_vis(new_vis)
set_parent(parent_obj)
set_visibility(new_vis)
update_fqsn(enc_scope=None)

fortls.parsers.internal.block module

class fortls.parsers.internal.block.Block(file_ast, line_number, name)

Bases: Scope

get_children(public_only=False)
get_desc()
get_type(no_link=False)
req_named_end()

fortls.parsers.internal.diagnostics module

class fortls.parsers.internal.diagnostics.Diagnostic(sline, message, severity=1, find_word=None)

Bases: object

build(file_obj)

fortls.parsers.internal.do module

class fortls.parsers.internal.do.Do(file_ast, line_number, name)

Bases: Block

get_desc()
get_type(no_link=False)

fortls.parsers.internal.enum module

class fortls.parsers.internal.enum.Enum(file_ast, line_number, name)

Bases: Block

get_desc()
get_type(no_link=False)

fortls.parsers.internal.function module

class fortls.parsers.internal.function.Function(file_ast, line_number, name, args='', mod_flag=False, keywords=None, keyword_info=None, result_type=None, result_name=None)

Bases: Subroutine

copy_interface(copy_source)
get_desc()
get_hover(long=False, drop_arg=-1)

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

  • drop_arg (int, optional) – Ignore argument at position drop_arg in the argument list, by default -1

Returns:

String representative of the hover message and the long flag used

Return type:

tuple[str, bool]

get_interface(name_replace=None, drop_arg=-1, change_strings=None)
get_type(no_link=False)
is_callable()

fortls.parsers.internal.if_block module

class fortls.parsers.internal.if_block.If(file_ast, line_number, name)

Bases: Block

get_desc()
get_type(no_link=False)

fortls.parsers.internal.imports module

class fortls.parsers.internal.imports.Import(name, import_type=-1, only_list=None, rename_map=None, line_number=0)

Bases: Use

AST node for IMPORT statement

property scope

Parent scope of IMPORT statement i.e. parent of the interface

class fortls.parsers.internal.imports.ImportTypes

Bases: object

ALL = 1
DEFAULT = -1
NONE = 0
ONLY = 2

fortls.parsers.internal.include module

class fortls.parsers.internal.include.Include(file_ast, line_number, name, keywords=None)

Bases: Scope

get_desc()

fortls.parsers.internal.interface module

class fortls.parsers.internal.interface.Interface(file_ast, line_number, name, abstract=False)

Bases: Scope

get_desc()
get_type(no_link=False)
is_abstract()
is_callable()
is_external_int()

fortls.parsers.internal.intrinsics module

class fortls.parsers.internal.intrinsics.Intrinsic(name, type, doc_str=None, args='', parent=None)

Bases: FortranObj

get_desc()
get_hover(long=False)
get_hover_md(long=False)
get_signature()
get_snippet(name_replace=None, drop_arg=-1)
get_type()
is_callable()
fortls.parsers.internal.intrinsics.get_intrinsic_keywords(statements, keywords, context=-1)
fortls.parsers.internal.intrinsics.intrinsics_case(name, args)
fortls.parsers.internal.intrinsics.load_intrinsics()
fortls.parsers.internal.intrinsics.set_lowercase_intrinsics()
fortls.parsers.internal.intrinsics.update_m_intrinsics()

fortls.parsers.internal.method module

class fortls.parsers.internal.method.Method(file_ast, line_number, name, var_desc, keywords, keyword_info, proc_ptr='', link_obj=None)

Bases: Variable

check_definition(obj_tree, known_types=None, interface=False)
get_documentation()
get_hover(long=False, drop_arg=-1)
get_interface(name_replace=None, drop_arg=-1, change_strings=None)
get_signature(drop_arg=-1)
get_snippet(name_replace=None, drop_arg=-1)
get_type(no_link=False)
is_callable()
set_parent(parent_obj)

fortls.parsers.internal.module module

class fortls.parsers.internal.module.Module(file_ast, line_number, name, keywords=None)

Bases: Scope

check_valid_parent()
Return type:

bool

get_desc()
get_hover(long=False, drop_arg=-1)
get_type(no_link=False)

fortls.parsers.internal.parser module

class fortls.parsers.internal.parser.FortranFile(path=None, pp_suffixes=None)

Bases: object

apply_change(change)

Apply a change to the file.

Return type:

bool

check_file(obj_tree, max_line_length=-1, max_comment_line_length=-1)
copy()

Copy content to new file object (does not copy objects)

Return type:

FortranFile

find_word_in_code_line(line_no, word, forward=True, backward=False, pp_content=False)
get_code_line(line_no, forward=True, backward=True, pp_content=False, strip_comment=False)

Get full code line from file including any adjacent continuations

get_comment_regexs()
get_docstring(ln, line, match, docs)

Extract entire documentation strings from the current file position

Parameters:
  • ln (int) – Line number

  • line (str) – Document line, not necessarily produced by get_line()

  • match (Match[str]) – Regular expression DOC match

  • docs (list[str]) – Docstrings that are pending processing e.g. single line docstrings

Returns:

The new line number at the end of the docstring, the docstring and a boolean flag indicating whether the docstring precedes the AST node (Doxygen style) or succeeds it (traditional FORD style)

Return type:

tuple[int, list[str], bool]

get_fortran_definition(line)
get_line(line_no, pp_content=False)

Get single line from file

Return type:

str

get_single_line_docstring(line)

Get a docstring of a single line. This is the same for both Legacy and Modern Fortran

Parameters:

line (str) – Line of code

Returns:

A list containing the docstring. List will be empty if there is no match or the match is an empty string itself

Return type:

list[str]

load_from_disk()

Read file from disk or update file contents only if they have changed A MD5 hash is used to determine that

Returns:

str : string containing IO error message else None bool: boolean indicating if the file has changed

Return type:

tuple[str|None, bool|None]

parse(debug=False, pp_defs=None, include_dirs=None)

Parse Fortran file contents of a fortran_file object and build an Abstract Syntax Tree (AST)

Parameters:
  • debug (bool, optional) – Set to true to enable debugging, by default False

  • pp_defs (dict, optional) – Preprocessor definitions and their values, by default None

  • include_dirs (set, optional) – Preprocessor include directories, by default None

Returns:

An Abstract Syntax Tree

Return type:

fortran_ast

parse_contains(line, ln, file_ast)

Parse contain statements

Parameters:
  • line (str) – Document line

  • ln (int) – Line number

  • file_ast (fortran_ast) – AST object

Returns:

True if a contains is present, False otherwise

Return type:

bool

parse_do_fixed_format(line, ln, file_ast, line_label, block_id_stack)
parse_docs(line, ln, file_ast, docs)

Parse documentation stings of style Doxygen or FORD. Multiline docstrings are detected if the first comment starts with !> docstring continuations are detected with either !>, !< or !!

Parameters:
  • line (str) – Document line

  • ln (int) – Line number

  • file_ast (fortran_ast) – AST object

  • docs (list[str]) – Docstrings that are pending processing e.g. single line docstrings

parse_end_scope_word(line, ln, file_ast, match)

Parses END keyword marking the end of scopes

Parameters:
  • line (str) – Document line

  • ln (int) – Line number

  • file_ast (fortran_ast) – AST object

  • match (re.Match) – END word regular expression match

Returns:

True if a AST scope is closed, False otherwise

Return type:

bool

parse_imp_char(line)

Parse the implicit character length from a variable e.g. var_name*10 or var_name*(10), var_name*(size(val, 1))

Parameters:

line (str) – line containing potential variable

Returns:

truncated line, character length

Return type:

tuple[str, str]

parse_imp_dim(line)

Parse the implicit dimension of an array e.g. var(3,4), var_name(size(val,1)*10)

Parameters:

line (str) – line containing variable name

Returns:

truncated line, dimension string

Return type:

tuple[str, str]

parse_implicit(line, ln, file_ast)

Parse implicit statements from a line

Parameters:
  • line (str) – Document line

  • ln (int) – Line number

  • file_ast (fortran_ast) – AST object

Returns:

True if an IMPLICIT statements present, False otherwise

Return type:

bool

preprocess(pp_defs=None, include_dirs=None, debug=False)
set_contents(contents_split, detect_format=True)

Set file contents

strip_comment(line)

Strip comment from line

Return type:

str

fortls.parsers.internal.parser.find_external(file_ast, desc_string, name, new_var)

Find a procedure, function, subroutine, etc. that has been defined as EXTERNAL. EXTERNAL``s are parsed as ``fortran_var, since there is no way of knowing if real, external :: val is a function or a subroutine.

This method exists solely for EXTERNAL s that are defined across multiple lines e.g.

EXTERNAL VAR
REAL VAR

or

REAL VAR
EXTERNAL VAR
Parameters:
  • file_ast (fortran_ast) – AST

  • desc_string (str) – Variable type e.g. REAL, INTEGER, EXTERNAL

  • name (str) – Variable name

  • new_var (fortran_var) – The line variable that we are attempting to match with an EXTERNAL definition

Returns:

True if the variable is EXTERNAL and we manage to link it to the rest of its components, else False

Return type:

bool

fortls.parsers.internal.parser.find_external_attr(file_ast, name, new_var)

Check if this NORMAL Fortran variable is in the external_objs with only EXTERNAL as its type. Used to detect seperated EXTERNAL declarations.

Parameters:
  • file_ast (fortran_ast) – AST file

  • name (str) – Variable name, stripped

  • new_var (fortran_var) – Fortran variable to check against

Returns:

True if only a single EXTERNAL definition is encountered False for everything else, which will cause a diagnostic error to be raised

Return type:

bool

fortls.parsers.internal.parser.find_external_type(file_ast, desc_string, name)

Encountered a variable with EXTERNAL as its type Try and find an already defined variable with a NORMAL Fortran Type

Return type:

bool

fortls.parsers.internal.parser.get_line_context(line)

Get context of ending position in line (for completion)

Parameters:

line (str) – file line

Returns:

Possible string values: var_key, pro_line, var_only, mod_mems, mod_only, pro_link, skip, import, vis, call, type_only, int_only, first, default

Return type:

tuple[str, None]

fortls.parsers.internal.parser.get_procedure_modifiers(line, regex)

Attempt to match procedure modifiers for FUNCTIONS and SUBROUTINES

Parameters:
  • line (str) – document line

  • regex (Pattern) – regular expression to use e.g. Function or Subroutine sig

Returns:

procedure name, arguments, trailing line

Return type:

tuple[str, str, str] | tuple[None, None, None]

fortls.parsers.internal.parser.parse_var_keywords(test_str)

Parse Fortran variable declaration keywords

fortls.parsers.internal.parser.preprocess_file(contents_split, file_path=None, pp_defs=None, include_dirs=None, debug=False)
fortls.parsers.internal.parser.read_associate_def(line)
fortls.parsers.internal.parser.read_block_def(line)

Attempt to read BLOCK definition line

fortls.parsers.internal.parser.read_do_def(line)

Attempt to read a DO loop

Returns:

Tuple with “do” and a fixed format tag if present

Return type:

tuple[Literal[“do”], str] | None

fortls.parsers.internal.parser.read_enum_def(line)

Attempt to read ENUM definition line

fortls.parsers.internal.parser.read_fun_def(line, result=None, mod_flag=False)

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 (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:

a named tuple

Return type:

tuple[Literal[“fun”], FUN_sig] | None

fortls.parsers.internal.parser.read_generic_def(line)

Attempt to read generic procedure definition line

fortls.parsers.internal.parser.read_if_def(line)

Attempt to read an IF conditional

Returns:

A Literal “if” and None tuple

Return type:

tuple[Literal[“if”], None] | None

fortls.parsers.internal.parser.read_imp_stmt(line)

Attempt to read IMPORT statement

fortls.parsers.internal.parser.read_inc_stmt(line)

Attempt to read INCLUDE statement

fortls.parsers.internal.parser.read_int_def(line)

Attempt to read INTERFACE definition line

fortls.parsers.internal.parser.read_mod_def(line)

Attempt to read MODULE and MODULE PROCEDURE, MODULE FUNCTION definition lines

fortls.parsers.internal.parser.read_prog_def(line)

Attempt to read PROGRAM definition line

fortls.parsers.internal.parser.read_select_def(line)

Attempt to read SELECT definition line

fortls.parsers.internal.parser.read_sub_def(line, mod_flag=False)

Attempt to read a SUBROUTINE definition line

Parameters:
  • line (str) – document line

  • mod_flag (bool, optional) – flag for module and module procedure parsing, by default False

Returns:

a SUB_info dataclass object

Return type:

tuple[Literal[“sub”], SUB_info] | None

fortls.parsers.internal.parser.read_submod_def(line)

Attempt to read SUBMODULE definition line

fortls.parsers.internal.parser.read_type_def(line)

Attempt to read TYPE definition line

fortls.parsers.internal.parser.read_use_stmt(line)

Attempt to read USE statement

fortls.parsers.internal.parser.read_var_def(line, var_type=None, fun_only=False)

Attempt to read variable definition line

fortls.parsers.internal.parser.read_vis_stmnt(line)

Attempt to read PUBLIC/PRIVATE statement

fortls.parsers.internal.parser.read_where_def(line)

Attempt to read a WHERE block

Returns:

Tuple with “where” and a boolean indicating if labelled on unlabelled

Return type:

tuple[Literal[“where”], bool] | None

fortls.parsers.internal.program module

class fortls.parsers.internal.program.Program(file_ast, line_number, name, keywords=None)

Bases: Module

get_desc()

fortls.parsers.internal.scope module

class fortls.parsers.internal.scope.Scope(file_ast, line_number, name, keywords=None)

Bases: FortranObj

add_child(child)
add_member(member)
add_subroutine(interface_string, no_contains=False)
add_use(use_mod)
check_definitions(obj_tree)

Check for definition errors in scope

check_use(obj_tree)
copy_from(copy_source)
get_children(public_only=False)
mark_contains(line_number)
set_implicit(implicit_flag, line_number)
set_inherit(inherit_type)
set_parent(parent_obj)
update_fqsn(enc_scope=None)

fortls.parsers.internal.select module

class fortls.parsers.internal.select.Select(file_ast, line_number, name, select_info)

Bases: Block

create_binding_variable(file_ast, line_number, var_desc, case_type)
get_desc()
get_type(no_link=False)
is_type_binding()
is_type_region()

fortls.parsers.internal.submodule module

class fortls.parsers.internal.submodule.Submodule(file_ast, line_number, name, ancestor_name='')

Bases: Module

get_ancestors()
get_desc()
get_type(no_link=False)
require_inherit()
resolve_inherit(obj_tree, inherit_version)

fortls.parsers.internal.subroutine module

class fortls.parsers.internal.subroutine.Subroutine(file_ast, line_number, name, args='', mod_flag=False, keywords=None)

Bases: Scope

check_valid_parent()
copy_interface(copy_source)
get_children(public_only=False)
get_desc()
get_diagnostics()
get_docs_full(hover_array, long=False, drop_arg=-1)

Construct the full documentation with the code signature and the documentation string + the documentation of any arguments.

Parameters:
  • hover_array (list[str]) – The list of strings to append the documentation to.

  • long (bool, optional) – Whether or not to fetch the docs of the arguments, by default False

  • drop_arg (int, optional) – Whether or not to drop certain arguments from the results, by default -1

Returns:

Tuple containing the Fortran signature that should be in code blocks and the documentation string that should be in normal Markdown.

Return type:

tuple[list[str], list[str]]

get_hover(long=False, drop_arg=-1)
get_hover_md(long=False, drop_arg=-1)
get_interface(name_replace=None, drop_arg=-1, change_strings=None)
get_interface_array(keywords, signature, drop_arg=-1, change_strings=None)
get_signature(drop_arg=-1)
get_snippet(name_replace=None, drop_arg=-1)
get_type(no_link=False)
is_callable()
is_mod_scope()

fortls.parsers.internal.type module

class fortls.parsers.internal.type.Type(file_ast, line_number, name, keywords)

Bases: Scope

check_valid_parent()
get_actions(sline, eline)
get_children(public_only=False)
get_desc()
get_diagnostics()
get_hover(long=False, drop_arg=-1)
get_overridden(field_name)
get_type(no_link=False)
require_inherit()
resolve_inherit(obj_tree, inherit_version)

fortls.parsers.internal.use module

class fortls.parsers.internal.use.Use(mod_name, only_list=None, rename_map=None, line_number=0)

Bases: object

AST node for USE statement

property line_number
rename(only_list=None)

Rename ONLY:, statements

fortls.parsers.internal.utilities module

fortls.parsers.internal.utilities.climb_type_tree(var_stack, curr_scope, obj_tree)

Walk up user-defined type sequence to determine final field type

fortls.parsers.internal.utilities.find_in_scope(scope, var_name, obj_tree, interface=False, local_only=False, var_line_number=None)
fortls.parsers.internal.utilities.find_in_workspace(obj_tree, query, filter_public=False, exact_match=False)
fortls.parsers.internal.utilities.get_use_tree(scope, use_dict, obj_tree, only_list=None, rename_map=None, curr_path=None)

fortls.parsers.internal.variable module

class fortls.parsers.internal.variable.Variable(file_ast, line_number, name, var_desc, keywords, keyword_info=None, kind=None, link_obj=None)

Bases: FortranObj

check_definition(obj_tree, known_types=None, interface=False)
get_desc(no_link=False)
get_hover(long=False, drop_arg=-1)
get_hover_md(long=False, drop_arg=-1)
get_keywords()
get_snippet(name_replace=None, drop_arg=-1)
get_type(no_link=False)
get_type_obj(obj_tree)
is_callable()
is_optional()
is_parameter()
set_dim(dim_str)
set_external_attr()
set_parameter_val(val)
update_fqsn(enc_scope=None)

fortls.parsers.internal.where module

class fortls.parsers.internal.where.Where(file_ast, line_number, name)

Bases: Block

get_desc()
get_type(no_link=False)

Module contents