@@ -5,7 +5,7 @@ module fpm_meta_base
5
5
use fpm_command_line, only: fpm_cmd_settings, fpm_run_settings
6
6
use fpm_manifest_dependency, only: dependency_config_t
7
7
use fpm_manifest, only: package_config_t
8
- use fpm_strings, only: string_t, len_trim
8
+ use fpm_strings, only: string_t, len_trim, split, join
9
9
10
10
implicit none
11
11
@@ -111,30 +111,30 @@ subroutine resolve_model(self,model,error)
111
111
112
112
! Add global build flags, to apply to all sources
113
113
if (self% has_build_flags) then
114
- model % fortran_compile_flags = model% fortran_compile_flags// self% flags% s
115
- model % c_compile_flags = model% c_compile_flags// self% flags% s
116
- model % cxx_compile_flags = model% cxx_compile_flags// self% flags% s
114
+ call append_flags_without_duplicates( model% fortran_compile_flags, self% flags% s)
115
+ call append_flags_without_duplicates( model% c_compile_flags, self% flags% s)
116
+ call append_flags_without_duplicates( model% cxx_compile_flags, self% flags% s)
117
117
endif
118
118
119
119
! Add language-specific flags
120
- if (self% has_fortran_flags) model % fortran_compile_flags = model% fortran_compile_flags// self% fflags% s
121
- if (self% has_c_flags) model % c_compile_flags = model% c_compile_flags// self% cflags% s
122
- if (self% has_cxx_flags) model % cxx_compile_flags = model% cxx_compile_flags// self% cxxflags% s
120
+ if (self% has_fortran_flags) call append_flags_without_duplicates( model% fortran_compile_flags, self% fflags% s)
121
+ if (self% has_c_flags) call append_flags_without_duplicates( model% c_compile_flags, self% cflags% s)
122
+ if (self% has_cxx_flags) call append_flags_without_duplicates( model% cxx_compile_flags, self% cxxflags% s)
123
123
124
124
if (self% has_link_flags) then
125
- model % link_flags = model% link_flags// ' ' // self% link_flags% s
125
+ call append_flags_without_duplicates( model% link_flags, self% link_flags% s)
126
126
end if
127
127
128
128
if (self% has_link_libraries) then
129
- model % link_libraries = [ model% link_libraries,self% link_libs]
129
+ call append_array_without_duplicates( model% link_libraries, self% link_libs)
130
130
end if
131
131
132
132
if (self% has_include_dirs) then
133
- model % include_dirs = [ model% include_dirs,self% incl_dirs]
133
+ call append_array_without_duplicates( model% include_dirs, self% incl_dirs)
134
134
end if
135
135
136
136
if (self% has_external_modules) then
137
- model % external_modules = [ model% external_modules,self% external_modules]
137
+ call append_array_without_duplicates( model% external_modules, self% external_modules)
138
138
end if
139
139
140
140
end subroutine resolve_model
@@ -185,6 +185,72 @@ pure function dn(bool)
185
185
end if
186
186
end function dn
187
187
188
-
189
188
end subroutine resolve_package_config
189
+
190
+ subroutine append_flags_without_duplicates (flags , new_flags )
191
+ character (:), intent (inout ), allocatable :: flags
192
+ character (* ), intent (in ) :: new_flags
193
+
194
+ character (len= :), allocatable :: flags_array(:), new_flags_array(:)
195
+ type (string_t), allocatable :: flags_str_array(:), new_flags_str_array(:)
196
+ integer :: i, max_len
197
+
198
+ call split(flags, flags_array, " " )
199
+ call split(new_flags, new_flags_array, " " )
200
+
201
+ allocate (flags_str_array(size (flags_array, 1 )))
202
+ allocate (new_flags_str_array(size (new_flags_array, 1 )))
203
+ do i = 1 , size (flags_array)
204
+ flags_str_array(i) = string_t(flags_array(i))
205
+ end do
206
+ do i = 1 , size (new_flags_array)
207
+ new_flags_str_array(i) = string_t(new_flags_array(i))
208
+ end do
209
+
210
+ call append_array_without_duplicates(flags_str_array, new_flags_str_array)
211
+
212
+ max_len = 0
213
+ do i = 1 , size (flags_str_array)
214
+ max_len = max (max_len, len_trim (flags_str_array(i)% s))
215
+ end do
216
+ deallocate (flags_array)
217
+ allocate (character (len= max_len) :: flags_array(size (flags_str_array)))
218
+ do i = 1 , size (flags_str_array)
219
+ flags_array(i) = flags_str_array(i)% s
220
+ end do
221
+
222
+ flags = join(flags_array, " " )
223
+
224
+ end subroutine append_flags_without_duplicates
225
+
226
+ subroutine append_array_without_duplicates (str_array , new_elements )
227
+ type (string_t), allocatable , intent (inout ) :: str_array(:)
228
+ type (string_t), intent (in ) :: new_elements(:)
229
+ integer :: i
230
+
231
+ do i = 1 , size (new_elements)
232
+ if (contains_element(str_array, new_elements(i))) cycle
233
+ ! Filter out empty flags
234
+ if (new_elements(i)% s == " " ) cycle
235
+ if (new_elements(i)% s == " -l" ) cycle
236
+ if (new_elements(i)% s == " -L" ) cycle
237
+ if (new_elements(i)% s == " -I" ) cycle
238
+ if (new_elements(i)% s == " -J" ) cycle
239
+ str_array = [str_array, new_elements(i)]
240
+ end do
241
+ end subroutine append_array_without_duplicates
242
+
243
+ function contains_element (str_array , element )
244
+ logical :: contains_element
245
+ type (string_t), intent (in ) :: str_array(:), element
246
+ integer :: i
247
+
248
+ contains_element = .false.
249
+ do i = 1 , size (str_array)
250
+ if (str_array(i)% s == element% s) then
251
+ contains_element = .true.
252
+ exit
253
+ end if
254
+ end do
255
+ end function contains_element
190
256
end module fpm_meta_base
0 commit comments