fpm_compile_commands Module

Store compiler commands in a compile_commands.json table



Derived Types

type, public, extends(serializable_t) ::  compile_command_t

Definition of a build command

Components

Type Visibility Attributes Name Initial
type(string_t), public, allocatable :: arguments(:)
type(string_t), public :: directory
type(string_t), public :: file

Type-Bound Procedures

procedure, public :: destroy => compile_command_destroy ../../

Operation

generic, public :: dump => dump_to_toml, dump_to_file, dump_to_unit
procedure, public :: dump_to_toml => compile_command_dump_toml
generic, public :: load => load_from_toml, load_from_file, load_from_unit
procedure, public :: load_from_toml => compile_command_load_toml
generic, public :: operator(==) => serializable_is_same
procedure, public :: serializable_is_same => compile_command_is_same ../../

Serialization interface

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

Test load/write roundtrip

type, public, extends(serializable_t) ::  compile_command_table_t

Components

Type Visibility Attributes Name Initial
type(compile_command_t), public, allocatable :: command(:)

Type-Bound Procedures

procedure, public :: destroy => cct_destroy ../../

Operation

generic, public :: dump => dump_to_toml, dump_to_file, dump_to_unit
procedure, public :: dump_to_toml => cct_dump_toml
generic, public :: load => load_from_toml, load_from_file, load_from_unit
procedure, public :: load_from_toml => cct_load_toml
generic, public :: operator(==) => serializable_is_same
generic, public :: register => cct_register, cct_register_object
procedure, public :: serializable_is_same => cct_is_same ../../

Serialization interface

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

Test load/write roundtrip

procedure, public :: write => cct_write

Functions

public function cct_is_same(this, that)

Check that two compile_command_table_t objects are equal All checks passed!

Arguments

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

Return Value logical

public function compile_command_is_same(this, that)

Check that two compile_command_t objects are equal All checks passed!

Arguments

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

Return Value logical


Subroutines

public elemental subroutine cct_destroy(self)

Cleanup a compile command table

Arguments

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

Instance of the serializable object

public subroutine cct_dump_array(self, array, error)

Dump compile_command_table_t to a toml array

Arguments

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

Instance of the serializable object

type(toml_array), intent(inout) :: array

Data structure

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

Error handling

public subroutine cct_dump_toml(self, table, error)

Dump compile_command_table_t to toml table

Arguments

Type IntentOptional Attributes Name
class(compile_command_table_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 cct_load_toml(self, table, error)

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

Arguments

Type IntentOptional Attributes Name
class(compile_command_table_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 cct_register(self, command, target_os, error)

Register a new compile command

Arguments

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

Instance of the serializable object

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

Data structure

integer, intent(in) :: target_os

The target OS of the compile_commands.json (may be cross-compiling)

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

Error handling

public pure subroutine cct_register_object(self, command, error)

Arguments

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

Instance of the serializable object

type(compile_command_t), intent(in) :: command

Data structure

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

Error handling

public subroutine cct_write(self, filename, error)

Write compile_commands.json file. Because Jonquil does not support non-named arrays, create a custom json here.

Arguments

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

Instance of the serializable object

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

The file name

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

Error handling

public elemental subroutine compile_command_destroy(self)

Cleanup compile command

Arguments

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

Instance of the serializable object

public subroutine compile_command_dump_toml(self, table, error)

Dump compile_command_t to toml table

Arguments

Type IntentOptional Attributes Name
class(compile_command_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 compile_command_load_toml(self, table, error)

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

Arguments

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