Skip to content

Commit 4f7bc5c

Browse files
gnikitAljenU
authored andcommitted
refactor: preprocessor elif test
1 parent a1645e6 commit 4f7bc5c

File tree

5 files changed

+118
-132
lines changed

5 files changed

+118
-132
lines changed

test/test_preproc.py

Lines changed: 11 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -34,13 +34,14 @@ def check_return(result_array, checks):
3434
string += hover_req(file_path, 8, 12)
3535
string += hover_req(file_path, 18, 12)
3636
file_path = root_dir / "preproc_elif.F90"
37-
string += hover_req(file_path, 15, 12)
38-
string += hover_req(file_path, 19, 15)
39-
string += hover_req(file_path, 21, 10)
40-
string += hover_req(file_path, 46, 36)
41-
string += hover_req(file_path, 76, 36)
42-
string += hover_req(file_path, 106, 36)
43-
string += hover_req(file_path, 136, 36)
37+
string += hover_req(file_path, 22, 15)
38+
string += hover_req(file_path, 24, 10)
39+
file_path = root_dir / "preproc_elif_elif_skip.F90"
40+
string += hover_req(file_path, 30, 23)
41+
file_path = root_dir / "preproc_if_elif_else.F90"
42+
string += hover_req(file_path, 30, 23)
43+
file_path = root_dir / "preproc_if_elif_skip.F90"
44+
string += hover_req(file_path, 30, 23)
4445
config = str(root_dir / ".pp_conf.json")
4546
errcode, results = run_request(string, ["--config", config])
4647
assert errcode == 0
@@ -62,13 +63,11 @@ def check_return(result_array, checks):
6263
"```fortran90\nREAL, CONTIGUOUS, POINTER, DIMENSION(:) :: var1\n```",
6364
"```fortran90\nINTEGER :: var0\n```",
6465
"```fortran90\nREAL :: var1\n```",
65-
"```fortran90\nLOGICAL :: var1\n```",
6666
"```fortran90\nINTEGER :: var2\n```",
6767
"```fortran90\nINTEGER, INTENT(INOUT) :: var\n```",
68-
"```fortran90\nREAL(1, 5, 5, 5) :: var3\n```",
69-
"```fortran90\nREAL(5, 2, 5, 5) :: var4\n```",
70-
"```fortran90\nREAL(5, 5, 5, 4) :: var5\n```",
71-
"```fortran90\nREAL(1, 5, 5, 5) :: var6\n```",
68+
"```fortran90\nINTEGER, PARAMETER :: res = 0+1+0+0\n```",
69+
"```fortran90\nINTEGER, PARAMETER :: res = 0+0+0+1\n```",
70+
"```fortran90\nINTEGER, PARAMETER :: res = 1+0+0+0\n```",
7271
)
7372
assert len(ref_results) == len(results) - 1
7473
check_return(results[1:], ref_results)

test/test_source/pp/preproc_elif.F90

Lines changed: 8 additions & 120 deletions
Original file line numberDiff line numberDiff line change
@@ -1,139 +1,27 @@
11
subroutine preprocessor_elif(var, var3, var4, var5, var6)
22

3+
! This file, as used in test_preproc, checks that
4+
! 1. the steps after the preprocessor parsing has fully finished, are only
5+
! using content from the parts within the preprocessor if-elif-else that
6+
! should be used. To do this, it has some regular fortran code within the
7+
! #if and #elif.
8+
! 2. the #endif correctly concludes the if-elif, so any new #define statements
9+
! that come after the #endif, are picked up during the preprocessor parsing.
10+
311
#if 0
4-
#define MYTYPE character
512
integer, intent(in) :: var
613
#elif 1
7-
#define MYTYPE logical
814
integer, intent(inout) :: var
915
var = 3
1016
#else
11-
#define MYTYPE integer
1217
integer, intent(out) :: var
1318
var = 5
1419
#endif
1520

16-
MYTYPE :: var1
17-
1821
#define OTHERTYPE integer
1922

2023
OTHERTYPE :: var2
2124

2225
PRINT*, var
2326

