Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
12 changes: 10 additions & 2 deletions .github/workflows/CI.yml
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ jobs:
- {compiler: gcc, version: 12}
- {compiler: gcc, version: 13}
- {compiler: gcc, version: 14}
- {compiler: gcc, version: 15}
- {compiler: intel, version: 2025.1}
exclude:
- os: macos-13 # No Intel on MacOS anymore since 2024
Expand All @@ -36,6 +37,10 @@ jobs:
toolchain: {compiler: intel, version: '2025.1'}
- os: windows-latest # gcc 14 not available on Windows yet
toolchain: {compiler: gcc, version: 14}
- os: windows-latest # gcc 15 not available on Windows yet
toolchain: {compiler: gcc, version: 15}
- os: ubuntu-latest # gcc 15 not available on Ubuntu via setup-fortran yet
toolchain: {compiler: gcc, version: 15}
include:
- os: ubuntu-latest
os-arch: linux-x86_64
Expand All @@ -47,13 +52,16 @@ jobs:
os-arch: windows-x86_64
release-flags: --flag '--static -g -fbacktrace -O3'
exe: .exe
- os: macos-13
toolchain: {compiler: gcc, version: 15}
release-flags: --flag '-g -fbacktrace -Og -fcheck=all,no-recursion -Wno-external-argument-mismatch'

steps:
- name: Checkout code
uses: actions/checkout@v4

- name: Setup Fortran compiler
uses: fortran-lang/setup-fortran@v1.6.3
uses: fortran-lang/setup-fortran@v1.7.0
id: setup-fortran
with:
compiler: ${{ matrix.toolchain.compiler }}
Expand Down Expand Up @@ -112,7 +120,7 @@ jobs:
- name: Test Fortran fpm (bootstrap)
shell: bash
run: |
${{ env.BOOTSTRAP }} test
${{ env.BOOTSTRAP }} test --flag " -Wno-external-argument-mismatch"

- name: Install Fortran fpm (bootstrap)
shell: bash
Expand Down
2 changes: 1 addition & 1 deletion ci/run_tests.sh
Original file line number Diff line number Diff line change
Expand Up @@ -231,7 +231,7 @@ pushd fpm_test_exe_issues
popd

pushd cpp_files
"$fpm" test
"$fpm" test --verbose
popd

# Test Fortran features
Expand Down
2 changes: 1 addition & 1 deletion example_packages/cpp_files/src/cpp_files.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module cpp_files
public :: intvec_maxval

interface
integer function intvec_maxval(array, n) bind(C, name = "intvec_maxval")
integer(c_int) function intvec_maxval(array, n) bind(C, name = "intvec_maxval")
import :: c_int, c_size_t
integer(c_int), intent(in) :: array(*)
integer(c_size_t), intent(in), value :: n
Expand Down
31 changes: 20 additions & 11 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -45,13 +45,16 @@ subroutine build_model(model, settings, package_config, error)
type(error_t), allocatable, intent(out) :: error

integer :: i, j
type(package_config_t), target :: package, dependency_config, dependency
type(package_config_t), allocatable, target :: package, dependency_config, dependency
type(package_config_t), pointer :: manifest
type(platform_config_t) :: target_platform
type(platform_config_t), allocatable, target :: target_platform
character(len=:), allocatable :: file_name, lib_dir
logical :: has_cpp
logical :: duplicates_found, auto_exe, auto_example, auto_test
type(string_t) :: include_dir

! Large variables -> safer on heap
allocate(package,dependency_config,dependency,target_platform)

model%package_name = package_config%name

Expand Down Expand Up @@ -472,13 +475,16 @@ end subroutine check_module_names
subroutine cmd_build(settings)
type(fpm_build_settings), intent(inout) :: settings

type(package_config_t) :: package
type(fpm_model_t) :: model
type(package_config_t), allocatable :: package
type(fpm_model_t), allocatable :: model
type(build_target_ptr), allocatable :: targets(:)
type(error_t), allocatable :: error

integer :: i

! Large variables -> safer on heap
allocate(package, model)

