hash_table Derived Type

type, public :: hash_table

type~~hash_table~~InheritsGraph type~hash_table hash_table type~dictionary dictionary type~dictionary->type~hash_table bucket type~dictionary_node dictionary_node type~dictionary_node->type~dictionary head, tail type~dictionary_node->type~dictionary_node next, previous type~key_base key_base type~key_base->type~dictionary_node key
Help


Hash table class to storage any contents by means of generic dictionary buckets.


Source Code


Components

TypeVisibility AttributesNameInitial
type(dictionary), private, allocatable:: bucket(:)

Hash table buckets.

integer(kind=I8P), private, allocatable:: ids_(:,:)

Minimum and maximum id values actually stored into each bucket.

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

Number of nodes actually stored, namely the hash table length.

integer(kind=I4P), private :: me =0

Index of current CAF image.

integer(kind=I4P), private :: images_number =0

Number of CAF images.

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

Number of buckets used.

logical, private :: is_homogeneous_ =.false.

Homogeneity status-guardian.

logical, private :: is_initialized_ =.false.

Initialization status.

class(*), private, allocatable:: typeguard_key

Key type guard (mold) for homogeneous keys check.

class(*), private, allocatable:: typeguard_content

Content type guard (mold) for homogeneous contents check.


Finalization Procedures

final :: finalize

Finalize the hash table.

  • private elemental subroutine finalize(self)

    Finalize the hash table.

    Arguments

    Type IntentOptional AttributesName
    type(hash_table), intent(inout) :: self

    The hash table.


Type-Bound Procedures

procedure, public, pass(self) :: add_pointer

Add a node pointer to the hash table.

  • private subroutine add_pointer(self, key, content)

    Add a node pointer to the hash table.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(inout) :: self

    The hash table.

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

    The key.

    class(*), intent(in), pointer:: content

    The content.

procedure, public, pass(self) :: add_clone

Add a node to the hash table cloning contents (non pointer add).

  • private subroutine add_clone(self, key, content)

    Add a node to the hash table cloning content (non pointer add).

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(inout) :: self

    The hash table.

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

    The key.

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

    The content.

procedure, public, pass(self) :: destroy

Destroy the hash table.

  • private elemental subroutine destroy(self)

    Destroy the hash table.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(inout) :: self

    The hash table.

procedure, public, pass(self) :: get_clone

Return a node's content in the hash table by cloning.

  • public subroutine get_clone(self, key, content)

    Return a node's content by cloning.

    Arguments

    Type IntentOptional AttributesName
    class(dictionary), intent(in) :: self

    The dictionary.

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

    The key.

    class(*), intent(out), allocatable:: content

    Content of the queried node.

procedure, public, pass(self) :: get_pointer

Return a pointer to a node's content in the hash table.

  • private function get_pointer(self, key) result(content)

    Return a pointer to a node's content in the hash table.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(in) :: self

    The hash table.

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

    The key.

    Return Value class(*), pointer

    Content pointer of the queried node.

procedure, public, pass(self) :: has_key

Check if the key is present in the hash table.

  • private function has_key(self, key)

    Check if the key is present in the hash table.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(in) :: self

    The hash table.

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

    The key.

    Return Value logical

    Check result.

procedure, public, pass(self) :: ids

Return the list of ids actually stored.

  • private pure function ids(self, global)

    Return the minimum and maximum unique key id values actually stored.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(in) :: self

    The hash table.

    logical, intent(in), optional :: global

    Check the global values on all CAF images rather only on the local image.

    Return Value integer(kind=I8P) (1:2)

    Minimum and maximum id values actually stored.

procedure, public, pass(self) :: initialize

Initialize the hash table.

  • private subroutine initialize(self, buckets_number, use_prime, homogeneous, typeguard_key, typeguard_content)

    Initialize the hash table.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(inout) :: self

    The hash table.

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

    Number of buckets for initialize the hash table.

    logical, intent(in), optional :: use_prime

    If true the buckets number is rendered prime.

    logical, intent(in), optional :: homogeneous

    If true the hash is supposed to accept only homogeneous nodes.

    class(*), intent(in), optional :: typeguard_key

    Key type guard (mold) for homogeneous keys check.

    class(*), intent(in), optional :: typeguard_content

    content type guard (mold) for homogeneous contents check.

procedure, public, pass(self) :: is_homogeneous

Return homogeneity status.

  • private elemental function is_homogeneous(self)

    Return homogeneity status.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(in) :: self

    The hash table.

    Return Value logical

    Homogeneity status.

procedure, public, pass(self) :: is_initialized

Return initialization status.

  • private elemental function is_initialized(self)

    Return initialization status.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(in) :: self

    The hash table.

    Return Value logical

    Initialization status.

procedure, public, pass(self) :: print_keys

Print the hash table keys.

  • private subroutine print_keys(self)

    Print the hash table keys.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(in) :: self

    The hash table.

procedure, public, pass(self) :: remove

Remove a node from the hash table, given the key.

  • private subroutine remove(self, key)

    Remove a node from the hash table, given the key.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(inout) :: self

    The hash table.

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

    The key.

procedure, public, pass(self) :: traverse

Traverse hash table calling the iterator procedure.

  • private subroutine traverse(self, iterator)

    Traverse hash table calling the iterator procedure.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(in) :: self

    The hash_table.

    procedure(key_iterator_interface) :: iterator

    The (key) iterator procedure to call for each node.

procedure, private, pass(self) :: allocate_members

