dag Derived Type

type, public :: dag

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


Inherits

type~~dag~~InheritsGraph type~dag dag type~vertex vertex type~dag->type~vertex vertices type~edge edge type~vertex->type~edge edges

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

  • 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)

procedure, public :: number_of_vertices => dag_get_number_of_vertices

  • 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

procedure, public :: get_edge_metadata => dag_get_edge_metadata

  • 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

procedure, public :: get_vertex_metadata => dag_get_vertex_metadata

  • 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

procedure, public :: get_edges => dag_get_edges

  • 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

procedure, public :: get_dependencies => dag_get_dependencies

  • 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

procedure, public :: set_vertices => dag_set_vertices

  • 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

procedure, public :: set_vertex_info => dag_set_vertex_info

  • 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

procedure, public :: add_edge => dag_add_edge

  • 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

generic, public :: set_edges => dag_set_edges_no_atts, dag_set_edges_vector_atts

  • 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_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

procedure, public :: remove_edge => dag_remove_edge

  • 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

procedure, public :: remove_vertex => dag_remove_node

  • 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

procedure, public :: toposort => dag_toposort

  • 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…

procedure, public :: traverse => dag_traverse

  • 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

procedure, public :: generate_digraph => dag_generate_digraph

  • 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

procedure, public :: generate_dependency_matrix => dag_generate_dependency_matrix

  • 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

procedure, public :: save_digraph => dag_save_digraph

  • 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)

procedure, public :: destroy => dag_destroy

  • private subroutine dag_destroy(me)

    Destroy the dag.

    Arguments

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

procedure, public :: get_edge_index

  • 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)

procedure, private :: init_internal_vars

private routine to initialize some internal variables

  • 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

procedure, private :: dag_set_edges_vector_atts

  • 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

procedure, private :: dag_set_edges_no_atts

  • 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

Source Code

    type,public :: dag
        !! a directed acyclic graph (DAG).
        !! a collection of vertices (nodes) that are connected to other vertices.
        private
        integer(ip) :: n = 0 !! number of vertices (size of `vertices` array)
        type(vertex),dimension(:),allocatable :: vertices  !! the vertices in the DAG. The index in
                                                           !! this array if the vertex number.
    contains
        private

        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 :: init_internal_vars !! private routine to initialize some internal variables
        procedure :: dag_set_edges_no_atts, dag_set_edges_vector_atts

    end type dag