Run a single-source Fortran program using the current compiler Compile a Fortran object Create temporary source file Write contents Get flags Intel: Needs -warn last for error on unknown command line arguments to work Compile and link program Run and retrieve exit code
Successful exit on 0 exit code
Delete files
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self |
Instance of the compiler object |
||
character(len=*), | intent(in) | :: | input |
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 |
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 |
logical function check_fortran_source_runs(self, input, compile_flags, link_flags) result(success) !> Instance of the compiler object class(compiler_t), intent(in) :: self !> 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//'.f90' object = exe//'.o' logf = exe//'.log' open(newunit=unit, file=source, action='readwrite', iostat=stat) if (stat/=0) return !> Write contents write(unit,*) input close(unit) !> Get flags flags = self%get_default_flags(release=.false.) ldflags = self%get_default_flags(release=.false.) if (present(compile_flags)) flags = flags//" "//compile_flags if (present(link_flags)) ldflags = ldflags//" "//link_flags !> Intel: Needs -warn last for error on unknown command line arguments to work if (self%id == id_intel_llvm_nix) then flags = flags//" "//flag_intel_warn ldflags = ldflags//" "//flag_intel_warn elseif (self%id == id_intel_llvm_windows) then flags = flags//" "//flag_intel_warn_win ldflags = ldflags//" "//flag_intel_warn_win end if !> Compile and link program call self%compile_fortran(source, object, flags, logf, stat) if (stat==0) & call self%link(exe, ldflags//" "//object, logf, stat) !> Run and retrieve exit code if (stat==0) & call run(exe,echo=.false., exitstat=stat, verbose=.false., redirect=logf) !> Successful exit on 0 exit code success = stat==0 !> Delete 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_fortran_source_runs