fpm_compiler Module

Define compiler command options

This module defines compiler options to use for the debug and release builds.



Contents


Variables

Type Visibility Attributes Name Initial
integer, public, parameter :: compiler_enum = kind(id_unknown)
character(len=*), public, parameter :: flag_cray_fixed_form = " -ffixed"
character(len=*), public, parameter :: flag_cray_free_form = " -ffree"
character(len=*), public, parameter :: flag_cray_implicit_typing = " -el"
character(len=*), public, parameter :: flag_cray_no_implicit_typing = " -dl"
character(len=*), public, parameter :: flag_gnu_backtrace = " -fbacktrace"
character(len=*), public, parameter :: flag_gnu_check = " -fcheck=bounds -fcheck=array-temps"
character(len=*), public, parameter :: flag_gnu_coarray = " -fcoarray=single"
character(len=*), public, parameter :: flag_gnu_debug = " -g"
character(len=*), public, parameter :: flag_gnu_external = " -Wimplicit-interface"
character(len=*), public, parameter :: flag_gnu_fixed_form = " -ffixed-form"
character(len=*), public, parameter :: flag_gnu_free_form = " -ffree-form"
character(len=*), public, parameter :: flag_gnu_limit = " -fmax-errors=1"
character(len=*), public, parameter :: flag_gnu_no_implicit_external = " -Werror=implicit-interface"
character(len=*), public, parameter :: flag_gnu_no_implicit_typing = " -fimplicit-none"
character(len=*), public, parameter :: flag_gnu_openmp = " -fopenmp"
character(len=*), public, parameter :: flag_gnu_opt = " -O3 -funroll-loops"
character(len=*), public, parameter :: flag_gnu_pic = " -fPIC"
character(len=*), public, parameter :: flag_gnu_warn = " -Wall -Wextra"
character(len=*), public, parameter :: flag_ibmxl_backslash = " -qnoescape"
character(len=*), public, parameter :: flag_intel_align = " -align all"
character(len=*), public, parameter :: flag_intel_align_win = " /align:all"
character(len=*), public, parameter :: flag_intel_backtrace = " -traceback"
character(len=*), public, parameter :: flag_intel_backtrace_win = " /traceback"
character(len=*), public, parameter :: flag_intel_byterecl = " -assume byterecl"
character(len=*), public, parameter :: flag_intel_byterecl_win = " /assume:byterecl"
character(len=*), public, parameter :: flag_intel_check = " -check all"
character(len=*), public, parameter :: flag_intel_check_win = " /check:all"
character(len=*), public, parameter :: flag_intel_debug = " -O0 -g"
character(len=*), public, parameter :: flag_intel_debug_win = " /Od /Z7"
character(len=*), public, parameter :: flag_intel_fixed_form = " -fixed"
character(len=*), public, parameter :: flag_intel_fixed_form_win = " /fixed"
character(len=*), public, parameter :: flag_intel_fp = " -fp-model precise -pc64"
character(len=*), public, parameter :: flag_intel_fp_win = " /fp:precise"
character(len=*), public, parameter :: flag_intel_free_form = " -free"
character(len=*), public, parameter :: flag_intel_free_form_win = " /free"
character(len=*), public, parameter :: flag_intel_limit = " -error-limit 1"
character(len=*), public, parameter :: flag_intel_limit_win = " /error-limit:1"
character(len=*), public, parameter :: flag_intel_nogen = " -nogen-interfaces"
character(len=*), public, parameter :: flag_intel_nogen_win = " /nogen-interfaces"
character(len=*), public, parameter :: flag_intel_openmp = " -qopenmp"
character(len=*), public, parameter :: flag_intel_openmp_win = " /Qopenmp"
character(len=*), public, parameter :: flag_intel_opt = " -O3"
character(len=*), public, parameter :: flag_intel_opt_win = " /O3"
character(len=*), public, parameter :: flag_intel_pthread = " -reentrancy threaded"
character(len=*), public, parameter :: flag_intel_pthread_win = " /reentrancy:threaded"
character(len=*), public, parameter :: flag_intel_standard_compliance = " -standard-semantics"
character(len=*), public, parameter :: flag_intel_standard_compliance_win = " /standard-semantics"
character(len=*), public, parameter :: flag_intel_warn = " -warn all"
character(len=*), public, parameter :: flag_intel_warn_win = " /warn:all"
character(len=*), public, parameter :: flag_lfortran_fixed_form = " --fixed-form"
character(len=*), public, parameter :: flag_lfortran_implicit_external = " --allow-implicit-interface"
character(len=*), public, parameter :: flag_lfortran_implicit_typing = " --implicit-typing"
character(len=*), public, parameter :: flag_lfortran_openmp = " --openmp"
character(len=*), public, parameter :: flag_lfortran_opt = " --fast"
character(len=*), public, parameter :: flag_nag_backtrace = " -gline"
character(len=*), public, parameter :: flag_nag_check = " -C"
character(len=*), public, parameter :: flag_nag_coarray = " -coarray=single"
character(len=*), public, parameter :: flag_nag_debug = " -g -O0"
character(len=*), public, parameter :: flag_nag_fixed_form = " -fixed"
character(len=*), public, parameter :: flag_nag_free_form = " -free"
character(len=*), public, parameter :: flag_nag_no_implicit_typing = " -u"
character(len=*), public, parameter :: flag_nag_openmp = " -openmp"
character(len=*), public, parameter :: flag_nag_opt = " -O4"
character(len=*), public, parameter :: flag_nag_pic = " -PIC"
character(len=*), public, parameter :: flag_pgi_backslash = " -Mbackslash"
character(len=*), public, parameter :: flag_pgi_check = " -Mbounds -Mchkptr -Mchkstk"
character(len=*), public, parameter :: flag_pgi_debug = " -g"
character(len=*), public, parameter :: flag_pgi_fixed_form = " -Mfixed"
character(len=*), public, parameter :: flag_pgi_free_form = " -Mfree"
character(len=*), public, parameter :: flag_pgi_openmp = " -mp"
character(len=*), public, parameter :: flag_pgi_traceback = " -traceback"
character(len=*), public, parameter :: flag_pgi_warn = " -Minform=inform"

