dag_module Module

DAG Module.


Uses

  • module~~dag_module~~UsesGraph module~dag_module dag_module iso_fortran_env iso_fortran_env module~dag_module->iso_fortran_env

Variables

Type Visibility Attributes Name Initial
integer, public, parameter :: daglib_ip = int32

Integer working precision if not specified [4 bytes]

integer, private, parameter :: ip = daglib_ip

local copy of daglib_ip with a shorter name

integer(kind=ip), private, parameter :: MAX_INT_STR_LEN = 64

maximum length of an integer string


Interfaces

private interface edge

constructor for an edge type.

  • private pure elemental function edge_constructor(ivertex, label, attributes, metadata) result(e)

    Constructor for edge type.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ip), intent(in), optional :: ivertex

    vertex number defining the destination of this edge

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

    vertex name for grahviz

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

    other attributes for graphviz

    class(*), intent(in), optional :: metadata

    optional user-defined metadata

    Return Value type(edge)


Abstract Interfaces

abstract interface

  • private subroutine traverse_func(ivertex, stop, iedge)

    user-provided function for traversing a dag.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ip), intent(in) :: ivertex

    vertex number

    logical, intent(out) :: stop

    set to true to stop the process

    integer(kind=ip), intent(in), optional :: iedge

    edge index for this vertex (note: not the vertex number, the index in the array of edge vertices) [not present if this is the starting node]


Derived Types

type, private ::  edge

the "to" vertex that defines an edge. This is part of the array of vertices contained without the "from" vertex type. an edge can also have optional attrubutes for graphviz.

Components

Type Visibility Attributes Name Initial
integer(kind=ip), public :: ivertex = 0

vertex number (the index in the dag vertices array)

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

used for diagraph

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

used for diagraph

class(*), public, allocatable :: metadata

user-defined metadata

Constructor

constructor for an edge type.

private pure, elemental function edge_constructor (ivertex, label, attributes, metadata)

Constructor for edge type.

type, private ::  vertex

a vertex (or node) of a directed acyclic graph (DAG)

Components

Type Visibility Attributes Name Initial
type(edge), private, dimension(:), allocatable :: edges

these are the vertices that this vertex depends on. (edges of the graph).

integer(kind=ip), private :: ivertex = 0

vertex number (the index in the dag vertices array)

logical, private :: checking = .false.

used for toposort

logical, private :: marked = .false.

used for toposort

character(len=:), private, allocatable :: label

used for diagraph

character(len=:), private, allocatable :: attributes

used for diagraph

class(*), private, allocatable :: metadata

user-defined metadata

Type-Bound Procedures

generic, private :: set_edges => set_edge_vector_vector, add_edge
procedure, private :: add_edge
procedure, private :: set_edge_vector_vector
procedure, private :: remove_edge

type, public ::  dag

a directed acyclic graph (DAG). a collection of vertices (nodes) that are connected to other vertices.

Components

Type Visibility Attributes Name Initial
integer(kind=ip), private :: n = 0

number of vertices (size of vertices array)

type(vertex), private, dimension(:), allocatable :: vertices

the vertices in the DAG. The index in this array if the vertex number.

Type-Bound Procedures

procedure, public :: vertex => dag_get_vertex

not very useful for now, since all vertex attributes are private

procedure, public :: number_of_vertices => dag_get_number_of_vertices
procedure, public :: get_edge_metadata => dag_get_edge_metadata
procedure, public :: get_vertex_metadata => dag_get_vertex_metadata
procedure, public :: get_edges => dag_get_edges
procedure, public :: get_dependencies => dag_get_dependencies
procedure, public :: set_vertices => dag_set_vertices
procedure, public :: set_vertex_info => dag_set_vertex_info
procedure, public :: add_edge => dag_add_edge
generic, public :: set_edges => dag_set_edges_no_atts, dag_set_edges_vector_atts
procedure, public :: remove_edge => dag_remove_edge
procedure, public :: remove_vertex => dag_remove_node
procedure, public :: toposort => dag_toposort
procedure, public :: traverse => dag_traverse
procedure, public :: generate_digraph => dag_generate_digraph
procedure, public :: generate_dependency_matrix => dag_generate_dependency_matrix
procedure, public :: save_digraph => dag_save_digraph
procedure, public :: destroy => dag_destroy
procedure, public :: get_edge_index
procedure, private :: init_internal_vars

private routine to initialize some internal variables

procedure, private :: dag_set_edges_vector_atts
procedure, private :: dag_set_edges_no_atts

Functions

private pure elemental function edge_constructor(ivertex, label, attributes, metadata) result(e)

Constructor for edge type.

Arguments

Type IntentOptional Attributes Name
integer(kind=ip), intent(in), optional :: ivertex

vertex number defining the destination of this edge

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

