fortls package#

Submodules#

fortls.constants module#

fortls.constants.FORTRAN_LITERAL = '0^=__LITERAL_INTERNAL_DUMMY_VAR_'#

A string used to mark literals e.g. 10, 3.14, “words”, etc. The description name chosen is non-ambiguous and cannot naturally occur in Fortran (with/out C preproc) code It is invalid syntax to define a type starting with numerics it cannot also be a comment that requires !, c, d and ^= (xor_eq) operator is invalid in Fortran C++ preproc

class fortls.constants.Severity#

Bases: object

error = 1#
info = 3#
warn = 2#

fortls.ftypes module#

class fortls.ftypes.ClassInfo(name, parent, keywords)#

Bases: object

Holds information about a Fortran CLASS

keywords: list[str]#

Keywords associated with the class

name: str#

Class name

parent: str#

Parent object of class e.g. TYPE, EXTENDS(scaled_vector) :: a

class fortls.ftypes.FunSig(name, args, keywords=<factory>, mod_flag=False, result=<factory>)#

Bases: SubInfo

Holds information about a Fortran FUNCTION

result: ResultSig#

Function’s result with default result.name = name

class fortls.ftypes.GenProcDefInfo(bound_name, pro_links, vis_flag)#

Bases: object

Holds information about a GENERIC PROCEDURE DEFINITION

bound_name: str#

Procedure name

Procedure links

vis_flag: int#

Visibility flag, public or private

class fortls.ftypes.IncludeInfo(line_number, path, file, scope_objs)#

Bases: object

Holds information about a Fortran INCLUDE statement

file: None#
line_number: int#

Line number of include

path: str#

File path to include

scope_objs: list[str]#

A list of available scopes

class fortls.ftypes.InterInfo(name, abstract)#

Bases: object

Holds information about a Fortran INTERFACE

abstract: bool#

Whether or not the interface is abstract

name: str#

Interface name

class fortls.ftypes.Range(start, end)#

Bases: tuple

A single line range tuple

end: int#

Alias for field number 1

start: int#

Alias for field number 0

class fortls.ftypes.ResultSig(name=None, type=None, kind=None, keywords=<factory>)#

Bases: object

Holds information about the RESULT section of a Fortran FUNCTION

keywords: list[str]#

Keywords associated with the result variable, can append without init

kind: str | None = None#

Variable kind of result

name: str | None = None#

Variable name of result

type: str | None = None#

Variable type of result

class fortls.ftypes.SelectInfo(type, binding, desc)#

Bases: object

Holds information about a SELECT construct

binding: str#

Variable/Object being selected upon

desc: str#

Description of select e.g. “TYPE”, “CLASS”, None

type: int#

Type of SELECT e.g. normal, select type, select kind, select rank

class fortls.ftypes.SmodInfo(name, parent)#

Bases: object

Holds information about Fortran SUBMODULES

name: str#

Submodule name

parent: str#

Submodule i.e. module, parent

class fortls.ftypes.SubInfo(name, args, keywords=<factory>, mod_flag=False)#

Bases: object

Holds information about a Fortran SUBROUTINE

args: str#

Argument list

keywords: list[str]#

Keywords associated with procedure

mod_flag: bool = False#

Whether or not this is a MODULE PROCEDURE

name: str#

Procedure name

class fortls.ftypes.UseInfo(mod_name, only_list, rename_map)#

Bases: object

Holds information about a Fortran USE statement

mod_name: str#

Module name

only_list: set[str]#

List of procedures, variables, interfaces, etc. imported via only

rename_map: dict[str, str]#

A dictionary holding the new names after a rename operation

class fortls.ftypes.VarInfo(var_type, keywords, var_names, var_kind=None)#

Bases: object

Holds information about a Fortran VARIABLE

keywords: list[str]#

Keywords associated with variable

var_kind: str | None = None#

Kind of variable e.g. INTEGER*4 etc.

var_names: list[str]#

Variable names

var_type: str#

Type of variable e.g. INTEGER, REAL, etc.

class fortls.ftypes.VisInfo(type, obj_names)#

Bases: object

Holds information about the VISIBILITY of a module’s contents

obj_names: list[str]#

Module variables, procedures, etc. with that visibility

type: int#

PRIVATE TODO: convert to boolean

Type:

Visibility type 0

Type:

PUBLIC 1

fortls.helper_functions module#

fortls.helper_functions.detect_fixed_format(file_lines)#

Detect fixed/free format by looking for characters in label columns and variable declarations before column 6. Treat intersection format files as free format.

Parameters:

file_lines (list[str]) – List of consecutive file lines

Returns:

True if file_lines are of Fixed Fortran style

Return type:

bool

Examples

>>> detect_fixed_format([' free format'])
False
>>> detect_fixed_format([' INTEGER, PARAMETER :: N = 10'])
False
>>> detect_fixed_format(['C Fixed format'])
True

Lines wih ampersands are not fixed format >>> detect_fixed_format([‘trailing line & ! comment’]) False

fortls.helper_functions.expand_name(line, char_pos)#

Get full word containing given cursor position

Parameters:
  • line (str) – Text line

  • char_pos (int) – Column position along the line

Returns:

Word regex match for the input column

Return type:

str

fortls.helper_functions.find_paren_match(string)#

Find matching closing parenthesis from an already open parenthesis scope by forward search of the string, returns -1 if no match is found

Parameters:

string (str) – Input string

Returns:

The index of the matching ) character in the string

Return type:

int

Examples

>>> find_paren_match('a, b)')
4

Multiple parenthesis that are closed

>>> find_paren_match('a, (b, c), d)')
12

If the outermost parenthesis is not closed function returns -1

>>> find_paren_match('a, (b, (c, d)')
-1
fortls.helper_functions.find_word_in_line(line, word)#

Find Fortran word in line

