16
16
! >
17
17
module fpm_source_parsing
18
18
use fpm_error, only: error_t, file_parse_error, fatal_error, file_not_found_error
19
- use fpm_strings, only: string_t, string_cat, len_trim, split, lower, str_ends_with, fnv_1a, is_fortran_name
19
+ use fpm_strings, only: string_t, string_cat, len_trim, split, lower, str_ends_with, fnv_1a, &
20
+ is_fortran_name, operator (.in .)
20
21
use fpm_model, only: srcfile_t, &
21
22
FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
22
23
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
@@ -31,6 +32,76 @@ module fpm_source_parsing
31
32
32
33
contains
33
34
35
+ ! > Start a CPP conditional block (active or inactive)
36
+ pure subroutine start_cpp_block (conditional_depth , inside_conditional_block , is_active )
37
+ integer , intent (inout ) :: conditional_depth
38
+ logical , intent (inout ) :: inside_conditional_block
39
+ logical , intent (in ) :: is_active
40
+
41
+ conditional_depth = conditional_depth + 1
42
+ if (conditional_depth == 1 ) then
43
+ inside_conditional_block = .not. is_active
44
+ end if
45
+ end subroutine start_cpp_block
46
+
47
+ ! > End a CPP conditional block
48
+ pure subroutine end_cpp_block (conditional_depth , inside_conditional_block )
49
+ integer , intent (inout ) :: conditional_depth
50
+ logical , intent (inout ) :: inside_conditional_block
51
+
52
+ conditional_depth = max (0 , conditional_depth - 1 )
53
+ if (conditional_depth == 0 ) then
54
+ inside_conditional_block = .false.
55
+ end if
56
+ end subroutine end_cpp_block
57
+
58
+ ! > Parse CPP conditional directive and determine if block should be active
59
+ function parse_cpp_condition (line , macros ) result(is_active)
60
+ character (* ), intent (in ) :: line
61
+ type (string_t), intent (in ) :: macros(:)
62
+ logical :: is_active
63
+ character (:), allocatable :: macro_name
64
+ integer :: start_pos, end_pos
65
+
66
+ is_active = .false.
67
+
68
+ if (index (line, ' #ifdef' ) == 1 ) then
69
+ ! #ifdef MACRO
70
+ start_pos = index (line, ' ' ) + 1
71
+ macro_name = trim (adjustl (line(start_pos:)))
72
+ is_active = macro_name .in . macros
73
+
74
+ elseif (index (line, ' #ifndef' ) == 1 ) then
75
+ ! #ifndef MACRO
76
+ start_pos = index (line, ' ' ) + 1
77
+ macro_name = trim (adjustl (line(start_pos:)))
78
+ is_active = .not. (macro_name .in . macros)
79
+
80
+ elseif (index (line, ' #if ' ) == 1 ) then
81
+ ! Handle various #if patterns
82
+ if (index (line, ' defined(' ) > 0 ) then
83
+ ! #if defined(MACRO) or #if !defined(MACRO)
84
+ start_pos = index (line, ' defined(' ) + 8
85
+ end_pos = index (line(start_pos:), ' )' ) - 1
86
+ if (end_pos > 0 ) then
87
+ macro_name = line(start_pos:start_pos + end_pos - 1 )
88
+ if (index (line, ' !defined(' ) > 0 ) then
89
+ is_active = .not. (macro_name .in . macros)
90
+ else
91
+ is_active = macro_name .in . macros
92
+ end if
93
+ end if
94
+ else
95
+ ! #if MACRO (simple macro check)
96
+ start_pos = 4 ! Skip "#if "
97
+ end_pos = len_trim (line)
98
+ macro_name = trim (adjustl (line(start_pos:end_pos)))
99
+ is_active = macro_name .in . macros
100
+ end if
101
+ end if
102
+
103
+ end function parse_cpp_condition
104
+
34
105
! > Parsing of free-form fortran source files
35
106
! >
36
107
! > The following statements are recognised and parsed:
@@ -127,24 +198,25 @@ function parse_f_source(f_filename,error,preprocess) result(f_source)
127
198
! Check for conditional compilation directives
128
199
if (index (file_lines_lower(i)% s,' #ifdef' ) == 1 .or. &
129
200
index (file_lines_lower(i)% s,' #ifndef' ) == 1 .or. &
130
- index (file_lines_lower(i)% s,' #if' ) == 1 ) then
201
+ index (file_lines_lower(i)% s,' #if ' ) == 1 ) then
131
202
132
- conditional_depth = conditional_depth + 1
133
- if (conditional_depth == 1 ) then
134
- inside_conditional_block = .true.
203
+ ! Determine if this conditional block should be active
204
+ if (present (preprocess) .and. allocated (preprocess% macros)) then
205
+ call start_cpp_block(conditional_depth, inside_conditional_block, &
206
+ parse_cpp_condition(file_lines_lower(i)% s, preprocess% macros))
207
+ else
208
+ ! No macros defined, treat all conditions as inactive
209
+ call start_cpp_block(conditional_depth, inside_conditional_block, .false. )
135
210
end if
136
211
137
212
elseif (index (file_lines_lower(i)% s,' #endif' ) == 1 ) then
138
213
139
- conditional_depth = max (0 , conditional_depth - 1 )
140
- if (conditional_depth == 0 ) then
141
- inside_conditional_block = .false.
142
- end if
214
+ call end_cpp_block(conditional_depth, inside_conditional_block)
143
215
144
216
elseif (index (file_lines_lower(i)% s,' #else' ) == 1 .or. &
145
217
index (file_lines_lower(i)% s,' #elif' ) == 1 ) then
146
218
! For simplicity, treat #else/#elif as keeping the conditional block active
147
- ! In a more sophisticated implementation, we would evaluate conditions
219
+ ! TODO: More sophisticated handling would flip the condition for #else
148
220
continue
149
221
150
222
end if
0 commit comments