Skip to content

Commit 81fa25a

Browse files
committed
Merge remote-tracking branch 'upstream/main' into ifx_compile
2 parents bed12ae + cc704c8 commit 81fa25a

File tree

3 files changed

+61
-4
lines changed

3 files changed

+61
-4
lines changed

src/fpm_compiler.F90

Lines changed: 26 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -125,6 +125,7 @@ module fpm_compiler
125125
procedure :: load_from_toml => compiler_load
126126
!> Fortran feature support
127127
procedure :: check_fortran_source_runs
128+
procedure :: check_flags_supported
128129
procedure :: with_xdp
129130
procedure :: with_qp
130131
!> Return compiler name
@@ -1452,14 +1453,16 @@ end function compiler_name
14521453

14531454
!> Run a single-source Fortran program using the current compiler
14541455
!> Compile a Fortran object
1455-
logical function check_fortran_source_runs(self, input) result(success)
1456+
logical function check_fortran_source_runs(self, input, compile_flags, link_flags) result(success)
14561457
!> Instance of the compiler object
14571458
class(compiler_t), intent(in) :: self
14581459
!> Program Source
14591460
character(len=*), intent(in) :: input
1461+
!> Optional build and link flags
1462+
character(len=*), optional, intent(in) :: compile_flags, link_flags
14601463

14611464
integer :: stat,unit
1462-
character(:), allocatable :: source,object,logf,exe
1465+
character(:), allocatable :: source,object,logf,exe,flags,ldflags
14631466

14641467
success = .false.
14651468

@@ -1475,10 +1478,17 @@ logical function check_fortran_source_runs(self, input) result(success)
14751478
write(unit,*) input
14761479
close(unit)
14771480

1481+
!> Get flags
1482+
flags = self%get_default_flags(release=.false.)
1483+
ldflags = self%get_default_flags(release=.false.)
1484+
1485+
if (present(compile_flags)) flags = flags//" "//compile_flags
1486+
if (present(link_flags)) ldflags = ldflags//" "//link_flags
1487+
14781488
!> Compile and link program
1479-
call self%compile_fortran(source, object, self%get_default_flags(release=.false.), logf, stat)
1489+
call self%compile_fortran(source, object, flags, logf, stat)
14801490
if (stat==0) &
1481-
call self%link(exe, self%get_default_flags(release=.false.)//" "//object, logf, stat)
1491+
call self%link(exe, ldflags//" "//object, logf, stat)
14821492

14831493
!> Run and retrieve exit code
14841494
if (stat==0) &
@@ -1499,6 +1509,18 @@ logical function check_fortran_source_runs(self, input) result(success)
14991509

15001510
end function check_fortran_source_runs
15011511

1512+
!> Check if the given compile and/or link flags are accepted by the compiler
1513+
logical function check_flags_supported(self, compile_flags, link_flags)
1514+
class(compiler_t), intent(in) :: self
1515+
character(len=*), optional, intent(in) :: compile_flags, link_flags
1516+
1517+
! Minimal program that always compiles
1518+
character(len=*), parameter :: hello_world = "print *, 'Hello, World!'; end"
1519+
1520+
check_flags_supported = self%check_fortran_source_runs(hello_world, compile_flags, link_flags)
1521+
1522+
end function check_flags_supported
1523+
15021524
!> Check if the current compiler supports 128-bit real precision
15031525
logical function with_qp(self)
15041526
!> Instance of the compiler object

src/metapackage/fpm_meta_netcdf.f90

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -39,13 +39,15 @@ subroutine init_netcdf(this, compiler, error)
3939

4040
if (.not. pkgcfg_has_package('netcdf')) then
4141
call fatal_error(error, 'pkg-config could not find a suitable netcdf package.')
42+
return
4243
end if
4344
call add_pkg_config_compile_options(this, 'netcdf', include_flag, libdir, error)
4445
if (allocated(error)) return
4546

4647
if (.not. pkgcfg_has_package('netcdf-fortran')) then
4748
call fatal_error(error, &
4849
'pkg-config could not find a suitable netcdf-fortran package.')
50+
return
4951
end if
5052
call add_pkg_config_compile_options(this, 'netcdf-fortran', include_flag, libdir, error)
5153
if (allocated(error)) return

test/fpm_test/test_compiler.f90

Lines changed: 33 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,39 @@ subroutine test_check_fortran_source_runs(error)
5151
call test_failed(error, "Cannot run Fortran hello world")
5252
return
5353
end if
54+
55+
!> Test with invalid flags
56+
if (compiler%check_fortran_source_runs("print *, 'Hello world!'; end", &
57+
link_flags=" -some-really-invalid-link-flag")) then
58+
call test_failed(error, "Invalid link flags did not trigger an error")
59+
return
60+
end if
61+
if (compiler%check_fortran_source_runs("print *, 'Hello world!'; end", &
62+
compile_flags=" -certainly-not-a-build/flag")) then
63+
call test_failed(error, "Invalid compile flags did not trigger an error")
64+
return
65+
end if
66+
if (compiler%check_fortran_source_runs("print *, 'Hello world!'; end", &
67+
compile_flags=" -certainly-not-a-build/flag", &
68+
link_flags=" -some-really-invalid-link-flag")) then
69+
call test_failed(error, "Invalid build and link flags did not trigger an error")
70+
return
71+
end if
72+
73+
!> Test the flag check wrapper
74+
if (compiler%check_flags_supported(compile_flags='-Werror=unknown-flag')) then
75+
call test_failed(error, "Invalid compile flags did not trigger an error")
76+
return
77+
end if
78+
if (compiler%check_flags_supported(link_flags='-Wl,--nonexistent-linker-option')) then
79+
call test_failed(error, "Invalid link flags did not trigger an error")
80+
return
81+
end if
82+
if (compiler%check_flags_supported(compile_flags='-Werror=unknown-flag', &
83+
link_flags='-Wl,--nonexistent-linker-option')) then
84+
call test_failed(error, "Invalid compile and link flags did not trigger an error")
85+
return
86+
end if
5487

5588
end subroutine test_check_fortran_source_runs
5689

0 commit comments

Comments
 (0)