Skip to content

Commit f556321

Browse files
committed
new test: compiler flags
1 parent d5ca48a commit f556321

File tree

2 files changed

+135
-5
lines changed

2 files changed

+135
-5
lines changed

src/fpm.f90

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,7 @@ module fpm
3333
implicit none
3434
private
3535
public :: cmd_build, cmd_run, cmd_clean
36-
public :: build_model, check_modules_for_duplicates
36+
public :: build_model, check_modules_for_duplicates, new_compiler_flags
3737

3838
contains
3939

@@ -80,9 +80,6 @@ subroutine build_model(model, settings, package_config, error)
8080
model%build_prefix = join_path(settings%build_dir, basename(model%compiler%fc))
8181
model%include_tests = settings%build_tests
8282

83-
if (allocated(settings%features)) print *, 'features: ',(settings%features(i)%s//' ',i=1,size(settings%features))
84-
if (allocated(settings%profile)) print *, 'profile: ',settings%profile
85-
8683
! Extract the current package configuration request
8784
package = package_config%export_config(target_platform,settings%features,settings%profile,error)
8885
if (allocated(error)) return

test/fpm_test/test_features.f90

Lines changed: 134 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,8 @@ subroutine collect_features(testsuite)
4949
& test_feature_complex_chain_compiler_os_compiler, should_fail=.true.), &
5050
& new_unittest("feature-complex-chain-os-compiler-os", &
5151
& test_feature_complex_chain_os_compiler_os, should_fail=.true.), &
52-
& new_unittest("feature-mixed-valid-chains", test_feature_mixed_valid_chains) &
52+
& new_unittest("feature-mixed-valid-chains", test_feature_mixed_valid_chains), &
53+
& new_unittest("feature-compiler-flags-integration", test_feature_compiler_flags_integration) &
5354
& ]
5455

5556
end subroutine collect_features
@@ -1470,4 +1471,136 @@ subroutine test_feature_mixed_valid_chains(error)
14701471

14711472
end subroutine test_feature_mixed_valid_chains
14721473

