hashtbl_obj Derived Type

type, public :: hashtbl_obj

A hash table. E.g. of a hash table with vec_len=4

vect(1) :: key1 --> key2 --> key3 --> key4 --> nul() | | | | | | val1 val2 val3 val4 | vect(2) :: key1 --> null() | | | val1 | vect(3) :: null() | | | vect(4) :: key1 --> key2 --> null() | | | | val1 val2


Inherits

type~~hashtbl_obj~~InheritsGraph type~hashtbl_obj hashtbl_obj type~sllist_obj sllist_obj type~hashtbl_obj->type~sllist_obj vec type~sllist_obj->type~sllist_obj child

Inherited by

type~~hashtbl_obj~~InheritedByGraph type~hashtbl_obj hashtbl_obj type~bc_set bc_set type~bc_set->type~hashtbl_obj tbl type~hdf5_obj hdf5_obj type~bc_set->type~hdf5_obj hdf5 type~region_obj region_obj type~bc_set->type~region_obj region type~block_obj block_obj type~bc_set->type~block_obj block type~eulerian_set eulerian_set type~eulerian_set->type~hashtbl_obj tbl type~eulerian_set->type~block_obj block type~eulerian_ptr eulerian_ptr type~eulerian_set->type~eulerian_ptr field type~hdf5_obj->type~hashtbl_obj tbl type~monitor_set monitor_set type~monitor_set->type~hashtbl_obj tbl type~region_obj->type~hashtbl_obj tbl type~region_obj->type~block_obj region type~timer_obj timer_obj type~timer_obj->type~hashtbl_obj tbl type~block_obj->type~hdf5_obj hdf5 type~cdifs_obj cdifs_obj type~cdifs_obj->type~bc_set bcs type~cdifs_obj->type~eulerian_set fields type~cdifs_obj->type~hdf5_obj hdf5 type~cdifs_obj->type~monitor_set monitors, pmonitor type~cdifs_obj->type~block_obj block type~collision_obj collision_obj type~cdifs_obj->type~collision_obj collisions type~marker_set marker_set type~cdifs_obj->type~marker_set IB type~respart_set ResPart_set type~cdifs_obj->type~respart_set RP type~solver_obj solver_obj type~cdifs_obj->type~solver_obj type~hypre_obj hypre_obj type~cdifs_obj->type~hypre_obj hypre, VFSolver type~op_obj op_obj type~cdifs_obj->type~op_obj op type~eulerian_obj_i eulerian_obj_i type~cdifs_obj->type~eulerian_obj_i maskV type~eulerian_obj_r eulerian_obj_r type~cdifs_obj->type~eulerian_obj_r V, P, dP, ibS, ibVF, ibF, ibN, Vold, resV, rhs, divu, Vm, srcV type~collision_obj->type~monitor_set monitors type~collision_obj->type~timer_obj timer type~collision_obj->type~block_obj cblock type~collision_obj->type~marker_set IB type~particle_set particle_set type~collision_obj->type~particle_set PP type~collision_obj->type~respart_set RP type~grans_obj grans_obj type~grans_obj->type~bc_set bcs type~grans_obj->type~eulerian_set fields type~grans_obj->type~hdf5_obj hdf5 type~grans_obj->type~monitor_set monitors type~grans_obj->type~block_obj block type~grans_obj->type~collision_obj collisions type~grans_obj->type~marker_set IB type~grans_obj->type~particle_set PP type~grans_obj->type~respart_set RP type~grans_obj->type~solver_obj type~grans_obj->type~hypre_obj VFSolver type~grans_obj->type~op_obj op type~grans_obj->type~eulerian_obj_r ibVF, PVF, ibS, Fp, ibF, ibN, rhs type~h5hut_obj h5hut_obj type~h5hut_obj->type~hdf5_obj hdf5 type~marker_set->type~bc_set bcs type~marker_set->type~monitor_set monitors type~marker_set->type~timer_obj timer type~lagrangian_set lagrangian_set type~marker_set->type~lagrangian_set type~marker_set->type~op_obj op type~particle_set->type~monitor_set monitors type~particle_set->type~timer_obj timer type~particle_set->type~lagrangian_set type~particle_set->type~op_obj op type~respart_set->type~bc_set bcs type~respart_set->type~monitor_set monitors type~respart_set->type~timer_obj timer type~respart_set->type~marker_set ib type~respart_set->type~lagrangian_set type~respart_set->type~op_obj op type~solver_obj->type~timer_obj timer type~eulerian_obj_base eulerian_obj_base type~eulerian_obj_base->type~block_obj block type~hypre_obj->type~block_obj block type~hypre_obj->type~eulerian_obj_i irow type~lagrangian_set->type~block_obj block type~op_obj->type~block_obj block type~solid_obj solid_obj type~solid_obj->type~marker_set type~solid_set solid_set type~solid_set->type~block_obj block type~solid_set->type~solid_obj p type~eulerian_obj_i->type~eulerian_obj_base type~eulerian_obj_r->type~eulerian_obj_base type~eulerian_ptr->type~eulerian_obj_base p

Components

Type Visibility Attributes Name Initial
type(sllist_obj), public, allocatable :: vec(:)
integer, public :: vec_len = 0

Type-Bound Procedures

