Skip to content

Commit 7c983c5

Browse files
committed
chore: Update Fortran regex
1 parent 81cc997 commit 7c983c5

File tree

1 file changed

+22
-23
lines changed

1 file changed

+22
-23
lines changed

fortls/regex_patterns.py

Lines changed: 22 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -16,39 +16,38 @@ class FortranRegularExpressions:
1616
CONTAINS: Pattern = compile(r"[ ]*(CONTAINS)[ ]*$", I)
1717
IMPLICIT: Pattern = compile(r"[ ]*IMPLICIT[ ]+([a-z]*)", I)
1818
SUB_MOD: Pattern = compile(r"[ ]*\b(PURE|IMPURE|ELEMENTAL|RECURSIVE)\b", I)
19-
SUB: Pattern = compile(r"[ ]*SUBROUTINE[ ]+([a-z0-9_]+)", I)
19+
SUB: Pattern = compile(r"[ ]*SUBROUTINE[ ]+(\w+)", I)
2020
END_SUB: Pattern = compile(r"SUBROUTINE", I)
21-
FUN: Pattern = compile(r"[ ]*FUNCTION[ ]+([a-z0-9_]+)", I)
22-
RESULT: Pattern = compile(r"RESULT[ ]*\(([a-z0-9_]*)\)", I)
21+
FUN: Pattern = compile(r"[ ]*FUNCTION[ ]+(\w+)", I)
22+
RESULT: Pattern = compile(r"RESULT[ ]*\((\w*)\)", I)
2323
END_FUN: Pattern = compile(r"FUNCTION", I)
24-
MOD: Pattern = compile(r"[ ]*MODULE[ ]+([a-z0-9_]+)", I)
24+
MOD: Pattern = compile(r"[ ]*MODULE[ ]+(\w+)", I)
2525
END_MOD: Pattern = compile(r"MODULE", I)
2626
SUBMOD: Pattern = compile(r"[ ]*SUBMODULE[ ]*\(", I)
2727
END_SMOD: Pattern = compile(r"SUBMODULE", I)
2828
END_PRO: Pattern = compile(r"(MODULE)?[ ]*PROCEDURE", I)
29-
BLOCK: Pattern = compile(r"[ ]*([a-z_][a-z0-9_]*[ ]*:[ ]*)?BLOCK(?![a-z0-9_])", I)
29+
BLOCK: Pattern = compile(r"[ ]*([a-z_]\w*[ ]*:[ ]*)?BLOCK(?!\w)", I)
3030
END_BLOCK: Pattern = compile(r"BLOCK", I)
31-
DO: Pattern = compile(r"[ ]*(?:[a-z_][a-z0-9_]*[ ]*:[ ]*)?DO([ ]+[0-9]*|$)", I)
31+
DO: Pattern = compile(r"[ ]*(?:[a-z_]\w*[ ]*:[ ]*)?DO([ ]+[0-9]*|$)", I)
3232
END_DO: Pattern = compile(r"DO", I)
3333
WHERE: Pattern = compile(r"[ ]*WHERE[ ]*\(", I)
3434
END_WHERE: Pattern = compile(r"WHERE", I)
35-
IF: Pattern = compile(r"[ ]*(?:[a-z_][a-z0-9_]*[ ]*:[ ]*)?IF[ ]*\(", I)
35+
IF: Pattern = compile(r"[ ]*(?:[a-z_]\w*[ ]*:[ ]*)?IF[ ]*\(", I)
3636
THEN: Pattern = compile(r"\)[ ]*THEN$", I)
3737
END_IF: Pattern = compile(r"IF", I)
3838
ASSOCIATE: Pattern = compile(r"[ ]*ASSOCIATE[ ]*\(", I)
3939
END_ASSOCIATE: Pattern = compile(r"ASSOCIATE", I)
4040
END_FIXED: Pattern = compile(r"[ ]*([0-9]*)[ ]*CONTINUE", I)
4141
SELECT: Pattern = compile(
42-
r"[ ]*(?:[a-z_][a-z0-9_]*[ ]*:[ ]*)?SELECT[ ]*"
43-
r"(CASE|TYPE)[ ]*\(([a-z0-9_=> ]*)",
42+
r"[ ]*(?:[a-z_]\w*[ ]*:[ ]*)?SELECT[ ]*" r"(CASE|TYPE)[ ]*\(([\w=> ]*)",
4443
I,
4544
)
46-
SELECT_TYPE: Pattern = compile(r"[ ]*(TYPE|CLASS)[ ]+IS[ ]*\(([a-z0-9_ ]*)", I)
45+
SELECT_TYPE: Pattern = compile(r"[ ]*(TYPE|CLASS)[ ]+IS[ ]*\(([\w ]*)", I)
4746
SELECT_DEFAULT: Pattern = compile(r"[ ]*CLASS[ ]+DEFAULT", I)
4847
END_SELECT: Pattern = compile(r"SELECT", I)
49-
PROG: Pattern = compile(r"[ ]*PROGRAM[ ]+([a-z0-9_]+)", I)
48+
PROG: Pattern = compile(r"[ ]*PROGRAM[ ]+(\w+)", I)
5049
END_PROG: Pattern = compile(r"PROGRAM", I)
51-
INT: Pattern = compile(r"[ ]*(ABSTRACT)?[ ]*INTERFACE[ ]*([a-z0-9_]*)", I)
50+
INT: Pattern = compile(r"[ ]*(ABSTRACT)?[ ]*INTERFACE[ ]*(\w*)", I)
5251
END_INT: Pattern = compile(r"INTERFACE", I)
5352
END_WORD: Pattern = compile(
5453
r"[ ]*END[ ]*(DO|WHERE|IF|BLOCK|ASSOCIATE|SELECT"
@@ -57,7 +56,7 @@ class FortranRegularExpressions:
5756
I,
5857
)
5958
TYPE_DEF: Pattern = compile(r"[ ]*(TYPE)[, :]+", I)
60-
EXTENDS: Pattern = compile(r"EXTENDS[ ]*\(([a-z0-9_]*)\)", I)
59+
EXTENDS: Pattern = compile(r"EXTENDS[ ]*\((\w*)\)", I)
6160
GENERIC_PRO: Pattern = compile(
6261
r"[ ]*(GENERIC)[, ]*(PRIVATE|PUBLIC)?[ ]*::[ ]*[a-z]", I
6362
)
@@ -71,7 +70,7 @@ class FortranRegularExpressions:
7170
r"|EXTERNAL|CLASS|TYPE)", # external :: variable is handled by this
7271
I,
7372
)
74-
KIND_SPEC: Pattern = compile(r"[ ]*([*]?\([ ]*[a-z0-9_*:]|\*[ ]*[0-9:]*)", I)
73+
KIND_SPEC: Pattern = compile(r"[ ]*([*]?\([ ]*[\w*:]|\*[ ]*[0-9:]*)", I)
7574
KEYWORD_LIST: Pattern = compile(
7675
r"[ ]*,[ ]*(PUBLIC|PRIVATE|ALLOCATABLE|"
7776
r"POINTER|TARGET|DIMENSION[ ]*\(|"
@@ -82,22 +81,22 @@ class FortranRegularExpressions:
8281
)
8382
PARAMETER_VAL: Pattern = compile(r"\w*[\s\&]*=[\s\&]*([\w\.\*\-\+\\\'\"]*)", I)
8483
TATTR_LIST: Pattern = compile(
85-
r"[ ]*,[ ]*(PUBLIC|PRIVATE|ABSTRACT|EXTENDS\([a-z0-9_]*\))", I
84+
r"[ ]*,[ ]*(PUBLIC|PRIVATE|ABSTRACT|EXTENDS\(\w*\))", I
8685
)
8786
VIS: Pattern = compile(r"[ ]*\b(PUBLIC|PRIVATE)\b", I)
88-
WORD: Pattern = compile(r"[a-z_][a-z0-9_]*", I)
87+
WORD: Pattern = compile(r"[a-z_]\w*", I)
8988
NUMBER: Pattern = compile(
9089
r"[\+\-]?(\b\d+\.?\d*|\.\d+)(_\w+|d[\+\-]?\d+|e[\+\-]?\d+(_\w+)?)?(?!\w)",
9190
I,
9291
)
9392
LOGICAL: Pattern = compile(r".true.|.false.", I)
94-
SUB_PAREN: Pattern = compile(r"\([a-z0-9_, ]*\)", I)
95-
# KIND_SPEC_MATCH: Pattern = compile(r"\([a-z0-9_, =*]*\)", I)
93+
SUB_PAREN: Pattern = compile(r"\([\w, ]*\)", I)
94+
# KIND_SPEC_MATCH: Pattern = compile(r"\([\w, =*]*\)", I)
9695

