fpm_targets Module

Build target handling

This module handles the construction of the build target list from the sources list ([[targets_from_sources]]), the resolution of module-dependencies between build targets ([[resolve_module_dependencies]]), and the enumeration of objects required for link targets ([[resolve_target_linking]]).

A build target ([[build_target_t]]) is a file to be generated by the backend (compilation and linking).

@note Note The current implementation is ignorant to the existence of module files (.mod,.smod). Dependencies arising from modules are based on the corresponding object files (.o) only.

For more information, please read the documentation for the procedures:

  • [[build_target_list]]
  • [[resolve_module_dependencies]]

Enumerations

Target type: FPM_TARGET_* Describes the type of build target — determines backend build rules



Variables

Type Visibility Attributes Name Initial
integer, public, parameter :: FPM_TARGET_ARCHIVE = 2

Target type is library archive

integer, public, parameter :: FPM_TARGET_CPP_OBJECT = 5

Target type is cpp compiled object

integer, public, parameter :: FPM_TARGET_C_OBJECT = 4

Target type is c compiled object

integer, public, parameter :: FPM_TARGET_EXECUTABLE = 1

Target type is executable

integer, public, parameter :: FPM_TARGET_OBJECT = 3

Target type is compiled object

integer, public, parameter :: FPM_TARGET_UNKNOWN = -1

Target type is unknown (ignored)


Derived Types

type, public ::  build_target_ptr

Wrapper type for constructing arrays of [[build_target_t]] pointers

Components

Type Visibility Attributes Name Initial
type(build_target_t), public, pointer :: ptr => null()

type, public ::  build_target_t

Type describing a generated build target

Components

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

Compile flags for this build target

type(build_target_ptr), public, allocatable :: dependencies(:)

Resolved build dependencies

integer(kind=int64), public, allocatable :: digest_cached

Previous source file hash

type(fortran_features_t), public :: features

Language features

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

Link flags for this build target

type(string_t), public, allocatable :: link_libraries(:)

Native libraries to link against

type(string_t), public, allocatable :: link_objects(:)

Objects needed to link this target

type(string_t), public, allocatable :: macros(:)

List of macros

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

File path of output directory

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

File path of build target object relative to cwd

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

File path of build log file relative to cwd

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

File path of build target object relative to output_dir

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

Name of parent package

integer, public :: schedule = -1

Targets in the same schedule group are guaranteed to be independent

logical, public :: skip = .false.

Flag set if build target will be skipped (not built)

logical, public :: sorted = .false.

Flag set if build target is sorted for building

type(srcfile_t), public, allocatable :: source

Primary source for this build target

integer, public :: target_type = FPM_TARGET_UNKNOWN

Target type

logical, public :: touched = .false.

Flag set when first visited to check for circular dependencies

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

Version number


Functions

public pure function FPM_TARGET_NAME(type) result(msg)

Target type name

Arguments

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

Return Value character(len=:), allocatable


Subroutines

public subroutine add_dependency(target, dependency)

Add pointer to dependeny in target%dependencies

Arguments

Type IntentOptional Attributes Name
type(build_target_t), intent(inout) :: target
type(build_target_t), intent(in), target :: dependency

public subroutine add_target(targets, package, type, output_name, source, link_libraries, features, preprocess, version)

Allocate a new target and append to target list

Arguments

Type IntentOptional Attributes Name
type(build_target_ptr), intent(inout), allocatable :: targets(:)
character(len=*), intent(in) :: package
integer, intent(in) :: type
character(len=*), intent(in) :: output_name
type(srcfile_t), intent(in), optional :: source
type(string_t), intent(in), optional :: link_libraries(:)
type(fortran_features_t), intent(in), optional :: features
type(preprocess_config_t), intent(in), optional :: preprocess
character(len=*), intent(in), optional :: version

public subroutine filter_executable_targets(targets, scope, list)

Arguments

Type IntentOptional Attributes Name
type(build_target_ptr), intent(in) :: targets(:)
integer, intent(in) :: scope
type(string_t), intent(out), allocatable :: list(:)

public subroutine filter_library_targets(targets, list)

Arguments

Type IntentOptional Attributes Name
type(build_target_ptr), intent(in) :: targets(:)
type(string_t), intent(out), allocatable :: list(:)

public subroutine filter_modules(targets, list)

Arguments

Type IntentOptional Attributes Name
type(build_target_ptr), intent(in) :: targets(:)
type(string_t), intent(out), allocatable :: list(:)

public subroutine resolve_module_dependencies(targets, external_modules, error)

Add dependencies to source-based targets (FPM_TARGET_OBJECT) based on any modules used by the corresponding source file.

Read more…

Arguments

Type IntentOptional Attributes Name
type(build_target_ptr), intent(inout), target :: targets(:)
type(string_t), intent(in) :: external_modules(:)
type(error_t), intent(out), allocatable :: error

public subroutine targets_from_sources(targets, model, prune, error)

High-level wrapper to generate build target information

Arguments

Type IntentOptional Attributes Name
type(build_target_ptr), intent(out), allocatable :: targets(:)

The generated list of build targets

type(fpm_model_t), intent(inout), target :: model

The package model from which to construct the target list

logical, intent(in) :: prune

Enable tree-shaking/pruning of module dependencies

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

Error structure