Skip to content

Commit 27033d0

Browse files
committed
fix: 1) strings: a = [a, b] -> add_strings; 2) eval GNU/Clang backend on mac
1 parent d271832 commit 27033d0

File tree

5 files changed

+75
-44
lines changed

5 files changed

+75
-44
lines changed

src/fpm/manifest/preprocess.f90

Lines changed: 8 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@
1212

1313
module fpm_manifest_preprocess
1414
use fpm_error, only : error_t, syntax_error
15-
use fpm_strings, only : string_t, operator(==)
15+
use fpm_strings, only : string_t, operator(==), add_strings
1616
use tomlf, only : toml_table, toml_key, toml_stat
1717
use fpm_toml, only : get_value, get_list, serializable_t, set_value, set_list, &
1818
set_string
@@ -326,31 +326,16 @@ subroutine add_config(this,that)
326326
if (.not.allocated(this%name)) this%name = that%name
327327

328328
! Add macros
329-
if (allocated(that%macros)) then
330-
if (allocated(this%macros)) then
331-
this%macros = [this%macros, that%macros]
332-
else
333-
allocate(this%macros, source = that%macros)
334-
end if
335-
endif
336-
329+
if (allocated(that%macros)) &
330+
call add_strings(this%macros, that%macros)
331+
337332
! Add suffixes
338-
if (allocated(that%suffixes)) then
339-
if (allocated(this%suffixes)) then
340-
this%suffixes = [this%suffixes, that%suffixes]
341-
else
342-
allocate(this%suffixes, source = that%suffixes)
343-
end if
344-
endif
333+
if (allocated(that%suffixes)) &
334+
call add_strings(this%suffixes, that%suffixes)
345335

346336
! Add directories
347-
if (allocated(that%directories)) then
348-
if (allocated(this%directories)) then
349-
this%directories = [this%directories, that%directories]
350-
else
351-
allocate(this%directories, source = that%directories)
352-
end if
353-
endif
337+
if (allocated(that%directories)) &
338+
call add_strings(this%directories, that%directories)
354339

355340
end subroutine add_config
356341

src/fpm_compiler.F90

Lines changed: 40 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ module fpm_compiler
4141
use fpm_filesystem, only: join_path, basename, get_temp_filename, delete_file, unix_path, &
4242
& getline, run
4343
use fpm_strings, only: split, string_cat, string_t, str_ends_with, str_begins_with_str, &
44-
& string_array_contains, lower
44+
& string_array_contains, lower, add_strings
4545
use fpm_error, only: error_t, fatal_error, fpm_stop
4646
use tomlf, only: toml_table
4747
use fpm_toml, only: serializable_t, set_string, set_value, toml_stat, get_value
@@ -53,7 +53,7 @@ module fpm_compiler
5353
public :: append_clean_flags, append_clean_flags_array
5454
public :: debug
5555
public :: id_gcc,id_all
56-
public :: match_compiler_type, compiler_id_name, validate_compiler_name
56+
public :: match_compiler_type, compiler_id_name, validate_compiler_name, is_cxx_gnu_based
5757

5858
enum, bind(C)
5959
enumerator :: &
@@ -932,6 +932,43 @@ subroutine get_default_cxx_compiler(f_compiler, cxx_compiler)
932932

933933
end subroutine get_default_cxx_compiler
934934