Enumerations

enum, bind(c)

Enumerators

enumerator:: id_unknown = 0
enumerator:: id_gcc = 1
enumerator:: id_f95 = 2
enumerator:: id_caf = 3
enumerator:: id_intel_classic_nix = 4
enumerator:: id_intel_classic_mac = 5
enumerator:: id_intel_classic_windows = 6
enumerator:: id_intel_llvm_nix = 7
enumerator:: id_intel_llvm_windows = 8
enumerator:: id_intel_llvm_unknown = 9
enumerator:: id_pgi = 10
enumerator:: id_nvhpc = 11
enumerator:: id_nag = 12
enumerator:: id_flang = 13
enumerator:: id_flang_new = 14
enumerator:: id_f18 = 15
enumerator:: id_ibmxl = 16
enumerator:: id_cray = 17
enumerator:: id_lahey = 18
enumerator:: id_lfortran = 19

Interfaces

public interface debug

Create debug printout

  • public pure function debug_compiler(self) result(repr)

    String representation of a compiler object

    Arguments

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

    Instance of the compiler object

    Return Value character(len=:), allocatable

    Representation as string

  • public pure function debug_archiver(self) result(repr)

    String representation of an archiver object

    Arguments

    Type IntentOptional Attributes Name
    type(archiver_t), intent(in) :: self

    Instance of the archiver object

    Return Value character(len=:), allocatable

    Representation as string


Derived Types

type, public ::  archiver_t

Definition of archiver object

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: ar

Path to archiver

logical, public :: echo = .true.

Print all command

logical, public :: use_response_file = .false.

Use response files to pass arguments

logical, public :: verbose = .true.

Verbose output of command

Type-Bound Procedures

procedure , public , :: make_archive Subroutine

Create static archive

type, public ::  compiler_t

Definition of compiler object

Components

Type Visibility Attributes Name Initial
character(len=:), public, allocatable :: cc

Path to the C compiler

character(len=:), public, allocatable :: cxx

Path to the C++ compiler

logical, public :: echo = .true.

Print all commands

character(len=:), public, allocatable :: fc

Path to the Fortran compiler

integer(kind=compiler_enum), public :: id = id_unknown

Identifier of the compiler

logical, public :: verbose = .true.

Verbose output of command

Type-Bound Procedures

procedure , public , :: compile_c Subroutine

Compile a C object

procedure , public , :: compile_cpp Subroutine

Compile a CPP object

procedure , public , :: compile_fortran Subroutine

Compile a Fortran object

procedure , public , :: enumerate_libraries Function

Enumerate libraries, based on compiler and platform

procedure , public , :: get_default_flags Function

Get default compiler flags

procedure , public , :: get_feature_flag Function

Get feature flag

procedure , public , :: get_include_flag Function

Get flag for include directories

procedure , public , :: get_main_flags Subroutine

Get flags for the main linking command

procedure , public , :: get_module_flag Function

Get flag for module output directories

procedure , public , :: is_gnu Function

Check whether this is a GNU compiler

procedure , public , :: is_intel Function

Check whether this is an Intel compiler

procedure , public , :: is_unknown Function

Check whether compiler is recognized

procedure , public , :: link Subroutine

Link executable

procedure , public , :: name => compiler_name Function

Return compiler name


Functions

public function check_compiler(compiler, expected) result(match)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: compiler
character(len=*), intent(in) :: expected

Return Value logical

public pure function compiler_name(self) result(name)

Return a compiler name string

Arguments

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

Instance of the compiler object

Return Value character(len=:), allocatable

Representation as string

public pure function debug_archiver(self) result(repr)

String representation of an archiver object

Arguments

Type IntentOptional Attributes Name
type(archiver_t), intent(in) :: self

Instance of the archiver object

Return Value character(len=:), allocatable

Representation as string

public pure function debug_compiler(self) result(repr)

String representation of a compiler object

Arguments

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

Instance of the compiler object

Return Value character(len=:), allocatable

Representation as string

public function enumerate_libraries(self, prefix, libs) result(r)

