xml_tag Derived Type

type, public :: xml_tag

XML tag class.

A valid XML tag must have the following syntax for a tag without a content (with only attributes):

 <Tag_Name att#1_Name="att#1_val" att#2_Name="att#2_val"... att#Nt_Name="att#Nt_val"/>

while a tag with a content must have the following syntax:

 <Tag_Name att#1_Name="att#1_val" att#2_Name="att#2_val"... att#Nt_Name="att#Nt_val">Tag_Content</Tag_Name>

It is worth noting that the syntax is case sensitive and that the attributes are optional. Each attribute name must be followed by '="' without any additional white spaces and its value must be termined by '"'. Each attribute is separated by one or more white spaces.


Inherits

type~~xml_tag~~InheritsGraph type~xml_tag xml_tag string string type~xml_tag->string tag_name, tag_content, attribute

Inherited by

type~~xml_tag~~InheritedByGraph type~xml_tag xml_tag type~xml_file xml_file type~xml_file->type~xml_tag tag

Components

Type Visibility Attributes Name Initial
type(string), private :: tag_name

Tag name.

type(string), private :: tag_content

Tag content.

integer(kind=I4P), private :: pos(3) = [0_I4P, 0_I4P, 0_I4P]

Characters position (in source) indexes (start, content, end).

type(string), private, allocatable :: attribute(:,:)

Attributes names/values pairs, [1:2, 1:].

integer(kind=I4P), private :: attributes_number = 0_I4P

Number of defined attributes.

integer(kind=I4P), private :: indent = 0_I4P

Number of indent-white-spaces.

logical, private :: is_self_closing = .false.

Self closing tag flag.

integer(kind=I4P), private :: level = 0_I4P

Tag hierarchy level.

integer(kind=I4P), private :: id = 0_I4P

Uniq tag ID.

integer(kind=I4P), private :: parent_id = 0_I4P

Uniq ID of parent tag.

integer(kind=I4P), public :: children_number = 0_I4P

Number of children tags.

integer(kind=I4P), public, allocatable :: child_id(:)

Uniq ID of children tags.


Constructor

public interface xml_tag

Overload xml_tag with creator procedures.

  • private pure function create_tag_flat(name, attribute, attributes, attributes_stream, sanitize_attributes_value, pos, content, indent, is_content_indented, is_self_closing, id, level, parent_id, attributes_stream_alloc, content_alloc) result(tag)

    Return an instance of xml tag.

    Arguments

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

    Tag name.

    character(len=*), intent(in), optional :: attribute(1:)

    Attribute name/value pair [1:2].

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

    Attributes list of name/value pairs [1:2,1:].

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

    Attributes list as single stream.

    logical, intent(in), optional :: sanitize_attributes_value

    Sanitize attributes value.

    integer(kind=I4P), intent(in), optional :: pos(1:)

    Characters position (in source) indexes.

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

    Tag value.

    integer(kind=I4P), intent(in), optional :: indent

    Number of indent-white-spaces.

    logical, intent(in), optional :: is_content_indented

    Activate content indentation.

    logical, intent(in), optional :: is_self_closing

    The tag is self closing.

    integer(kind=I4P), intent(in), optional :: id

    Uniq ID.

    integer(kind=I4P), intent(in), optional :: level

    Tag hierarchy level.

    integer(kind=I4P), intent(in), optional :: parent_id

    Parent uniq ID.

    character(len=:), intent(in), optional, allocatable :: attributes_stream_alloc

    Attributes list stream, allocatable input.

    character(len=:), intent(in), optional, allocatable :: content_alloc

    Tag value, allocatable input.

    Return Value type(xml_tag)

    XML tag.

  • private pure function create_tag_nested(name, content, attribute, attributes, attributes_stream, sanitize_attributes_value, pos, indent, is_content_indented, id, level, parent_id, attributes_stream_alloc, content_alloc) result(tag)

    Return an instance of xml tag with value being a nested tag.

    Arguments

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

    Tag name.

    type(xml_tag), intent(in) :: content

    Tag value as nested tag..

    character(len=*), intent(in), optional :: attribute(1:)

    Attribute name/value pair [1:2].

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

    Attributes list of name/value pairs [1:2,1:].

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

    Attributes list as single stream.

    logical, intent(in), optional :: sanitize_attributes_value

    Sanitize attributes value.

    integer(kind=I4P), intent(in), optional :: pos(1:)

    Characters position (in source) indexes.

    integer(kind=I4P), intent(in), optional :: indent

    Number of indent-white-spaces.

    logical, intent(in), optional :: is_content_indented

    Activate value indentation.

    integer(kind=I4P), intent(in), optional :: id

    Uniq ID.

    integer(kind=I4P), intent(in), optional :: level

    Tag hierarchy level.

    integer(kind=I4P), intent(in), optional :: parent_id

    Parent uniq ID.

    character(len=:), intent(in), optional, allocatable :: attributes_stream_alloc

    Attributes list stream, allocatable input.

    character(len=:), intent(in), optional, allocatable :: content_alloc

    Tag value, allocatable input.

    Return Value type(xml_tag)

    XML tag.