Parameters:
  • line (str) – Text line

  • word (str) – word to find in line

Returns:

start and end positions (indices) of the word if not found it returns -1, len(word) -1

Return type:

Range

fortls.helper_functions.fortran_md(code, docs)#

Convert Fortran code to markdown

Parameters:
  • code (str) – Fortran code

  • docs (str | None) – Documentation string

Returns:

Markdown string

Return type:

str

fortls.helper_functions.get_keywords(keywords, keyword_info={})#
fortls.helper_functions.get_line_prefix(pre_lines, curr_line, col, qs=True)#

Get code line prefix from current line and preceding continuation lines

Parameters:
  • pre_lines (list) – for multiline cases get all the previous, relevant lines

  • curr_line (str) – the current line

  • col (int) – column index of the current line

  • qs (bool, optional) – strip quotes i.e. string literals from curr_line and pre_lines. Need this disable when hovering over string literals, by default True

Returns:

part of the line including any relevant line continuations before col

Return type:

str

Examples

>>> get_line_prefix([''], '#pragma once', 0) is None
True
fortls.helper_functions.get_paren_level(line)#

Get sub-string corresponding to a single parenthesis level, via backward search up through the line.

Parameters:

line (str) – Document line

Returns:

Arguments as a string and a list of Ranges for the arguments against line

Return type:

tuple[str, list[Range]]

Examples

>>> get_paren_level('CALL sub1(arg1,arg2')
('arg1,arg2', [Range(start=10, end=19)])

If the range is interrupted by parenthesis, another Range variable is used to mark the start and end of the argument

>>> get_paren_level('CALL sub1(arg1(i),arg2')
('arg1,arg2', [Range(start=10, end=14), Range(start=17, end=22)])
>>> get_paren_level('')
('', [Range(start=0, end=0)])
fortls.helper_functions.get_paren_substring(string)#

Get the contents enclosed by the first pair of parenthesis

Parameters:

string (str) – A string

Returns:

The part of the string enclosed in parenthesis e.g. or None

Return type:

str | None

Examples

>>> get_paren_substring('some line(a, b, (c, d))')
'a, b, (c, d)'

