Skip to content

Commit e9aa312

Browse files
authored
CI: enable gcc-15 on macOS, and related fixes (#1185)
2 parents 501cc61 + e14e4da commit e9aa312

File tree

10 files changed

+175
-122
lines changed

10 files changed

+175
-122
lines changed

.github/workflows/CI.yml

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ jobs:
2828
- {compiler: gcc, version: 12}
2929
- {compiler: gcc, version: 13}
3030
- {compiler: gcc, version: 14}
31+
- {compiler: gcc, version: 15}
3132
- {compiler: intel, version: 2025.1}
3233
exclude:
3334
- os: macos-13 # No Intel on MacOS anymore since 2024
@@ -36,6 +37,10 @@ jobs:
3637
toolchain: {compiler: intel, version: '2025.1'}
3738
- os: windows-latest # gcc 14 not available on Windows yet
3839
toolchain: {compiler: gcc, version: 14}
40+
- os: windows-latest # gcc 15 not available on Windows yet
41+
toolchain: {compiler: gcc, version: 15}
42+
- os: ubuntu-latest # gcc 15 not available on Ubuntu via setup-fortran yet
43+
toolchain: {compiler: gcc, version: 15}
3944
include:
4045
- os: ubuntu-latest
4146
os-arch: linux-x86_64
@@ -47,13 +52,16 @@ jobs:
4752
os-arch: windows-x86_64
4853
release-flags: --flag '--static -g -fbacktrace -O3'
4954
exe: .exe
55+
- os: macos-13
56+
toolchain: {compiler: gcc, version: 15}
57+
release-flags: --flag '-g -fbacktrace -Og -fcheck=all,no-recursion -Wno-external-argument-mismatch'
5058

5159
steps:
5260
- name: Checkout code
5361
uses: actions/checkout@v4
5462

5563
- name: Setup Fortran compiler
56-
uses: fortran-lang/setup-fortran@v1.6.3
64+
uses: fortran-lang/setup-fortran@v1.7.0
5765
id: setup-fortran
5866
with:
5967
compiler: ${{ matrix.toolchain.compiler }}
@@ -112,7 +120,7 @@ jobs:
112120
- name: Test Fortran fpm (bootstrap)
113121
shell: bash
114122
run: |
115-
${{ env.BOOTSTRAP }} test
123+
${{ env.BOOTSTRAP }} test --flag " -Wno-external-argument-mismatch"
116124
117125
- name: Install Fortran fpm (bootstrap)
118126
shell: bash

ci/run_tests.sh

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -231,7 +231,7 @@ pushd fpm_test_exe_issues
231231
popd
232232

233233
pushd cpp_files
234-
"$fpm" test
234+
"$fpm" test --verbose
235235
popd
236236

237237
# Test Fortran features

example_packages/cpp_files/src/cpp_files.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ module cpp_files
66
public :: intvec_maxval
77

88
interface
9-
integer function intvec_maxval(array, n) bind(C, name = "intvec_maxval")
9+
integer(c_int) function intvec_maxval(array, n) bind(C, name = "intvec_maxval")
1010
import :: c_int, c_size_t
1111
integer(c_int), intent(in) :: array(*)
1212
integer(c_size_t), intent(in), value :: n

src/fpm.f90

Lines changed: 20 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -45,13 +45,16 @@ subroutine build_model(model, settings, package_config, error)
4545
type(error_t), allocatable, intent(out) :: error
4646

4747
integer :: i, j
48-
type(package_config_t), target :: package, dependency_config, dependency
48+
type(package_config_t), allocatable, target :: package, dependency_config, dependency
4949
type(package_config_t), pointer :: manifest
50-
type(platform_config_t) :: target_platform
50+
type(platform_config_t), allocatable, target :: target_platform
5151
character(len=:), allocatable :: file_name, lib_dir
5252
logical :: has_cpp
5353
logical :: duplicates_found, auto_exe, auto_example, auto_test
5454
type(string_t) :: include_dir
55+
56+
! Large variables -> safer on heap
57+
allocate(package,dependency_config,dependency,target_platform)
5558

5659
model%package_name = package_config%name
5760

@@ -472,13 +475,16 @@ end subroutine check_module_names
472475
subroutine cmd_build(settings)
473476
type(fpm_build_settings), intent(inout) :: settings
474477

475-
type(package_config_t) :: package
476-
type(fpm_model_t) :: model
478+
type(package_config_t), allocatable :: package
479+
type(fpm_model_t), allocatable :: model
477480
type(build_target_ptr), allocatable :: targets(:)
478481
type(error_t), allocatable :: error
479482

480483
integer :: i
481484

485+
! Large variables -> safer on heap
486+
allocate(package, model)
487+
482488
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
483489
if (allocated(error)) then
484490
call fpm_stop(1,'*cmd_build* Package error: '//error%message)
@@ -520,8 +526,8 @@ subroutine cmd_run(settings,test)
520526
integer :: i, j, col_width
521527
logical :: found(size(settings%name))
522528
type(error_t), allocatable :: error
523-
type(package_config_t) :: package
524-
type(fpm_model_t) :: model
529+
type(package_config_t), allocatable :: package
530+
type(fpm_model_t), allocatable :: model
525531
type(build_target_ptr), allocatable :: targets(:)
526532
type(string_t) :: exe_cmd
527533
type(string_t), allocatable :: executables(:)
@@ -530,6 +536,9 @@ subroutine cmd_run(settings,test)
530536
integer :: run_scope,firsterror
531537
integer, allocatable :: stat(:),target_ID(:)
532538
character(len=:),allocatable :: line,run_cmd,library_path
539+
540+
! Large variables -> safer on heap
541+
allocate(package,model)
533542

534543
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
535544
if (allocated(error)) then
@@ -753,10 +762,13 @@ subroutine delete_targets(settings, error)
753762
class(fpm_clean_settings), intent(inout) :: settings
754763
type(error_t), allocatable, intent(out) :: error
755764

756-
type(package_config_t) :: package
757-
type(fpm_model_t) :: model
765+
type(package_config_t), allocatable :: package
766+
type(fpm_model_t), allocatable :: model
758767
type(build_target_ptr), allocatable :: targets(:)
759768
logical :: deleted_any
769+
770+
! Large variables -> safer on heap
771+
allocate(package,model)
760772

761773
! Get package configuration
762774
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
@@ -1000,7 +1012,4 @@ subroutine restore_library_path(saved_path, error)
10001012

10011013
end subroutine restore_library_path
10021014

1003-
1004-
1005-
10061015
end module fpm

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: 44 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,47 @@ 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(self) result(is_gnu)
937+
class(compiler_t), intent(in) :: self
938+
logical :: is_gnu
939+
character(len=:), allocatable :: output_file, version_output
940+
integer :: stat, io
941+
942+
is_gnu = .false.
943+
944+
if (.not.allocated(self%cxx)) return
945+
if (len_trim(self%cxx)<=0) return
946+
947+
! Get temporary file for compiler version output
948+
output_file = get_temp_filename()
949+
950+
! Run compiler with --version to get version info
951+
call run(self%cxx//" --version > "//output_file//" 2>&1", &
952+
echo=.false., exitstat=stat)
953+
954+
if (stat == 0) then
955+
! Read the version output
956+
open(file=output_file, newunit=io, iostat=stat)
957+
if (stat == 0) then
958+
call getline(io, version_output, stat)
959+
close(io, iostat=stat)
960+
961+
! Check if output contains GNU indicators
962+
if (allocated(version_output)) then
963+
is_gnu = index(version_output, 'gcc') > 0 .or. &
964+
index(version_output, 'GCC') > 0 .or. &
965+
index(version_output, 'GNU') > 0 .or. &
966+
index(version_output, 'Free Software Foundation') > 0
967+
end if
968+
end if
969+
end if
970+
971+
! Clean up temporary file
972+
call run("rm -f "//output_file, echo=.false., exitstat=stat)
973+
974+
end function is_cxx_gnu_based
975+
935976

936977
function get_compiler_id(compiler) result(id)
937978
character(len=*), intent(in) :: compiler
@@ -2101,7 +2142,7 @@ subroutine append_clean_flags_array(flags_array, new_flags_array)
21012142
if (trim(new_flags_array(i)%s) == "-I") cycle
21022143
if (trim(new_flags_array(i)%s) == "-J") cycle
21032144
if (trim(new_flags_array(i)%s) == "-M") cycle
2104-
flags_array = [flags_array, new_flags_array(i)]
2145+
call add_strings(flags_array, new_flags_array(i))
21052146
end do
21062147
end subroutine append_clean_flags_array
21072148

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

0 commit comments

Comments
 (0)