Enumerate libraries, based on compiler and platform

Arguments

Type IntentOptional Attributes Name
class(compiler_t), intent(in) :: self
character(len=*), intent(in) :: prefix
type(string_t), intent(in) :: libs(:)

Return Value character(len=:), allocatable

public function get_compiler_id(compiler) result(id)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: compiler

Return Value integer(kind=compiler_enum)

public function get_default_flags(self, release) result(flags)

Arguments

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

Return Value character(len=:), allocatable

public function get_feature_flag(self, feature) result(flags)

Arguments

Type IntentOptional Attributes Name
class(compiler_t), intent(in) :: self
character(len=*), intent(in) :: feature

Return Value character(len=:), allocatable

public function get_id(compiler) result(id)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: compiler

Return Value integer(kind=compiler_enum)

public function get_include_flag(self, path) result(flags)

Arguments

Type IntentOptional Attributes Name
class(compiler_t), intent(in) :: self
character(len=*), intent(in) :: path

Return Value character(len=:), allocatable

public function get_macros(id, macros_list, version) result(macros)

This function will parse and read the macros list and return them as defined flags. Set macro defintion symbol on the basis of compiler used Check if macros are not allocated. Split the macro name and value.

Read more…

Arguments

Type IntentOptional Attributes Name
integer(kind=compiler_enum), intent(in) :: id
type(string_t), intent(in), allocatable :: macros_list(:)
character(len=:), intent(in), allocatable :: version

Return Value character(len=:), allocatable

public function get_module_flag(self, path) result(flags)

Arguments

Type IntentOptional Attributes Name
class(compiler_t), intent(in) :: self
character(len=*), intent(in) :: path

Return Value character(len=:), allocatable

public pure function is_gnu(self)

Arguments

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

Return Value logical

public pure function is_intel(self)

Arguments

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

Return Value logical

public pure function is_unknown(self)

Arguments

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

Return Value logical


Subroutines

public subroutine compile_c(self, input, output, args, log_file, stat)

Compile a C object

Arguments

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

Instance of the compiler object

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

Source file input

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

public subroutine compile_cpp(self, input, output, args, log_file, stat)

Compile a CPP object

Arguments

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

Instance of the compiler object

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

Source file input

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

public subroutine compile_fortran(self, input, output, args, log_file, stat)

Compile a Fortran object

Arguments

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

Instance of the compiler object

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

Source file input

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

public subroutine get_debug_compile_flags(id, flags)

Arguments

Type IntentOptional Attributes Name
integer(kind=compiler_enum), intent(in) :: id
character(len=:), intent(out), allocatable :: flags

public subroutine get_default_c_compiler(f_compiler, c_compiler)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: f_compiler
character(len=:), intent(out), allocatable :: c_compiler

public subroutine get_default_cxx_compiler(f_compiler, cxx_compiler)

Get C++ Compiler.

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: f_compiler
character(len=:), intent(out), allocatable :: cxx_compiler

public subroutine get_main_flags(self, language, flags)

Get special flags for the main linker

Arguments

Type IntentOptional Attributes Name
class(compiler_t), intent(in) :: self
character(len=*), intent(in) :: language
character(len=:), intent(out), allocatable :: flags

public subroutine get_release_compile_flags(id, flags)

Arguments

Type IntentOptional Attributes Name
integer(kind=compiler_enum), intent(in) :: id
character(len=:), intent(out), allocatable :: flags

public subroutine link(self, output, args, log_file, stat)

Link an executable

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

public subroutine make_archive(self, output, args, log_file, stat)

Create an archive

Read more…

Arguments

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

Instance of the archiver object

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

Name of the archive to generate

type(string_t), intent(in) :: args(:)

Object files to include into the archive

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

Compiler output log file

integer, intent(out) :: stat

Status flag

public subroutine new_archiver(self, ar, echo, verbose)

Create new archiver instance

Arguments

Type IntentOptional Attributes Name
type(archiver_t), intent(out) :: self

New instance of the archiver

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

User provided archiver command

logical, intent(in) :: echo

Echo compiler command

logical, intent(in) :: verbose

Verbose mode: dump compiler output

public subroutine new_compiler(self, fc, cc, cxx, echo, verbose)

Create new compiler instance

Arguments

Type IntentOptional Attributes Name
type(compiler_t), intent(out) :: self

New instance of the compiler

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

Fortran compiler name or path

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

C compiler name or path

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

C++ Compiler name or path

logical, intent(in) :: echo

Echo compiler command

logical, intent(in) :: verbose

Verbose mode: dump compiler output

public pure subroutine set_cpp_preprocessor_flags(id, flags)

Modify the flag_cpp_preprocessor on the basis of the compiler.

Arguments

Type IntentOptional Attributes Name
integer(kind=compiler_enum), intent(in) :: id
character(len=:), intent(inout), allocatable :: flags

public subroutine write_response_file(name, argv)

Response files allow to read command line options from files. Whitespace is used to separate the arguments, we will use newlines as separator to create readable response files which can be inspected in case of errors.

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: name
type(string_t), intent(in) :: argv(:)