fpm_dependency Module

Dependency management

Fetching dependencies and creating a dependency tree

Dependencies on the top-level can be specified from:

  • package%dependencies
  • package%dev_dependencies
  • package%executable(:)%dependencies
  • package%test(:)%dependencies

Each dependency is fetched in some way and provides a path to its package manifest. The package%dependencies of the dependencies are resolved recursively.

To initialize the dependency tree all dependencies are recursively fetched and stored in a flat data structure to avoid retrieving a package twice. The data structure used to store this information should describe the current status of the dependency tree. Important information are:

  • name of the package
  • version of the package
  • path to the package root

Additionally, for version controlled dependencies the following should be stored along with the package:

  • the upstream url
  • the current checked out revision

Fetching a remote (version controlled) dependency turns it for our purpose into a local path dependency which is handled by the same means.

Updating dependencies

For a given dependency tree all top-level dependencies can be updated. We have two cases to consider, a remote dependency and a local dependency, again, remote dependencies turn into local dependencies by fetching. Therefore we will update remote dependencies by simply refetching them.

For remote dependencies we have to refetch if the revision in the manifest changes or the upstream HEAD has changed (for branches and tags).

Note

For our purpose a tag is just a fancy branch name. Tags can be delete and modified afterwards, therefore they do not differ too much from branches from our perspective.

For the latter case we only know if we actually fetch from the upstream URL.

In case of local (and fetched remote) dependencies we have to read the package manifest and compare its dependencies against our dependency tree, any change requires updating the respective dependencies as well.

Handling dependency compatibilties

Currenly ignored. First come, first serve.



Interfaces

public interface resize

Overloaded reallocation interface

  • private pure subroutine resize_dependency_node(var, n)

    Reallocate a list of dependencies

    Arguments

    Type IntentOptional Attributes Name
    type(dependency_node_t), intent(inout), allocatable :: var(:)

    Instance of the array to be resized

    integer, intent(in), optional :: n

    Dimension of the final array size


Derived Types

type, public, extends(dependency_config_t) ::  dependency_node_t

Dependency node in the projects dependency tree

Components

Type Visibility Attributes Name Initial
logical, public :: cached = .false.

Dependency was loaded from a cache

logical, public :: done = .false.

Dependency is handled

type(git_target_t), public, allocatable :: git

Git descriptor

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

Name of the dependency

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

Namespace which the dependency belongs to. Enables multiple dependencies with the same name. Required for dependencies that are obtained via the official registry.

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

Package dependencies of this node

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

Local target

type(preprocess_config_t), public, allocatable :: preprocess(:)

Requested macros for the dependency

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

Installation prefix of this dependencies

type(version_t), public, allocatable :: requested_version

The requested version of the dependency. The latest version is used if not specified.

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

Checked out revision of the version control system

logical, public :: update = .false.

Dependency should be updated

type(version_t), public, allocatable :: version

Actual version of this dependency

Type-Bound Procedures

procedure, public :: add_preprocess

Add a preprocessor configuration

generic, public :: dump => dump_to_toml, dump_to_file, dump_to_unit
procedure, public :: dump_to_toml => node_dump_to_toml
procedure, public :: get_from_registry

Get dependency from the registry.

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 => node_load_from_toml
generic, public :: operator(==) => serializable_is_same
procedure, public :: register

Update dependency from project manifest.

procedure, public :: serializable_is_same => dependency_node_is_same

Serialization interface

procedure, public, non_overridable :: test_serialization

Test load/write roundtrip

type, public, extends(serializable_t) ::  dependency_tree_t

Respresentation of a projects dependencies

Read more…

Components

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

Cache file

type(dependency_node_t), public, allocatable :: dep(:)

Flattend list of all dependencies

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

Installation prefix for dependencies

integer, public :: ndep = 0

Number of currently registered dependencies

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

Custom path to the global config file

integer, public :: unit = output_unit

Unit for IO

integer, public :: verbosity = 1

Verbosity of printout

Type-Bound Procedures

generic, public :: add => add_project, add_project_dependencies, add_dependencies, add_dependency, add_dependency_node

Overload procedure to add new dependencies to the tree

generic, public :: dump => dump_to_toml, dump_to_file, dump_to_unit
generic, public :: dump_cache => dump_cache_to_file, dump_cache_to_unit, dump_cache_to_toml

Writing of dependency tree

procedure, public :: dump_to_toml => tree_dump_to_toml
generic, public :: find => find_name

Find a dependency in the tree

procedure, public :: finished

Depedendncy resolution finished

generic, public :: has => has_dependency

True if entity can be found

generic, public :: load => load_from_toml, load_from_file, load_from_unit
generic, public :: load_cache => load_cache_from_file, load_cache_from_unit, load_cache_from_toml

Reading of dependency tree

procedure, public :: load_from_toml => tree_load_from_toml
procedure, public :: local_link_order

Establish local link order for a node’s package dependencies

generic, public :: operator(==) => serializable_is_same
generic, public :: resolve => resolve_dependencies, resolve_dependency

Resolve dependencies

procedure, public :: serializable_is_same => dependency_tree_is_same

Serialization interface

procedure, public, non_overridable :: test_serialization

Test load/write roundtrip

generic, public :: update => update_dependency, update_tree

Update dependency tree


Subroutines

public subroutine check_and_read_pkg_data(json, node, download_url, version, error)

Arguments

Type IntentOptional Attributes Name
type(json_object), intent(inout) :: json
class(dependency_node_t), intent(in) :: node
character(len=:), intent(out), allocatable :: download_url
type(version_t), intent(out) :: version
type(error_t), intent(out), allocatable :: error

public elemental subroutine destroy_dependency_node(self)

Destructor

Arguments

Type IntentOptional Attributes Name
class(dependency_node_t), intent(inout) :: self

public subroutine new_dependency_node(self, dependency, version, proj_dir, update)

Create a new dependency node from a configuration

Arguments

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

Instance of the dependency node

type(dependency_config_t), intent(in) :: dependency

Dependency configuration data

type(version_t), intent(in), optional :: version

Version of the dependency

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

Installation prefix of the dependency

logical, intent(in), optional :: update

Dependency should be updated

public subroutine new_dependency_tree(self, verbosity, cache, path_to_config)

Create a new dependency tree

Arguments

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

Instance of the dependency tree

integer, intent(in), optional :: verbosity

Verbosity of printout

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

Name of the cache file

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

Path to the global config file.