Skip to content

Commit 83b4412

Browse files
authored
Check that Fortran sources run; Robust Fortran features (qp, xdp) #1051
2 parents 06cdf47 + 49c67ae commit 83b4412

File tree

4 files changed

+130
-3
lines changed

4 files changed

+130
-3
lines changed

src/fpm_command_line.f90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,8 @@ module fpm_command_line
5252
fpm_update_settings, &
5353
fpm_clean_settings, &
5454
fpm_publish_settings, &
55-
get_command_line_settings
55+
get_command_line_settings, &
56+
get_fpm_env
5657

5758
type, abstract :: fpm_cmd_settings
5859
character(len=:), allocatable :: working_dir

src/fpm_compiler.F90

Lines changed: 68 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -119,6 +119,10 @@ module fpm_compiler
119119
procedure :: serializable_is_same => compiler_is_same
120120
procedure :: dump_to_toml => compiler_dump
121121
procedure :: load_from_toml => compiler_load
122+
!> Fortran feature support
123+
procedure :: check_fortran_source_runs
124+
procedure :: with_xdp
125+
procedure :: with_qp
122126
!> Return compiler name
123127
procedure :: name => compiler_name
124128

@@ -1034,6 +1038,7 @@ subroutine new_compiler(self, fc, cc, cxx, echo, verbose)
10341038
else
10351039
call get_default_cxx_compiler(self%fc, self%cxx)
10361040
end if
1041+
10371042
end subroutine new_compiler
10381043

10391044

@@ -1424,6 +1429,69 @@ pure function compiler_name(self) result(name)
14241429
end select
14251430
end function compiler_name
14261431