935+
!> Check if C++ compiler is GNU-based by checking its version output
936+
function is_cxx_gnu_based(cxx_compiler) result(is_gnu)
937+
character(len=*), intent(in) :: cxx_compiler
938+
logical :: is_gnu
939+
character(len=:), allocatable :: output_file, version_output
940+
integer :: stat, io
941+
942+
is_gnu = .false.
943+
944+
! Get temporary file for compiler version output
945+
output_file = get_temp_filename()
946+
947+
! Run compiler with --version to get version info
948+
call run(cxx_compiler//" --version > "//output_file//" 2>&1", &
949+
echo=.false., exitstat=stat)
950+
951+
if (stat == 0) then
952+
! Read the version output
953+
open(file=output_file, newunit=io, iostat=stat)
954+
if (stat == 0) then
955+
call getline(io, version_output, stat)
956+
close(io, iostat=stat)
957+
958+
! Check if output contains GNU indicators
959+
if (allocated(version_output)) then
960+
is_gnu = index(version_output, 'gcc') > 0 .or. &
961+
index(version_output, 'GCC') > 0 .or. &
962+
index(version_output, 'GNU') > 0 .or. &
963+
index(version_output, 'Free Software Foundation') > 0
964+
end if
965+
end if
966+
967+
! Clean up temporary file
968+
call run("rm -f "//output_file, echo=.false., exitstat=stat)
969+
970+
end function is_cxx_gnu_based
971+
935972

936973
function get_compiler_id(compiler) result(id)
937974
character(len=*), intent(in) :: compiler
@@ -2101,7 +2138,7 @@ subroutine append_clean_flags_array(flags_array, new_flags_array)
21012138
if (trim(new_flags_array(i)%s) == "-I") cycle
21022139
if (trim(new_flags_array(i)%s) == "-J") cycle
21032140
if (trim(new_flags_array(i)%s) == "-M") cycle
2104-
flags_array = [flags_array, new_flags_array(i)]
2141+
call add_strings(flags_array, new_flags_array(i))
21052142
end do
21062143
end subroutine append_clean_flags_array
21072144

src/fpm_filesystem.F90

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,8 @@ module fpm_filesystem
77
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
88
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
99
use fpm_environment, only: separator, get_env, os_is_unix
10-
use fpm_strings, only: f_string, replace, string_t, split, split_lines_first_last, dilate, str_begins_with_str
10+
use fpm_strings, only: f_string, replace, string_t, split, split_lines_first_last, dilate, add_strings, &
11+
str_begins_with_str
1112
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer
1213
use fpm_error, only : fpm_stop, error_t, fatal_error
1314
implicit none
@@ -443,7 +444,7 @@ recursive subroutine list_files(dir, files, recurse)
443444
i = i + 1
444445

445446
if (i > N_MAX) then
446-
files = [files, files_tmp]
447+
call add_strings(files, files_tmp)
447448
i = 1
448449
end if
449450

@@ -459,7 +460,7 @@ recursive subroutine list_files(dir, files, recurse)
459460
end if
460461

461462
if (i > 0) then
462-
files = [files, files_tmp(1:i)]
463+
call add_strings(files, files_tmp(1:i))
463464
end if
464465

465466
if (present(recurse)) then
@@ -470,11 +471,11 @@ recursive subroutine list_files(dir, files, recurse)
470471
do i=1,size(files)
471472
if (c_is_dir(files(i)%s//c_null_char) /= 0) then
472473
call list_files(files(i)%s, dir_files, recurse=.true.)
473-
sub_dir_files = [sub_dir_files, dir_files]
474+
call add_strings(sub_dir_files, dir_files)
474475
end if
475476
end do
476477

477-
files = [files, sub_dir_files]
478+
call add_strings(files, sub_dir_files)
478479
end if
479480
end if
480481
end subroutine list_files
@@ -531,12 +532,12 @@ recursive subroutine list_files(dir, files, recurse)
531532
if (is_dir(files(i)%s)) then
532533

533534
call list_files(files(i)%s, dir_files, recurse=.true.)
534-
sub_dir_files = [sub_dir_files, dir_files]
535+
call add_strings(sub_dir_files, dir_files)
535536

536537
end if
537538
end do
538539

539-
files = [files, sub_dir_files]
540+
call add_strings(files, sub_dir_files)
540541

541542
end if
542543
end if

src/fpm_targets.f90

Lines changed: 17 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ module fpm_targets
3232
use fpm_filesystem, only: dirname, join_path, canon_path
3333
use fpm_strings, only: string_t, operator(.in.), string_cat, fnv_1a, resize, lower, str_ends_with, &
3434
add_strings
35-
use fpm_compiler, only: get_macros
35+
use fpm_compiler, only: get_macros, is_cxx_gnu_based
3636
use fpm_sources, only: get_exe_name_with_suffix
3737
use fpm_manifest_library, only: library_config_t
3838
use fpm_manifest_preprocess, only: preprocess_config_t
@@ -317,8 +317,8 @@ subroutine build_target_list(targets,model,library)
317317

318318
integer :: i, j, k, n_source, exe_type
319319
character(:), allocatable :: exe_dir, compile_flags, lib_name
320-
logical :: with_lib, monolithic, shared_lib, static_lib
321-
320+
logical :: with_lib, monolithic, shared_lib, static_lib, clang_cxx_backend_macos
321+
322322
! Initialize targets
323323
allocate(targets(0))
324324

@@ -327,6 +327,12 @@ subroutine build_target_list(targets,model,library)
327327
j=1,size(model%packages))])
328328

