link_executable Subroutine

public subroutine link_executable(self, output, args, log_file, stat, dry_run)

Link an executable

Type Bound

compiler_t

Arguments

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

Instance of the compiler object

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

Output file of object

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

Arguments for compiler

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

Compiler output log file

integer, intent(out) :: stat

Status flag

logical, intent(in), optional :: dry_run

Optional mocking


Variables

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: command
logical, public :: mock

Source Code

subroutine link_executable(self, output, args, log_file, stat, dry_run)
    !> Instance of the compiler object
    class(compiler_t), intent(in) :: self
    !> Output file of object
    character(len=*), intent(in) :: output
    !> Arguments for compiler
    character(len=*), intent(in) :: args
    !> Compiler output log file
    character(len=*), intent(in) :: log_file
    !> Status flag
    integer, intent(out) :: stat
    !> Optional mocking
    logical, optional, intent(in) :: dry_run    
    
    character(len=:), allocatable :: command 
    logical :: mock
        
    ! Check if we're actually linking
    mock = .false.
    if (present(dry_run)) mock = dry_run                
        
    ! Set command
    command = self%fc // " " // args // " -o " // output    
    
    ! Execute command
    if (.not.mock) &
    call run(command, echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
    
end subroutine link_executable