Finalization Procedures

final :: finalize

Free dynamic memory when finalizing.

  • private elemental subroutine finalize(tag)

    Free dynamic memory when finalizing.

    Arguments

    Type IntentOptional Attributes Name
    type(xml_tag), intent(inout) :: tag

    XML tag.


Type-Bound Procedures

generic, public :: add_attributes => add_single_attribute, add_multiple_attributes, add_stream_attributes

Add attributes name/value pairs.

  • private pure subroutine add_single_attribute(self, attribute, sanitize_value)

    Add one attribute name/value pair.

    Read more…

    Arguments

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

    XML tag.

    character(len=*), intent(in) :: attribute(1:)

    Attribute name/value pair [1:2].

    logical, intent(in), optional :: sanitize_value

    Sanitize attribute value.

  • private pure subroutine add_multiple_attributes(self, attributes, sanitize_values)

    Add list of attributes name/value pairs.

    Arguments

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

    XML tag.

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

    Attribute name/value pair list [1:2,1:].

    logical, intent(in), optional :: sanitize_values

    Sanitize attribute values.

  • private pure subroutine add_stream_attributes(self, attributes_stream, sanitize_values)

    Add list of attributes name/value pairs passed as stream.

    Read more…

    Arguments

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

    XML tag.

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

    Attribute name/value pair list passed as stream.

    logical, intent(in), optional :: sanitize_values

    Sanitize attribute values.

procedure, public, pass(self) :: add_child_id

Add child ID to children IDs list.

  • private pure subroutine add_child_id(self, child_id)

    Add child ID to children IDs list.

    Arguments

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

    XML tag.

    integer(kind=I4P), intent(in) :: child_id

    Child ID.

procedure, public, pass(self) :: attributes

Return attributes name/value pairs as string.

  • private pure function attributes(self) result(att_)

    Return attributes name/value pairs as string.

    Arguments

    Type IntentOptional Attributes Name
    class(xml_tag), intent(in) :: self

    XML tag.

    Return Value character(len=:), allocatable

    The attributes string.

generic, public :: delete_attributes => delete_single_attribute, delete_multiple_attributes

Delete attributes name/value pairs.

  • private pure subroutine delete_single_attribute(self, name)

    Delete one attribute name/value pair.

    Arguments

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

    XML tag.

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

    Attribute name.

  • private pure subroutine delete_multiple_attributes(self, name)

    Delete list of attributes name/value pairs.

    Arguments

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

    XML tag.

    character(len=*), intent(in) :: name(1:)

    Attributes names.

procedure, public, pass(self) :: delete_content

Delete tag conent.

  • private pure subroutine delete_content(self)

    Delete tag content.

    Arguments

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

    XML tag.

procedure, public, pass(self) :: end_tag

Return </tag_name> end tag.

  • private pure function end_tag(self, is_indented) result(tag_)

    Return </tag_name> end tag.

    Arguments

    Type IntentOptional Attributes Name
    class(xml_tag), intent(in) :: self

    XML tag.

    logical, intent(in), optional :: is_indented

    Activate content indentation.

    Return Value character(len=:), allocatable

    The end tag string.

