xml_tag Derived Type

type, public :: xml_tag


Inherits

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

Inherited by

type~~xml_tag~~InheritedByGraph type~xml_tag xml_tag type~xml_writer_abstract xml_writer_abstract type~xml_writer_abstract->type~xml_tag tag type~xml_file xml_file type~xml_file->type~xml_tag tag type~pvtk_file pvtk_file type~pvtk_file->type~xml_writer_abstract xml_writer type~xml_writer_ascii_local xml_writer_ascii_local type~xml_writer_ascii_local->type~xml_writer_abstract type~xml_writer_appended xml_writer_appended type~xml_writer_appended->type~xml_writer_abstract type~vtk_file vtk_file type~vtk_file->type~xml_writer_abstract xml_writer type~xml_writer_binary_local xml_writer_binary_local type~xml_writer_binary_local->type~xml_writer_abstract type~vtm_file vtm_file type~vtm_file->type~xml_writer_abstract xml_writer

Contents

Source Code


Components

TypeVisibilityAttributesNameInitial
type(string), private :: tag_name
type(string), private :: tag_content
type(string), private, allocatable:: attribute(:,:)
integer(kind=I4P), private :: attributes_number =0
integer(kind=I4P), private :: indent =0
logical, private :: is_self_closing =.false.

Constructor

public interface xml_tag

  • private pure function create_tag_flat(name, attribute, attributes, attributes_stream, sanitize_attributes_value, content, indent, is_content_indented, is_self_closing) result(tag)

    Arguments

    TypeIntentOptionalAttributesName
    character, intent(in) :: name
    character, intent(in), optional :: attribute(1:)
    character, intent(in), optional :: attributes(1:,1:)
    character, intent(in), optional :: attributes_stream
    logical, intent(in), optional :: sanitize_attributes_value
    character, intent(in), optional :: content
    integer(kind=I4P), intent(in), optional :: indent
    logical, intent(in), optional :: is_content_indented
    logical, intent(in), optional :: is_self_closing

    Return Value type(xml_tag)

  • private pure function create_tag_nested(name, content, attribute, attributes, attributes_stream, sanitize_attributes_value, indent, is_content_indented) result(tag)

    Arguments

    TypeIntentOptionalAttributesName
    character, intent(in) :: name
    type(xml_tag), intent(in) :: content
    character, intent(in), optional :: attribute(1:)
    character, intent(in), optional :: attributes(1:,1:)
    character, intent(in), optional :: attributes_stream
    logical, intent(in), optional :: sanitize_attributes_value
    integer(kind=I4P), intent(in), optional :: indent
    logical, intent(in), optional :: is_content_indented

    Return Value type(xml_tag)


Type-Bound Procedures

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: attribute(1:)
    logical, intent(in), optional :: sanitize_value
  • private pure subroutine add_multiple_attributes(self, attributes, sanitize_values)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: attributes(1:,1:)
    logical, intent(in), optional :: sanitize_values
  • private pure subroutine add_stream_attributes(self, attributes_stream, sanitize_values)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: attributes_stream
    logical, intent(in), optional :: sanitize_values

procedure, public, pass(self) :: attributes

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(in) :: self

    Return Value character(len=:),allocatable

procedure, public, pass(self) :: get_content

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(in) :: self
    character, intent(in) :: name
    character(len=:), intent(out), allocatable:: content

generic, public :: delete_attributes => delete_single_attribute, delete_multiple_attributes

  • private pure subroutine delete_single_attribute(self, name)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: name
  • private pure subroutine delete_multiple_attributes(self, name)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: name(1:)

procedure, public, pass(self) :: delete_content

  • private pure subroutine delete_content(self)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self

procedure, public, pass(self) :: end_tag

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(in) :: self
    logical, intent(in), optional :: is_indented

    Return Value character(len=:),allocatable

procedure, public, pass(self) :: free

  • private elemental subroutine free(self)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self

procedure, public, pass(self) :: is_attribute_present

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(in) :: self
    character, intent(in) :: name

    Return Value logical

procedure, public, pass(self) :: is_parsed

  • private elemental function is_parsed(self)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(in) :: self

    Return Value logical

procedure, public, pass(self) :: name

  • private pure function name(self)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(in) :: self

    Return Value character(len=:),allocatable

procedure, public, pass(self) :: parse

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: source
    integer(kind=I4P), intent(out), optional :: tstart
    integer(kind=I4P), intent(out), optional :: tend

procedure, public, pass(self) :: self_closing_tag

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(in) :: self
    logical, intent(in), optional :: is_indented

    Return Value character(len=:),allocatable

