fpm_pkg_config Module

The fpm interface to pkg-config

This module contains wrapper functions to interface with a pkg-config installation.



Functions

public function assert_pkg_config()

Check whether pkg-config is available on the local system

Arguments

None

Return Value logical

public function pkgcfg_get_build_flags(name, allow_system, error) result(flags)

Get build flags (option to include flags from system directories, that gfortran does not look into by default)

Arguments

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

Package name

logical, intent(in) :: allow_system

Should pkg-config look in system paths? This is necessary for gfortran that doesn’t otherwise look into them

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

Error flag

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

List of compile flags

public function pkgcfg_get_libs(package, error) result(libraries)

Get package libraries from pkg-config

Arguments

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

Package name

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

Error handler

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

A list of libraries

public function pkgcfg_get_version(package, error) result(screen)

Get package version from pkg-config

Arguments

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

Package name

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

Error handler

Return Value type(string_t)

public function pkgcfg_has_package(name) result(success)

Check if pkgcfg has package

Read more…

Arguments

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

Package name

Return Value logical

public function pkgcfg_list_all(error, descriptions) result(modules)

Return whole list of available pkg-cfg packages

Read more…

Arguments

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

Error handler

type(string_t), intent(out), optional, allocatable :: descriptions(:)

An optional list of package descriptions

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

A list of all available packages


Subroutines

public subroutine run_wrapper(wrapper, args, verbose, exitcode, cmd_success, screen_output)

Simple call to execute_command_line involving one mpi* wrapper

Arguments

Type IntentOptional Attributes Name
type(string_t), intent(in) :: wrapper
type(string_t), intent(in), optional :: args(:)
logical, intent(in), optional :: verbose
integer, intent(out), optional :: exitcode
logical, intent(out), optional :: cmd_success
type(string_t), intent(out), optional :: screen_output