MAPL_Hash.F90 Source File


This file depends on

sourcefile~~mapl_hash.f90~~EfferentGraph sourcefile~mapl_hash.f90 MAPL_Hash.F90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~mapl_hash.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~errorhandling.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~mapl_throw.f90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90

Files dependent on this one

sourcefile~~mapl_hash.f90~~AfferentGraph sourcefile~mapl_hash.f90 MAPL_Hash.F90 sourcefile~base.f90 Base.F90 sourcefile~base.f90->sourcefile~mapl_hash.f90 sourcefile~mapl_locstreammod.f90 MAPL_LocStreamMod.F90 sourcefile~base.f90->sourcefile~mapl_locstreammod.f90 sourcefile~mapl_locstreammod.f90->sourcefile~mapl_hash.f90 sourcefile~maplshared.f90 MaplShared.F90 sourcefile~maplshared.f90->sourcefile~mapl_hash.f90 sourcefile~componentdriver.f90 ComponentDriver.F90 sourcefile~componentdriver.f90->sourcefile~maplshared.f90 sourcefile~cubedspheregeomspec_smod.f90 CubedSphereGeomSpec_smod.F90 sourcefile~cubedspheregeomspec_smod.f90->sourcefile~base.f90 sourcefile~equal_to.f90~2 equal_to.F90 sourcefile~equal_to.f90~2->sourcefile~base.f90 sourcefile~extdataroot_gridcomp.f90 ExtDataRoot_GridComp.F90 sourcefile~extdataroot_gridcomp.f90->sourcefile~maplshared.f90 sourcefile~fieldunits.f90 FieldUnits.F90 sourcefile~fieldunits.f90->sourcefile~maplshared.f90 sourcefile~make_decomposition.f90 make_decomposition.F90 sourcefile~make_decomposition.f90->sourcefile~base.f90 sourcefile~make_distribution.f90 make_distribution.F90 sourcefile~make_distribution.f90->sourcefile~base.f90 sourcefile~make_latlongeomspec_from_hconfig.f90 make_LatLonGeomSpec_from_hconfig.F90 sourcefile~make_latlongeomspec_from_hconfig.f90->sourcefile~base.f90 sourcefile~make_latlongeomspec_from_metadata.f90 make_LatLonGeomSpec_from_metadata.F90 sourcefile~make_latlongeomspec_from_metadata.f90->sourcefile~base.f90 sourcefile~mapl.f90 MAPL.F90 sourcefile~mapl.f90->sourcefile~base.f90 sourcefile~mapl_capgridcomp.f90 MAPL_CapGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~mapl_locstreammod.f90 sourcefile~mapl_generic.f90 MAPL_Generic.F90 sourcefile~mapl_generic.f90->sourcefile~mapl_locstreammod.f90 sourcefile~mapl_generic.f90->sourcefile~maplshared.f90 sourcefile~mapl_historygridcomp.f90 MAPL_HistoryGridComp.F90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_locstreammod.f90 sourcefile~mapl_nuopcwrappermod.f90 MAPL_NUOPCWrapperMod.F90 sourcefile~mapl_nuopcwrappermod.f90->sourcefile~base.f90 sourcefile~supports_hconfig.f90~2 supports_hconfig.F90 sourcefile~supports_hconfig.f90~2->sourcefile~base.f90 sourcefile~supports_metadata.f90~2 supports_metadata.F90 sourcefile~supports_metadata.f90~2->sourcefile~base.f90 sourcefile~test_cfio_bundle.pf Test_CFIO_Bundle.pf sourcefile~test_cfio_bundle.pf->sourcefile~base.f90 sourcefile~tstqsat.f90 tstqsat.F90 sourcefile~tstqsat.f90->sourcefile~base.f90 sourcefile~ut_extdata.f90 ut_ExtData.F90 sourcefile~ut_extdata.f90->sourcefile~base.f90 sourcefile~utcfio_bundle.f90 utCFIO_Bundle.F90 sourcefile~utcfio_bundle.f90->sourcefile~base.f90

Source Code

!------------------------------------------------------------------------------
!               Global Modeling and Assimilation Office (GMAO)                !
!                    Goddard Earth Observing System (GEOS)                    !
!                                 MAPL Component                              !
!------------------------------------------------------------------------------
!
#define INT_MAX 2147483647

