Skip to content

Commit 53dfdbf

Browse files
authored
Merge pull request #14 from dbroemmel/master
some minor changes
2 parents 16b3b8b + 7c4fa75 commit 53dfdbf

File tree

5 files changed

+161
-18
lines changed

5 files changed

+161
-18
lines changed
Lines changed: 57 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,57 @@
1+
module a_mod
2+
integer :: a_variable, another_variable
3+
4+
private :: a_variable, &
5+
another_variable
6+
contains
7+
8+
subroutine test_type(bohoo)
9+
class(*), intent(in) :: bohoo
10+
11+
select type (bohoo)
12+
type is (real)
13+
write (*, *) 'T'
14+
type is (integer)
15+
write (*, *) 'F'
16+
class default
17+
end select
18+
19+
return
20+
21+
end subroutine test_type
22+
23+
end module a_mod
24+
25+
program test
26+
use a_mod
27+
28+
integer :: block_test = 2, block = 2
29+
real :: res, factor = 2.81
30+
31+
namelist /test_nml/ block, block_test, res, factor
32+
33+
block = 5
34+
35+
block
36+
real :: another_real
37+
another_real = 4.5
38+
end block
39+
40+
call test_type(block)
41+
42+
block ! have more vars
43+
real :: block
44+
call test_type(block)
45+
end block
46+
47+
block = block*5/block_test + 1
48+
! whitespace 2
49+
! res = factor*5/block_test + 1
50+
res = factor*5/block_test + 1
51+
! whitespace 3
52+
! res = factor * 5 / block_test + 1
53+
res = factor*5/block_test + 1
54+
55+
stop
56+
57+
end program test
Lines changed: 57 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,57 @@
1+
module a_mod
2+
integer :: a_variable, another_variable
3+
4+
private :: a_variable, &
5+
another_variable
6+
contains
7+
8+
subroutine test_type(bohoo)
9+
class(*), intent(in) :: bohoo
10+
11+
select type(bohoo)
12+
type is(real)
13+
write(*,*) 'T'
14+
type is(integer)
15+
write(*,*) 'F'
16+
class default
17+
end select
18+
19+
return
20+
21+
end subroutine test_type
22+
23+
end module a_mod
24+
25+
program test
26+
use a_mod
27+
28+
integer :: block_test=2, block = 2
29+
real :: res, factor = 2.81
30+
31+
namelist/test_nml/block, block_test, res, factor
32+
33+
block = 5
34+
35+
block
36+
real :: another_real
37+
another_real = 4.5
38+
end block
39+
40+
call test_type(block)
41+
42+
block ! have more vars
43+
real :: block
44+
call test_type(block)
45+
end block
46+
47+
block = block*5/block_test+1
48+
! whitespace 2
49+
! res = factor*5/block_test + 1
50+
res = factor*5/block_test + 1
51+
! whitespace 3
52+
! res = factor * 5 / block_test + 1
53+
res = factor * 5 / block_test + 1
54+
55+
stop
56+
57+
end program test