Allocate dynamic memory members.

  • private subroutine allocate_members(self, typeguard_key, typeguard_content)

    Allocate dynamic memory members.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(inout) :: self

    The hash table.

    class(*), intent(in), optional :: typeguard_key

    Key type guard (mold) for homogeneous keys check.

    class(*), intent(in), optional :: typeguard_content

    content type guard (mold) for homogeneous contents check.

procedure, private, pass(self) :: check_type

Check type consistency.

  • private subroutine check_type(self, key, content)

    Check type consistency.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(inout) :: self

    The hash table.

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

    The key.

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

    The content.

procedure, private, pass(self) :: get_bucket_image_indexes

Get the bucket and image indexes corresponding to the given key.

  • private pure subroutine get_bucket_image_indexes(self, key, bucket, image)

    Get the bucket and image indexes corresponding to the given key.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(in) :: self

    The hash table.

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

    The key.

    integer(kind=I4P), intent(out) :: bucket

    Bucket index.

    integer(kind=I4P), intent(out) :: image

    Image index.

procedure, private, pass(self) :: hash

Hash the key.

  • private elemental function hash(self, key) result(bucket)

    Hash the key.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(in) :: self

    The hash table.

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

    Key to hash.

    Return Value integer(kind=I4P)

    Bucket index corresponding to the key.

procedure, private, pass(self) :: set_buckets_number

Set buckets number.

  • private pure subroutine set_buckets_number(self, buckets_number, use_prime)

    Set buckets number.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(inout) :: self

    The hash table.

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

    Number of buckets for initialize the hash table.

    logical, intent(in), optional :: use_prime

    If true the buckets number is rendered prime.

procedure, private, pass(self) :: set_caf_dimensions

Set CAF dimensions by means of intrinsic inquiring functions.

  • private pure subroutine set_caf_dimensions(self)

    Set CAF dimensions by means of intrinsic inquiring functions.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(inout) :: self

    The hash table.

procedure, private, pass(self) :: set_homogeneous

Set homogeneity flag.

  • private pure subroutine set_homogeneous(self, homogeneous)

    Set homogeneity flag.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(inout) :: self

    The hash table.

    logical, intent(in), optional :: homogeneous

    If true the hash is supposed to accept only homogeneous nodes.

procedure, private, pass(self) :: synchronize_images

Syncrhonize CAF images.

  • private subroutine synchronize_images(self)

    Synchronize CAF images.

    Arguments

    Type IntentOptional AttributesName
    class(hash_table), intent(inout) :: self

    The hash table.

Source Code

type :: hash_table
  !< **Hash table** class to storage any contents by means of generic dictionary buckets.
  private
#ifdef CAF
  type(dictionary), allocatable :: bucket(:)[:]            !< Hash table buckets.
  integer(I8P),     allocatable :: ids_(:,:)[:]            !< Minimum and maximum id values actually stored into each bucket.
  integer(I4P),     allocatable :: nodes_number_[:]        !< Number of nodes actually stored, namely the hash table length.
#else
  type(dictionary), allocatable :: bucket(:)               !< Hash table buckets.
  integer(I8P),     allocatable :: ids_(:,:)               !< Minimum and maximum id values actually stored into each bucket.
  integer(I4P)                  :: nodes_number_=0_I4P     !< Number of nodes actually stored, namely the hash table length.
#endif
  integer(I4P)                  :: me=0                    !< Index of current CAF image.
  integer(I4P)                  :: images_number=0         !< Number of CAF images.
  integer(I4P)                  :: buckets_number=0_I4P    !< Number of buckets used.
  logical                       :: is_homogeneous_=.false. !< Homogeneity status-guardian.
  logical                       :: is_initialized_=.false. !< Initialization status.
  class(*), allocatable         :: typeguard_key           !< Key type guard (mold) for homogeneous keys check.
  class(*), allocatable         :: typeguard_content       !< Content type guard (mold) for homogeneous contents check.
  contains
    ! public methods
    procedure, pass(self) :: add_pointer    !< Add a node pointer to the hash table.
    procedure, pass(self) :: add_clone      !< Add a node to the hash table cloning contents (non pointer add).
    procedure, pass(self) :: destroy        !< Destroy the hash table.
    procedure, pass(self) :: get_clone      !< Return a node's content in the hash table by cloning.
    procedure, pass(self) :: get_pointer    !< Return a pointer to a node's content in the hash table.
    procedure, pass(self) :: has_key        !< Check if the key is present in the hash table.
    procedure, pass(self) :: ids            !< Return the list of ids actually stored.
    procedure, pass(self) :: initialize     !< Initialize the hash table.
    procedure, pass(self) :: is_homogeneous !< Return homogeneity status.
    procedure, pass(self) :: is_initialized !< Return initialization status.
    procedure, pass(self) :: print_keys     !< Print the hash table keys.
    procedure, pass(self) :: remove         !< Remove a node from the hash table, given the key.
    procedure, pass(self) :: traverse       !< Traverse hash table calling the iterator procedure.
    ! private methods
    procedure, pass(self), private :: allocate_members         !< Allocate dynamic memory members.
    procedure, pass(self), private :: check_type               !< Check type consistency.
    procedure, pass(self), private :: get_bucket_image_indexes !< Get the bucket and image indexes corresponding to the given key.
    procedure, pass(self), private :: hash                     !< Hash the key.
    procedure, pass(self), private :: set_buckets_number       !< Set buckets number.
    procedure, pass(self), private :: set_caf_dimensions       !< Set CAF dimensions by means of intrinsic inquiring functions.
    procedure, pass(self), private :: set_homogeneous          !< Set homogeneity flag.
    procedure, pass(self), private :: synchronize_images       !< Syncrhonize CAF images.
    ! finalizer
    final :: finalize !< Finalize the hash table.
endtype hash_table