Skip to content

Commit 670c67f

Browse files
committed
more gcc-15 array initializer fixes
1 parent c112e6f commit 670c67f

File tree

4 files changed

+240
-12
lines changed

4 files changed

+240
-12
lines changed

src/fpm_compile_commands.F90

Lines changed: 60 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,12 @@ module fpm_compile_commands
5858
interface compile_command_t
5959
module procedure cct_new
6060
end interface compile_command_t
61+
62+
!> Add compile commands to array (gcc-15 bug workaround)
63+
interface add_compile_command
64+
module procedure add_compile_command_one
65+
module procedure add_compile_command_many
66+
end interface add_compile_command
6167

6268
contains
6369

@@ -330,7 +336,7 @@ pure subroutine cct_register_object(self, command, error)
330336
type(error_t), allocatable, intent(out) :: error
331337

332338
if (allocated(self%command)) then
333-
self%command = [self%command, command]
339+
call add_compile_command(self%command, command)
334340
else
335341
allocate(self%command(1), source=command)
336342
end if
@@ -442,6 +448,57 @@ logical function cct_is_same(this,that)
442448
!> All checks passed!
443449
cct_is_same = .true.
444450

445-
end function cct_is_same
446-
451+
end function cct_is_same
452+
453+
!> Add one compile command to array with a loop (gcc-15 bug on array initializer)
454+
pure subroutine add_compile_command_one(list,new)
455+
type(compile_command_t), allocatable, intent(inout) :: list(:)
456+
type(compile_command_t), intent(in) :: new
457+
458+
integer :: i,n
459+
type(compile_command_t), allocatable :: tmp(:)
460+
461+
if (allocated(list)) then
462+
n = size(list)
463+
else
464+
n = 0
465+
end if
466+
467+
allocate(tmp(n+1))
468+
do i=1,n
469+
tmp(i) = list(i)
470+
end do
471+
tmp(n+1) = new
472+
call move_alloc(from=tmp,to=list)
473+
474+
end subroutine add_compile_command_one
475+
476+
!> Add multiple compile commands to array with a loop (gcc-15 bug on array initializer)
477+
pure subroutine add_compile_command_many(list,new)
478+
type(compile_command_t), allocatable, intent(inout) :: list(:)
479+
type(compile_command_t), intent(in) :: new(:)
480+
481+
integer :: i,n,add
482+
type(compile_command_t), allocatable :: tmp(:)
483+
484+
if (allocated(list)) then
485+
n = size(list)
486+
else
487+
n = 0
488+
end if
489+
490+
add = size(new)
491+
if (add == 0) return
492+
493+
allocate(tmp(n+add))
494+
do i=1,n
495+
tmp(i) = list(i)
496+
end do
497+
do i=1,add
498+
tmp(n+i) = new(i)
499+
end do
500+
call move_alloc(from=tmp,to=list)
501+
502+
end subroutine add_compile_command_many
503+
447504
end module fpm_compile_commands

src/fpm_sources.f90

Lines changed: 62 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -8,20 +8,26 @@ module fpm_sources
88
use fpm_model, only: srcfile_t, FPM_UNIT_PROGRAM
99
use fpm_filesystem, only: basename, canon_path, dirname, join_path, list_files, is_hidden_file
1010
use fpm_environment, only: get_os_type,OS_WINDOWS
11-
use fpm_strings, only: lower, str_ends_with, string_t, operator(.in.)
11+
use fpm_strings, only: lower, str_ends_with, string_t, operator(.in.), add_strings
1212
use fpm_source_parsing, only: parse_f_source, parse_c_source
1313
use fpm_manifest_executable, only: executable_config_t
1414
use fpm_manifest_preprocess, only: preprocess_config_t
1515
implicit none
1616

1717
private
1818
public :: add_sources_from_dir, add_executable_sources
19-
public :: get_exe_name_with_suffix
19+
public :: get_exe_name_with_suffix, add_srcfile
2020

2121
character(4), parameter :: fortran_suffixes(2) = [".f90", &
2222
".f "]
2323
character(4), parameter :: c_suffixes(4) = [".c ", ".h ", ".cpp", ".hpp"]
2424

25+
!> Add one or multiple source files to a source file array (gcc-15 bug workaround)
26+
interface add_srcfile
27+
module procedure add_srcfile_one
28+
module procedure add_srcfile_many
29+
end interface add_srcfile
30+
2531
contains
2632