procedure, public, pass(self) :: set

  • private pure subroutine set(self, name, attribute, attributes, attributes_stream, sanitize_attributes_value, content, indent, is_content_indented, is_self_closing)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in), optional :: name
    character, intent(in), optional :: attribute(1:)
    character, intent(in), optional :: attributes(1:,1:)
    character, intent(in), optional :: attributes_stream
    logical, intent(in), optional :: sanitize_attributes_value
    character, intent(in), optional :: content
    integer(kind=I4P), intent(in), optional :: indent
    logical, intent(in), optional :: is_content_indented
    logical, intent(in), optional :: is_self_closing

procedure, public, pass(self) :: start_tag

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(in) :: self
    logical, intent(in), optional :: is_indented

    Return Value character(len=:),allocatable

procedure, public, pass(self) :: stringify

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(in) :: self
    logical, intent(in), optional :: is_indented
    logical, intent(in), optional :: is_content_indented
    logical, intent(in), optional :: only_start
    logical, intent(in), optional :: only_content
    logical, intent(in), optional :: only_end

    Return Value character(len=:),allocatable

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

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(in) :: self
    integer(kind=I4P), intent(in) :: unit
    logical, intent(in), optional :: is_indented
    logical, intent(in), optional :: is_content_indented
    character, intent(in), optional :: form
    character, intent(in), optional :: end_record
    logical, intent(in), optional :: only_start
    logical, intent(in), optional :: only_content
    logical, intent(in), optional :: only_end
    integer(kind=I4P), intent(out), optional :: iostat
    character, intent(out), optional :: iomsg

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

  • private elemental subroutine assign_tag(lhs, rhs)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: lhs
    type(xml_tag), intent(in) :: rhs

procedure, private, pass(self) :: add_single_attribute

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: attribute(1:)
    logical, intent(in), optional :: sanitize_value

procedure, private, pass(self) :: add_multiple_attributes

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: attributes(1:,1:)
    logical, intent(in), optional :: sanitize_values

procedure, private, pass(self) :: add_stream_attributes

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: attributes_stream
    logical, intent(in), optional :: sanitize_values

procedure, private, pass(self) :: alloc_attributes

  • private elemental subroutine alloc_attributes(self, Na)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    integer(kind=I4P), intent(in) :: Na

procedure, private, pass(self) :: delete_single_attribute

  • private pure subroutine delete_single_attribute(self, name)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: name

procedure, private, pass(self) :: delete_multiple_attributes

  • private pure subroutine delete_multiple_attributes(self, name)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: name(1:)

procedure, private, pass(self) :: get

  • private elemental subroutine get(self, source)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: source

procedure, private, pass(self) :: get_value

  • private elemental subroutine get_value(self, source)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: source

procedure, private, pass(self) :: get_attributes

  • private elemental subroutine get_attributes(self, source)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: source

procedure, private, pass(self) :: parse_tag_name

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: source
    integer(kind=I4P), intent(out), optional :: tstart
    integer(kind=I4P), intent(out), optional :: tend

procedure, private, pass(self) :: parse_attributes_names

  • private elemental subroutine parse_attributes_names(self, source)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: source

procedure, private, pass(self) :: search

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

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: self
    character, intent(in) :: tag_name
    character, intent(in) :: source
    integer(kind=I4P), intent(out), optional :: tstart
    integer(kind=I4P), intent(out), optional :: tend

procedure, private, pass(lhs) :: assign_tag

  • private elemental subroutine assign_tag(lhs, rhs)

    Arguments

    TypeIntentOptionalAttributesName
    class(xml_tag), intent(inout) :: lhs
    type(xml_tag), intent(in) :: rhs

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.
  type(string), allocatable :: attribute(:,:)          !< Attributes names/values pairs, [1:2, 1:].
  integer(I4P)              :: attributes_number=0     !< Number of defined attributes.
  integer(I4P)              :: indent=0                !< Number of indent-white-spaces.
  logical                   :: is_self_closing=.false. !< Self closing tag flag.
  contains
    ! public methods
    generic               :: add_attributes =>        &
                             add_single_attribute,    &
                             add_multiple_attributes, &
                             add_stream_attributes       !< Add attributes name/value pairs.
    procedure, pass(self) :: attributes                  !< Return attributes name/value pairs as string.
    procedure, pass(self) :: get_content                 !< Return tag content.
    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 dynamic memory.
    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) :: 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_tag_name             !< Parse the tag name contained into a string.
    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.
#if (__GNUC__ < 9)
    final                         :: finalize   !< Free dynamic memory when finalizing.
#endif
endtype xml_tag