fortran_tests/test_results/expected_results

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1917,15 +1917,15 @@ RosettaCodeData/Task/Accumulator-factory/Fortran/accumulator-factory-2.f : 06ff1
19171917
RosettaCodeData/Task/Arithmetic-Rational/Fortran/arithmetic-rational-1.f : d9798ac7d48984a81e6066f955431b6b1147c4a23676e2ce9161d6491a36c234
19181918
RosettaCodeData/Task/Classes/Fortran/classes.f : ab23f3823fb82e0ffff96b869f2aca7c2515db18add95104f4be86c881692d74
19191919
RosettaCodeData/Task/Constrained-genericity/Fortran/constrained-genericity.f : a2ddcb9eefef24be8475b19015a323a09a5245b7a0325faab6f14cd5d8c99232
1920-
RosettaCodeData/Task/Define-a-primitive-data-type/Fortran/define-a-primitive-data-type-1.f : a61ce7b5d3641ca7f223a03229a31cc8feb6d8aa473d827df5bf0a85baea6af7
1920+
RosettaCodeData/Task/Define-a-primitive-data-type/Fortran/define-a-primitive-data-type-1.f : 615b5f17286283068720f211d282558d186b9a7af06076739fea0a4e90898f18
19211921
RosettaCodeData/Task/Exponentiation-operator/Fortran/exponentiation-operator.f : 9dd247f51e19e4c445522b7577368fe009003524bec66ed3f2efbfb58d8e8fed
19221922
RosettaCodeData/Task/Fibonacci-sequence/Fortran/fibonacci-sequence-4.f : 758c9f5caeed8b02a4b54ec8c207c8bc70f2a92065455c76978b487d1fa8566d
19231923
RosettaCodeData/Task/Grayscale-image/Fortran/grayscale-image-3.f : ed4d53de1d0437d3fbc830ac7b75a48dd373f181183cbb35dc0c1fa2b23569cd
19241924
RosettaCodeData/Task/LU-decomposition/Fortran/lu-decomposition.f : 900a20c9ca96f7b3e019496fcda8396138061c6c28e796174eb08d7f86d9c80e
19251925
RosettaCodeData/Task/Long-multiplication/Fortran/long-multiplication-1.f : acbc61418d79d708837c1dd7780007bca8de3390e5474c5c3de7c4e6abf04f2e
19261926
RosettaCodeData/Task/Matrix-exponentiation-operator/Fortran/matrix-exponentiation-operator.f : a45ce9e65278545613d72f1cea16406f5484ec12ad5e721fdc4e9ab83c1f27ce
19271927
RosettaCodeData/Task/Polymorphic-copy/Fortran/polymorphic-copy.f : a5a9a5568a06157d085f5f1879a6b91bd1d102a0a63951ba451bda00fe2d702c
1928-
RosettaCodeData/Task/Quaternion-type/Fortran/quaternion-type.f : 734e5c5479150979cd2a48874dcde06903b708434cd81dcb9cdba3eda9f064e6
1928+
RosettaCodeData/Task/Quaternion-type/Fortran/quaternion-type.f : a331a9ff10e9cbc8b2d5fbdbbd56e2540a555a029aac61425250bed548fc28ab
19291929
FLAP/src/lib/flap.f90 : d8c91241624cf28e1cf1d5c2ba70b775a7bcfd3221d81e8697baf55532375f51
19301930
FLAP/src/lib/flap_command_line_argument_t.F90 : 763c6a6142ba8383518e84f5d088796c6cf3818d1ed97d11060957b11bfee767
19311931
FLAP/src/lib/flap_command_line_arguments_group_t.f90 : b0dec2d7c0174753bb2047bcf63e1e0392cbf929c9c6dade8a5cd63e70338420
@@ -1939,3 +1939,4 @@ FLAP/src/tests/test_hidden.f90 : 1fecd3c5a4844898f4fb5019c37a81f7bb1ef5340e79e02
19391939
FLAP/src/tests/test_minimal.f90 : 9ba58554d1e477b40ea311497e95099d064d4b46b9df6ff2ddbbc5f9fcaed885
19401940
FLAP/src/tests/test_nested.f90 : e6adb6a29770988006c6c83d0eb6572433882724a0bae51f47778899afc3e508
19411941
FLAP/src/tests/test_string.f90 : 7e1bce103b0997861d072ab1a506bf70db9eb29b7ab8867ff415b855aadf1f54
1942+
another_example.f90 : 90257fe1108c8689002b470e2e2620c2a0652ca6465ba1a5bbbd6667e2339be0

fprettify/__init__.py

Lines changed: 41 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -107,12 +107,15 @@
107107
SELCASE_RE = re.compile(
108108
SOL_STR + r"SELECT\s*(CASE|TYPE)\s*\(.+\)" + EOL_STR, RE_FLAGS)
109109
CASE_RE = re.compile(
110-
SOL_STR + r"(CASE|TYPE\s+IS|CLASS\s+IS)\s*(\(.+\)|DEFAULT)" + EOL_STR, RE_FLAGS)
110+
SOL_STR + r"((CASE|TYPE\s+IS|CLASS\s+IS)\s*(\(.+\)|DEFAULT)|CLASS\s+DEFAULT)" + EOL_STR, RE_FLAGS)
111111
ENDSEL_RE = re.compile(SOL_STR + r"END\s*SELECT" + EOL_STR, RE_FLAGS)
112112

113113
ASSOCIATE_RE = re.compile(SOL_STR + r"ASSOCIATE\s*\(.+\)" + EOL_STR, RE_FLAGS)
114114
ENDASSOCIATE_RE = re.compile(SOL_STR + r"END\s*ASSOCIATE" + EOL_STR, RE_FLAGS)
115115

