check_cxx_source_runs Function

public function check_cxx_source_runs(self, input, compile_flags, link_flags) result(success)

Check if the given C++ source code compiles, links, and runs successfully Create temporary source file Write contents Get flags Compile Link using C++ compiler for pure C++ programs Run Delete temporary files

Type Bound

compiler_t

Arguments

Type IntentOptional Attributes Name
class(compiler_t), intent(in) :: self

Instance of the compiler object

character(len=*), intent(in) :: input

C++ program source

character(len=*), intent(in), optional :: compile_flags

Optional build and link flags

character(len=*), intent(in), optional :: link_flags

Optional build and link flags

Return Value logical


Variables

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: exe
character(len=:), public, allocatable :: flags
character(len=:), public, allocatable :: ldflags
character(len=:), public, allocatable :: logf
character(len=:), public, allocatable :: object
character(len=:), public, allocatable :: source
integer, public :: stat
integer, public :: unit

Source Code

logical function check_cxx_source_runs(self, input, compile_flags, link_flags) result(success)
    !> Instance of the compiler object
    class(compiler_t), intent(in) :: self
    !> C++ program source
    character(len=*), intent(in) :: input
    !> Optional build and link flags
    character(len=*), optional, intent(in) :: compile_flags, link_flags
    integer :: stat,unit
    character(:), allocatable :: source,object,logf,exe,flags,ldflags
    
    success = .false.
    
    !> Create temporary source file
    exe    = get_temp_filename()
    source = exe//'.cpp'
    object = exe//'.o'
    logf   = exe//'.log'
    
    open(newunit=unit, file=source, action='readwrite', iostat=stat)
    if (stat/=0) return
    
    !> Write contents
    write(unit,'(a)') input
    close(unit)
    
    !> Get flags
    flags    = ""
    ldflags  = ""
    if (present(compile_flags)) flags = flags//" "//compile_flags
    if (present(link_flags)) ldflags = ldflags//" "//link_flags
    
    !> Compile
    call self%compile_cpp(source,object,flags,logf,stat,dry_run=.false.)
    if (stat/=0) return
    
    !> Link using C++ compiler for pure C++ programs
    call run(self%cxx//" "//ldflags//" "//object//" -o "//exe, &
              echo=self%echo, verbose=self%verbose, redirect=logf, exitstat=stat)
    if (stat/=0) return
    
    !> Run
    call run(exe//" > "//logf//" 2>&1",echo=.false.,exitstat=stat)
    success = (stat == 0)
    
    !> Delete temporary files
    open(newunit=unit, file=source, action='readwrite', iostat=stat)
    close(unit,status='delete')
    open(newunit=unit, file=object, action='readwrite', iostat=stat)
    close(unit,status='delete')
    open(newunit=unit, file=logf, action='readwrite', iostat=stat)
    close(unit,status='delete')
    open(newunit=unit, file=exe, action='readwrite', iostat=stat)
    close(unit,status='delete')
    
end function check_cxx_source_runs