vertex name for grahviz

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

other attributes for graphviz

class(*), intent(in), optional :: metadata

optional user-defined metadata

Return Value type(edge)

private pure function dag_get_edges(me, ivertex) result(edges)

get the edges for the vertex (all of the vertices that this vertex depends on).

Arguments

Type IntentOptional Attributes Name
class(dag), intent(in) :: me
integer(kind=ip), intent(in) :: ivertex

Return Value integer(kind=ip), dimension(:), allocatable

private pure function dag_get_dependencies(me, ivertex) result(dep)

get all the vertices that depend on this vertex.

Arguments

Type IntentOptional Attributes Name
class(dag), intent(in) :: me
integer(kind=ip), intent(in) :: ivertex

Return Value integer(kind=ip), dimension(:), allocatable

the set of all vertices than depend on ivertex

private pure function dag_get_number_of_vertices(me) result(nvertices)

Returns the number of vertices (nodes) in the dag.

Arguments

Type IntentOptional Attributes Name
class(dag), intent(in) :: me

Return Value integer(kind=ip)

number of vertices

private pure function dag_get_vertex_metadata(me, ivertex) result(m)

Returns the metadata for a vertex (node) in the dag.

Arguments

Type IntentOptional Attributes Name
class(dag), intent(in) :: me
integer(kind=ip), intent(in) :: ivertex

vertex number

Return Value class(*), allocatable

private pure function dag_get_edge_metadata(me, ivertex, iedge) result(m)

Returns the metadata for an edge in the dag.

Arguments

Type IntentOptional Attributes Name
class(dag), intent(in) :: me
integer(kind=ip), intent(in) :: ivertex

vertex number

integer(kind=ip), intent(in) :: iedge

edge vertex

Return Value class(*), allocatable

private pure function get_edge_index(me, ivertex, iedge) result(edge_index)

Returns the index in the edge array of the vertex.

Arguments

Type IntentOptional Attributes Name
class(dag), intent(in) :: me
integer(kind=ip), intent(in) :: ivertex

vertex number

integer(kind=ip), intent(in) :: iedge

edge vertex number

Return Value integer(kind=ip)

the index of the iedge vertex in the edge array (0 if not found)

private function dag_get_vertex(me, i) result(v)

Get the ith vertex.

Read more…

Arguments

Type IntentOptional Attributes Name
class(dag), intent(inout) :: me
integer(kind=ip), intent(in) :: i

vertex number

Return Value type(vertex)

private function dag_generate_digraph(me, rankdir, dpi) result(str)

Generate a Graphviz digraph structure for the DAG.

Read more…

Arguments

Type IntentOptional Attributes Name
class(dag), intent(in) :: me
character(len=*), intent(in), optional :: rankdir

right to left orientation (e.g. 'RL')

integer(kind=ip), intent(in), optional :: dpi

resolution (e.g. 300)

Return Value character(len=:), allocatable

private pure function integer_to_string(i) result(s)

Integer to allocatable string.

Arguments

Type IntentOptional Attributes Name
integer(kind=ip), intent(in) :: i

Return Value character(len=:), allocatable

private function unique(vec) result(vec_unique)

Return only the unique values from vec. The result is also sorted by ascending value.

Arguments

Type IntentOptional Attributes Name
type(edge), intent(in), dimension(:) :: vec

Return Value type(edge), dimension(:), allocatable

only the unique elements of vec


Subroutines

private subroutine dag_destroy(me)

Destroy the dag.

Arguments

Type IntentOptional Attributes Name
class(dag), intent(inout) :: me

private subroutine set_edge_vector_vector(me, edges, label, attributes, metadata)

specify the edge indices for this vertex

Arguments

Type IntentOptional Attributes Name
class(vertex), intent(inout) :: me
integer(kind=ip), intent(in), dimension(:) :: edges
character(len=*), intent(in), optional, dimension(:) :: label
character(len=*), intent(in), optional, dimension(:) :: attributes

other attributes when saving as a diagraph.

class(*), intent(in), optional :: metadata

optional user-defined metadata

private subroutine add_edge(me, e, label, attributes, metadata)

add an edge index for this vertex

Arguments

Type IntentOptional Attributes Name
class(vertex), intent(inout) :: me
integer(kind=ip), intent(in) :: e
character(len=*), intent(in), optional :: label
character(len=*), intent(in), optional :: attributes

other attributes when saving as a diagraph.

class(*), intent(in), optional :: metadata

optional user-defined metadata

private subroutine remove_edge(me, e)

remove an edge index from this vertex

Arguments

Type IntentOptional Attributes Name
class(vertex), intent(inout) :: me
integer(kind=ip), intent(in) :: e

private subroutine dag_remove_node(me, ivertex)

Remove a node from a dag. Will also remove any edges connected to it.