116+
BLK_RE = re.compile(SOL_STR + r"(\w+\s*:)?\s*BLOCK" + EOL_STR, RE_FLAGS)
117+
ENDBLK_RE = re.compile(SOL_STR + r"END\s*BLOCK(\s+\w+)?" + EOL_STR, RE_FLAGS)
118+
116119
SUBR_RE = re.compile(
117120
r"^([^\"'!]* )?SUBROUTINE\s+\w+\s*(\(.*\))?" + EOL_STR, RE_FLAGS)
118121
ENDSUBR_RE = re.compile(
@@ -151,6 +154,7 @@
151154

152155
ENDANY_RE = re.compile(SOL_STR + r"END" + EOL_STR, RE_FLAGS)
153156

157+
PRIVATE_RE = re.compile(SOL_STR + r"PRIVATE\s*::", RE_FLAGS)
154158
PUBLIC_RE = re.compile(SOL_STR + r"PUBLIC\s*::", RE_FLAGS)
155159

156160
# intrinsic statements with parenthesis notation that are not functions
@@ -165,6 +169,9 @@
165169
# Note: +/- in real literals and sign operator is ignored
166170
PLUSMINUS_RE = re.compile(
167171
r"(?<=[\w\)\]])(?<![\d\.]\w)\s*(\+|-)\s*", RE_FLAGS)
172+
# Note: ** or // (or any multiples of * or /) are ignored
173+
MULTDIV_RE = re.compile(
174+
r"(?<=[\w\)\]])\s*((?<!\*)\*(?!\*)|(?<!/)/(?!/))(?=[\s\w\(])", RE_FLAGS)
168175
REL_OP_RE = re.compile(
169176
r"(?<!\()\s*(\.(?:EQ|NE|LT|LE|GT|GE)\.|(?:==|\/=|<(?!=)|<=|(?<!=)>(?!=)|>=))\s*(?!\))",
170177
RE_FLAGS)
@@ -181,7 +188,7 @@
181188
EMPTY_RE = re.compile(SOL_STR + r"([!#].*)?$", RE_FLAGS)
182189

183190
# two-sided operators
184-
LR_OPS_RE = [REL_OP_RE, LOG_OP_RE, PLUSMINUS_RE, PRINT_RE]
191+
LR_OPS_RE = [REL_OP_RE, LOG_OP_RE, PLUSMINUS_RE, MULTDIV_RE, PRINT_RE]
185192

186193
USE_RE = re.compile(
187194
SOL_STR + "USE(\s+|(,.+?)?::\s*)\w+?((,.+?=>.+?)+|,\s*only\s*:.+?)?$" + EOL_STR, RE_FLAGS)
@@ -191,12 +198,17 @@
191198

192199
# combine regex that define subunits
193200
NEW_SCOPE_RE = [IF_RE, DO_RE, SELCASE_RE, SUBR_RE,
194-
FCT_RE, MOD_RE, PROG_RE, INTERFACE_RE, TYPE_RE, ENUM_RE, ASSOCIATE_RE, None]
201+
FCT_RE, MOD_RE, PROG_RE, INTERFACE_RE, TYPE_RE, ENUM_RE, ASSOCIATE_RE, None, BLK_RE]
195202
CONTINUE_SCOPE_RE = [ELSE_RE, None, CASE_RE, CONTAINS_RE,
196-
CONTAINS_RE, CONTAINS_RE, CONTAINS_RE, None, CONTAINS_RE, None, None, None]
203+
CONTAINS_RE, CONTAINS_RE, CONTAINS_RE, None, CONTAINS_RE, None, None, None, None]
197204
END_SCOPE_RE = [ENDIF_RE, ENDDO_RE, ENDSEL_RE, ENDSUBR_RE,
198-
ENDFCT_RE, ENDMOD_RE, ENDPROG_RE, ENDINTERFACE_RE, ENDTYPE_RE, ENDENUM_RE, ENDASSOCIATE_RE, ENDANY_RE]
205+
ENDFCT_RE, ENDMOD_RE, ENDPROG_RE, ENDINTERFACE_RE, ENDTYPE_RE, ENDENUM_RE, ENDASSOCIATE_RE, ENDANY_RE, ENDBLK_RE]
199206

207+
# match namelist names
208+
NML_RE = re.compile(r"(/\w+/)", RE_FLAGS)
209+
# find namelists and data statements
210+
NML_STMT_RE = re.compile(SOL_STR + r"NAMELIST.*/.*/", RE_FLAGS)
211+
DATA_STMT_RE = re.compile(SOL_STR + r"DATA\s+\w", RE_FLAGS)
200212

201213
class F90Indenter(object):
202214
"""
@@ -394,7 +406,7 @@ def process_lines_of_fline(self, f_line, lines, rel_ind, line_nr):
394406

395407
self.__init_line(line_nr)
396408

397-
is_decl = VAR_DECL_RE.search(f_line) or PUBLIC_RE.search(f_line)
409+
is_decl = VAR_DECL_RE.search(f_line) or PUBLIC_RE.search(f_line) or PRIVATE_RE.match(f_line)
398410
for pos, line in enumerate(lines):
399411
self.__align_line_continuations(
400412
line, is_decl, rel_ind, self._line_nr + pos)
@@ -566,7 +578,7 @@ def format_single_fline(f_line, whitespace, linebreak_pos, ampersand_sep,
566578
separating whitespace characters before ampersand (`ampersand_sep`).
567579
`filename` and `line_nr` just for error messages.
568580
The higher `whitespace`, the more white space characters inserted -
569-
whitespace = 0, 1, 2 are currently supported.
581+
whitespace = 0, 1, 2, 3 are currently supported.
570582
auto formatting can be turned off by setting `auto_format` to False.
571583
"""
572584