If the line has incomplete parenthesis however, None is returned >>> get_paren_substring(‘some line(a, b’) is None True

fortls.helper_functions.get_var_stack(line)#

Get user-defined type field sequence terminating the given line

Parameters:

line (str) – Document line

Returns:

list of objects split by %

Return type:

list[str]

Examples

>>> get_var_stack('myvar%foo%bar')
['myvar', 'foo', 'bar']
>>> get_var_stack('myarray(i)%foo%bar')
['myarray', 'foo', 'bar']
>>> get_var_stack('myarray( i ) % foo   % bar')
['myarray', 'foo', 'bar']

In this case it will operate at the end of the string i.e. 'this%foo'

>>> get_var_stack('CALL self%method(this%foo')
['this', 'foo']
>>> get_var_stack('')
['']
fortls.helper_functions.map_keywords(keywords)#
fortls.helper_functions.only_dirs(paths)#

From a list of strings returns only paths that are directories

Parameters:

paths (list[str]) – A list containing the files and directories

Returns:

A list containing only valid directories

Return type:

list[str]

Raises:

FileNotFoundError – A list containing all the non existing directories

Examples

>>> only_dirs(['./test/', './test/test_source/', './test/test_source/test.f90'])
['./test/', './test/test_source/']
>>> only_dirs(['/fake/dir/a', '/fake/dir/b', '/fake/dir/c'])
Traceback (most recent call last):
FileNotFoundError: /fake/dir/a
/fake/dir/b
/fake/dir/c
fortls.helper_functions.parenthetic_contents(string)#

Generate parenthesized contents in string as pairs (contents, start-position, level).

Examples

>>> list(parenthetic_contents('character*(10*size(val(1), 2)) :: name'))
[('1', 22, 2), ('val(1), 2', 18, 1), ('10*size(val(1), 2)', 10, 0)]
fortls.helper_functions.resolve_globs(glob_path, root_path=None)#

Resolve paths (absolute and relative) and glob patterns while nonexistent paths are ignored

Parameters:
  • glob_path (str) – Path containing the glob pattern follows fnmatch glob pattern, can include relative paths, etc. see fnmatch: https://docs.python.org/3/library/fnmatch.html#module-fnmatch

  • root_path (str, optional) – root path to start glob search. If left empty the root_path will be extracted from the glob_path, by default None

Returns:

Expanded glob patterns with absolute paths. Absolute paths are used to resolve any potential ambiguity

Return type:

list[str]

Examples

Relative to a root path >>> import os, pathlib >>> resolve_globs(‘test’, os.getcwd()) == [str(pathlib.Path(os.getcwd()) / ‘test’)] True

Absolute path resolution >>> resolve_globs(‘test’) == [str(pathlib.Path(os.getcwd()) / ‘test’)] True

fortls.helper_functions.separate_def_list(test_str)#

Separate definition lists, skipping parenthesis and bracket groups

Parameters:

test_str (str) – Text string

Returns:

[description]

Return type:

list[str] | None

Examples

>>> separate_def_list('var1, var2, var3')
['var1', 'var2', 'var3']
>>> separate_def_list('var, init_var(3) = [1,2,3], array(3,3)')
['var', 'init_var(3) = [1,2,3]', 'array(3,3)']
fortls.helper_functions.set_keyword_ordering(sorted)#
fortls.helper_functions.strip_line_label(line)#

Strip leading numeric line label

Parameters:

line (str) – Text line

Returns:

Output string, Line label returns None if no line label present

Return type:

tuple[str, str | None]

fortls.helper_functions.strip_strings(in_line, maintain_len=False)#

Strips string literals from code line

Parameters:
  • in_line (str) – Text string

  • maintain_len (bool, optional) – Maintain the len(in_line) in the output string, by default False

Returns:

Stripped string

Return type:

str

fortls.interface module#

class fortls.interface.SetAction(option_strings, dest, nargs=None, const=None, default=None, type=None, choices=None, required=False, help=None, metavar=None)#

Bases: Action

fortls.interface.cli(name='fortls')#

Parses the command line arguments to the Language Server

Returns:

command line arguments

Return type:

argparse.ArgumentParser

fortls.intrinsics module#

class fortls.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.intrinsics.get_intrinsic_keywords(statements, keywords, context=-1)#
fortls.intrinsics.intrinsics_case(name, args)#
fortls.intrinsics.load_intrinsics()#
fortls.intrinsics.set_lowercase_intrinsics()#
fortls.intrinsics.update_m_intrinsics()#

fortls.json_templates module#

fortls.json_templates.change_json(new_text, sln, sch, eln=None, ech=None)#
fortls.json_templates.diagnostic_json(sln, sch, eln, ech, msg, sev)#
fortls.json_templates.location_json(uri, sln, sch, eln=None, ech=None)#
fortls.json_templates.range_json(sln, sch, eln=None, ech=None)#
fortls.json_templates.symbol_json(name, kind, uri, sln, sch, eln=None, ech=None, container_name=None)#
fortls.json_templates.uri_json(uri, sln, sch, eln=None, ech=None)#

fortls.jsonrpc module#

class fortls.jsonrpc.JSONRPC2Connection(conn=None)#

Bases: object

read_message(want=None)#

Read a JSON RPC message sent over the current connection. If id is None, the next available message is returned.

send_notification(method, params)#
send_request(method, params)#
send_request_batch(requests)#

Pipelines requests and returns responses.

The responses is a generator where the nth response corresponds with the nth request. Users must read the generator until the end, otherwise you will leak a thread.

write_error(rid, code, message, data=None)#
write_response(rid, result)#
exception fortls.jsonrpc.JSONRPC2ProtocolError#

Bases: Exception

class fortls.jsonrpc.ReadWriter(reader, writer)#

Bases: object

read(*args)#
readline(*args)#
write(out)#
class fortls.jsonrpc.TCPReadWriter(reader, writer)#

Bases: ReadWriter

read(*args)#
readline(*args)#
write(out)#
fortls.jsonrpc.deque_find_and_pop(d, f)#
fortls.jsonrpc.path_from_uri(uri)#
Return type:

str

fortls.jsonrpc.path_to_uri(path)#
Return type:

str

fortls.jsonrpc.read_rpc_messages(content)#
fortls.jsonrpc.write_rpc_notification(method, params)#
fortls.jsonrpc.write_rpc_request(rid, method, params)#

fortls.langserver module#

exception fortls.langserver.JSONRPC2Error(code, message, data=None)#

Bases: Exception

class fortls.langserver.LangServer(conn, settings)#

Bases: object

static file_init(filepath, pp_defs, pp_suffixes, include_dirs, sort)#

Initialise a Fortran file

Parameters:
  • filepath (str) – Path to file

  • pp_defs (dict) – Preprocessor definitions

  • pp_suffixes (list[str]) – Preprocessor file extension, additional to default

  • include_dirs (set[str]) – Preprocessor only include directories, not used by normal parser

  • sort (bool) – Whether or not keywords should be sorted

Returns:

A Fortran file object or a string containing the error message

Return type:

fortran_file | str

get_all_references(def_obj, type_mem, file_obj=None)#
get_definition(def_file, def_line, def_char, hover_req=False)#

Return the Fortran object for the definition that matches the Fortran file, line number, column number

Parameters:
  • def_file (fortran_file) – File to query

  • def_line (int) – Line position in the file

  • def_char (int) – Column position in the file

  • hover_req (bool, optional) – Flag to enable if calling from a hover request, by default False

Returns:

Fortran object

Return type:

fortran_var | fortran_include | None

get_diagnostics(uri)#
handle(request)#
post_message(msg, severity=1, exc_info=False)#
run()#
send_diagnostics(uri)#
serve_autocomplete(request)#
serve_codeActions(request)#
serve_default(request)#

Raise an error in the Language Server

Parameters:

request (dict) – client dictionary with requests

Raises:

JSONRPC2Error – error with code -32601

serve_definition(request)#
serve_document_symbols(request)#
serve_exit(request)#
Return type:

None

serve_hover(request)#
serve_implementation(request)#
serve_initialize(request)#
serve_onChange(request)#
serve_onClose(request)#
serve_onOpen(request)#
serve_onSave(request, did_open=False, did_close=False)#
serve_references(request)#
serve_rename(request)#
serve_signature(request)#
serve_workspace_symbol(request)#
update_workspace_file(filepath, read_file=False, allow_empty=False, update_links=False)#
workspace_init()#

Initialise the workspace root across multiple threads

fortls.objects module#

class fortls.objects.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.objects.AssociateMap(var, bind_name, link_name)#

Bases: object

bind_name: str#
var: Variable#
class fortls.objects.Block(file_ast, line_number, name)#

Bases: Scope

get_children(public_only=False)#
get_desc()#
get_type(no_link=False)#
req_named_end()#
class fortls.objects.Diagnostic(sline, message, severity=1, find_word=None)#

Bases: object

build(file_obj)#
class fortls.objects.Do(file_ast, line_number, name)#

Bases: Block

get_desc()#
get_type(no_link=False)#
class fortls.objects.Enum(file_ast, line_number, name)#

Bases: Block

get_desc()#
get_type(no_link=False)#
class fortls.objects.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)#
class fortls.objects.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)#
static get_placeholders(arg_list)#
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)#
class fortls.objects.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, change_arg=-1, change_strings=None)#
get_type(no_link=False)#
is_callable()#
class fortls.objects.If(file_ast, line_number, name)#