9796
SQ_STRING: Pattern = compile(r"\'[^\']*\'", I)
9897
DQ_STRING: Pattern = compile(r"\"[^\"]*\"", I)
9998
LINE_LABEL: Pattern = compile(r"[ ]*([0-9]+)[ ]+", I)
100-
NON_DEF: Pattern = compile(r"[ ]*(CALL[ ]+[a-z_]|[a-z_][a-z0-9_%]*[ ]*=)", I)
99+
NON_DEF: Pattern = compile(r"[ ]*(CALL[ ]+[a-z_]|[a-z_][\w%]*[ ]*=)", I)
101100
# Fixed format matching rules
102101
FIXED_COMMENT: Pattern = compile(r"([!cd*])", I)
103102
FIXED_CONT: Pattern = compile(r"( {5}[\S])")
@@ -110,14 +109,14 @@ class FortranRegularExpressions:
110109
FREE_OPENMP: Pattern = compile(r"[ ]*!\$OMP", I)
111110
FREE_FORMAT_TEST: Pattern = compile(r"[ ]{1,4}[a-z]", I)
112111
# Preprocessor matching rules
113-
DEFINED: Pattern = compile(r"defined[ ]*\(?[ ]*([a-z_][a-z0-9_]*)[ ]*\)?", I)
112+
DEFINED: Pattern = compile(r"defined[ ]*\(?[ ]*([a-z_]\w*)[ ]*\)?", I)
114113
PP_REGEX: Pattern = compile(r"#(if |ifdef|ifndef|else|elif|endif)")
115114
PP_DEF: Pattern = compile(r"#(define|undef)[ ]*([\w]+)(\((\w+(,[ ]*)?)+\))?", I)
116-
PP_DEF_TEST: Pattern = compile(r"(![ ]*)?defined[ ]*\([ ]*([a-z0-9_]*)[ ]*\)$", I)
117-
PP_INCLUDE: Pattern = compile(r"#include[ ]*([\"a-z0-9_\.]*)", I)
115+
PP_DEF_TEST: Pattern = compile(r"(![ ]*)?defined[ ]*\([ ]*(\w*)[ ]*\)$", I)
116+
PP_INCLUDE: Pattern = compile(r"#include[ ]*([\"\w\.]*)", I)
118117
PP_ANY: Pattern = compile(r"(^#:?\w+)")
119118
# Context matching rules
120-
CALL: Pattern = compile(r"[ ]*CALL[ ]+[a-z0-9_%]*$", I)
119+
CALL: Pattern = compile(r"[ ]*CALL[ ]+[\w%]*$", I)
121120
INT_STMNT: Pattern = compile(r"^[ ]*[a-z]*$", I)
122121
TYPE_STMNT: Pattern = compile(r"[ ]*(TYPE|CLASS)[ ]*(IS)?[ ]*$", I)
123122
PROCEDURE_STMNT: Pattern = compile(r"[ ]*(PROCEDURE)[ ]*$", I)

0 commit comments

Comments
 (0)