fpm_manifest_profile Module

Implementation of the meta data for compiler flag profiles.

A profiles table can currently have the following subtables: Profile names - any string, if omitted, flags are appended to all matching profiles Compiler - any from the following list, omitting it yields an error

  • “gfortran”
  • “ifort”
  • “ifx”
  • “pgfortran”
  • “nvfortran”
  • “flang”
  • “caf”
  • “f95”
  • “lfortran”
  • “lfc”
  • “nagfor”
  • “crayftn”
  • “xlf90”
  • “ftn95”

OS - any from the following list, if omitted, the profile is used if and only if there is no profile perfectly matching the current configuration

  • “linux”
  • “macos”
  • “windows”
  • “cygwin”
  • “solaris”
  • “freebsd”
  • “openbsd”
  • “unknown”

Each of the subtables currently supports the following fields:

[profiles.debug.gfortran.linux]
 flags="-Wall -g -Og"
 c-flags="-g O1"
 cxx-flags="-g O1"
 link-time-flags="-xlinkopt"
 files={"hello_world.f90"="-Wall -O3"}


Variables

Type Visibility Attributes Name Initial
character(len=*), public, parameter :: DEFAULT_COMPILER = 'gfortran'

Name of the default compiler

integer, public, parameter :: OS_ALL = -1
character(len=:), public, allocatable :: path

Derived Types

type, public, extends(serializable_t) ::  file_scope_flag

Type storing file name - file scope compiler flags pairs

Components

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

Name of the file

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

File scope flags

Type-Bound Procedures

generic, public :: dump => dump_to_toml, dump_to_file, dump_to_unit
procedure, public :: dump_to_toml => file_scope_dump
generic, public :: load => load_from_toml, load_from_file, load_from_unit
procedure, public :: load_from_toml => file_scope_load
generic, public :: operator(==) => serializable_is_same
procedure, public :: serializable_is_same => file_scope_same ../../

Serialization interface

procedure, public, non_overridable :: test_serialization ../../

Test load/write roundtrip

type, public, extends(serializable_t) ::  profile_config_t

Configuration meta data for a profile

Components

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

C compiler flags

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

Name of the compiler

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

C++ compiler flags

type(file_scope_flag), public, allocatable :: file_scope_flags(:)

File scope flags

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

Fortran compiler flags

logical, public :: is_built_in = .false.

Is this profile one of the built-in ones?

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

Link time compiler flags

integer, public :: os_type = OS_ALL

Value repesenting OS

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

Name of the profile

Type-Bound Procedures

generic, public :: dump => dump_to_toml, dump_to_file, dump_to_unit
procedure, public :: dump_to_toml => profile_dump
procedure, public :: info ../../

Print information on this instance

generic, public :: load => load_from_toml, load_from_file, load_from_unit
procedure, public :: load_from_toml => profile_load
generic, public :: operator(==) => serializable_is_same
procedure, public :: serializable_is_same => profile_same ../../

Serialization interface

procedure, public, non_overridable :: test_serialization ../../

Test load/write roundtrip


Functions

public function file_scope_same(this, that)

All checks passed!

Arguments

Type IntentOptional Attributes Name
class(file_scope_flag), intent(in) :: this
class(serializable_t), intent(in) :: that

Return Value logical

public function get_default_profiles(error) result(default_profiles)

Construct an array of built-in profiles

Arguments

Type IntentOptional Attributes Name
type(error_t), intent(out), allocatable :: error

Error handling

Return Value type(profile_config_t), allocatable, (:)

public function info_profile(profile) result(s)

Print a representation of profile_config_t

Arguments

Type IntentOptional Attributes Name
type(profile_config_t), intent(in) :: profile

Profile to be represented

Return Value character(len=:), allocatable

String representation of given profile

public function new_profile(profile_name, compiler, os_type, flags, c_flags, cxx_flags, link_time_flags, file_scope_flags, is_built_in) result(profile)

Construct a new profile configuration from a TOML data structure

Arguments

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

Name of the profile

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

Name of the compiler

integer, intent(in) :: os_type

Type of the OS

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

Fortran compiler flags

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

C compiler flags

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

C++ compiler flags

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

Link time compiler flags

type(file_scope_flag), intent(in), optional :: file_scope_flags(:)

File scope flags

logical, intent(in), optional :: is_built_in

Is this profile one of the built-in ones?

Return Value type(profile_config_t)

public function os_type_name(os_type)

Match lowercase string with name of OS to os_type enum

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: os_type

Enum representing type of OS

Return Value character(len=:), allocatable

Name of operating system

public function profile_same(this, that)

All checks passed!

Arguments

Type IntentOptional Attributes Name
class(profile_config_t), intent(in) :: this
class(serializable_t), intent(in) :: that

Return Value logical


Subroutines

public subroutine file_scope_dump(self, table, error)

Dump to toml table

Arguments

Type IntentOptional Attributes Name
class(file_scope_flag), 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

public subroutine file_scope_load(self, table, error)

Read from toml table (no checks made at this stage)

Arguments

Type IntentOptional Attributes Name
class(file_scope_flag), 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

public subroutine find_profile(profiles, profile_name, compiler, os_type, found_matching, chosen_profile)

Look for profile with given configuration in array profiles

Arguments

Type IntentOptional Attributes Name
type(profile_config_t), intent(in), allocatable :: profiles(:)

Array of profiles

character(len=:), intent(in), allocatable :: profile_name

Name of profile

character(len=:), intent(in), allocatable :: compiler

Name of compiler