Bases: Block

get_desc()#
get_type(no_link=False)#
class fortls.objects.Import(name, import_type=-1, only_list={}, rename_map={}, 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.objects.ImportTypes#

Bases: object

ALL = 1#
DEFAULT = -1#
NONE = 0#
ONLY = 2#
class fortls.objects.Include(file_ast, line_number, name, keywords=None)#

Bases: Scope

get_desc()#
class fortls.objects.Interface(file_ast, line_number, name, abstract=False)#

Bases: Scope

get_desc()#
get_type(no_link=False)#
is_abstract()#
is_callable()#
is_external_int()#
class fortls.objects.Method(file_ast, line_number, name, var_desc, keywords, keyword_info, proc_ptr='', link_obj=None)#

Bases: Variable

check_definition(obj_tree, known_types={}, interface=False)#
get_documentation()#
get_hover(long=False, drop_arg=-1)#
get_interface(name_replace=None, change_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)#
class fortls.objects.Module(file_ast, line_number, name, keywords=None)#

Bases: Scope

check_valid_parent()#
get_desc()#
get_hover(long=False, drop_arg=-1)#
get_type(no_link=False)#
class fortls.objects.Program(file_ast, line_number, name, keywords=None)#

Bases: Module

get_desc()#
class fortls.objects.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)#
class fortls.objects.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()#
class fortls.objects.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)#
class fortls.objects.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, change_arg=-1, change_strings=None)#
get_interface_array(keywords, signature, change_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()#
class fortls.objects.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)#
class fortls.objects.Use(mod_name, only_list={}, rename_map={}, line_number=0)#

Bases: object

AST node for USE statement

property line_number#
rename(only_list=[])#

Rename ONLY:, statements

class fortls.objects.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={}, 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)#
class fortls.objects.Where(file_ast, line_number, name)#

Bases: Block

get_desc()#
get_type(no_link=False)#
fortls.objects.climb_type_tree(var_stack, curr_scope, obj_tree)#

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

fortls.objects.find_in_scope(scope, var_name, obj_tree, interface=False, local_only=False, var_line_number=None)#
fortls.objects.find_in_workspace(obj_tree, query, filter_public=False, exact_match=False)#
fortls.objects.get_use_tree(scope, use_dict, obj_tree, only_list={}, rename_map={}, curr_path=[])#

fortls.parse_fortran module#

class fortls.parse_fortran.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.parse_fortran.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.parse_fortran.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.parse_fortran.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.parse_fortran.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.parse_fortran.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.parse_fortran.parse_var_keywords(test_str)#

Parse Fortran variable declaration keywords

fortls.parse_fortran.preprocess_file(contents_split, file_path=None, pp_defs=None, include_dirs=None, debug=False)#
fortls.parse_fortran.read_associate_def(line)#
fortls.parse_fortran.read_block_def(line)#

Attempt to read BLOCK definition line

fortls.parse_fortran.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.parse_fortran.read_enum_def(line)#

Attempt to read ENUM definition line

fortls.parse_fortran.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.parse_fortran.read_generic_def(line)#

Attempt to read generic procedure definition line

fortls.parse_fortran.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.parse_fortran.read_imp_stmt(line)#

Attempt to read IMPORT statement

fortls.parse_fortran.read_inc_stmt(line)#

Attempt to read INCLUDE statement

fortls.parse_fortran.read_int_def(line)#

Attempt to read INTERFACE definition line

fortls.parse_fortran.read_mod_def(line)#

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

fortls.parse_fortran.read_prog_def(line)#

Attempt to read PROGRAM definition line

fortls.parse_fortran.read_select_def(line)#

Attempt to read SELECT definition line

fortls.parse_fortran.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.parse_fortran.read_submod_def(line)#

Attempt to read SUBMODULE definition line

fortls.parse_fortran.read_type_def(line)#

Attempt to read TYPE definition line

fortls.parse_fortran.read_use_stmt(line)#

Attempt to read USE statement

fortls.parse_fortran.read_var_def(line, var_type=None, fun_only=False)#

Attempt to read variable definition line

fortls.parse_fortran.read_vis_stmnt(line)#

Attempt to read PUBLIC/PRIVATE statement

fortls.parse_fortran.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.regex_patterns module#

