vertex Derived Type

type, private :: vertex

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


Inherits

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

Inherited by

type~~vertex~~InheritedByGraph type~vertex vertex type~dag dag type~dag->type~vertex vertices

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

  • 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

procedure, private :: add_edge

  • 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

procedure, private :: set_edge_vector_vector

  • 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

procedure, private :: remove_edge

  • 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

Source Code

    type :: vertex
        !! a vertex (or node) of a directed acyclic graph (DAG)
        private
        type(edge),dimension(:),allocatable :: edges  !! these are the vertices that this vertex
                                                      !! depends on. (edges of the graph).
        integer(ip) :: ivertex = 0 !! vertex number (the index in the [[dag]] `vertices` array)
        logical :: checking = .false.  !! used for toposort
        logical :: marked = .false.    !! used for toposort
        character(len=:),allocatable :: label      !! used for diagraph
        character(len=:),allocatable :: attributes !! used for diagraph
        class(*),allocatable :: metadata !! user-defined metadata
    contains
        private
        generic :: set_edges => set_edge_vector_vector, add_edge
        procedure :: set_edge_vector_vector, add_edge
        procedure :: remove_edge
    end type vertex