Skip to content

Commit cc704c8

Browse files
authored
[introspection] optional user-defined build and link flags (#1128)
2 parents 6827b8e + fc176f1 commit cc704c8

File tree

2 files changed

+59
-4
lines changed

2 files changed

+59
-4
lines changed

src/fpm_compiler.F90

Lines changed: 26 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -124,6 +124,7 @@ module fpm_compiler
124124
procedure :: load_from_toml => compiler_load
125125
!> Fortran feature support
126126
procedure :: check_fortran_source_runs
127+
procedure :: check_flags_supported
127128
procedure :: with_xdp
128129
procedure :: with_qp
129130
!> Return compiler name
@@ -1440,14 +1441,16 @@ end function compiler_name
14401441

14411442
!> Run a single-source Fortran program using the current compiler
14421443
!> Compile a Fortran object
1443-
logical function check_fortran_source_runs(self, input) result(success)
1444+
logical function check_fortran_source_runs(self, input, compile_flags, link_flags) result(success)
14441445
!> Instance of the compiler object
14451446
class(compiler_t), intent(in) :: self
14461447
!> Program Source
14471448
character(len=*), intent(in) :: input
1449+
!> Optional build and link flags
1450+
character(len=*), optional, intent(in) :: compile_flags, link_flags
14481451

14491452
integer :: stat,unit
1450-
character(:), allocatable :: source,object,logf,exe
1453+
character(:), allocatable :: source,object,logf,exe,flags,ldflags
14511454

14521455
success = .false.
14531456

@@ -1463,10 +1466,17 @@ logical function check_fortran_source_runs(self, input) result(success)
14631466
write(unit,*) input
14641467
close(unit)
14651468

1469+
!> Get flags
1470+
flags = self%get_default_flags(release=.false.)
1471+
ldflags = self%get_default_flags(release=.false.)
1472+
1473+
if (present(compile_flags)) flags = flags//" "//compile_flags
1474+
if (present(link_flags)) ldflags = ldflags//" "//link_flags
1475+
14661476
!> Compile and link program
1467-
call self%compile_fortran(source, object, self%get_default_flags(release=.false.), logf, stat)
1477+
call self%compile_fortran(source, object, flags, logf, stat)
14681478
if (stat==0) &
1469-
call self%link(exe, self%get_default_flags(release=.false.)//" "//object, logf, stat)
1479+
call self%link(exe, ldflags//" "//object, logf, stat)
14701480

14711481
!> Run and retrieve exit code
14721482
if (stat==0) &
@@ -1487,6 +1497,18 @@ logical function check_fortran_source_runs(self, input) result(success)
14871497

14881498
end function check_fortran_source_runs
14891499

1500+
!> Check if the given compile and/or link flags are accepted by the compiler
1501+
logical function check_flags_supported(self, compile_flags, link_flags)
1502+
class(compiler_t), intent(in) :: self
1503+
character(len=*), optional, intent(in) :: compile_flags, link_flags
1504+
1505+
! Minimal program that always compiles
1506+
character(len=*), parameter :: hello_world = "print *, 'Hello, World!'; end"
1507+
1508+
check_flags_supported = self%check_fortran_source_runs(hello_world, compile_flags, link_flags)
1509+
1510+
end function check_flags_supported
1511+
14901512
!> Check if the current compiler supports 128-bit real precision
14911513
logical function with_qp(self)
14921514
!> Instance of the compiler object

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)