class fortls.regex_patterns.FortranRegularExpressions(USE=re.compile('[ ]*USE([, ]+(?:INTRINSIC|NON_INTRINSIC))?[ :]+(\\\\w*)([, ]+ONLY[ :]+)?', re.IGNORECASE), IMPORT=re.compile('[ ]*IMPORT(?:[ ]*,[ ]*(?P<spec>ALL|NONE)|[ ]*,[ ]*(?P<only>ONLY)[ ]*:[ ]*(?P<start1>[\\\\w_])|[ ]+(?:::[ ]*)?(?P<start2>[\\\\w_]))?', re.IGNORECASE), INCLUDE=re.compile('[ ]*INCLUDE[ :]*[\\\\\\'\\\\"]([^\\\\\\'\\\\"]*)', re.IGNORECASE), CONTAINS=re.compile('[ ]*(CONTAINS)[ ]*$', re.IGNORECASE), IMPLICIT=re.compile('[ ]*IMPLICIT[ ]+([a-z]*)', re.IGNORECASE), SUB_MOD=re.compile('[ ]*(?!<[,\\\\()][ ]*)\\\\b(PURE|IMPURE|ELEMENTAL|RECURSIVE)\\\\b(?![,\\\\)][ ]*)', re.IGNORECASE), SUB=re.compile('[ ]*SUBROUTINE[ ]+(\\\\w+)', re.IGNORECASE), END_SUB=re.compile('SUBROUTINE', re.IGNORECASE), FUN=re.compile('[ ]*FUNCTION[ ]+(\\\\w+)', re.IGNORECASE), RESULT=re.compile('RESULT[ ]*\\\\((\\\\w*)\\\\)', re.IGNORECASE), END_FUN=re.compile('FUNCTION', re.IGNORECASE), MOD=re.compile('[ ]*MODULE[ ]+(\\\\w+)', re.IGNORECASE), END_MOD=re.compile('MODULE', re.IGNORECASE), SUBMOD=re.compile('[ ]*SUBMODULE[ ]*\\\\(', re.IGNORECASE), END_SMOD=re.compile('SUBMODULE', re.IGNORECASE), END_PRO=re.compile('(MODULE)?[ ]*PROCEDURE', re.IGNORECASE), BLOCK=re.compile('[ ]*([a-z_]\\\\w*[ ]*:[ ]*)?BLOCK|CRITICAL(?!\\\\w)', re.IGNORECASE), END_BLOCK=re.compile('BLOCK|CRITICAL', re.IGNORECASE), DO=re.compile('[ ]*(?:[a-z_]\\\\w*[ ]*:[ ]*)?DO([ ]+[0-9]*|$)', re.IGNORECASE), END_DO=re.compile('DO', re.IGNORECASE), WHERE=re.compile('[ ]*WHERE[ ]*\\\\(', re.IGNORECASE), END_WHERE=re.compile('WHERE', re.IGNORECASE), IF=re.compile('[ ]*(?:[a-z_]\\\\w*[ ]*:[ ]*)?IF[ ]*\\\\(', re.IGNORECASE), THEN=re.compile('\\\\)[ ]*THEN$', re.IGNORECASE), END_IF=re.compile('IF', re.IGNORECASE), ASSOCIATE=re.compile('[ ]*ASSOCIATE[ ]*\\\\(', re.IGNORECASE), END_ASSOCIATE=re.compile('ASSOCIATE', re.IGNORECASE), END_FIXED=re.compile('[ ]*([0-9]*)[ ]*CONTINUE', re.IGNORECASE), SELECT=re.compile('[ ]*(?:[a-z_]\\\\w*[ ]*:[ ]*)?SELECT[ ]*(CASE|TYPE)[ ]*\\\\(([\\\\w=> ]*)', re.IGNORECASE), SELECT_TYPE=re.compile('[ ]*(TYPE|CLASS)[ ]+IS[ ]*\\\\(([\\\\w ]*)', re.IGNORECASE), SELECT_DEFAULT=re.compile('[ ]*CLASS[ ]+DEFAULT', re.IGNORECASE), END_SELECT=re.compile('SELECT', re.IGNORECASE), PROG=re.compile('[ ]*PROGRAM[ ]+(\\\\w+)', re.IGNORECASE), END_PROG=re.compile('PROGRAM', re.IGNORECASE), INT=re.compile('[ ]*(ABSTRACT)?[ ]*INTERFACE[ ]*(\\\\w*)', re.IGNORECASE), END_INT=re.compile('INTERFACE', re.IGNORECASE), END_WORD=re.compile('[ ]*END[ ]*(DO|WHERE|IF|BLOCK|CRITICAL|ASSOCIATE|SELECT|TYPE|ENUM|MODULE|SUBMODULE|PROGRAM|INTERFACE|SUBROUTINE|FUNCTION|PROCEDURE|FORALL)?([ ]+(?!\\\\W)|$)', re.IGNORECASE), TYPE_DEF=re.compile('[ ]*(TYPE)[, :]+', re.IGNORECASE), EXTENDS=re.compile('EXTENDS[ ]*\\\\((\\\\w*)\\\\)', re.IGNORECASE), GENERIC_PRO=re.compile('[ ]*(GENERIC)[, ]*(PRIVATE|PUBLIC)?[ ]*::[ ]*[a-z]', re.IGNORECASE), GEN_ASSIGN=re.compile('(ASSIGNMENT|OPERATOR)\\\\(', re.IGNORECASE), END_TYPED=re.compile('TYPE', re.IGNORECASE), ENUM_DEF=re.compile('[ ]*ENUM[, ]+', re.IGNORECASE), END_ENUMD=re.compile('ENUM', re.IGNORECASE), VAR=re.compile('[ ]*(INTEGER|REAL|DOUBLE[ ]*PRECISION|COMPLEX|DOUBLE[ ]*COMPLEX|CHARACTER|LOGICAL|PROCEDURE|EXTERNAL|CLASS|TYPE)', re.IGNORECASE), KIND_SPEC=re.compile('[ ]*([*]?\\\\([ ]*[\\\\w*:]|\\\\*[ ]*[0-9:]*)', re.IGNORECASE), KEYWORD_LIST=re.compile('[ ]*,[ ]*(PUBLIC|PRIVATE|ALLOCATABLE|POINTER|TARGET|DIMENSION[ ]*\\\\(|OPTIONAL|INTENT[ ]*\\\\([ ]*(?:IN|OUT|IN[ ]*OUT)[ ]*\\\\)|DEFERRED|NOPASS|PASS[ ]*\\\\(\\\\w*\\\\)|SAVE|PARAMETER|EXTERNAL|CONTIGUOUS)', re.IGNORECASE), PARAMETER_VAL=re.compile('\\\\w*[\\\\s\\\\&]*=(([\\\\s\\\\&]*[\\\\w\\\\.\\\\-\\\\+\\\\*\\\\/\\\\\\'\\\\"])*)', re.IGNORECASE), TATTR_LIST=re.compile('[ ]*,[ ]*(PUBLIC|PRIVATE|ABSTRACT|EXTENDS\\\\(\\\\w*\\\\))', re.IGNORECASE), VIS=re.compile('[ ]*\\\\b(PUBLIC|PRIVATE)\\\\b', re.IGNORECASE), WORD=re.compile('[a-z_]\\\\w*', re.IGNORECASE), NUMBER=re.compile('[\\\\+\\\\-]?(\\\\b\\\\d+\\\\.?\\\\d*|\\\\.\\\\d+)(_\\\\w+|d[\\\\+\\\\-]?\\\\d+|e[\\\\+\\\\-]?\\\\d+(_\\\\w+)?)?(?!\\\\w)', re.IGNORECASE), LOGICAL=re.compile('.true.|.false.', re.IGNORECASE), SUB_PAREN=re.compile('\\\\([\\\\w, ]*\\\\)', re.IGNORECASE), SQ_STRING=re.compile("\\\\'[^\\\\']*\\\\'", re.IGNORECASE), DQ_STRING=re.compile('\\\\"[^\\\\"]*\\\\"', re.IGNORECASE), LINE_LABEL=re.compile('[ ]*([0-9]+)[ ]+', re.IGNORECASE), NON_DEF=re.compile('[ ]*(CALL[ ]+[a-z_]|[a-z_][\\\\w%]*[ ]*=)', re.IGNORECASE), FIXED_COMMENT=re.compile('([!cd*])', re.IGNORECASE), FIXED_CONT=re.compile('( {5}[\\\\S])'), FIXED_DOC=re.compile('(?:[!cd\\\\*])([<>!])', re.IGNORECASE), FIXED_OPENMP=re.compile('[!c\\\\*]\\\\$OMP', re.IGNORECASE), FREE_COMMENT=re.compile('([ ]*!)'), FREE_CONT=re.compile('([ ]*&)'), FREE_DOC=re.compile('[ ]*!([<>!])'), FREE_OPENMP=re.compile('[ ]*!\\\\$OMP', re.IGNORECASE), FREE_FORMAT_TEST=re.compile('[ ]{1,4}[a-z]', re.IGNORECASE), DEFINED=re.compile('defined[ ]*\\\\(?[ ]*([a-z_]\\\\w*)[ ]*\\\\)?', re.IGNORECASE), PP_REGEX=re.compile('#(if |ifdef|ifndef|else|elif|endif)'), PP_DEF=re.compile('#(define|undef)[ ]*([\\\\w]+)(\\\\((\\\\w+(,[ ]*)?)+\\\\))?', re.IGNORECASE), PP_DEF_TEST=re.compile('(![ ]*)?defined[ ]*\\\\([ ]*(\\\\w*)[ ]*\\\\)$', re.IGNORECASE), PP_INCLUDE=re.compile('#include[ ]*([\\\\"\\\\w\\\\.]*)', re.IGNORECASE), PP_ANY=re.compile('(^#:?\\\\w+)'), CALL=re.compile('[ ]*CALL[ ]+[\\\\w%]*$', re.IGNORECASE), INT_STMNT=re.compile('^[ ]*[a-z]*$', re.IGNORECASE), TYPE_STMNT=re.compile('[ ]*(TYPE|CLASS)[ ]*(IS)?[ ]*$', re.IGNORECASE), PROCEDURE_STMNT=re.compile('[ ]*(PROCEDURE)[ ]*$', re.IGNORECASE), PRO_LINK=re.compile('[ ]*(MODULE[ ]*PROCEDURE )', re.IGNORECASE), SCOPE_DEF=re.compile('[ ]*(MODULE|PROGRAM|SUBROUTINE|FUNCTION|INTERFACE)[ ]+', re.IGNORECASE), END=re.compile('[ ]*(END)( |MODULE|PROGRAM|SUBROUTINE|FUNCTION|PROCEDURE|TYPE|DO|IF|SELECT)?', re.IGNORECASE), CLASS_VAR=re.compile('(TYPE|CLASS)[ ]*\\\\(', re.IGNORECASE), DEF_KIND=re.compile('(\\\\w*)[ ]*\\\\((?:KIND|LEN)?[ =]*(\\\\w*)', re.IGNORECASE), OBJBREAK=re.compile('[\\\\/\\\\-(.,+*<>=$: ]', re.IGNORECASE))#

Bases: object

ASSOCIATE: Pattern = re.compile('[ ]*ASSOCIATE[ ]*\\(', re.IGNORECASE)#
BLOCK: Pattern = re.compile('[ ]*([a-z_]\\w*[ ]*:[ ]*)?BLOCK|CRITICAL(?!\\w)', re.IGNORECASE)#
CALL: Pattern = re.compile('[ ]*CALL[ ]+[\\w%]*$', re.IGNORECASE)#
CLASS_VAR: Pattern = re.compile('(TYPE|CLASS)[ ]*\\(', re.IGNORECASE)#
CONTAINS: Pattern = re.compile('[ ]*(CONTAINS)[ ]*$', re.IGNORECASE)#
DEFINED: Pattern = re.compile('defined[ ]*\\(?[ ]*([a-z_]\\w*)[ ]*\\)?', re.IGNORECASE)#
DEF_KIND: Pattern = re.compile('(\\w*)[ ]*\\((?:KIND|LEN)?[ =]*(\\w*)', re.IGNORECASE)#
DO: Pattern = re.compile('[ ]*(?:[a-z_]\\w*[ ]*:[ ]*)?DO([ ]+[0-9]*|$)', re.IGNORECASE)#
DQ_STRING: Pattern = re.compile('\\"[^\\"]*\\"', re.IGNORECASE)#
END: Pattern = re.compile('[ ]*(END)( |MODULE|PROGRAM|SUBROUTINE|FUNCTION|PROCEDURE|TYPE|DO|IF|SELECT)?', re.IGNORECASE)#
END_ASSOCIATE: Pattern = re.compile('ASSOCIATE', re.IGNORECASE)#
END_BLOCK: Pattern = re.compile('BLOCK|CRITICAL', re.IGNORECASE)#
END_DO: Pattern = re.compile('DO', re.IGNORECASE)#
END_ENUMD: Pattern = re.compile('ENUM', re.IGNORECASE)#
END_FIXED: Pattern = re.compile('[ ]*([0-9]*)[ ]*CONTINUE', re.IGNORECASE)#
END_FUN: Pattern = re.compile('FUNCTION', re.IGNORECASE)#
END_IF: Pattern = re.compile('IF', re.IGNORECASE)#
END_INT: Pattern = re.compile('INTERFACE', re.IGNORECASE)#
END_MOD: Pattern = re.compile('MODULE', re.IGNORECASE)#
END_PRO: Pattern = re.compile('(MODULE)?[ ]*PROCEDURE', re.IGNORECASE)#
END_PROG: Pattern = re.compile('PROGRAM', re.IGNORECASE)#
END_SELECT: Pattern = re.compile('SELECT', re.IGNORECASE)#
END_SMOD: Pattern = re.compile('SUBMODULE', re.IGNORECASE)#
END_SUB: Pattern = re.compile('SUBROUTINE', re.IGNORECASE)#
END_TYPED: Pattern = re.compile('TYPE', re.IGNORECASE)#
END_WHERE: Pattern = re.compile('WHERE', re.IGNORECASE)#
END_WORD: Pattern = re.compile('[ ]*END[ ]*(DO|WHERE|IF|BLOCK|CRITICAL|ASSOCIATE|SELECT|TYPE|ENUM|MODULE|SUBMODULE|PROGRAM|INTERFACE|SUBROUTINE|FUNCTION|PROCEDURE|FORALL)?([ ]+(?!\\W)|$)', re.IGNORECASE)#
ENUM_DEF: Pattern = re.compile('[ ]*ENUM[, ]+', re.IGNORECASE)#
EXTENDS: Pattern = re.compile('EXTENDS[ ]*\\((\\w*)\\)', re.IGNORECASE)#
FIXED_COMMENT: Pattern = re.compile('([!cd*])', re.IGNORECASE)#
FIXED_CONT: Pattern = re.compile('( {5}[\\S])')#
FIXED_DOC: Pattern = re.compile('(?:[!cd\\*])([<>!])', re.IGNORECASE)#
FIXED_OPENMP: Pattern = re.compile('[!c\\*]\\$OMP', re.IGNORECASE)#
FREE_COMMENT: Pattern = re.compile('([ ]*!)')#
FREE_CONT: Pattern = re.compile('([ ]*&)')#
FREE_DOC: Pattern = re.compile('[ ]*!([<>!])')#
FREE_FORMAT_TEST: Pattern = re.compile('[ ]{1,4}[a-z]', re.IGNORECASE)#
FREE_OPENMP: Pattern = re.compile('[ ]*!\\$OMP', re.IGNORECASE)#
FUN: Pattern = re.compile('[ ]*FUNCTION[ ]+(\\w+)', re.IGNORECASE)#
GENERIC_PRO: Pattern = re.compile('[ ]*(GENERIC)[, ]*(PRIVATE|PUBLIC)?[ ]*::[ ]*[a-z]', re.IGNORECASE)#
GEN_ASSIGN: Pattern = re.compile('(ASSIGNMENT|OPERATOR)\\(', re.IGNORECASE)#
IF: Pattern = re.compile('[ ]*(?:[a-z_]\\w*[ ]*:[ ]*)?IF[ ]*\\(', re.IGNORECASE)#
IMPLICIT: Pattern = re.compile('[ ]*IMPLICIT[ ]+([a-z]*)', re.IGNORECASE)#
IMPORT: Pattern = re.compile('[ ]*IMPORT(?:[ ]*,[ ]*(?P<spec>ALL|NONE)|[ ]*,[ ]*(?P<only>ONLY)[ ]*:[ ]*(?P<start1>[\\w_])|[ ]+(?:::[ ]*)?(?P<start2>[\\w_]))?', re.IGNORECASE)#
INCLUDE: Pattern = re.compile('[ ]*INCLUDE[ :]*[\\\'\\"]([^\\\'\\"]*)', re.IGNORECASE)#
INT: Pattern = re.compile('[ ]*(ABSTRACT)?[ ]*INTERFACE[ ]*(\\w*)', re.IGNORECASE)#
INT_STMNT: Pattern = re.compile('^[ ]*[a-z]*$', re.IGNORECASE)#
KEYWORD_LIST: Pattern = re.compile('[ ]*,[ ]*(PUBLIC|PRIVATE|ALLOCATABLE|POINTER|TARGET|DIMENSION[ ]*\\(|OPTIONAL|INTENT[ ]*\\([ ]*(?:IN|OUT|IN[ ]*OUT)[ ]*\\)|DEFERRED|NOPASS|PASS[ ]*\\(\\w*\\)|SAVE|PARAMETER|EXTERNAL|CONTIGUOUS)', re.IGNORECASE)#
KIND_SPEC: Pattern = re.compile('[ ]*([*]?\\([ ]*[\\w*:]|\\*[ ]*[0-9:]*)', re.IGNORECASE)#
LINE_LABEL: Pattern = re.compile('[ ]*([0-9]+)[ ]+', re.IGNORECASE)#
LOGICAL: Pattern = re.compile('.true.|.false.', re.IGNORECASE)#
MOD: Pattern = re.compile('[ ]*MODULE[ ]+(\\w+)', re.IGNORECASE)#
NON_DEF: Pattern = re.compile('[ ]*(CALL[ ]+[a-z_]|[a-z_][\\w%]*[ ]*=)', re.IGNORECASE)#
NUMBER: Pattern = re.compile('[\\+\\-]?(\\b\\d+\\.?\\d*|\\.\\d+)(_\\w+|d[\\+\\-]?\\d+|e[\\+\\-]?\\d+(_\\w+)?)?(?!\\w)', re.IGNORECASE)#
OBJBREAK: Pattern = re.compile('[\\/\\-(.,+*<>=$: ]', re.IGNORECASE)#
PARAMETER_VAL: Pattern = re.compile('\\w*[\\s\\&]*=(([\\s\\&]*[\\w\\.\\-\\+\\*\\/\\\'\\"])*)', re.IGNORECASE)#
PP_ANY: Pattern = re.compile('(^#:?\\w+)')#
PP_DEF: Pattern = re.compile('#(define|undef)[ ]*([\\w]+)(\\((\\w+(,[ ]*)?)+\\))?', re.IGNORECASE)#
PP_DEF_TEST: Pattern = re.compile('(![ ]*)?defined[ ]*\\([ ]*(\\w*)[ ]*\\)$', re.IGNORECASE)#
PP_INCLUDE: Pattern = re.compile('#include[ ]*([\\"\\w\\.]*)', re.IGNORECASE)#
PP_REGEX: Pattern = re.compile('#(if |ifdef|ifndef|else|elif|endif)')#
PROCEDURE_STMNT: Pattern = re.compile('[ ]*(PROCEDURE)[ ]*$', re.IGNORECASE)#
PROG: Pattern = re.compile('[ ]*PROGRAM[ ]+(\\w+)', re.IGNORECASE)#
RESULT: Pattern = re.compile('RESULT[ ]*\\((\\w*)\\)', re.IGNORECASE)#
SCOPE_DEF: Pattern = re.compile('[ ]*(MODULE|PROGRAM|SUBROUTINE|FUNCTION|INTERFACE)[ ]+', re.IGNORECASE)#
SELECT: Pattern = re.compile('[ ]*(?:[a-z_]\\w*[ ]*:[ ]*)?SELECT[ ]*(CASE|TYPE)[ ]*\\(([\\w=> ]*)', re.IGNORECASE)#
SELECT_DEFAULT: Pattern = re.compile('[ ]*CLASS[ ]+DEFAULT', re.IGNORECASE)#
SELECT_TYPE: Pattern = re.compile('[ ]*(TYPE|CLASS)[ ]+IS[ ]*\\(([\\w ]*)', re.IGNORECASE)#
SQ_STRING: Pattern = re.compile("\\'[^\\']*\\'", re.IGNORECASE)#
SUB: Pattern = re.compile('[ ]*SUBROUTINE[ ]+(\\w+)', re.IGNORECASE)#
SUBMOD: Pattern = re.compile('[ ]*SUBMODULE[ ]*\\(', re.IGNORECASE)#
SUB_MOD: Pattern = re.compile('[ ]*(?!<[,\\()][ ]*)\\b(PURE|IMPURE|ELEMENTAL|RECURSIVE)\\b(?![,\\)][ ]*)', re.IGNORECASE)#

Parse procedure keywords but not if they start with , or ( or end with , or ) This is to avoid parsing as keywords variables named pure, impure, etc.

SUB_PAREN: Pattern = re.compile('\\([\\w, ]*\\)', re.IGNORECASE)#
TATTR_LIST: Pattern = re.compile('[ ]*,[ ]*(PUBLIC|PRIVATE|ABSTRACT|EXTENDS\\(\\w*\\))', re.IGNORECASE)#
THEN: Pattern = re.compile('\\)[ ]*THEN$', re.IGNORECASE)#
TYPE_DEF: Pattern = re.compile('[ ]*(TYPE)[, :]+', re.IGNORECASE)#
TYPE_STMNT: Pattern = re.compile('[ ]*(TYPE|CLASS)[ ]*(IS)?[ ]*$', re.IGNORECASE)#
USE: Pattern = re.compile('[ ]*USE([, ]+(?:INTRINSIC|NON_INTRINSIC))?[ :]+(\\w*)([, ]+ONLY[ :]+)?', re.IGNORECASE)#
VAR: Pattern = re.compile('[ ]*(INTEGER|REAL|DOUBLE[ ]*PRECISION|COMPLEX|DOUBLE[ ]*COMPLEX|CHARACTER|LOGICAL|PROCEDURE|EXTERNAL|CLASS|TYPE)', re.IGNORECASE)#
VIS: Pattern = re.compile('[ ]*\\b(PUBLIC|PRIVATE)\\b', re.IGNORECASE)#
WHERE: Pattern = re.compile('[ ]*WHERE[ ]*\\(', re.IGNORECASE)#
WORD: Pattern = re.compile('[a-z_]\\w*', re.IGNORECASE)#
fortls.regex_patterns.create_src_file_exts_regex(input_exts=[])#

Create a REGEX for which sources the Language Server should parse.

Default extensions are (case insensitive): F F03 F05 F08 F18 F77 F90 F95 FOR FPP

Parameters:

input_exts (list[str], optional) – Additional list of file extensions to parse, in Python REGEX format that means special characters must be escaped , by default []

Examples

>>> regex = create_src_file_exts_regex([r"\.fypp", r"\.inc"])
>>> regex.search("test.fypp")
<re.Match object; span=(4, 9), match='.fypp'>
>>> regex.search("test.inc")
<re.Match object; span=(4, 8), match='.inc'>
>>> regex = create_src_file_exts_regex([r"\.inc.*"])
>>> regex.search("test.inc.1")
<re.Match object; span=(4, 10), match='.inc.1'>

Invalid regex expressions will cause the function to revert to the default extensions

>>> regex = create_src_file_exts_regex(["*.inc"])
>>> regex.search("test.inc") is None
True
Returns:

A compiled regular expression for matching file extensions

Return type:

Pattern[str]

fortls.regex_patterns.create_src_file_exts_str(input_exts=[])#

This is a version of create_src_file_exts_regex that takes a list sanitises the list of input_exts before compiling the regex. For more info see create_src_file_exts_regex

fortls.version module#

Module contents#