procedure, public :: Finalize => hashtbl_obj_Final

  • private pure subroutine hashtbl_obj_Final(this)

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(inout) :: this

    Hashtable object

  • private pure subroutine hashtbl_obj_Get_int4(this, key, val)

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(in) :: this

    Hashtable object

    integer, intent(in) :: key

    Key from key-val pair to retrieve from hashtable

    integer(kind=leapI4), intent(out) :: val

    Val from key-val pair to retrieve from hashtable

  • private pure subroutine hashtbl_obj_Get_int8(this, key, val)

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(in) :: this

    Hashtable object

    integer, intent(in) :: key

    Key from key-val pair to retrieve from hashtable

    integer(kind=leapI8), intent(out) :: val

    Val from key-val pair to retrieve from hashtable

  • private pure subroutine hashtbl_obj_Get_real_sp(this, key, val)

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(in) :: this

    Hashtable object

    integer, intent(in) :: key

    Key from key-val pair to retrieve from hashtable

    real(kind=leapSP), intent(out) :: val

    Val from key-val pair to retrieve from hashtable

  • private pure subroutine hashtbl_obj_Get_real_dp(this, key, val)

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(in) :: this

    Hashtable object

    integer, intent(in) :: key

    Key from key-val pair to retrieve from hashtable

    real(kind=leapDP), intent(out) :: val

    Val from key-val pair to retrieve from hashtable

procedure, public, nopass :: HashString => hashtbl_obj_HashString

  • private pure function hashtbl_obj_HashString(str) result(val)

    Arguments

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

    String to hash

    Return Value integer

    Returned hash

procedure, public :: Initialize => hashtbl_obj_Init

  • private pure subroutine hashtbl_obj_Init(this, tbl_len)

    Initializes the hashtable.

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(inout) :: this

    Hashtable object

    integer, intent(in) :: tbl_len

    Hashtable vector length

procedure, public :: Print => hashtbl_obj_Print

  • private impure subroutine hashtbl_obj_Print(this)

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(inout), target :: this

    Hashtable object

procedure, public :: Put => hashtbl_obj_Put

  • private pure subroutine hashtbl_obj_Put(this, key, val)

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(inout) :: this

    Hashtable object

    integer, intent(in) :: key

    Key from key-val pair to add in hashtable

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

    Val from key-val pair to add in hashtable

procedure, public :: Remove => hashtbl_obj_Remove

  • private pure subroutine hashtbl_obj_Remove(this, key)

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(inout) :: this

    Hashtable object

    integer, intent(in) :: key

    Key from key-val pair to remove from hashtable

procedure, private :: hashtbl_obj_Get_int4

  • private pure subroutine hashtbl_obj_Get_int4(this, key, val)

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(in) :: this

    Hashtable object

    integer, intent(in) :: key

    Key from key-val pair to retrieve from hashtable

    integer(kind=leapI4), intent(out) :: val

    Val from key-val pair to retrieve from hashtable

procedure, private :: hashtbl_obj_Get_int8

  • private pure subroutine hashtbl_obj_Get_int8(this, key, val)

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(in) :: this

    Hashtable object

    integer, intent(in) :: key

    Key from key-val pair to retrieve from hashtable

    integer(kind=leapI8), intent(out) :: val

    Val from key-val pair to retrieve from hashtable

procedure, private :: hashtbl_obj_Get_real_dp

  • private pure subroutine hashtbl_obj_Get_real_dp(this, key, val)

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(in) :: this

    Hashtable object

    integer, intent(in) :: key

    Key from key-val pair to retrieve from hashtable

    real(kind=leapDP), intent(out) :: val

    Val from key-val pair to retrieve from hashtable

procedure, private :: hashtbl_obj_Get_real_sp

  • private pure subroutine hashtbl_obj_Get_real_sp(this, key, val)

    Arguments

    Type IntentOptional Attributes Name
    class(hashtbl_obj), intent(in) :: this

    Hashtable object

    integer, intent(in) :: key

    Key from key-val pair to retrieve from hashtable

    real(kind=leapSP), intent(out) :: val

    Val from key-val pair to retrieve from hashtable

Source Code

  type :: hashtbl_obj
    !> A hash table.
    ! E.g. of a hash table with vec_len=4
    !
    !  vect(1) :: key1 --> key2 --> key3 --> key4 --> nul()
    !     |        |        |        |        |
    !     |       val1     val2     val3     val4
    !     |
    !  vect(2) :: key1 --> null()
    !     |        |
    !     |       val1
    !     |
    !  vect(3) :: null()
    !     |
    !     |
    !     |
    !  vect(4) :: key1 --> key2 --> null()
    !     |        |        |
    !     |       val1     val2
    type(sllist_obj), allocatable :: vec(:)
    integer                       :: vec_len = 0
    contains
      procedure :: Initialize          => hashtbl_obj_Init
      procedure :: Finalize            => hashtbl_obj_Final
      procedure :: Put                 => hashtbl_obj_Put
      generic   :: Get                 => hashtbl_obj_Get_int4,    &
                                          hashtbl_obj_Get_int8,    &
                                          hashtbl_obj_Get_real_sp, &
                                          hashtbl_obj_Get_real_dp
      procedure :: Remove              => hashtbl_obj_Remove
      procedure :: Print               => hashtbl_obj_Print
      procedure, nopass  :: HashString => hashtbl_obj_HashString
      ! Internal/private procedures
      procedure, private :: hashtbl_obj_Get_int4
      procedure, private :: hashtbl_obj_Get_int8
      procedure, private :: hashtbl_obj_Get_real_sp
      procedure, private :: hashtbl_obj_Get_real_dp
  end type hashtbl_obj