file_ini Derived Type

type, public :: file_ini

INI file class.


Inherits

type~~file_ini~~InheritsGraph type~file_ini file_ini type~section section type~file_ini->type~section sections type~option option type~section->type~option options string string type~option->string oname, ovals, ocomm

Contents

Source Code


Components

TypeVisibilityAttributesNameInitial
integer(kind=I4P), private :: Ns =0

Number of sections.

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

File name

character(len=1), private :: opt_sep =DEF_OPT_SEP

Separator character of option name/value.

type(section), private, allocatable:: sections(:)

Sections.


Type-Bound Procedures

generic, public :: add => add_section, add_option, add_a_option

Add a section. Add an option to a section (scalar). Add an option to a section (array).

  • private pure subroutine add_section(self, error, section_name)

    Add a section.

    Read more…

    Arguments

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

    File data.

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

    Error code.

    character, intent(in) :: section_name

    Section name.

  • private pure subroutine add_option(self, error, section_name, option_name, val)

    Add an option (with scalar value).

    Read more…

    Arguments

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

    File data.

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

    Error code.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

    class(*), intent(in) :: val

    Option value.

  • private pure subroutine add_a_option(self, error, section_name, option_name, val)

    Add an option (with array value).

    Read more…

    Arguments

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

    File data.

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

    Error code.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

    class(*), intent(in) :: val(1:)

    Option value.

procedure, private, pass(self) :: add_a_option

Add an option to a section (array).

  • private pure subroutine add_a_option(self, error, section_name, option_name, val)

    Add an option (with array value).

    Read more…

    Arguments

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

    File data.

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

    Error code.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

    class(*), intent(in) :: val(1:)

    Option value.

procedure, private, pass(self) :: add_option

Add an option to a section (scalar).

  • private pure subroutine add_option(self, error, section_name, option_name, val)

    Add an option (with scalar value).

    Read more…

    Arguments

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

    File data.

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

    Error code.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

    class(*), intent(in) :: val

    Option value.

procedure, private, pass(self) :: add_section

Add a section.

  • private pure subroutine add_section(self, error, section_name)

    Add a section.

    Read more…

    Arguments

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

    File data.

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

    Error code.

    character, intent(in) :: section_name

    Section name.

procedure, private, pass(lhs) :: assign_file_ini

Assignment overloading.

  • private elemental subroutine assign_file_ini(lhs, rhs)

    Assignment between two INI files.

    Arguments

    TypeIntentOptionalAttributesName
    class(file_ini), intent(inout) :: lhs

    Left hand side.

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

    Rigth hand side.

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

Procedure for section assignment overloading.

  • private elemental subroutine assign_file_ini(lhs, rhs)

    Assignment between two INI files.

    Arguments

    TypeIntentOptionalAttributesName
    class(file_ini), intent(inout) :: lhs

    Left hand side.

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

    Rigth hand side.

procedure, public, pass(self) :: count_values

Count option value(s).

  • private elemental function count_values(self, delimiter, section_name, option_name) result(Nv)

    Get the number of values of option into section data.

    Arguments

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

    File data.

    character, intent(in), optional :: delimiter

    Delimiter used for separating values.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

    Return Value integer(kind=I4P)

    Number of values.

generic, public :: del => free_option_of_section, free_section

Remove (freeing) an option of a section. Remove (freeing) a section.

  • private elemental subroutine free_option_of_section(self, section_name, option_name)

    Free all options of a section.

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

  • private elemental subroutine free_section(self, section_name)

    Free all options of a section.

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

procedure, public, pass(self) :: free

Free dynamic memory destroyng file data.

  • private elemental subroutine free(self)

    Free dynamic memory.

    Arguments

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

    File data.

procedure, private, pass(self) :: free_option_of_section

Free an option of a section.

  • private elemental subroutine free_option_of_section(self, section_name, option_name)

    Free all options of a section.

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

Free all options. Free all options of a section. Free an option of a section.

  • private elemental subroutine free_options_all(self)

    Free all options of all sections.

    Arguments

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

    File data.

  • private elemental subroutine free_options_of_section(self, section_name)

    Free all options of a section.

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

  • private elemental subroutine free_option_of_section(self, section_name, option_name)

    Free all options of a section.

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

procedure, private, pass(self) :: free_options_all

Free all options of all sections.

  • private elemental subroutine free_options_all(self)

    Free all options of all sections.

    Arguments

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

    File data.

procedure, private, pass(self) :: free_options_of_section

Free all options of a section.

  • private elemental subroutine free_options_of_section(self, section_name)

    Free all options of a section.

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

procedure, private, pass(self) :: free_section

Free a section.

  • private elemental subroutine free_section(self, section_name)

    Free all options of a section.

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

generic, public :: get => get_option, get_a_option

Get option value (scalar). Get option value (array).

  • private subroutine get_option(self, section_name, option_name, val, error)

    Get option value (scalar).

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

    class(*), intent(inout) :: val

    Value.

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

    Error code.

  • private subroutine get_a_option(self, section_name, option_name, val, delimiter, error)

    Get option value (array)

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

    class(*), intent(inout) :: val(1:)

    Value.

    character, intent(in), optional :: delimiter

    Delimiter used for separating values.

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

    Error code.