procedure, public, pass(self) :: free

Free (reset) tag.

  • private elemental subroutine free(self)

    Free (reset) tag.

    Arguments

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

    XML tag.

procedure, public, pass(self) :: get_content

Return tag content.

  • private pure subroutine get_content(self, name, content)

    Return tag content of self (or its nested tags) if named name.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(xml_tag), intent(in) :: self

    XML tag.

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

    Searched tag name.

    character(len=:), intent(out), allocatable :: content

    Tag content.

procedure, public, pass(self) :: is_attribute_present

Return .true. it the queried attribute name is defined.

  • private pure function is_attribute_present(self, name) result(is_present)

    Return .true. it the queried attribute name is defined, .false. otherwise.

    Arguments

    Type IntentOptional Attributes Name
    class(xml_tag), intent(in) :: self

    XML tag.

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

    Attribute name.

    Return Value logical

    Inquire result.

procedure, public, pass(self) :: is_parsed

Check is tag is correctly parsed, i.e. its tag_name is allocated.

  • private elemental function is_parsed(self)

    Check is tag is correctly parsed, i.e. its tag_name is allocated.

    Arguments

    Type IntentOptional Attributes Name
    class(xml_tag), intent(in) :: self

    XML tag.

    Return Value logical

    Result of check.

procedure, public, pass(self) :: name

Return tag name.

  • private pure function name(self)

    Return tag name.

    Arguments

    Type IntentOptional Attributes Name
    class(xml_tag), intent(in) :: self

    XML tag.

    Return Value character(len=:), allocatable

    XML tag name.

procedure, public, pass(self) :: parse

Parse the tag contained into a source string.

  • private elemental subroutine parse(self, source, tstart, tend)

    Parse the tag contained into a source string.

    Read more…

    Arguments

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

    XML tag.

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

    String containing the input.

    integer(kind=I4P), intent(out), optional :: tstart

    Starting index of tag inside the string.

    integer(kind=I4P), intent(out), optional :: tend

    Ending index of tag inside the string.

procedure, public, pass(self) :: parse_tag_name

Parse the tag name contained into a string.

  • private elemental subroutine parse_tag_name(self, source, tstart, tend)

    Parse the tag name contained into a string.

    Read more…

    Arguments

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

    XML tag.

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

    String containing the input.

    integer(kind=I4P), intent(out), optional :: tstart

    Starting index of tag inside the source.

    integer(kind=I4P), intent(out), optional :: tend

    Ending index of tag inside the source.

procedure, public, pass(self) :: self_closing_tag

Return <tag_name.../> self closing tag.

  • private pure function self_closing_tag(self, is_indented) result(tag_)

    Return <tag_name.../> self closing tag.

    Arguments

    Type IntentOptional Attributes Name
    class(xml_tag), intent(in) :: self

    XML tag.

    logical, intent(in), optional :: is_indented

    Flag to check if tag is indented.

    Return Value character(len=:), allocatable

    The self closing tag string.

procedure, public, pass(self) :: set

Set tag data.

  • private pure subroutine set(self, name, attribute, attributes, attributes_stream, sanitize_attributes_value, content, pos, indent, is_content_indented, is_self_closing, id, level, parent_id, attributes_stream_alloc, content_alloc)

    Set tag data.

    Arguments

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

    XML tag.

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

    Tag name.

    character(len=*), intent(in), optional :: attribute(1:)

    Attribute name/value pair [1:2].

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

    Attributes list of name/value pairs [1:2,1:].

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

    Attributes list of name/value pairs as stream.

    logical, intent(in), optional :: sanitize_attributes_value

    Sanitize attributes value.

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

    Tag value.

    integer(kind=I4P), intent(in), optional :: pos(1:)

    Characters position (in source) indexes.

    integer(kind=I4P), intent(in), optional :: indent

    Number of indent-white-spaces.

    logical, intent(in), optional :: is_content_indented

    Activate value indentation.

    logical, intent(in), optional :: is_self_closing

    The tag is self closing.

    integer(kind=I4P), intent(in), optional :: id

    Uniq ID.

    integer(kind=I4P), intent(in), optional :: level

    Tag hierarchy level.

    integer(kind=I4P), intent(in), optional :: parent_id

    Parent uniq ID.

    character(len=:), intent(in), optional, allocatable :: attributes_stream_alloc

    Attributes list stream, allocatable input.

    character(len=:), intent(in), optional, allocatable :: content_alloc

    Tag value, allocatable input.

