Skip to content

Commit d271832

Browse files
committed
move add_strings to fpm_strings
1 parent 014a917 commit d271832

File tree

3 files changed

+62
-61
lines changed

3 files changed

+62
-61
lines changed

src/fpm_strings.f90

Lines changed: 57 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ module fpm_strings
4343

4444
private
4545
public :: f_string, lower, upper, split, split_first_last, split_lines_first_last, str_ends_with, string_t, str_begins_with_str
46-
public :: to_fortran_name, is_fortran_name
46+
public :: to_fortran_name, is_fortran_name, add_strings
4747
public :: string_array_contains, string_cat, len_trim, operator(.in.), fnv_1a
4848
public :: replace, resize, str, join, glob
4949
public :: notabs, dilate, remove_newline_characters, remove_characters_in_set
@@ -99,6 +99,11 @@ module fpm_strings
9999
module procedure string_arrays_same
100100
end interface
101101

102+
interface add_strings
103+
module procedure add_strings_one
104+
module procedure add_strings_many
105+
end interface add_strings
106+
102107
contains
103108

104109
!> test if a CHARACTER string ends with a specified suffix
@@ -1659,4 +1664,55 @@ function dilate(instr) result(outstr)
16591664

16601665
end function dilate
16611666

1667+
!> Add one element to a string array with a loop (gcc-15 bug on array initializer)
1668+
pure subroutine add_strings_one(list,new)
1669+
type(string_t), allocatable, intent(inout) :: list(:)
1670+
type(string_t), intent(in) :: new
1671+
1672+
integer :: i,n
1673+
type(string_t), allocatable :: tmp(:)
1674+
1675+
if (allocated(list)) then
1676+
n = size(list)
1677+
else
1678+
n = 0
1679+
endif
1680+
1681+
allocate(tmp(n+1))
1682+
do i=1,n
1683+
tmp(i) = list(i)
1684+
end do
1685+
tmp(n+1) = new
1686+
call move_alloc(from=tmp,to=list)
1687+
1688+
end subroutine add_strings_one
1689+
1690+
!> Add elements to a string array with a loop (gcc-15 bug on array initializer)
1691+
pure subroutine add_strings_many(list,new)
1692+
type(string_t), allocatable, intent(inout) :: list(:)
1693+
type(string_t), intent(in) :: new(:)
1694+
1695+
integer :: i,n,add
1696+
type(string_t), allocatable :: tmp(:)
1697+
1698+
if (allocated(list)) then
1699+
n = size(list)
1700+
else
1701+
n = 0
1702+
endif
1703+
1704+
add = size(new)
1705+
if (add<=0) return
1706+
1707+
allocate(tmp(n+add))
1708+
do i=1,n
1709+
tmp(i) = list(i)
1710+
end do
1711+
do i=1,add
1712+
tmp(n+i) = new(i)
1713+
end do
1714+
call move_alloc(from=tmp,to=list)
1715+
1716+
end subroutine add_strings_many
1717+
16621718
end module fpm_strings

src/fpm_targets.f90

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,8 @@ module fpm_targets
3030
use fpm_compiler, only : compiler_t
3131
use fpm_environment, only: get_os_type, OS_WINDOWS, OS_MACOS, library_filename
3232
use fpm_filesystem, only: dirname, join_path, canon_path
33-
use fpm_strings, only: string_t, operator(.in.), string_cat, fnv_1a, resize, lower, str_ends_with
33+
use fpm_strings, only: string_t, operator(.in.), string_cat, fnv_1a, resize, lower, str_ends_with, &
34+
add_strings
3435
use fpm_compiler, only: get_macros
3536
use fpm_sources, only: get_exe_name_with_suffix
3637
use fpm_manifest_library, only: library_config_t
@@ -437,9 +438,9 @@ subroutine build_target_list(targets,model,library)
437438
if (.not. ("stdc++" .in. model%link_libraries)) then
438439

439440
if (get_os_type() == OS_MACOS) then
440-
model%link_libraries = [model%link_libraries, string_t("c++")]
441+
call add_strings(model%link_libraries, string_t("c++"))
441442
else
442-
model%link_libraries = [model%link_libraries, string_t("stdc++")]
443+
call add_strings(model%link_libraries, string_t("stdc++"))
443444
end if
444445

445446
end if

src/metapackage/fpm_meta_util.f90

Lines changed: 1 addition & 57 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
module fpm_meta_util
22
use fpm_meta_base, only: metapackage_t, destroy
33
use fpm_filesystem, only: join_path
4-
use fpm_strings, only: split, string_t, str_begins_with_str
4+
use fpm_strings, only: split, string_t, str_begins_with_str, add_strings
55
use fpm_error, only: error_t
66
use fpm_versioning, only: new_version
77
use fpm_pkg_config, only: pkgcfg_get_libs, pkgcfg_get_build_flags, pkgcfg_get_version
@@ -12,11 +12,6 @@ module fpm_meta_util
1212

1313
public :: add_pkg_config_compile_options, lib_get_trailing, add_strings
1414

15-
interface add_strings
16-
module procedure add_strings_one
17-
module procedure add_strings_many
18-
end interface add_strings
19-
2015
contains
2116

2217
!> Add pkgconfig compile options to a metapackage
@@ -125,55 +120,4 @@ subroutine lib_get_trailing(lib_name,lib_dir,prefix,suffix,found)
125120

126121
end subroutine lib_get_trailing
127122

128-
!> Add one element to a string array with a loop (gcc-15 bug on array initializer)
129-
pure subroutine add_strings_one(list,new)
130-
type(string_t), allocatable, intent(inout) :: list(:)
131-
type(string_t), intent(in) :: new
132-
133-
integer :: i,n
134-
type(string_t), allocatable :: tmp(:)
135-
136-
if (allocated(list)) then
137-
n = size(list)
138-
else
139-
n = 0
140-
endif
141-
142-
allocate(tmp(n+1))
143-
do i=1,n
144-
tmp(i) = list(i)
145-
end do
146-
tmp(n+1) = new
147-
call move_alloc(from=tmp,to=list)
148-
149-
end subroutine add_strings_one
150-
151-
!> Add elements to a string array with a loop (gcc-15 bug on array initializer)
152-
pure subroutine add_strings_many(list,new)
153-
type(string_t), allocatable, intent(inout) :: list(:)
154-
type(string_t), intent(in) :: new(:)
155-
156-
integer :: i,n,add
157-
type(string_t), allocatable :: tmp(:)
158-
159-
if (allocated(list)) then
160-
n = size(list)
161-
else
162-
n = 0
163-
endif
164-
165-
add = size(new)
166-
if (add<=0) return
167-
168-
allocate(tmp(n+add))
169-
do i=1,n
170-
tmp(i) = list(i)
171-
end do
172-
do i=1,add
173-
tmp(n+i) = new(i)
174-
end do
175-
call move_alloc(from=tmp,to=list)
176-
177-
end subroutine add_strings_many
178-
179123
end module fpm_meta_util

0 commit comments

Comments
 (0)