@@ -576,14 +588,17 @@ def format_single_fline(f_line, whitespace, linebreak_pos, ampersand_sep,
576588
# 2: relational operators
577589
# 3: logical operators
578590
# 4: arithm. operators plus and minus
579-
# 5: print / read statements
591+
# 5: arithm. operators multiply and divide
592+
# 6: print / read statements
580593

581594
if whitespace == 0:
582-
spacey = [0, 0, 0, 0, 0, 0]
595+
spacey = [0, 0, 0, 0, 0, 0, 0]
583596
elif whitespace == 1:
584-
spacey = [1, 1, 1, 1, 0, 1]
597+
spacey = [1, 1, 1, 1, 0, 0, 1]
585598
elif whitespace == 2:
586-
spacey = [1, 1, 1, 1, 1, 1]
599+
spacey = [1, 1, 1, 1, 1, 0, 1]
600+
elif whitespace == 3:
601+
spacey = [1, 1, 1, 1, 1, 1, 1]
587602
else:
588603
raise NotImplementedError("unknown value for whitespace")
589604

@@ -668,6 +683,8 @@ def add_whitespace_charwise(line, spacey, filename, line_nr):
668683
line[:pos], RE_FLAGS) or
669684
re.search(SOL_STR + r"SELECT\s*TYPE\s*",
670685
line[:pos], RE_FLAGS) or
686+
re.search(SOL_STR + r"CLASS\s*DEFAULT\s*",
687+
line[:pos], RE_FLAGS) or
671688
re.search(SOL_STR + r"(TYPE|CLASS)\s+IS\s*",
672689
line[:pos], RE_FLAGS) or
673690
re.search(r"\b" + INTR_STMTS_PAR + r"\s*$",
@@ -764,13 +781,23 @@ def add_whitespace_context(line, spacey):
764781
if pos == len(line) - 1:
765782
line_parts.append(line[str_end + 1:])
766783

784+
# format namelists with spaces around /
785+
if NML_STMT_RE.match(line):
786+
for pos, part in enumerate(line_parts):
787+
# exclude comments, strings:
788+
if not re.match(r"['\"!]", part, RE_FLAGS):
789+
partsplit = NML_RE.split(part)
790+
line_parts[pos] = (' '.join(partsplit))
791+
767792
# Two-sided operators
768793
for n_op, lr_re in enumerate(LR_OPS_RE):
769794
for pos, part in enumerate(line_parts):
770795
# exclude comments, strings:
771796
if not re.search(r"^['\"!]", part, RE_FLAGS):
772-
partsplit = lr_re.split(part)
773-
line_parts[pos] = (' ' * spacey[n_op + 2]).join(partsplit)
797+
# also exclude / if we see a namelist and data statement
798+
if not ( NML_STMT_RE.match(line) or DATA_STMT_RE.match(line) ):
799+
partsplit = lr_re.split(part)
800+
line_parts[pos] = (' ' * spacey[n_op + 2]).join(partsplit)
774801

775802
line = ''.join(line_parts)
776803

@@ -1216,7 +1243,7 @@ def run(argv=sys.argv): # pragma: no cover
12161243
parser.add_argument("-i", "--indent", type=int, default=3,
12171244
help="relative indentation width")
12181245
parser.add_argument("-w", "--whitespace", type=int,
1219-
choices=range(0, 3), default=2, help="Amount of whitespace")
1246+
choices=range(0, 4), default=2, help="Amount of whitespace")
12201247
parser.add_argument("-s", "--stdout", action='store_true', default=False,
12211248
help="Write to stdout instead of formatting inplace")
12221249

fprettify/tests/__init__.py

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -124,10 +124,11 @@ def test_whitespace(self):
124124
instring = "(/-a-b-(a+b-c)/(-c)*d**e,f[1]%v/)"
125125
outstring_exp = ["(/-a-b-(a+b-c)/(-c)*d**e,f[1]%v/)",
126126
"(/-a-b-(a+b-c)/(-c)*d**e, f[1]%v/)",
127-
"(/-a - b - (a + b - c)/(-c)*d**e, f[1]%v/)"]
127+
"(/-a - b - (a + b - c)/(-c)*d**e, f[1]%v/)",
128+
"(/-a - b - (a + b - c) / (-c) * d**e, f[1]%v/)"]
128129

129130
outstring = []
130-
for w, out in zip(range(0, 3), outstring_exp):
131+
for w, out in zip(range(0, 4), outstring_exp):
131132
args = ['-w', str(w)]
132133
self.assert_fprettify_result(args, instring, out)
133134

0 commit comments

Comments
 (0)