procedure, public, pass(self) :: start_tag

Return <tag_name...> start tag.

  • private pure function start_tag(self, is_indented) result(tag_)

    Return <tag_name...> start tag.

    Arguments

    Type IntentOptional Attributes Name
    class(xml_tag), intent(in) :: self

    XML tag.

    logical, intent(in), optional :: is_indented

    Flag to check if tag is indented.

    Return Value character(len=:), allocatable

    The start tag string.

procedure, public, pass(self) :: stringify

Convert the whole tag into a string.

  • private pure function stringify(self, is_indented, is_content_indented, only_start, only_content, only_end, linearize) result(stringed)

    Convert the whole tag into a string.

    Arguments

    Type IntentOptional Attributes Name
    class(xml_tag), intent(in) :: self

    XML tag.

    logical, intent(in), optional :: is_indented

    Activate content indentation.

    logical, intent(in), optional :: is_content_indented

    Activate content indentation.

    logical, intent(in), optional :: only_start

    Write only start tag.

    logical, intent(in), optional :: only_content

    Write only content.

    logical, intent(in), optional :: only_end

    Write only end tag.

    logical, intent(in), optional :: linearize

    Return a "linearized" string of tags without the XML hieararchy.

    Return Value character(len=:), allocatable

    Output string containing the whole tag.

procedure, public, pass(self) :: write => write_tag

Write tag to unit file.

  • private subroutine write_tag(self, unit, is_indented, is_content_indented, form, end_record, only_start, only_content, only_end, iostat, iomsg)

    Write tag to unit file.

    Arguments

    Type IntentOptional Attributes Name
    class(xml_tag), intent(in) :: self

    XML tag.

    integer(kind=I4P), intent(in) :: unit

    File unit.

    logical, intent(in), optional :: is_indented

    Activate content indentation.

    logical, intent(in), optional :: is_content_indented

    Activate content indentation.

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

    Format.

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

    Ending record.

    logical, intent(in), optional :: only_start

    Write only start tag.

    logical, intent(in), optional :: only_content

    Write only content.

    logical, intent(in), optional :: only_end

    Write only end tag.

    integer(kind=I4P), intent(out), optional :: iostat

    IO status.

    character(len=*), intent(out), optional :: iomsg

    IO message.

generic, public :: assignment(=) => assign_tag

Assignment operator overloading.

  • private elemental subroutine assign_tag(lhs, rhs)

    Assignment between two tags.

    Arguments

    Type IntentOptional Attributes Name
    class(xml_tag), intent(inout) :: lhs

    Left hand side.

    type(xml_tag), intent(in) :: rhs

    Right hand side.

procedure, private, pass(self) :: add_single_attribute

Add one attribute name/value pair.

  • private pure subroutine add_single_attribute(self, attribute, sanitize_value)

    Add one attribute name/value pair.

    Read more…

    Arguments

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

    XML tag.

    character(len=*), intent(in) :: attribute(1:)

    Attribute name/value pair [1:2].

    logical, intent(in), optional :: sanitize_value

    Sanitize attribute value.

procedure, private, pass(self) :: add_multiple_attributes

Add list of attributes name/value pairs.

  • private pure subroutine add_multiple_attributes(self, attributes, sanitize_values)

    Add list of attributes name/value pairs.

    Arguments

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

    XML tag.

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

    Attribute name/value pair list [1:2,1:].

    logical, intent(in), optional :: sanitize_values

    Sanitize attribute values.

procedure, private, pass(self) :: add_stream_attributes