24-
#if 1
25-
#define PART1 1,
26-
#elif 0
27-
#define PART2 2,
28-
#elif 1
29-
#define PART3 3,
30-
#else
31-
#define PART4 4
32-
#endif
33-
34-
#ifndef PART1
35-
#define PART1 5,
36-
#endif
37-
#ifndef PART2
38-
#define PART2 5,
39-
#endif
40-
#ifndef PART3
41-
#define PART3 5,
42-
#endif
43-
#ifndef PART4
44-
#define PART4 5
45-
#endif
46-
47-
REAL(PART1 PART2 PART3 PART4) :: var3
48-
49-
#undef PART1
50-
#undef PART2
51-
#undef PART3
52-
#undef PART4
53-
54-
#if 0
55-
#define PART1 1,
56-
#elif 1
57-
#define PART2 2,
58-
#elif 1
59-
#define PART3 3,
60-
#else
61-
#define PART4 4
62-
#endif
63-
64-
#ifndef PART1
65-
#define PART1 5,
66-
#endif
67-
#ifndef PART2
68-
#define PART2 5,
69-
#endif
70-
#ifndef PART3
71-
#define PART3 5,
72-
#endif
73-
#ifndef PART4
74-
#define PART4 5
75-
#endif
76-
77-
REAL(PART1 PART2 PART3 PART4) :: var4
78-
79-
#undef PART1
80-
#undef PART2
81-
#undef PART3
82-
#undef PART4
83-
84-
#if 0
85-
#define PART1 1,
86-
#elif 0
87-
#define PART2 2,
88-
#elif 0
89-
#define PART3 3,
90-
#else
91-
#define PART4 4
92-
#endif
93-
94-
#ifndef PART1
95-
#define PART1 5,
96-
#endif
97-
#ifndef PART2
98-
#define PART2 5,
99-
#endif
100-
#ifndef PART3
101-
#define PART3 5,
102-
#endif
103-
#ifndef PART4
104-
#define PART4 5
105-
#endif
106-
107-
REAL(PART1 PART2 PART3 PART4) :: var5
108-
109-
#undef PART1
110-
#undef PART2
111-
#undef PART3
112-
#undef PART4
113-
114-
#if 1
115-
#define PART1 1,
116-
#elif 1
117-
#define PART2 2,
118-
#elif 0
119-
#define PART3 3,
120-
#else
121-
#define PART4 4
122-
#endif
123-
124-
#ifndef PART1
125-
#define PART1 5,
126-
#endif
127-
#ifndef PART2
128-
#define PART2 5,
129-
#endif
130-
#ifndef PART3
131-
#define PART3 5,
132-
#endif
133-
#ifndef PART4
134-
#define PART4 5
135-
#endif
136-
137-
REAL(PART1 PART2 PART3 PART4) :: var6
138-
13927
endsubroutine preprocessor_elif
Lines changed: 33 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,33 @@
1+
subroutine preprocessor_elif_elif_skip()
2+
3+
! This file, as used in test_preproc, and together with the two similar files,
4+
! tests that when there is an if-elif-elif-else, only the first branch that
5+
! evaluates to true is used, and the others ignored. Also when multiple
6+
! conditions evaluate to true.
7+
8+
#if 0
9+
#define PART1 0
10+
#elif 1
11+
#define PART2 1
12+
#elif 1
13+
#define PART3 0
14+
#else
15+
#define PART4 0
16+
#endif
17+
18+
#ifndef PART1
19+
#define PART1 0
20+
#endif
21+
#ifndef PART2
22+
#define PART2 0
23+
#endif
24+
#ifndef PART3
25+
#define PART3 0
26+
#endif
27+
#ifndef PART4
28+
#define PART4 0
29+
#endif
30+
31+
integer, parameter :: res = PART1+PART2+PART3+PART4
32+
33+
end subroutine preprocessor_elif_elif_skip
Lines changed: 33 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,33 @@
1+
subroutine preprocessor_if_elif_else()
2+
3+
! This file, as used in test_preproc, and together with the two similar files,
4+
! tests that when there is an if-elif-elif-else, only the first branch that
5+
! evaluates to true is used, and the others ignored. Also when multiple
6+
! conditions evaluate to true.
7+
8+
#if 0
9+
#define PART1 0
10+
#elif 0
11+
#define PART2 0
12+
#elif 0
13+
#define PART3 0
14+
#else
15+
#define PART4 1
16+
#endif
17+
18+
#ifndef PART1
19+
#define PART1 0
20+
#endif
21+
#ifndef PART2
22+
#define PART2 0
23+
#endif
24+
#ifndef PART3
25+
#define PART3 0
26+
#endif
27+
#ifndef PART4
28+
#define PART4 0
29+
#endif
30+
31+
integer, parameter :: res = PART1+PART2+PART3+PART4
32+
33+
endsubroutine preprocessor_if_elif_else
Lines changed: 33 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,33 @@
1+
subroutine preprocessor_if_elif_skip()
2+
3+
! This file, as used in test_preproc, and together with the two similar files,
4+
! tests that when there is an if-elif-elif-else, only the first branch that
5+
! evaluates to true is used, and the others ignored. Also when multiple
6+
! conditions evaluate to true.
7+
8+
#if 1
9+
#define PART1 1
10+
#elif 0
11+
#define PART2 0
12+
#elif 1
13+
#define PART3 0
14+
#else
15+
#define PART4 0
16+
#endif
17+
18+
#ifndef PART1
19+
#define PART1 0
20+
#endif
21+
#ifndef PART2
22+
#define PART2 0
23+
#endif
24+
#ifndef PART3
25+
#define PART3 0
26+
#endif
27+
#ifndef PART4
28+
#define PART4 0
29+
#endif
30+
31+
integer, parameter :: res = PART1+PART2+PART3+PART4
32+
33+
end subroutine preprocessor_if_elif_skip

0 commit comments

Comments
 (0)