Read more…

Arguments

Type IntentOptional Attributes Name
class(dag), intent(inout) :: me
integer(kind=ip), intent(in) :: ivertex

the node to remove

private subroutine dag_set_vertices(me, nvertices, labels, attributes, metadata)

set the number of vertices (nodes) in the dag.

Read more…

Arguments

Type IntentOptional Attributes Name
class(dag), intent(inout) :: me
integer(kind=ip), intent(in) :: nvertices

number of vertices

character(len=*), intent(in), optional, dimension(nvertices) :: labels

vertex name strings

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

other attributes when saving as a diagraph.

class(*), intent(in), optional :: metadata

optional user-defined metadata

private subroutine dag_set_vertex_info(me, ivertex, label, attributes, metadata)

set info about a vertex in a dag.

Arguments

Type IntentOptional Attributes Name
class(dag), intent(inout) :: me
integer(kind=ip), intent(in) :: ivertex

vertex number

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

if a label is not set, then the integer vertex number is used.

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

other attributes when saving as a diagraph.

class(*), intent(in), optional :: metadata

optional user-defined metadata

private subroutine dag_add_edge(me, ivertex, iedge, label, attributes, metadata)

Add an edge to a dag.

Arguments

Type IntentOptional Attributes Name
class(dag), intent(inout) :: me
integer(kind=ip), intent(in) :: ivertex

vertex number

integer(kind=ip), intent(in) :: iedge

the vertex to connect to ivertex

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

edge label

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

other attributes when saving as a diagraph.

class(*), intent(in), optional :: metadata

optional user-defined metadata

private subroutine dag_set_edges_no_atts(me, ivertex, edges)

set the edges for a vertex in a dag

Arguments

Type IntentOptional Attributes Name
class(dag), intent(inout) :: me
integer(kind=ip), intent(in) :: ivertex

vertex number

integer(kind=ip), intent(in), dimension(:) :: edges

private subroutine dag_remove_edge(me, ivertex, iedge)

Remove an edge from a dag.

Arguments

Type IntentOptional Attributes Name
class(dag), intent(inout) :: me
integer(kind=ip), intent(in) :: ivertex

vertex number

integer(kind=ip), intent(in) :: iedge

the edge to remove

private subroutine dag_set_edges_vector_atts(me, ivertex, edges, attributes, label)

set the edges for a vertex in a dag

Arguments

Type IntentOptional Attributes Name
class(dag), intent(inout) :: me
integer(kind=ip), intent(in) :: ivertex

vertex number

integer(kind=ip), intent(in), dimension(:) :: edges
character(len=*), intent(in), dimension(:) :: attributes

other attributes when saving as a diagraph.

character(len=*), intent(in), optional, dimension(:) :: label

private subroutine init_internal_vars(me)

Initialize the internal private variables used for graph traversal.

Arguments

Type IntentOptional Attributes Name
class(dag), intent(inout) :: me

private subroutine dag_toposort(me, order, istat)

Main toposort routine

Arguments

Type IntentOptional Attributes Name
class(dag), intent(inout) :: me
integer(kind=ip), intent(out), dimension(:), allocatable :: order

the toposort order

integer(kind=ip), intent(out) :: istat

Status flag:

Read more…

private subroutine dag_traverse(me, ivertex, userfunc)

depth-first graph traversal of the dag.

Read more…

Arguments

Type IntentOptional Attributes Name
class(dag), intent(inout) :: me
integer(kind=ip), intent(in) :: ivertex

the vertex number to start on

procedure(traverse_func) :: userfunc

a user-provided function that will be called for each vertex/edge combination

private subroutine dag_generate_dependency_matrix(me, mat)

Generate the dependency matrix for the DAG.

Read more…

Arguments

Type IntentOptional Attributes Name
class(dag), intent(in) :: me
logical, intent(out), dimension(:,:), allocatable :: mat

dependency matrix

private subroutine dag_save_digraph(me, filename, rankdir, dpi)

Generate a Graphviz digraph structure for the DAG and write it to a file.

Arguments

Type IntentOptional Attributes Name
class(dag), intent(in) :: me
character(len=*), intent(in), optional :: filename

file name for diagraph

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

right to left orientation (e.g. 'RL')

integer(kind=ip), intent(in), optional :: dpi

resolution (e.g. 300)

private subroutine sort_ascending(ivec)

Sorts an edge array ivec in increasing order by vertex number. Uses a basic recursive quicksort (with insertion sort for partitions with 20 elements).

Arguments

Type IntentOptional Attributes Name
type(edge), intent(inout), dimension(:) :: ivec

private pure elemental subroutine swap(i1, i2)

Swap two edge values.

Arguments

Type IntentOptional Attributes Name
type(edge), intent(inout) :: i1
type(edge), intent(inout) :: i2