procedure, private, pass(self) :: get_a_option

Get option value (array).

  • private subroutine get_a_option(self, section_name, option_name, val, delimiter, error)

    Get option value (array)

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

    class(*), intent(inout) :: val(1:)

    Value.

    character, intent(in), optional :: delimiter

    Delimiter used for separating values.

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

    Error code.

procedure, public, pass(self) :: get_items

Get list of pairs option name/value.

  • private pure subroutine get_items(self, items)

    Get list of pairs option name/value.

    Arguments

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

    File data.

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

    Items, list of pairs option name/value for all options [1:No,1:2].

procedure, private, pass(self) :: get_option

Get option value (scalar).

  • private subroutine get_option(self, section_name, option_name, val, error)

    Get option value (scalar).

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

    class(*), intent(inout) :: val

    Value.

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

    Error code.

procedure, public, pass(self) :: get_sections_list

Get sections names list.

  • private pure subroutine get_sections_list(self, list)

    Get sections names list.

    Arguments

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

    File data.

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

    Sections names list.

procedure, public, pass(self) :: has_option

Inquire the presence of an option.

  • private function has_option(self, option_name, section_name) result(pres)

    Inquire the presence of (at least one) option with the name passed.

    Read more…

    Arguments

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

    File data.

    character, intent(in) :: option_name

    Option name.

    character, intent(inout), optional :: section_name

    Section name.

    Return Value logical

    Inquiring flag.

procedure, public, pass(self) :: has_section

Inquire the presence of a section.

  • private elemental function has_section(self, section_name) result(pres)

    Inquire the presence of (at least one) section with the name passed.

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

    Return Value logical

    Inquiring flag.

generic, public :: index => index_section, index_option

Return the index of a section. Return the index of an option.

  • private elemental function index_section(self, back, section_name) result(ind)

    Return the index of the section matching the name passed.

    Read more…

    Arguments

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

    File data.

    logical, intent(in), optional :: back

    If back appears with the value true, the last matching index is returned.

    character, intent(in) :: section_name

    Section name.

    Return Value integer(kind=I4P)

    Index of searched section.

  • private elemental function index_option(self, back, section_name, option_name) result(ind)

    Return the index of the option (inside a section) matching the name(s) passed.

    Read more…

    Arguments

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

    File data.

    logical, intent(in), optional :: back

    If back appears with the value true, the last matching index is returned.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

    Return Value integer(kind=I4P)

    Index of searched section.

procedure, private, pass(self) :: index_option

Return the index of an option.

  • private elemental function index_option(self, back, section_name, option_name) result(ind)

    Return the index of the option (inside a section) matching the name(s) passed.

    Read more…

    Arguments

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

    File data.

    logical, intent(in), optional :: back

    If back appears with the value true, the last matching index is returned.

    character, intent(in) :: section_name

    Section name.

    character, intent(in) :: option_name

    Option name.

    Return Value integer(kind=I4P)

    Index of searched section.

procedure, private, pass(self) :: index_section

Return the index of a section.

  • private elemental function index_section(self, back, section_name) result(ind)

    Return the index of the section matching the name passed.

    Read more…

    Arguments

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

    File data.

    logical, intent(in), optional :: back

    If back appears with the value true, the last matching index is returned.

    character, intent(in) :: section_name

    Section name.

    Return Value integer(kind=I4P)

    Index of searched section.

procedure, public, pass(self) :: initialize

Initialize file.

  • private elemental subroutine initialize(self, filename)

    Initialize file.

    Arguments

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

    File data.

    character, intent(in), optional :: filename

    File name.

procedure, public, pass(self) :: load

Load file data.

  • private subroutine load(self, separator, filename, source, error)

    Get file data from a file or a source string.

    Read more…

    Arguments

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

    File data.

    character(len=1), intent(in), optional :: separator

    Separator of options name/value.

    character, intent(in), optional :: filename

    File name.

    character, intent(in), optional :: source

    File source contents.

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

    Error code.

generic, public :: loop => loop_options_section, loop_options

Loop over options of a section. Loop over all options.

  • private function loop_options_section(self, section_name, option_pairs) result(again)

    Loop returning option name/value defined into section.

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

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

    Pairs option name/value [1:2].

    Return Value logical

    Flag continuing the loop.

  • private recursive function loop_options(self, option_pairs) result(again)

    Loop returning option name/value defined into all sections.

    Arguments

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

    File data.

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

    Pairs option name/value [1:2].

    Return Value logical

    Flag continuing the loop.

procedure, private, pass(self) :: loop_options

Loop over all options.

  • private recursive function loop_options(self, option_pairs) result(again)

    Loop returning option name/value defined into all sections.

    Arguments

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

    File data.

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

    Pairs option name/value [1:2].

    Return Value logical

    Flag continuing the loop.

procedure, private, pass(self) :: loop_options_section