2733
!> Wrapper to source parsing routines.
@@ -159,7 +165,7 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,with_f_
159165
if (.not.allocated(sources)) then
160166
sources = pack(dir_sources,.not.exclude_source)
161167
else
162-
sources = [sources, pack(dir_sources,.not.exclude_source)]
168+
call add_srcfile(sources, pack(dir_sources,.not.exclude_source))
163169
end if
164170

165171
end subroutine add_sources_from_dir
@@ -239,7 +245,7 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,with_f
239245
if (.not.allocated(sources)) then
240246
sources = [exe_source]
241247
else
242-
sources = [sources, exe_source]
248+
call add_srcfile(sources, exe_source)
243249
end if
244250

245251
end do exe_loop
@@ -274,7 +280,7 @@ subroutine get_executable_source_dirs(exe_dirs,executables)
274280
if (.not.allocated(exe_dirs)) then
275281
exe_dirs = dirs_temp(1:n)
276282
else
277-
exe_dirs = [exe_dirs,dirs_temp(1:n)]
283+
call add_strings(exe_dirs,dirs_temp(1:n))
278284
end if
279285

280286
end subroutine get_executable_source_dirs
@@ -296,4 +302,55 @@ function get_exe_name_with_suffix(source) result(suffixed)
296302

297303
end function get_exe_name_with_suffix
298304

305+
!> Add one source file to a source file array with a loop (gcc-15 bug on array initializer)
306+
pure subroutine add_srcfile_one(list,new)
307+
type(srcfile_t), allocatable, intent(inout) :: list(:)
308+
type(srcfile_t), intent(in) :: new
309+
310+
integer :: i,n
311+
type(srcfile_t), allocatable :: tmp(:)
312+
313+
if (allocated(list)) then
314+
n = size(list)
315+
else
316+
n = 0
317+
end if
318+
319+
allocate(tmp(n+1))
320+
do i=1,n
321+
tmp(i) = list(i)
322+
end do
323+
tmp(n+1) = new
324+
call move_alloc(from=tmp,to=list)
325+
326+
end subroutine add_srcfile_one
327+
328+
!> Add multiple source files to a source file array with a loop (gcc-15 bug on array initializer)
329+
pure subroutine add_srcfile_many(list,new)
330+
type(srcfile_t), allocatable, intent(inout) :: list(:)
331+
type(srcfile_t), intent(in) :: new(:)
332+
333+
integer :: i,n,add
334+
type(srcfile_t), allocatable :: tmp(:)
335+
336+
if (allocated(list)) then
337+
n = size(list)
338+
else
339+
n = 0
340+
end if
341+
342+
add = size(new)
343+
if (add == 0) return
344+
345+
allocate(tmp(n+add))
346+
do i=1,n
347+
tmp(i) = list(i)
348+
end do
349+
do i=1,add
350+
tmp(n+i) = new(i)
351+
end do
352+
call move_alloc(from=tmp,to=list)
353+
354+
end subroutine add_srcfile_many
355+
299356
end module fpm_sources

src/fpm_targets.f90

Lines changed: 60 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ module fpm_targets
4747
FPM_TARGET_SHARED, FPM_TARGET_NAME
4848
public build_target_t, build_target_ptr
4949
public targets_from_sources, resolve_module_dependencies
50-
public add_target, new_target, add_dependency, get_library_dirs
50+
public add_target, new_target, add_dependency, get_library_dirs, add_target_ptr
5151
public filter_library_targets, filter_executable_targets, filter_modules
5252

5353

@@ -156,6 +156,12 @@ module fpm_targets
156156
module procedure add_old_targets
157157
end interface
158158

159+
!> Add one or multiple build target pointers to array (gcc-15 bug workaround)
160+
interface add_target_ptr
161+
module procedure add_target_ptr_one
162+
module procedure add_target_ptr_many
163+
end interface add_target_ptr
164+
159165
contains
160166

161167
!> Target type name
@@ -699,7 +705,7 @@ subroutine add_old_targets(targets, add_targets)
699705
endassociate
700706
end do
701707

702-
targets = [targets, add_targets ]
708+
call add_target_ptr(targets, add_targets)
703709

704710
end subroutine add_old_targets
705711

@@ -723,7 +729,7 @@ subroutine add_dependency(target, dependency)
723729
end do
724730
if (dependency%output_name==target%output_name) return
725731

726-
target%dependencies = [target%dependencies, build_target_ptr(dependency)]
732+
call add_target_ptr(target%dependencies, build_target_ptr(dependency))
727733

728734
end subroutine add_dependency
729735

@@ -1545,4 +1551,55 @@ subroutine library_targets_to_deps(model, targets, target_ID)
15451551

15461552
end subroutine library_targets_to_deps
15471553