integer, intent(in) :: os_type

Type of operating system (enum)

logical, intent(out) :: found_matching

Boolean value containing true if matching profile was found

type(profile_config_t), intent(out) :: chosen_profile

Last matching profile in the profiles array

public subroutine get_flags(profile_name, compiler_name, os_type, key_list, table, profiles, profindex, os_valid)

Look for flags, c-flags, link-time-flags key-val pairs and files table in a given table and create new profiles

Arguments

Type IntentOptional Attributes Name
character(len=:), intent(in), allocatable :: profile_name

Name of profile

character(len=:), intent(in), allocatable :: compiler_name

Name of compiler

integer, intent(in) :: os_type

OS type

type(toml_key), intent(in), allocatable :: key_list(:)

List of keys in the table

type(toml_table), intent(in), pointer :: table

Table containing OS tables

type(profile_config_t), intent(inout), allocatable :: profiles(:)

List of profiles

integer, intent(inout) :: profindex

Index in the list of profiles

logical, intent(in) :: os_valid

Was called with valid operating system

public subroutine info(self, unit, verbosity)

Write information on instance

Arguments

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

Instance of the profile configuration

integer, intent(in) :: unit

Unit for IO

integer, intent(in), optional :: verbosity

Verbosity of the printout

public subroutine match_os_type(os_name, os_type)

Match os_type enum to a lowercase string with name of OS

Arguments

Type IntentOptional Attributes Name
character(len=:), intent(in), allocatable :: os_name

Name of operating system

integer, intent(out) :: os_type

Enum representing type of OS

public subroutine new_profiles(profiles, table, error)

Construct new profiles array from a TOML data structure

Arguments

Type IntentOptional Attributes Name
type(profile_config_t), intent(out), allocatable :: profiles(:)

Instance of the dependency configuration

type(toml_table), intent(inout), target :: table

Instance of the TOML data structure

type(error_t), intent(out), allocatable :: error

Error handling

public subroutine profile_dump(self, table, error)

Dump to toml table

Read more…

Arguments

Type IntentOptional Attributes Name
class(profile_config_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

public subroutine profile_load(self, table, error)

Read from toml table (no checks made at this stage)

Read more…

Arguments

Type IntentOptional Attributes Name
class(profile_config_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

public subroutine traverse_compilers(profile_name, comp_list, table, error, profiles_size, profiles, profindex)

Traverse compiler tables

Arguments

Type IntentOptional Attributes Name
character(len=:), intent(in), allocatable :: profile_name

Name of profile

type(toml_key), intent(in), allocatable :: comp_list(:)

List of OSs in table with profile name given

type(toml_table), intent(in), pointer :: table

Table containing compiler tables

type(error_t), intent(out), allocatable :: error

Error handling

integer, intent(inout), optional :: profiles_size

Number of profiles in list of profiles

type(profile_config_t), intent(inout), optional, allocatable :: profiles(:)

List of profiles

integer, intent(inout), optional :: profindex

Index in the list of profiles

public subroutine traverse_oss(profile_name, compiler_name, os_list, table, profiles, profindex, error)

Traverse operating system tables to obtain profiles

Arguments

Type IntentOptional Attributes Name
character(len=:), intent(in), allocatable :: profile_name

Name of profile

character(len=:), intent(in), allocatable :: compiler_name

Name of compiler

type(toml_key), intent(in), allocatable :: os_list(:)

List of OSs in table with profile name and compiler name given

type(toml_table), intent(in), pointer :: table

Table containing OS tables

type(profile_config_t), intent(inout), allocatable :: profiles(:)

List of profiles

integer, intent(inout) :: profindex

Index in the list of profiles

type(error_t), intent(out), allocatable :: error

Error handling

public subroutine traverse_oss_for_size(profile_name, compiler_name, os_list, table, profiles_size, error)

Traverse operating system tables to obtain number of profiles

Arguments

Type IntentOptional Attributes Name
character(len=:), intent(in), allocatable :: profile_name

Name of profile

character(len=:), intent(in), allocatable :: compiler_name

Name of compiler

type(toml_key), intent(in), allocatable :: os_list(:)

List of OSs in table with profile name and compiler name given

type(toml_table), intent(in), pointer :: table

Table containing OS tables

integer, intent(inout) :: profiles_size

Number of profiles in list of profiles

type(error_t), intent(out), allocatable :: error

Error handling

public subroutine validate_compiler_name(compiler_name, is_valid)

Check if compiler name is a valid compiler name

Arguments

Type IntentOptional Attributes Name
character(len=:), intent(in), allocatable :: compiler_name

Name of a compiler

logical, intent(out) :: is_valid

Boolean value of whether compiler_name is valid or not

public subroutine validate_os_name(os_name, is_valid)

Check if os_name is a valid name of a supported OS

Arguments

Type IntentOptional Attributes Name
character(len=:), intent(in), allocatable :: os_name

Name of an operating system

logical, intent(out) :: is_valid

Boolean value of whether os_name is valid or not

public subroutine validate_profile_table(profile_name, compiler_name, key_list, table, error, os_valid)

Arguments

Type IntentOptional Attributes Name
character(len=:), intent(in), allocatable :: profile_name

Name of profile

character(len=:), intent(in), allocatable :: compiler_name

Name of compiler

type(toml_key), intent(in), allocatable :: key_list(:)

List of keys in the table

type(toml_table), intent(in), pointer :: table

Table containing OS tables

type(error_t), intent(out), allocatable :: error

Error handling

logical, intent(in) :: os_valid

Was called with valid operating system