This module defines compiler options to use for the debug and release builds.
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_llvm_check | = | " -check all,nouninit" | |
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 | = | " --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" |
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 |
Create debug printout
String representation of a compiler object
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(compiler_t), | intent(in) | :: | self |
Instance of the compiler object |
Representation as string
String representation of an archiver object
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(archiver_t), | intent(in) | :: | self |
Instance of the archiver object |
Representation as string
Definition of archiver object
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 |
generic, public :: dump => dump_to_toml, dump_to_file, dump_to_unit | |
procedure, public :: dump_to_toml | |
generic, public :: load => load_from_toml, load_from_file, load_from_unit | |
procedure, public :: load_from_toml | |
procedure, public :: make_archive | ../../ Create static archive |
generic, public :: operator(==) => serializable_is_same | |
procedure, public :: serializable_is_same => ar_is_same | ../../ Serialization interface |
procedure, public, non_overridable :: test_serialization | ../../ Test load/write roundtrip |
Definition of compiler object
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 |
procedure, public :: check_fortran_source_runs | ../../ Fortran feature support |
procedure, public :: compile_c | ../../ Compile a C object |
procedure, public :: compile_cpp | ../../ Compile a CPP object |
procedure, public :: compile_fortran | ../../ Compile a Fortran object |
generic, public :: dump => dump_to_toml, dump_to_file, dump_to_unit | |
procedure, public :: dump_to_toml => compiler_dump | |
procedure, public :: enumerate_libraries | ../../ Enumerate libraries, based on compiler and platform |
procedure, public :: get_default_flags | ../../ Get default compiler flags |
procedure, public :: get_feature_flag | ../../ Get feature flag |
procedure, public :: get_include_flag | ../../ Get flag for include directories |
procedure, public :: get_main_flags | ../../ Get flags for the main linking command |
procedure, public :: get_module_flag | ../../ Get flag for module output directories |
procedure, public :: is_gnu | ../../ Check whether this is a GNU compiler |
procedure, public :: is_intel | ../../ Check whether this is an Intel compiler |
procedure, public :: is_unknown | ../../ Check whether compiler is recognized |
procedure, public :: link | ../../ Link executable |
generic, public :: load => load_from_toml, load_from_file, load_from_unit | |
procedure, public :: load_from_toml => compiler_load | |
procedure, public :: name => compiler_name | ../../ Return compiler name |
generic, public :: operator(==) => serializable_is_same | |
procedure, public :: serializable_is_same => compiler_is_same | ../../ Serialization interface |
procedure, public, non_overridable :: test_serialization | ../../ Test load/write roundtrip |
procedure, public :: with_qp | |
procedure, public :: with_xdp |
Check that two archiver_t objects are equal All checks passed!
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(archiver_t), | intent(in) | :: | this | |||
class(serializable_t), | intent(in) | :: | that |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | compiler | |||
character(len=*), | intent(in) | :: | expected |
Run a single-source Fortran program using the current compiler Compile a Fortran object Create temporary source file Write contents Compile and link program Run and retrieve exit code
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self |
Instance of the compiler object |
||
character(len=*), | intent(in) | :: | input |
Program Source |
Check that two compiler_t objects are equal All checks passed!
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | this | |||
class(serializable_t), | intent(in) | :: | that |
Return a compiler name string
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self |
Instance of the compiler object |
Representation as string
String representation of an archiver object
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(archiver_t), | intent(in) | :: | self |
Instance of the archiver object |
Representation as string
String representation of a compiler object
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(compiler_t), | intent(in) | :: | self |
Instance of the compiler object |
Representation as string
Enumerate libraries, based on compiler and platform
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self | |||
character(len=*), | intent(in) | :: | prefix | |||
type(string_t), | intent(in) | :: | libs(:) |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | compiler |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self | |||
logical, | intent(in) | :: | release |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self | |||
character(len=*), | intent(in) | :: | feature |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | compiler |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self | |||
character(len=*), | intent(in) | :: | path |
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.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=compiler_enum), | intent(in) | :: | id | |||
type(string_t), | intent(in), | allocatable | :: | macros_list(:) | ||
character(len=:), | intent(in), | allocatable | :: | version |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self | |||
character(len=*), | intent(in) | :: | path |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self |
Check if the current compiler supports 128-bit real precision
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self |
Instance of the compiler object |
Check if the current compiler supports 80-bit “extended” real precision
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self |
Instance of the compiler object |
Compile a C object
Type | Intent | Optional | 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 |
Compile a CPP object
Type | Intent | Optional | 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 |
Compile a Fortran object
Type | Intent | Optional | 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 |
Dump dependency to toml table
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(inout) | :: | self |
Instance of the serializable object |
||
type(toml_table), | intent(inout) | :: | table |
Data structure |
||
type(error_t), | intent(out), | allocatable | :: | error |
Error handling |
Read dependency from toml table (no checks made at this stage)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(inout) | :: | self |
Instance of the serializable object |
||
type(toml_table), | intent(inout) | :: | table |
Data structure |
||
type(error_t), | intent(out), | allocatable | :: | error |
Error handling |
Dump dependency to toml table
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(archiver_t), | intent(inout) | :: | self |
Instance of the serializable object |
||
type(toml_table), | intent(inout) | :: | table |
Data structure |
||
type(error_t), | intent(out), | allocatable | :: | error |
Error handling |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=compiler_enum), | intent(in) | :: | id | |||
character(len=:), | intent(out), | allocatable | :: | flags |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | f_compiler | |||
character(len=:), | intent(out), | allocatable | :: | c_compiler |
Get C++ Compiler.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | f_compiler | |||
character(len=:), | intent(out), | allocatable | :: | cxx_compiler |
Get special flags for the main linker
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(compiler_t), | intent(in) | :: | self | |||
character(len=*), | intent(in) | :: | language | |||
character(len=:), | intent(out), | allocatable | :: | flags |
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=compiler_enum), | intent(in) | :: | id | |||
character(len=:), | intent(out), | allocatable | :: | flags |
Link an executable
Type | Intent | Optional | 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 |
Read dependency from toml table (no checks made at this stage)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(archiver_t), | intent(inout) | :: | self |
Instance of the serializable object |
||
type(toml_table), | intent(inout) | :: | table |
Data structure |
||
type(error_t), | intent(out), | allocatable | :: | error |
Error handling |
Create an archive
Type | Intent | Optional | 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 |
Create new archiver instance
Type | Intent | Optional | 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 |
Create new compiler instance
Type | Intent | Optional | 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 |
Modify the flag_cpp_preprocessor on the basis of the compiler.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=compiler_enum), | intent(in) | :: | id | |||
character(len=:), | intent(inout), | allocatable | :: | flags |
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.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | name | |||
type(string_t), | intent(in) | :: | argv(:) |