Add list of attributes name/value pairs passed as stream.

  • private pure subroutine add_stream_attributes(self, attributes_stream, sanitize_values)

    Add list of attributes name/value pairs passed as stream.

    Read more…

    Arguments

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

    XML tag.

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

    Attribute name/value pair list passed as stream.

    logical, intent(in), optional :: sanitize_values

    Sanitize attribute values.

procedure, private, pass(self) :: alloc_attributes

Allocate (prepare for filling) dynamic memory of attributes.

  • private elemental subroutine alloc_attributes(self, Na)

    Allocate (prepare for filling) dynamic memory of attributes.

    Arguments

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

    XML tag.

    integer(kind=I4P), intent(in) :: Na

    Number of attributes.

procedure, private, pass(self) :: delete_single_attribute

Delete one attribute name/value pair.

  • private pure subroutine delete_single_attribute(self, name)

    Delete one attribute name/value pair.

    Arguments

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

    XML tag.

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

    Attribute name.

procedure, private, pass(self) :: delete_multiple_attributes

Delete list of attributes name/value pairs.

  • private pure subroutine delete_multiple_attributes(self, name)

    Delete list of attributes name/value pairs.

    Arguments

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

    XML tag.

    character(len=*), intent(in) :: name(1:)

    Attributes names.

procedure, private, pass(self) :: get

Get the tag value and attributes from source.

  • private elemental subroutine get(self, source)

    Get the tag content and attributes from source after tag_name and attributes names have been set.

    Arguments

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

    XML tag.

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

    String containing data.

procedure, private, pass(self) :: get_value

Get the tag value from source after tag_name has been set.

  • private elemental subroutine get_value(self, source)

    Get the tag value from source after tag_name has been set.

    Arguments

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

    XML tag.

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

    String containing data.

procedure, private, pass(self) :: get_attributes

Get the attributes values from source.

  • private elemental subroutine get_attributes(self, source)

    Get the attributes values from source after tag_name and attributes names have been set.

    Arguments

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

    XML tag.

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

    String containing data.

procedure, private, pass(self) :: parse_attributes_names

Parse the tag attributes names contained into a string.

  • private elemental subroutine parse_attributes_names(self, source)

    Parse the tag attributes names contained into a string.

    Read more…

    Arguments

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

    XML tag.

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

    String containing the input.

procedure, private, pass(self) :: search

Search tag named tag_name into a string.

  • private elemental subroutine search(self, tag_name, source, tstart, tend)

    Search tag named tag_name into a string and, in case it is found, store into self.

    Read more…

    Arguments

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

    XML tag.

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

    Searched tag name.

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

    String containing the input.

    integer(kind=I4P), intent(out), optional :: tstart

    Starting index of tag inside the source.

    integer(kind=I4P), intent(out), optional :: tend

    Ending index of tag inside the source.

procedure, private, pass(lhs) :: assign_tag

Assignment between two tags.

  • private elemental subroutine assign_tag(lhs, rhs)

    Assignment between two tags.

    Arguments

    Type IntentOptional Attributes Name
    class(xml_tag), intent(inout) :: lhs

    Left hand side.

    type(xml_tag), intent(in) :: rhs

    Right hand side.

Source Code