1554+
!> Add one build target pointer to array with a loop (gcc-15 bug on array initializer)
1555+
subroutine add_target_ptr_one(list,new)
1556+
type(build_target_ptr), allocatable, intent(inout) :: list(:)
1557+
type(build_target_ptr), intent(in) :: new
1558+
1559+
integer :: i,n
1560+
type(build_target_ptr), allocatable :: tmp(:)
1561+
1562+
if (allocated(list)) then
1563+
n = size(list)
1564+
else
1565+
n = 0
1566+
end if
1567+
1568+
allocate(tmp(n+1))
1569+
do i=1,n
1570+
tmp(i) = list(i)
1571+
end do
1572+
tmp(n+1) = new
1573+
call move_alloc(from=tmp,to=list)
1574+
1575+
end subroutine add_target_ptr_one
1576+
1577+
!> Add multiple build target pointers to array with a loop (gcc-15 bug on array initializer)
1578+
subroutine add_target_ptr_many(list,new)
1579+
type(build_target_ptr), allocatable, intent(inout) :: list(:)
1580+
type(build_target_ptr), intent(in) :: new(:)
1581+
1582+
integer :: i,n,add
1583+
type(build_target_ptr), allocatable :: tmp(:)
1584+
1585+
if (allocated(list)) then
1586+
n = size(list)
1587+
else
1588+
n = 0
1589+
end if
1590+
1591+
add = size(new)
1592+
if (add == 0) return
1593+
1594+
allocate(tmp(n+add))
1595+
do i=1,n
1596+
tmp(i) = list(i)
1597+
end do
1598+
do i=1,add
1599+
tmp(n+i) = new(i)
1600+
end do
1601+
call move_alloc(from=tmp,to=list)
1602+
1603+
end subroutine add_target_ptr_many
1604+
15481605
end module fpm_targets

src/metapackage/fpm_meta_base.f90

Lines changed: 58 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,12 @@ module fpm_meta_base
6969

7070
end type metapackage_t
7171

72+
!> Add dependencies to array (gcc-15 bug workaround)
73+
interface add_dependency_config
74+
module procedure add_dependency_config_one
75+
module procedure add_dependency_config_many
76+
end interface add_dependency_config
77+
7278
contains
7379

7480
elemental subroutine destroy(this)
@@ -161,7 +167,7 @@ subroutine resolve_package_config(self,package,error)
161167
! as they may change if built upstream
162168
if (self%has_dependencies) then
163169
if (allocated(package%dev_dependency)) then
164-
package%dev_dependency = [package%dev_dependency,self%dependency]
170+
call add_dependency_config(package%dev_dependency,self%dependency)
165171
else
166172
package%dev_dependency = self%dependency
167173
end if
@@ -234,4 +240,55 @@ end function dn
234240

235241
end subroutine resolve_package_config
236242

243+
!> Add one dependency to array with a loop (gcc-15 bug on array initializer)
244+
pure subroutine add_dependency_config_one(list,new)
245+
type(dependency_config_t), allocatable, intent(inout) :: list(:)
246+
type(dependency_config_t), intent(in) :: new
247+
248+
integer :: i,n
249+
type(dependency_config_t), allocatable :: tmp(:)
250+
251+
if (allocated(list)) then
252+
n = size(list)
253+
else
254+
n = 0
255+
end if
256+
257+
allocate(tmp(n+1))
258+
do i=1,n
259+
tmp(i) = list(i)
260+
end do
261+
tmp(n+1) = new
262+
call move_alloc(from=tmp,to=list)
263+
264+
end subroutine add_dependency_config_one
265+
266+
!> Add multiple dependencies to array with a loop (gcc-15 bug on array initializer)
267+
pure subroutine add_dependency_config_many(list,new)
268+
type(dependency_config_t), allocatable, intent(inout) :: list(:)
269+
type(dependency_config_t), intent(in) :: new(:)
270+
271+
integer :: i,n,add
272+
type(dependency_config_t), allocatable :: tmp(:)
273+
274+
if (allocated(list)) then
275+
n = size(list)
276+
else
277+
n = 0
278+
end if
279+
280+
add = size(new)
281+
if (add == 0) return
282+
283+
allocate(tmp(n+add))
284+
do i=1,n
285+
tmp(i) = list(i)
286+
end do
287+
do i=1,add
288+
tmp(n+i) = new(i)
289+
end do
290+
call move_alloc(from=tmp,to=list)
291+
292+
end subroutine add_dependency_config_many
293+
237294
end module fpm_meta_base

0 commit comments

Comments
 (0)