Loop over options of a section.

  • private function loop_options_section(self, section_name, option_pairs) result(again)

    Loop returning option name/value defined into section.

    Arguments

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

    File data.

    character, intent(in) :: section_name

    Section name.

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

    Pairs option name/value [1:2].

    Return Value logical

    Flag continuing the loop.

procedure, private, pass(self) :: parse

Parse file data.

  • private subroutine parse(self, source, error)

    Parse file either from the self source data or from a source string.

    Arguments

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

    File data.

    type(string), intent(in) :: source

    String source.

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

    Error code.

procedure, public, pass(self) :: print => print_file_ini

Pretty printing data.

  • private subroutine print_file_ini(self, unit, pref, retain_comments, iostat, iomsg)

    Print data with a pretty format.

    Arguments

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

    File data.

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

    Logic unit.

    character, intent(in), optional :: pref

    Prefixing string.

    logical, intent(in), optional :: retain_comments

    Flag for retaining eventual comments.

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

    IO error.

    character, intent(out), optional :: iomsg

    IO error message.

procedure, public, pass(self) :: save => save_file_ini

Save data.

  • private subroutine save_file_ini(self, retain_comments, iostat, iomsg, filename)

    Save data.

    Arguments

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

    File data.

    logical, intent(in), optional :: retain_comments

    Flag for retaining eventual comments.

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

    IO error.

    character, intent(out), optional :: iomsg

    IO error message.

    character, intent(in), optional :: filename

    File name.

procedure, public, pass(self) :: section => section_file_ini

Get section name once provided an index.

  • private pure function section_file_ini(self, section_index) result(sname)

    Get section name once an index (valid) is provided.

    Arguments

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

    File data.

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

    Section index.

    Return Value character(len=:),allocatable

    Section name.

Source Code

type :: file_ini
  !< INI file class.
  private
  character(len=:), allocatable, public :: filename              !< File name
  integer(I4P)                          :: Ns = 0                !< Number of sections.
  character(1)                          :: opt_sep = DEF_OPT_SEP !< Separator character of option name/value.
  type(section), allocatable            :: sections(:)           !< Sections.
  contains
    ! public methods
    generic               :: add          => add_section, &             !< Add a section.
                                             add_option,  &             !< Add an option to a section (scalar).
                                             add_a_option               !< Add an option to a section (array).
    procedure, pass(self) :: count_values                               !< Count option value(s).
    generic               :: del          => free_option_of_section, &  !< Remove (freeing) an option of a section.
                                             free_section               !< Remove (freeing) a section.
    procedure, pass(self) :: free                                       !< Free dynamic memory destroyng file data.
    generic               :: free_options => free_options_all,        & !< Free all options.
                                             free_options_of_section, & !< Free all options of a section.
                                             free_option_of_section     !< Free an option of a section.
    generic               :: get          => get_option, &              !< Get option value (scalar).
                                             get_a_option               !< Get option value (array).
    procedure, pass(self) :: get_items                                  !< Get list of pairs option name/value.
    procedure, pass(self) :: get_sections_list                          !< Get sections names list.
    procedure, pass(self) :: initialize                                 !< Initialize file.
    procedure, pass(self) :: has_option                                 !< Inquire the presence of an option.
    procedure, pass(self) :: has_section                                !< Inquire the presence of a section.
    generic               :: index        => index_section, &           !< Return the index of a section.
                                             index_option               !< Return the index of an option.
    procedure, pass(self) :: load                                       !< Load file data.
    generic               :: loop         => loop_options_section, &    !< Loop over options of a section.
                                             loop_options               !< Loop over all options.
    procedure, pass(self) :: print        => print_file_ini             !< Pretty printing data.
    procedure, pass(self) :: save         => save_file_ini              !< Save data.
    procedure, pass(self) :: section      => section_file_ini           !< Get section name once provided an index.
    ! operators overloading
    generic :: assignment(=) => assign_file_ini !< Procedure for section assignment overloading.
    ! private methods
    procedure, private, pass(self) :: add_a_option            !< Add an option to a section (array).
    procedure, private, pass(self) :: add_option              !< Add an option to a section (scalar).
    procedure, private, pass(self) :: add_section             !< Add a section.
    procedure, private, pass(self) :: free_options_all        !< Free all options of all sections.
    procedure, private, pass(self) :: free_options_of_section !< Free all options of a section.
    procedure, private, pass(self) :: free_option_of_section  !< Free an option of a section.
    procedure, private, pass(self) :: free_section            !< Free a section.
    procedure, private, pass(self) :: get_a_option            !< Get option value (array).
    procedure, private, pass(self) :: get_option              !< Get option value (scalar).
    procedure, private, pass(self) :: index_option            !< Return the index of an option.
    procedure, private, pass(self) :: index_section           !< Return the index of a section.
    procedure, private, pass(self) :: loop_options            !< Loop over all options.
    procedure, private, pass(self) :: loop_options_section    !< Loop over options of a section.
    procedure, private, pass(self) :: parse                   !< Parse file data.
    ! assignments
    procedure, private, pass(lhs) :: assign_file_ini !< Assignment overloading.
endtype file_ini