call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
if (allocated(error)) then
call fpm_stop(1,'*cmd_build* Package error: '//error%message)
Expand Down Expand Up @@ -520,8 +526,8 @@ subroutine cmd_run(settings,test)
integer :: i, j, col_width
logical :: found(size(settings%name))
type(error_t), allocatable :: error
type(package_config_t) :: package
type(fpm_model_t) :: model
type(package_config_t), allocatable :: package
type(fpm_model_t), allocatable :: model
type(build_target_ptr), allocatable :: targets(:)
type(string_t) :: exe_cmd
type(string_t), allocatable :: executables(:)
Expand All @@ -530,6 +536,9 @@ subroutine cmd_run(settings,test)
integer :: run_scope,firsterror
integer, allocatable :: stat(:),target_ID(:)
character(len=:),allocatable :: line,run_cmd,library_path

! Large variables -> safer on heap
allocate(package,model)

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

type(package_config_t) :: package
type(fpm_model_t) :: model
type(package_config_t), allocatable :: package
type(fpm_model_t), allocatable :: model
type(build_target_ptr), allocatable :: targets(:)
logical :: deleted_any

! Large variables -> safer on heap
allocate(package,model)

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

end subroutine restore_library_path




end module fpm
31 changes: 8 additions & 23 deletions src/fpm/manifest/preprocess.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@

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

! Add macros
if (allocated(that%macros)) then
if (allocated(this%macros)) then
this%macros = [this%macros, that%macros]
else
allocate(this%macros, source = that%macros)
end if
endif

if (allocated(that%macros)) &
call add_strings(this%macros, that%macros)

! Add suffixes
if (allocated(that%suffixes)) then
if (allocated(this%suffixes)) then
this%suffixes = [this%suffixes, that%suffixes]
else
allocate(this%suffixes, source = that%suffixes)
end if
endif
if (allocated(that%suffixes)) &
call add_strings(this%suffixes, that%suffixes)

! Add directories
if (allocated(that%directories)) then
if (allocated(this%directories)) then
this%directories = [this%directories, that%directories]
else
allocate(this%directories, source = that%directories)
end if
endif
if (allocated(that%directories)) &
call add_strings(this%directories, that%directories)

end subroutine add_config

Expand Down
47 changes: 44 additions & 3 deletions src/fpm_compiler.F90
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ module fpm_compiler
use fpm_filesystem, only: join_path, basename, get_temp_filename, delete_file, unix_path, &
& getline, run
use fpm_strings, only: split, string_cat, string_t, str_ends_with, str_begins_with_str, &
& string_array_contains, lower
& string_array_contains, lower, add_strings
use fpm_error, only: error_t, fatal_error, fpm_stop
use tomlf, only: toml_table
use fpm_toml, only: serializable_t, set_string, set_value, toml_stat, get_value
Expand All @@ -53,7 +53,7 @@ module fpm_compiler
public :: append_clean_flags, append_clean_flags_array
public :: debug
public :: id_gcc,id_all
public :: match_compiler_type, compiler_id_name, validate_compiler_name
public :: match_compiler_type, compiler_id_name, validate_compiler_name, is_cxx_gnu_based

enum, bind(C)
enumerator :: &
Expand Down Expand Up @@ -932,6 +932,47 @@ subroutine get_default_cxx_compiler(f_compiler, cxx_compiler)

end subroutine get_default_cxx_compiler

!> Check if C++ compiler is GNU-based by checking its version output
function is_cxx_gnu_based(self) result(is_gnu)
class(compiler_t), intent(in) :: self
logical :: is_gnu
character(len=:), allocatable :: output_file, version_output
integer :: stat, io

is_gnu = .false.

if (.not.allocated(self%cxx)) return
if (len_trim(self%cxx)<=0) return

! Get temporary file for compiler version output
output_file = get_temp_filename()

! Run compiler with --version to get version info
call run(self%cxx//" --version > "//output_file//" 2>&1", &
echo=.false., exitstat=stat)

if (stat == 0) then
! Read the version output
open(file=output_file, newunit=io, iostat=stat)
if (stat == 0) then
call getline(io, version_output, stat)
close(io, iostat=stat)

! Check if output contains GNU indicators
if (allocated(version_output)) then
is_gnu = index(version_output, 'gcc') > 0 .or. &
index(version_output, 'GCC') > 0 .or. &
index(version_output, 'GNU') > 0 .or. &
index(version_output, 'Free Software Foundation') > 0
end if
end if
end if

! Clean up temporary file
call run("rm -f "//output_file, echo=.false., exitstat=stat)

end function is_cxx_gnu_based


function get_compiler_id(compiler) result(id)
character(len=*), intent(in) :: compiler
Expand Down Expand Up @@ -2101,7 +2142,7 @@ subroutine append_clean_flags_array(flags_array, new_flags_array)
if (trim(new_flags_array(i)%s) == "-I") cycle
if (trim(new_flags_array(i)%s) == "-J") cycle
if (trim(new_flags_array(i)%s) == "-M") cycle
flags_array = [flags_array, new_flags_array(i)]
call add_strings(flags_array, new_flags_array(i))
end do
end subroutine append_clean_flags_array

Expand Down
15 changes: 8 additions & 7 deletions src/fpm_filesystem.F90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,8 @@ module fpm_filesystem
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
use fpm_environment, only: separator, get_env, os_is_unix
use fpm_strings, only: f_string, replace, string_t, split, split_lines_first_last, dilate, str_begins_with_str
use fpm_strings, only: f_string, replace, string_t, split, split_lines_first_last, dilate, add_strings, &
str_begins_with_str
use iso_c_binding, only: c_char, c_ptr, c_int, c_null_char, c_associated, c_f_pointer
use fpm_error, only : fpm_stop, error_t, fatal_error
implicit none
Expand Down Expand Up @@ -443,7 +444,7 @@ recursive subroutine list_files(dir, files, recurse)
i = i + 1

if (i > N_MAX) then
files = [files, files_tmp]
call add_strings(files, files_tmp)
i = 1
end if

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

if (i > 0) then
files = [files, files_tmp(1:i)]
call add_strings(files, files_tmp(1:i))
end if

if (present(recurse)) then
Expand All @@ -470,11 +471,11 @@ recursive subroutine list_files(dir, files, recurse)
do i=1,size(files)
if (c_is_dir(files(i)%s//c_null_char) /= 0) then
call list_files(files(i)%s, dir_files, recurse=.true.)
sub_dir_files = [sub_dir_files, dir_files]
call add_strings(sub_dir_files, dir_files)
end if
end do

files = [files, sub_dir_files]
call add_strings(files, sub_dir_files)
end if
end if
end subroutine list_files
Expand Down Expand Up @@ -531,12 +532,12 @@ recursive subroutine list_files(dir, files, recurse)
if (is_dir(files(i)%s)) then

call list_files(files(i)%s, dir_files, recurse=.true.)
sub_dir_files = [sub_dir_files, dir_files]
call add_strings(sub_dir_files, dir_files)

end if
end do

files = [files, sub_dir_files]
call add_strings(files, sub_dir_files)

end if
end if
Expand Down
Loading
Loading