@@ -119,6 +119,8 @@ 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
122124 ! > Return compiler name
123125 procedure :: name = > compiler_name
124126
@@ -1017,6 +1019,8 @@ subroutine new_compiler(self, fc, cc, cxx, echo, verbose)
10171019 logical , intent (in ) :: echo
10181020 ! > Verbose mode: dump compiler output
10191021 logical , intent (in ) :: verbose
1022+
1023+ logical :: quad
10201024
10211025 self% id = get_compiler_id(fc)
10221026
@@ -1034,6 +1038,14 @@ 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+
1042+
1043+ quad = has_quad_precision(self)
1044+
1045+ print * , ' has quad=' ,quad
1046+
1047+ stop ' temporary: new compiler'
1048+
10371049end subroutine new_compiler
10381050
10391051
@@ -1424,6 +1436,53 @@ pure function compiler_name(self) result(name)
14241436 end select
14251437end function compiler_name
14261438
1427-
1439+ ! > Run a single-source Fortran program using the current compiler
1440+ ! > Compile a Fortran object
1441+ logical function check_fortran_source_runs (self , input ) result(success)
1442+ ! > Instance of the compiler object
1443+ class(compiler_t), intent (in ) :: self
1444+ ! > Program Source
1445+ character (len=* ), intent (in ) :: input
1446+
1447+ integer :: stat,unit
1448+ character (:), allocatable :: source,object,logf,exe
1449+
1450+ success = .false.
1451+
1452+ ! > Create temporary source file
1453+ exe = get_temp_filename()
1454+ source = exe// ' .f90'
1455+ object = exe// ' .o'
1456+ logf = exe// ' .log'
1457+ open (newunit= unit, file= source, action= ' readwrite' , iostat= stat)
1458+ if (stat/= 0 ) return
1459+
1460+ ! > Write contents
1461+ write (unit,* ) input
1462+ close (unit)
1463+
1464+ ! > Compile and link program
1465+ call self% compile_fortran(source, object, self% get_default_flags(release= .false. ), logf, stat)
1466+ if (stat== 0 ) &
1467+ call self% link(exe, self% get_default_flags(release= .false. )// " " // object, logf, stat)
1468+
1469+ ! > Run and retrieve exit code
1470+ if (stat== 0 ) &
1471+ call run(exe,echo= .false. , exitstat= stat)
1472+
1473+ ! > Successful exit on 0 exit code
1474+ success = stat== 0
1475+
1476+ ! > Delete files
1477+ open (newunit= unit, file= source, action= ' readwrite' , iostat= stat)
1478+ close (unit,status= ' delete' )
1479+ open (newunit= unit, file= object, action= ' readwrite' , iostat= stat)
1480+ close (unit,status= ' delete' )
1481+ open (newunit= unit, file= logf, action= ' readwrite' , iostat= stat)
1482+ close (unit,status= ' delete' )
1483+ open (newunit= unit, file= exe, action= ' readwrite' , iostat= stat)
1484+ close (unit,status= ' delete' )
1485+
1486+ end function check_fortran_source_runs
14281487
14291488end module fpm_compiler
0 commit comments