FTValueDictionaryClass Module

The FTValueDictionary subclass of FTDictionary adds convenient methods to easily add fundamental (Real, integer,…) values to a dictionary.

As a subclass, all other methods are still available.

Usage:

Adding a value

 CALL dict % addValueForKey(1,"integer")
 CALL dict % addValueForKey(3.14,"real")
 CALL dict % addValueForKey(98.6d0,"double")
 CALL dict % addValueForKey(.true.,"logical")
 CALL dict % addValueForKey("Hello World","string")

Accessing a value

 i = dict % integerValueForKey("integer")
 r = dict % realValueForKey("real")
 d = dict % doublePrecisionValueForKey("double")
 l = dict % logicalValueForKey("logical")
 s = dict % stringValueForKey("string",15)

Converting an FTDictionary to an FTValueDictionary

        valueDict => valueDictionaryFromDictionary(dict)

Converting an FTObject to an FTValueDictionary

        valueDict => valueDictionaryFromObject(obj)


Interfaces

public interface release

  • public subroutine releaseFTValueDictionary(self)

    Public, generic name: release(self)

    Call release(self) on an object to release control of an object. If its reference count is zero, then it is deallocated.

    Arguments

    Type IntentOptional Attributes Name
    type(FTValueDictionary), POINTER :: self

Derived Types

type, public, extends(FTDictionary) ::  FTValueDictionary

Components

Type Visibility Attributes Name Initial
integer, public :: numberOfEntries
logical, public :: isCaseSensitive
type(FTLinkedList), public, DIMENSION(:), POINTER :: entries => NULL()

Type-Bound Procedures

procedure, public, non_overridable :: copy => copyFTObject
procedure, public, non_overridable :: retain => retainFTObject
procedure, public, non_overridable :: isUnreferenced
procedure, public, non_overridable :: refCount
procedure, public :: initWithSize
procedure, public :: init
procedure, public :: setCaseSensitive
procedure, public :: caseSensitive
procedure, public :: allKeys => AllKeys
procedure, public :: allObjects => AllObjects
procedure, public :: destruct => destructFTDictionary
procedure, public :: addObjectForKey
procedure, public :: removeObjectForKey
procedure, public :: description => FTDictionaryDescription
procedure, public :: printDescription => printFTDictionaryDescription
procedure, public :: objectForKey
procedure, public :: containsKey
procedure, public :: COUNT
generic, public :: addValueForKey => addRealValueForKey, addDoublePrecisionValueForKey, addIntegerValueForKey, addStringValueForKey, addLogicalValueForKey
generic, public :: addValueForKey => addQuadValueForKey
procedure, public :: realValueForKey
procedure, public :: doublePrecisionValueForKey
procedure, public :: quadValueForKey
procedure, public :: integerValueForKey
procedure, public :: stringValueForKey
procedure, public :: logicalValueForKey
generic, public :: getValueOrDefault => getRealValueOrDefault, getDoublePrescisionValueOrDefault, getIntegerValueOrDefault, getLogicalValueOrDefault
procedure, public :: className => valueDictionaryClassName

Functions

public function realValueForKey(self, key)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
character(len=*) :: key

Return Value real

public function integerValueForKey(self, key)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
character(len=*) :: key

Return Value integer

public function doublePrecisionValueForKey(self, key)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
character(len=*) :: key

Return Value doubleprecision

public function quadValueForKey(self, key)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
character(len=*) :: key

Return Value real(kind=selected_real_kind(quad_digits))

public function logicalValueForKey(self, key)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
character(len=*) :: key

Return Value logical

public function stringValueForKey(self, key, requestedLength)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
character(len=*) :: key
integer :: requestedLength

Return Value character(len=requestedLength)

public function valueDictionaryFromDictionary(dict) result(valueDict)

Arguments

Type IntentOptional Attributes Name
class(FTDictionary), POINTER :: dict

Return Value class(FTValueDictionary), POINTER

public function valueDictionaryFromObject(obj) result(valueDict)

Arguments

Type IntentOptional Attributes Name
class(FTObject), POINTER :: obj

Return Value class(FTValueDictionary), POINTER

public function valueDictionaryClassName(self) result(s)

Class name returns a string with the name of the type of the object

Read more…

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self

Return Value character(len=CLASS_NAME_CHARACTER_LENGTH)

public function getIntegerValueOrDefault(self, key, default) result(val)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
character(len=*), intent(in) :: key
integer, intent(in) :: default

Return Value integer

public function getRealValueOrDefault(self, key, default) result(val)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
character(len=*), intent(in) :: key
real, intent(in) :: default

Return Value real

public function getDoublePrescisionValueOrDefault(self, key, default) result(val)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
character(len=*), intent(in) :: key
double precision, intent(in) :: default

Return Value double precision

public function getLogicalValueOrDefault(self, key, default) result(val)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
character(len=*), intent(in) :: key
logical, intent(in) :: default

Return Value logical


Subroutines

public subroutine releaseFTValueDictionary(self)

Public, generic name: release(self)

Read more…

Arguments

Type IntentOptional Attributes Name
type(FTValueDictionary), POINTER :: self

public subroutine addIntegerValueForKey(self, i, key)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
integer :: i
character(len=*) :: key

public subroutine addRealValueForKey(self, r, key)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
real :: r
character(len=*) :: key

public subroutine addDoublePrecisionValueForKey(self, r, key)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
double precision :: r
character(len=*) :: key

public subroutine addQuadValueForKey(self, r, key)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
real(kind=SELECTED_REAL_KIND(QUAD_DIGITS)) :: r
character(len=*) :: key

public subroutine addStringValueForKey(self, s, key)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
character(len=*) :: s
character(len=*) :: key

public subroutine addLogicalValueForKey(self, l, key)

Arguments

Type IntentOptional Attributes Name
class(FTValueDictionary) :: self
logical :: l
character(len=*) :: key

public subroutine castDictionaryToValueDictionary(dict, valueDict)

Arguments

Type IntentOptional Attributes Name
class(FTDictionary), POINTER :: dict
class(FTValueDictionary), POINTER :: valueDict

public subroutine castObjectToValueDictionary(obj, valueDict)

Arguments

Type IntentOptional Attributes Name
class(FTObject), POINTER :: obj
class(FTValueDictionary), POINTER :: valueDict