1474+
!> Test integration of feature compiler flags with new_compiler_flags
1475+
subroutine test_feature_compiler_flags_integration(error)
1476+
use fpm, only: new_compiler_flags
1477+
use fpm_model, only: fpm_model_t
1478+
use fpm_command_line, only: fpm_build_settings
1479+
use fpm_compiler, only: new_compiler, id_gcc
1480+
1481+
!> Error handling
1482+
type(error_t), allocatable, intent(out) :: error
1483+
1484+
type(package_config_t) :: package_config,package
1485+
type(fpm_model_t) :: model
1486+
type(fpm_build_settings) :: settings
1487+
type(platform_config_t) :: target_platform
1488+
character(:), allocatable :: temp_file
1489+
integer :: unit
1490+
1491+
allocate(temp_file, source=get_temp_filename())
1492+
1493+
! Create a test package with feature-based compiler flags
1494+
open(newunit=unit, file=temp_file, status='unknown')
1495+
write(unit, '(a)') 'name = "test_flags"'
1496+
write(unit, '(a)') 'version = "0.1.0"'
1497+
write(unit, '(a)') ''
1498+
write(unit, '(a)') '[library]'
1499+
write(unit, '(a)') 'source-dir = "src"'
1500+
write(unit, '(a)') ''
1501+
write(unit, '(a)') '[features]'
1502+
write(unit, '(a)') 'debug.gfortran.flags = "-g -Wall -fcheck=bounds"'
1503+
write(unit, '(a)') 'debug.flags = "-g"'
1504+
write(unit, '(a)') 'release.gfortran.flags = "-O3 -march=native"'
1505+
write(unit, '(a)') 'release.flags = "-O2"'
1506+
write(unit, '(a)') ''
1507+
write(unit, '(a)') '[profiles]'
1508+
write(unit, '(a)') 'development = ["debug"]'
1509+
write(unit, '(a)') 'production = ["release"]'
1510+
close(unit)
1511+
1512+
! Set up build settings without CLI flags
1513+
settings%flag = ""
1514+
settings%cflag = ""
1515+
settings%cxxflag = ""
1516+
settings%ldflag = ""
1517+
1518+
! Load the package configuration
1519+
call get_package_data(package_config, temp_file, error, apply_defaults=.true.)
1520+
if (allocated(error)) return
1521+
1522+
! 1) Choose first desired target platform: gfortran on Linux with development profile
1523+
target_platform = platform_config_t(id_gcc, OS_LINUX)
1524+
settings%profile = "development" ! This should activate debug features
1525+
1526+
! Extract the current package configuration request
1527+
package = package_config%export_config(target_platform, profile=settings%profile, error=error)
1528+
if (allocated(error)) return
1529+
1530+
! Set up model with mock compiler
1531+
call new_compiler(model%compiler, "gfortran", "gcc", "g++", echo=.false., verbose=.false.)
1532+
1533+
! Test that package flags are used when no CLI flags provided
1534+
call new_compiler_flags(model, settings, package)
1535+
1536+
! 2) Ensure flags are picked from gfortran platform (should include both base debug and gfortran-specific)
1537+
if (.not. allocated(model%fortran_compile_flags)) then
1538+
call test_failed(error, "Expected fortran_compile_flags to be allocated for gfortran")
1539+
return
1540+
end if
1541+
1542+
if (index(model%fortran_compile_flags, "-g") == 0) then
1543+
call test_failed(error, "Expected debug flags to contain '-g' for gfortran platform")
1544+
return
1545+
end if
1546+
1547+
if (index(model%fortran_compile_flags, "-Wall") == 0) then
1548+
call test_failed(error, "Expected gfortran-specific flags to contain '-Wall'")
1549+
return
1550+
end if
1551+
1552+
if (index(model%fortran_compile_flags, "-fcheck=bounds") == 0) then
1553+
call test_failed(error, "Expected gfortran-specific flags to contain '-fcheck=bounds'")
1554+
return
1555+
end if
1556+
1557+
! 3) Choose another target platform: gfortran on Linux with production profile
1558+
settings%profile = "production" ! This should activate release features
1559+
1560+
! Extract the new package configuration request
1561+
package = package_config%export_config(target_platform, profile=settings%profile, error=error)
1562+
if (allocated(error)) return
1563+
1564+
! Reset flags and test production profile
1565+
call new_compiler_flags(model, settings, package)
1566+
1567+
! 4) Ensure flags are picked from the release platform (should include release flags)
1568+
if (.not. allocated(model%fortran_compile_flags)) then
1569+
call test_failed(error, "Expected fortran_compile_flags to be allocated for release")
1570+
return
1571+
end if
1572+
1573+
if (index(model%fortran_compile_flags, "-O3") == 0) then
1574+
call test_failed(error, "Expected release gfortran flags to contain '-O3'")
1575+
return
1576+
end if
1577+
1578+
if (index(model%fortran_compile_flags, "-march=native") == 0) then
1579+
call test_failed(error, "Expected release gfortran flags to contain '-march=native'")
1580+
return
1581+
end if
1582+
1583+
if (index(model%fortran_compile_flags, "-O2") == 0) then
1584+
call test_failed(error, "Expected base release flags to contain '-O2'")
1585+
return
1586+
end if
1587+
1588+
! Test CLI flags still override package flags
1589+
settings%flag = "-O1 -DCUSTOM"
1590+
call new_compiler_flags(model, settings, package)
1591+
1592+
if (index(model%fortran_compile_flags, "-O1") == 0) then
1593+
call test_failed(error, "Expected CLI flags to be used when provided")
1594+
return
1595+
end if
1596+
1597+
if (index(model%fortran_compile_flags, "-DCUSTOM") == 0) then
1598+
call test_failed(error, "Expected CLI flags to contain custom flags")
1599+
return
1600+
end if
1601+
1602+
! Clean up - file was already closed after writing
1603+
1604+
end subroutine test_feature_compiler_flags_integration
1605+
14731606
end module test_features

0 commit comments

Comments
 (0)