#include "MAPL_ErrLog.h"
!
!>
!### MODULE: `MAPL_HashMod`
!
! Author: GMAO SI-Team
!
! `MAPL_HashMod`  -- A utility to manage hash tables.
! 
! `MAPL_HashMod` is a FORTRAN binding to a simple C has facility.
!
! The API is:
!```fortran
!
!   ! Create a hash table with Nbuckets
!
!       integer function MAPL_HashCreate(Nbuckets)
!         integer, intent(IN) :: Nbuckets
! 
!   ! Update table Hash with integer[s] i[,j]
!   ! The return value is the order of occurence of the integer[s].
!   ! If i is new, the return value is the new hash size.
!
!       integer function MAPL_HashIncrement(Hash,i,j)
!         integer,           intent(IN) :: Hash
!         integer,           intent(IN) :: i
!         integer, optional, intent(IN) :: j
!
!   ! Dump the list of integers or integer pairs in the hash.
!   !  The list is in no particular order.
!   ! If the arrays are not long enough, nothing is dumped and -1
!   !  is returned; otherwise it returns the current hash size 
!   !  (the length of the list).
!
!       integer function MAPL_HashDump(Hash,i,j)
!         integer,           intent(IN)  :: Hash
!         integer,           intent(OUT) :: i(:)
!         integer, optional, intent(OUT) :: j(:)
!
!   ! Get the size of a hash
!
!       integer function MAPL_HashSize(Hash)
!         integer, intent(IN) :: Hash
!
!   ! Destroy a hash table
!
!       subroutine MAPL_HashDestroy(Hash)
!         integer, intent(IN) :: Hash
!```
!
! The following is a sample usage that makes a list of
! unique integers in the large array II. It can similarly
! be used to find ordered pairs of integers. The asserts
! are put in to clarify the usage.
!
!```fortran       
!       integer :: Hash, k, II(100000), FoundOrder(10000)
!
!       Hash = MAPL_HashCreate(1000)
!
!       latest = 0
!       do i=1,100000
!         k = MAPL_HashIncrement(Hash,ii(i))
!         if(k>latest) then
!           latest   = k
!           isnew    = .true.
!           FoundOrder(k) = ii(i)
!           _ASSERT(k==MAPL_HashSize(Hash),'needs informative message')
!         else
!           isnew = .false.
!           _ASSERT(FoundOrder(k)==ii(i),'needs informative message')
!         endif
!       enddo
!```
!
module MAPL_HashMod

  use MAPL_ExceptionHandling

  implicit none
  private

! !PUBLIC ROUTINES:

  public MAPL_HashCreate
  public MAPL_HashIncrement
  public MAPL_HashDestroy
  public MAPL_HashSize
  public MAPL_HashDump

!=============================================================================

contains

integer function  MAPL_HashCreate(Nbuckets)
  integer,           intent(IN) :: Nbuckets

  integer CREATEHASH
  MAPL_HashCreate = CREATEHASH(Nbuckets)

end function MAPL_HashCreate

!----------------------------------------------

integer function MAPL_HashIncrement(Hash,i,j,k)
  integer,           intent(IN) :: Hash
  integer,           intent(IN) :: i
  integer, optional, intent(IN) :: j
  integer, optional, intent(IN) :: k

  integer :: INCREMENTHASH, rc

  if    (present(k)) then
     _ASSERT(present(j),'needs informative message')
     MAPL_HashIncrement = INCREMENTHASH(HASH,I,J,K)
  elseif(present(j)) then
     MAPL_HashIncrement = INCREMENTHASH(HASH,I,J,INT_MAX)
  else
     MAPL_HashIncrement = INCREMENTHASH(HASH,I,INT_MAX,INT_MAX)
  endif

end function MAPL_HashIncrement

!----------------------------------------------

subroutine MAPL_HashDestroy(Hash)
  integer, intent(IN) :: Hash

  call DESTROYHASH(HASH)

end subroutine MAPL_HashDestroy

!----------------------------------------------

integer function MAPL_HashDump(Hash,i,j)
  integer, intent(IN ) :: Hash
  integer, intent(OUT) :: i(:)
  integer, optional, intent(OUT) :: j(:)

  integer, allocatable :: jj(:)

  integer :: rc

  MAPL_HashDump = MAPL_HashSize(HASH)

  if(size(i) < MAPL_HashSize(HASH)) then
     MAPL_HashDump = -1
     return
  end if

  if(present(j)) then
     _ASSERT(size(i) == size(j),'needs informative message')
     call DUMPHASH(HASH,I,J)
  else
     allocate(jj(size(i)))
     call DUMPHASH(HASH,I,JJ)
     deallocate(JJ)
  end if

end function MAPL_HashDump

!----------------------------------------------

integer function  MAPL_HashSize(Hash)
  integer, intent(IN) :: Hash

  integer HASHSIZE
  MAPL_HashSize = HASHSIZE(Hash)

end function MAPL_HashSize

!----------------------------------------------

end module MAPL_HashMod