Skip to content

Commit 500a7bc

Browse files
committed
Initial work on parsing kind seperately for vars
1 parent c3e8694 commit 500a7bc

File tree

3 files changed

+105
-45
lines changed

3 files changed

+105
-45
lines changed

fortls/ftypes.py

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@ class VarInfo:
1515
#: keywords associated with this variable e.g. SAVE, DIMENSION, etc.
1616
keywords: list[str] #: Keywords associated with variable
1717
var_names: list[str] #: Variable names
18+
var_kind: str = field(default=None) #: Kind of variable e.g. ``INTEGER*4`` etc.
1819

1920

2021
@dataclass

fortls/helper_functions.py

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -372,6 +372,19 @@ def get_keywords(keywords: list, keyword_info: dict = {}):
372372
return keyword_strings
373373

374374

375+
def parenthetic_contents(string: str):
376+
"""Generate parenthesized contents in string as pairs
377+
(contents, start-position, level).
378+
"""
379+
stack = []
380+
for i, c in enumerate(string):
381+
if c == "(":
382+
stack.append(i)
383+
elif c == ")" and stack:
384+
start = stack.pop()
385+
yield (string[start + 1 : i], start, len(stack))
386+
387+
375388
def get_paren_substring(string: str) -> str | None:
376389
"""Get the contents enclosed by the first pair of parenthesis
377390

fortls/parse_fortran.py

Lines changed: 91 additions & 45 deletions
Original file line numberDiff line numberDiff line change
@@ -169,47 +169,58 @@ def parse_var_keywords(test_str: str) -> tuple[list[str], str]:
169169

170170
def read_var_def(line: str, var_type: str = None, fun_only: bool = False):
171171
"""Attempt to read variable definition line"""
172+
173+
def parse_kind(line: str):
174+
match = FRegex.KIND_SPEC.match(line)
175+
if not match:
176+
return None, line
177+
kind_str = match.group(1).replace(" ", "")
178+
line = line[match.end(0) :]
179+
if kind_str.find("(") >= 0:
180+
match_char = find_paren_match(line)
181+
if match_char < 0: # this triggers while typing with autocomplete
182+
raise ValueError("Incomplete kind specification")
183+
kind_str += line[: match_char + 1].strip()
184+
line = line[match_char + 1 :]
185+
return kind_str, line
186+
172187
if var_type is None:
173188
type_match = FRegex.VAR.match(line)
174189
if type_match is None:
175190
return None
176-
else:
177-
var_type = type_match.group(0).strip()
178-
trailing_line = line[type_match.end(0) :]
191+
var_type = type_match.group(0).strip()
192+
trailing_line = line[type_match.end(0) :]
179193
else:
180194
trailing_line = line[len(var_type) :]
181195
var_type = var_type.upper()
182196
trailing_line = trailing_line.split("!")[0]
183197
if len(trailing_line) == 0:
184198
return None
185-
#
186-
kind_match = FRegex.KIND_SPEC.match(trailing_line)
187-
if kind_match:
188-
kind_str = kind_match.group(1).replace(" ", "")
189-
var_type += kind_str
190-
trailing_line = trailing_line[kind_match.end(0) :]
191-
if kind_str.find("(") >= 0:
192-
match_char = find_paren_match(trailing_line)
193-
if match_char < 0:
194-
return None # Incomplete type spec
195-
else:
196-
kind_word = trailing_line[: match_char + 1].strip()
197-
var_type += kind_word
198-
trailing_line = trailing_line[match_char + 1 :]
199-
else:
200-
# Class and Type statements need a kind spec
201-
if var_type in ("TYPE", "CLASS"):
202-
return None
203-
# Make sure next character is space or comma or colon
204-
if not trailing_line[0] in (" ", ",", ":"):
205-
return None
199+
200+
# Parse the global kind, if any, for the current line definition
201+
# The global kind in some cases, like characters can be overriden by a locally
202+
# defined kind
203+
try:
204+
kind_str, trailing_line = parse_kind(trailing_line)
205+
var_type += kind_str # XXX: see below
206+
except ValueError:
207+
return None
208+
except TypeError: # XXX: remove with explicit kind specification in VarInfo
209+
pass
210+
211+
# Class and Type statements need a kind spec
212+
if not kind_str and var_type in ("TYPE", "CLASS"):
213+
return None
214+
# Make sure next character is space or comma or colon
215+
if not kind_str and not trailing_line[0] in (" ", ",", ":"):
216+
return None
206217
#
207218
keywords, trailing_line = parse_var_keywords(trailing_line)
208219
# Check if this is a function definition
209220
fun_def = read_fun_def(trailing_line, ResultSig(type=var_type, keywords=keywords))
210-
if (fun_def is not None) or fun_only:
221+
if fun_def or fun_only:
211222
return fun_def
212-
#
223+
# Split the type and variable name
213224
line_split = trailing_line.split("::")
214225
if len(line_split) == 1:
215226
if len(keywords) > 0:
@@ -222,8 +233,8 @@ def read_var_def(line: str, var_type: str = None, fun_only: bool = False):
222233
var_words = separate_def_list(trailing_line.strip())
223234
if var_words is None:
224235
var_words = []
225-
#
226-
return "var", VarInfo(var_type, keywords, var_words)
236+
237+
return "var", VarInfo(var_type, keywords, var_words, kind_str)
227238

228239

229240
def get_procedure_modifiers(
@@ -1356,9 +1367,13 @@ def parse(
13561367
procedure_def = True
13571368
link_name = get_paren_substring(desc_string)
13581369
for var_name in obj_info.var_names:
1370+
desc = desc_string
13591371
link_name: str = None
13601372
if var_name.find("=>") > -1:
13611373
name_split = var_name.split("=>")
1374+
# TODO: rename name_raw to name
1375+
# TODO: rename name_stripped to name
1376+
# TODO: rename desc_string to desc
13621377
name_raw = name_split[0]
13631378
link_name = name_split[1].split("(")[0].strip()
13641379
if link_name.lower() == "null":
@@ -1367,28 +1382,27 @@ def parse(
13671382
name_raw = var_name.split("=")[0]
13681383
# Add dimension if specified
13691384
# TODO: turn into function and add support for co-arrays i.e. [*]
1370-
key_tmp = obj_info.keywords[:]
1371-
iparen = name_raw.find("(")
1372-
if iparen == 0:
1385+
# Copy global keywords to the individual variable
1386+
var_keywords: list[str] = obj_info.keywords[:]
1387+
# The name starts with (
1388+
if name_raw.find("(") == 0:
13731389
continue
1374-
elif iparen > 0:
1375-
if name_raw[iparen - 1] == "*":
1376-
iparen -= 1
1377-
if desc_string.find("(") < 0:
1378-
desc_string += f"*({get_paren_substring(name_raw)})"
1379-
else:
1380-
key_tmp.append(
1381-
f"dimension({get_paren_substring(name_raw)})"
1382-
)
1383-
name_raw = name_raw[:iparen]
1390+
name_raw, dims = self.parse_imp_dim(name_raw)
1391+
name_raw, char_len = self.parse_imp_char(name_raw)
1392+
if dims:
1393+
var_keywords.append(dims)
1394+
if char_len:
1395+
desc += char_len
1396+
13841397
name_stripped = name_raw.strip()
1385-
keywords, keyword_info = map_keywords(key_tmp)
1398+
keywords, keyword_info = map_keywords(var_keywords)
1399+
13861400
if procedure_def:
13871401
new_var = Method(
13881402
file_ast,
13891403
line_no,
13901404
name_stripped,
1391-
desc_string,
1405+
desc,
13921406
keywords,
13931407
keyword_info=keyword_info,
13941408
link_obj=link_name,
@@ -1398,9 +1412,10 @@ def parse(
13981412
file_ast,
13991413
line_no,
14001414
name_stripped,
1401-
desc_string,
1415+
desc,
14021416
keywords,
14031417
keyword_info=keyword_info,
1418+
# kind=obj_info.var_kind,
14041419
link_obj=link_name,
14051420
)
14061421
# If the object is fortran_var and a parameter include
@@ -1413,7 +1428,7 @@ def parse(
14131428
new_var.set_parameter_val(var)
14141429

14151430
# Check if the "variable" is external and if so cycle
1416-
if find_external(file_ast, desc_string, name_stripped, new_var):
1431+
if find_external(file_ast, desc, name_stripped, new_var):
14171432
continue
14181433

14191434
# if not merge_external:
@@ -1643,6 +1658,37 @@ def parse(
16431658
log.debug(f"{error['range']}: {error['message']}")
16441659
return file_ast
16451660

1661+
def parse_imp_dim(self, name: str):
1662+
regex = re.compile(r"[ ]*\w+[ ]*(\()", re.I)
1663+
# TODO: replace space
1664+
m = regex.match(name)
1665+
if not m:
1666+
return name, None
1667+
i = find_paren_match(name[m.end(1) :])
1668+
if i < 0:
1669+
return name, None # triggers for autocomplete
1670+
dims = name[m.start(1) : m.end(1) + i + 1]
1671+
name = name[: m.start(1)] + name[m.end(1) + i + 1 :]
1672+
return name, f"dimension{dims}"
1673+
1674+
def parse_imp_char(self, name: str):
1675+
implicit_len = re.compile(r"(\w+)[ ]*\*[ ]*(\d+|\()", re.I)
1676+
# TODO: replace space in name
1677+
match = re.match(implicit_len, name)
1678+
if not match:
1679+
return name, None
1680+
if match.group(2) == "(":
1681+
i = find_paren_match(name[match.end(2) :])
1682+
if i < 0:
1683+
return name, None # triggers for autocomplete
1684+
char_len = name[match.start(2) : match.end(2) + i + 1]
1685+
elif match.group(2).isdigit():
1686+
char_len = match.group(2)
1687+
else:
1688+
raise ValueError("No matching group(2) for implicit length")
1689+
name = match.group(1)
1690+
return name, f"*{char_len}"
1691+
16461692
def parse_end_scope_word(
16471693
self, line: str, ln: int, file_ast: FortranAST, match: re.Match
16481694
) -> bool:

0 commit comments

Comments
 (0)