1432+
!> Run a single-source Fortran program using the current compiler
1433+
!> Compile a Fortran object
1434+
logical function check_fortran_source_runs(self, input) result(success)
1435+
!> Instance of the compiler object
1436+
class(compiler_t), intent(in) :: self
1437+
!> Program Source
1438+
character(len=*), intent(in) :: input
1439+
1440+
integer :: stat,unit
1441+
character(:), allocatable :: source,object,logf,exe
1442+
1443+
success = .false.
1444+
1445+
!> Create temporary source file
1446+
exe = get_temp_filename()
1447+
source = exe//'.f90'
1448+
object = exe//'.o'
1449+
logf = exe//'.log'
1450+
open(newunit=unit, file=source, action='readwrite', iostat=stat)
1451+
if (stat/=0) return
1452+
1453+
!> Write contents
1454+
write(unit,*) input
1455+
close(unit)
1456+
1457+
!> Compile and link program
1458+
call self%compile_fortran(source, object, self%get_default_flags(release=.false.), logf, stat)
1459+
if (stat==0) &
1460+
call self%link(exe, self%get_default_flags(release=.false.)//" "//object, logf, stat)
1461+
1462+
!> Run and retrieve exit code
1463+
if (stat==0) &
1464+
call run(exe,echo=.false., exitstat=stat, verbose=.false., redirect=logf)
1465+
1466+
!> Successful exit on 0 exit code
1467+
success = stat==0
1468+
1469+
!> Delete files
1470+
open(newunit=unit, file=source, action='readwrite', iostat=stat)
1471+
close(unit,status='delete')
1472+
open(newunit=unit, file=object, action='readwrite', iostat=stat)
1473+
close(unit,status='delete')
1474+
open(newunit=unit, file=logf, action='readwrite', iostat=stat)
1475+
close(unit,status='delete')
1476+
open(newunit=unit, file=exe, action='readwrite', iostat=stat)
1477+
close(unit,status='delete')
1478+
1479+
end function check_fortran_source_runs
1480+
1481+
!> Check if the current compiler supports 128-bit real precision
1482+
logical function with_qp(self)
1483+
!> Instance of the compiler object
1484+
class(compiler_t), intent(in) :: self
1485+
with_qp = self%check_fortran_source_runs &
1486+
('if (selected_real_kind(33) == -1) stop 1; end')
1487+
end function with_qp
14271488

1489+
!> Check if the current compiler supports 80-bit "extended" real precision
1490+
logical function with_xdp(self)
1491+
!> Instance of the compiler object
1492+
class(compiler_t), intent(in) :: self
1493+
with_xdp = self%check_fortran_source_runs &
1494+
('if (any(selected_real_kind(18) == [-1, selected_real_kind(33)])) stop 1; end')
1495+
end function with_xdp
14281496

14291497
end module fpm_compiler

test/fpm_test/main.f90

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ program fpm_testing
33
use, intrinsic :: iso_fortran_env, only : error_unit
44
use testsuite, only : run_testsuite, new_testsuite, testsuite_t, select_suite, run_selected
55
use test_toml, only : collect_toml
6+
use test_compiler, only : collect_compiler
67
use test_manifest, only : collect_manifest
78
use test_filesystem, only : collect_filesystem
89
use test_source_parsing, only : collect_source_parsing
@@ -23,7 +24,7 @@ program fpm_testing
2324
stat = 0
2425

2526
suite = [ &
26-
& new_testsuite("fpm_toml", collect_toml), &
27+
& new_testsuite("fpm_toml", collect_toml), &
2728
& new_testsuite("fpm_manifest", collect_manifest), &
2829
& new_testsuite("fpm_filesystem", collect_filesystem), &
2930
& new_testsuite("fpm_source_parsing", collect_source_parsing), &
@@ -33,7 +34,8 @@ program fpm_testing
3334
& new_testsuite("fpm_installer", collect_installer), &
3435
& new_testsuite("fpm_versioning", collect_versioning), &
3536
& new_testsuite("fpm_settings", collect_settings), &
36-
& new_testsuite("fpm_os", collect_os) &
37+
& new_testsuite("fpm_os", collect_os), &
38+
& new_testsuite("fpm_compiler", collect_compiler) &
3739
& ]
3840

3941
call get_argument(1, suite_name)

test/fpm_test/test_compiler.f90

Lines changed: 56 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,56 @@
1+
!> Define tests for the `fpm_compiler` module
2+
module test_compiler
3+
use testsuite, only : new_unittest, unittest_t, error_t, test_failed, &
4+
& check_string
5+
use fpm_environment, only : OS_WINDOWS, OS_LINUX
6+
use fpm_compiler , only : compiler_t, new_compiler
7+
use fpm_command_line, only: get_fpm_env
8+
implicit none
9+
private
10+
11+
public :: collect_compiler
12+
13+
14+
contains
15+
16+
!> Collect all exported unit tests
17+
subroutine collect_compiler(testsuite)
18+
!> Collection of tests
19+
type(unittest_t), allocatable, intent(out) :: testsuite(:)
20+
21+
testsuite = [ &
22+
& new_unittest("check-fortran-source-runs", test_check_fortran_source_runs)]
23+
24+
end subroutine collect_compiler
25+
26+
subroutine test_check_fortran_source_runs(error)
27+
!> Error handling
28+
type(error_t), allocatable, intent(out) :: error
29+
30+
character(:), allocatable :: fc,cc,cxx
31+
32+
33+
type(compiler_t) :: compiler
34+
35+
!> Get default compiler
36+
fc = get_fpm_env("FC", default="gfortran")
37+
cc = get_fpm_env("CC", default=" ")
38+
cxx = get_fpm_env("CXX", default=" ")
39+
40+
call new_compiler(compiler, fc, cc, cxx, echo=.false., verbose=.false.)
41+
42+
if (compiler%is_unknown()) then
43+
call test_failed(error, "Cannot initialize Fortran compiler")
44+
return
45+
end if
46+
47+
!> Test fortran-source runs
48+
if (.not.compiler%check_fortran_source_runs("print *, 'Hello world!'; end")) then
49+
call test_failed(error, "Cannot run Fortran hello world")
50+
return
51+
end if
52+
53+
end subroutine test_check_fortran_source_runs
54+
55+
56+
end module test_compiler

0 commit comments

Comments
 (0)