type :: xml_tag
   !< XML tag class.
   !<
   !< A valid XML tag must have the following syntax for a tag without a content (with only attributes):
   !<```xml
   !<   <Tag_Name att#1_Name="att#1_val" att#2_Name="att#2_val"... att#Nt_Name="att#Nt_val"/>
   !<```
   !< while a tag with a content must have the following syntax:
   !<```xml
   !<   <Tag_Name att#1_Name="att#1_val" att#2_Name="att#2_val"... att#Nt_Name="att#Nt_val">Tag_Content</Tag_Name>
   !<```
   !<
   !< It is worth noting that the syntax is case sensitive and that the attributes are optional. Each attribute name must be
   !< followed by '="' without any additional white spaces and its value must be termined by '"'. Each attribute is separated
   !< by one or more white spaces.
   private
   type(string)                      :: tag_name                   !< Tag name.
   type(string)                      :: tag_content                !< Tag content.
   integer(I4P)                      :: pos(3)=[0_I4P,0_I4P,0_I4P] !< Characters position (in source) indexes (start, content, end).
   type(string), allocatable         :: attribute(:,:)             !< Attributes names/values pairs, [1:2, 1:].
   integer(I4P)                      :: attributes_number=0_I4P    !< Number of defined attributes.
   integer(I4P)                      :: indent=0_I4P               !< Number of indent-white-spaces.
   logical                           :: is_self_closing=.false.    !< Self closing tag flag.
   integer(I4P)                      :: level=0_I4P                !< Tag hierarchy level.
   integer(I4P)                      :: id=0_I4P                   !< Uniq tag ID.
   integer(I4P)                      :: parent_id=0_I4P            !< Uniq ID of parent tag.
   integer(I4P), public              :: children_number=0_I4P      !< Number of children tags.
   integer(I4P), public, allocatable :: child_id(:)                !< Uniq ID of children tags.
   contains
      ! public methods
      generic               :: add_attributes =>        &
                               add_single_attribute,    &
                               add_multiple_attributes, &
                               add_stream_attributes       !< Add attributes name/value pairs.
      procedure, pass(self) :: add_child_id                !< Add child ID to children IDs list.
      procedure, pass(self) :: attributes                  !< Return attributes name/value pairs as string.
      generic               :: delete_attributes =>     &
                               delete_single_attribute, &
                               delete_multiple_attributes  !< Delete attributes name/value pairs.
      procedure, pass(self) :: delete_content              !< Delete tag conent.
      procedure, pass(self) :: end_tag                     !< Return `</tag_name>` end tag.
      procedure, pass(self) :: free                        !< Free (reset) tag.
      procedure, pass(self) :: get_content                 !< Return tag content.
      procedure, pass(self) :: is_attribute_present        !< Return .true. it the queried attribute name is defined.
      procedure, pass(self) :: is_parsed                   !< Check is tag is correctly parsed, i.e. its *tag_name* is allocated.
      procedure, pass(self) :: name                        !< Return tag name.
      procedure, pass(self) :: parse                       !< Parse the tag contained into a source string.
      procedure, pass(self) :: parse_tag_name              !< Parse the tag name contained into a string.
      procedure, pass(self) :: self_closing_tag            !< Return `<tag_name.../>` self closing tag.
      procedure, pass(self) :: set                         !< Set tag data.
      procedure, pass(self) :: start_tag                   !< Return `<tag_name...>` start tag.
      procedure, pass(self) :: stringify                   !< Convert the whole tag into a string.
      procedure, pass(self) :: write => write_tag          !< Write tag to unit file.
      generic               :: assignment(=) => assign_tag !< Assignment operator overloading.
      ! private methods
      procedure, pass(self), private :: add_single_attribute       !< Add one attribute name/value pair.
      procedure, pass(self), private :: add_multiple_attributes    !< Add list of attributes name/value pairs.
      procedure, pass(self), private :: add_stream_attributes      !< Add list of attributes name/value pairs passed as stream.
      procedure, pass(self), private :: alloc_attributes           !< Allocate (prepare for filling) dynamic memory of attributes.
      procedure, pass(self), private :: delete_single_attribute    !< Delete one attribute name/value pair.
      procedure, pass(self), private :: delete_multiple_attributes !< Delete list of attributes name/value pairs.
      procedure, pass(self), private :: get                        !< Get the tag value and attributes from source.
      procedure, pass(self), private :: get_value                  !< Get the tag value from source after tag_name has been set.
      procedure, pass(self), private :: get_attributes             !< Get the attributes values from source.
      procedure, pass(self), private :: parse_attributes_names     !< Parse the tag attributes names contained into a string.
      procedure, pass(self), private :: search                     !< Search tag named *tag_name* into a string.
      ! operators
      procedure, pass(lhs), private :: assign_tag !< Assignment between two tags.
      final                         :: finalize   !< Free dynamic memory when finalizing.
endtype xml_tag