329329
if (n_source < 1) return
330+
331+
if (get_os_type()==OS_MACOS) then
332+
clang_cxx_backend_macos = .not. is_cxx_gnu_based(model%compiler%cxx)
333+
else
334+
clang_cxx_backend_macos = .false.
335+
endif
330336

331337
with_lib = any(model%packages%has_library())
332338

@@ -436,10 +442,12 @@ subroutine build_target_list(targets,model,library)
436442

437443
!> Add stdc++ as a linker flag. If not already there.
438444
if (.not. ("stdc++" .in. model%link_libraries)) then
439-
440-
if (get_os_type() == OS_MACOS) then
445+
446+
if (clang_cxx_backend_macos) then
447+
! On macOS with non-GNU C++ compiler (e.g., Clang), use "c++"
441448
call add_strings(model%link_libraries, string_t("c++"))
442449
else
450+
! For GNU C++ compiler or non-macOS systems, use "stdc++"
443451
call add_strings(model%link_libraries, string_t("stdc++"))
444452
end if
445453

@@ -1010,7 +1018,7 @@ recursive subroutine collect_used_modules(target)
10101018

10111019
if (.not.(target%source%modules_provided(j)%s .in. modules_used)) then
10121020

1013-
modules_used = [modules_used, target%source%modules_provided(j)]
1021+
call add_strings(modules_used, target%source%modules_provided(j))
10141022

10151023
end if
10161024

@@ -1295,7 +1303,7 @@ recursive subroutine get_link_objects(link_objects,target,is_exe)
12951303

12961304
! Add dependency object file to link object list
12971305
temp_str%s = dep%output_file
1298-
link_objects = [link_objects, temp_str]
1306+
call add_strings(link_objects, temp_str)
12991307

13001308
! For executable objects, also need to include non-library
13011309
! dependencies from dependencies (recurse)
@@ -1324,7 +1332,7 @@ subroutine add_include_build_dirs(model, targets)
13241332
if (target%target_type /= FPM_TARGET_OBJECT) cycle
13251333
if (target%output_dir .in. build_dirs) cycle
13261334
temp%s = target%output_dir
1327-
build_dirs = [build_dirs, temp]
1335+
call add_strings(build_dirs, temp)
13281336
end associate
13291337
end do
13301338

@@ -1356,7 +1364,7 @@ subroutine get_library_dirs(model, targets, shared_lib_dirs)
13561364
if (all(target%target_type /= [FPM_TARGET_SHARED,FPM_TARGET_ARCHIVE])) cycle
13571365
if (target%output_dir .in. shared_lib_dirs) cycle
13581366
temp = string_t(target%output_dir)
1359-
shared_lib_dirs = [shared_lib_dirs, temp]
1367+
call add_strings(shared_lib_dirs, temp)
13601368
end associate
13611369
end do
13621370

src/metapackage/fpm_meta_util.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ subroutine add_pkg_config_compile_options(this, name, include_flag, libdir, erro
4545
current_lib = string_t(libs(i)%s(3:))
4646
if (len_trim(current_lib%s) == 0) cycle
4747
this%has_link_libraries = .true.
48-
this%link_libs = [this%link_libs, current_lib]
48+
call add_strings(this%link_libs, current_lib)
4949
else ! -L and others: concatenate
5050
this%has_link_flags = .true.
5151
this%link_flags = string_t(trim(this%link_flags%s)//' '//libs(i)%s)
@@ -68,7 +68,7 @@ subroutine add_pkg_config_compile_options(this, name, include_flag, libdir, erro
6868
current_include_dir = string_t(flags(i)%s(len(include_flag)+1:))
6969
if (len_trim(current_include_dir%s) == 0) cycle
7070
this%has_include_dirs = .true.
71-
this%incl_dirs = [this%incl_dirs, current_include_dir]
71+
call add_strings(this%incl_dirs, current_include_dir)
7272
else
7373
this%has_build_flags = .true.
7474
this%flags = string_t(trim(this%flags%s)//' '//flags(i)%s)

0 commit comments

Comments
 (0)