M_hashkeys Module

use,intrinsic :: iso_c_binding, only : c_int32_t



Variables

Type Visibility Attributes Name Initial
integer, public, parameter :: int128 = selected_real_kind(1*precision(1.0_int64))

integer,parameter :: int128 = selected_real_kind(2*precision(1.0_int64))


Interfaces

public interface crc32_hash

  • private function crc32_hash_arr(anything, continue) result(crc_64)

    NAME

    crc32_hash(3f) - [M_hashkeys] CRC (Cyclic Redundancy Check)
    (LICENSE:PD)
    

    SYNOPSIS

    function crc32_hash(a,continue) result (crc)

    class(*),intent(in)          :: anything(:)
    logical,intent(in),optional  :: continue
    integer(int64)               :: crc_out
    

    DESCRIPTION

    This ia 32-bit version of the Cyclic Redundancy Check(CRC).
    This variant of CRC-32 uses LSB-first order, sets the initial CRC to
    FFFFFFFF_int32, and complements the final CRC.
    
    The result should be in accordance with ISO 3309, ITU-T V.42, Gzip
    and PNG.
    

    OPTIONS

    anything  input value to generate a CRC check for. May be a array
              or scalar of numeric or string values of type CHARACTER,
              int8, int16, int32, int64, real32, real64, real128
    continue  optional parameter. If not present or .F. starts new
              CRC sum. If .T. continues a CRC starting with last CRC
              calculated.
    

    RETURNS

    crc       The calculated CRC sum. It is calculated as a 32-bit value
              but returned as a 64-bit value, as Fortran does not
              currently support unsigned integers.
    

    REFERENCES

    Algorithms are described in "Computation of CRC" in Wikipedia.
    Also see
    
       https://en.wikipedia.org/wiki/Cyclic_redundancy_check
    

    AUTHOR

    This was derived from an unattributed example on http://rosettacode.org,
    but has been modified.
    

    EXAMPLE

    Sample program:

    program demo_crc32_hash
    use,intrinsic :: ISO_FORTRAN_ENV, only : int64
    use M_hashkeys, only : crc32_hash
    implicit none
    integer :: i
    integer(int64) :: crc
    character(*), parameter :: s = "The quick brown fox jumps over the lazy dog"
       ! string
       crc=crc32_hash(s)
       print "(Z8)", crc
       print "(i0)", crc
       ! character array
       print "(i0)", crc32_hash([ &
               & 'T','h','e',' ',&
               & 'q','u','i','c','k',' ',&
               & 'b','r','o','w','n',' ',&
               & 'f','o','x',' '])
       print "(i0)", crc32_hash([ &
               & 'j','u','m','p','s',' ',&
               & 'o','v','e','r',' ',&
               & 't','h','e',' ',&
               & 'l','a','z','y',' ',&
               & 'd','o','g'],continue=.true.)
       ! numeric array
       print "(i0)", crc32_hash([(i,i=1,100)])
    end program demo_crc32_hash
    

    Expected output:

    414FA339
    1095738169
    2293265890
    1095738169
    1783575711
    

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in) :: anything(:)
    logical, intent(in), optional :: continue

    Return Value integer(kind=int64)

  • private function crc32_hash_scalar(anything, continue) result(hash_64)

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in) :: anything
    logical, intent(in), optional :: continue

    Return Value integer(kind=int64)

public interface djb2_hash

  • private function djb2_hash_arr(anything, continue) result(hash_128)

    NAME

    djb2_hash(3f) - [M_hashkeys:bucket_hash] djb2 string hash (algorithm by Daniel J. Bernstein)
    (LICENSE:PD)
    

    SYNOPSIS

    function djb2_hash_arr(anything,continue) result(hash_128)
    
     class(*),intent(in)          :: anything(:)
     logical,intent(in),optional  :: continue
     !! use,intrinsic : ISO_FORTRAN_ENV, only : int64
     integer(kind=int128)         :: hash_128
    

    DESCRIPTION

     djb2_hash(3f) is based on the string hash routine commonly known as
     djb2(3c). This algorithm was first described by Dan J. Bernstein many
     years ago in comp.lang.c. This version returns a value calculated
     using a 64-bit hash, which is returned as a 128bit value (not always
     available in Fortran) to allow the value to always be a positive
     value; as Fortran does not (currently) support a standard unsigned
     integer. If the value is changed to be a 64-bit value on platforms
     that do not support 128-bit INTEGER values the value may be negative,
     but is otherwise usable.
    
     Such non-reversible hashes may be used for data or file fingerprints,
     to confirm unchanging results during regression testing, ...
    
     More information is widely available on string hashes (including the
     well-known djb2(3c) algorithm) on such sources as Wikipedia. Consult
     such resources to confirm the suitability of this algorithm for your
     use. This algorithm was probably first proposed as a bucket hash.
    
     The algorithm does not consider the Endian of the programming
     environment.
    

    OPTIONS

     STR    May be a CHARACTER string or an array of common intrinsic
            types. Currently, the types defined in the procedure
            are character(len=*); complex; integer(kind=int8);
            integer(kind=int16); integer(kind=int32); integer(kind=int64);
            integer(kind=int128); real(kind=real32); real(kind=real64);
            real(kind=real128).
    
     CONTINUE   indicate whether to continue accumulating the hash value
                from the last call. This is not threadsafe. This allows
                for continued hashes so that a hash can be calculated for
                a series of calls.
    

    RETURNS

     djb2_hash   A 128-bit INTEGER hash value for the (possibly accumulated) data.
    

    EXAMPLE

    Sample program:
    
     program demo_djb2_hash
     use M_hashkeys, only : djb2_hash, int128
     implicit none
     integer(kind=int128)         :: hash
     character(len=:),allocatable :: string
     integer                      :: i
     ! string
     string='test djb2_hash'
     hash=djb2_hash(string)
     write(*,*)'string=',string,' hash=',hash
     ! array of characters
     hash=djb2_hash(['t','e','s','t',' ','d','j','b','2','_','h','a','s','h'])
     write(*,*)'string=',string,' hash=',hash
     ! continued hash
     hash=djb2_hash(['t','e','s','t'])
     hash=djb2_hash([' ','d','j','b','2'],continue=.true.)
     hash=djb2_hash(['_','h','a','s','h'],continue=.true.)
     write(*,*)'string=',string,' hash=',hash
     ! array of integers
     hash=djb2_hash([(i,i=0,100)])
     write(*,*)'hash for values 0 to 100 is ',hash
     !
     end program demo_djb2_hash
    

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in) :: anything(:)
    logical, intent(in), optional :: continue

    Return Value integer(kind=int128)

  • private function djb2_hash_scalar(anything, continue) result(hash_128)

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in) :: anything
    logical, intent(in), optional :: continue

    Return Value integer(kind=int128)

public interface sdbm_hash

  • private function sdbm_hash_arr(anything, continue) result(hash_128)

    NAME

    sdbm_hash(3f) - [M_hashkeys:bucket_hash] sdbm string hash
    (LICENSE:PD)
    

    SYNOPSIS

    use,intrinsic : ISO_FORTRAN_ENV, only : int64
    function sdbm_hash_arr(anything,continue) result(hash_128)
    
     class(*),intent(in)          :: anything(:)
     logical,intent(in),optional  :: continue
     integer(kind=int128)         :: hash_128
    

    DESCRIPTION

    sdbm_hash(3f) is based on the string hash routine commonly known as
    sdbm(3c).
    
    this algorithm was created for the sdbm (a public-domain
    reimplementation of ndbm) database library. It was found to do well
    in scrambling bits, causing good distribution of the keys and fewer
    splits. it also happens to be a good general hashing function with
    good distribution. the actual function is
    
       hash(i) = hash(i - 1) * 65599 + str[i]
    
    what is available here is the faster version used
    in gawk. [there is even a faster, duff-device version]. The magic
    constant 65599 was picked out of thin air while experimenting with
    different constants, and turns out to be a prime. this is one of the
    algorithms used in berkeley db (see sleepycat) and elsewhere.
    
    This version returns a value calculated using a 64-bit hash, which
    is returned as a 128bit value (not always available in Fortran) to
    allow the value to always be a positive value; as Fortran does not
    (currently) support a standard unsigned integer. If the value is
    changed to be a 64-bit value on platforms that do not support 128-bit
    INTEGER values the value may be negative, but is otherwise usable.
    
    Such non-reversible hashes may be used for data or file fingerprints,
    to confirm unchanging results during regression testing, ...
    
    More information is widely available on string hashes (including the
    well-known sdbm(3c) algorithm) on such sources as Wikipedia. Consult
    such resources to confirm the suitability of this algorithm for
    your use.
    
    The algorithm does not consider the Endian of the programming
    environment.
    

    OPTIONS

     STR    May be a CHARACTER string or an array of common intrinsic
            types. Currently, the types defined in the procedure
            are character(len=*); complex; integer(kind=int8);
            integer(kind=int16); integer(kind=int32); integer(kind=int64);
            integer(kind=int128); real(kind=real32); real(kind=real64);
            real(kind=real128).
    
     CONTINUE   indicate whether to continue accumulating the hash value
                from the last call. This is not threadsafe. This allows
                for continued hashes so that a hash can be calculated for
                a series of calls.
    

    RETURNS

     sdbm_hash   A 128-bit INTEGER hash value for the (possibly accumulated) data.
    

    EXAMPLE

    Sample program:
    
     program demo_sdbm_hash
     use M_hashkeys, only : sdbm_hash, int128
     implicit none
     integer(kind=int128)         :: hash
     character(len=:),allocatable :: string
     integer                      :: i
     ! string
     string='test sdbm_hash'
     hash=sdbm_hash(string)
     write(*,*)'string=',string,' hash=',hash
     ! array of characters
     hash=sdbm_hash(['t','e','s','t',' ','s','d','b','m','_','h','a','s','h'])
     write(*,*)'string=',string,' hash=',hash
     ! continued hash
     hash=sdbm_hash(['t','e','s','t'])
     hash=sdbm_hash([' ','s','d','b','m'],continue=.true.)
     hash=sdbm_hash(['_','h','a','s','h'],continue=.true.)
     write(*,*)'string=',string,' hash=',hash
     ! array of integers
     hash=sdbm_hash([(i,i=0,100)])
     write(*,*)'hash for values 0 to 100 is ',hash
     !
     end program demo_sdbm_hash
    

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in) :: anything(:)
    logical, intent(in), optional :: continue

    Return Value integer(kind=int128)

  • private function sdbm_hash_scalar(anything, continue) result(hash_128)

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in) :: anything
    logical, intent(in), optional :: continue

    Return Value integer(kind=int128)


Functions

public function b3hs_hash_key_jenkins(key, range) result(code)

b3hs_hash_key_jenkins(3f) - [M_hashkeys] hash key algorithm by Bob Jenkins (LICENSE:PD)

Read more…

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: key
integer, intent(in) :: range

Return Value integer

public function dirty_sha256(str)

function dirtys_sha256(str)

Read more…

Arguments

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

Return Value character(len=64)

public function djb2(anything)

Arguments

Type IntentOptional Attributes Name
class(*), intent(in) :: anything(:)

Return Value integer(kind=int128)

public function luhn_checksum(string)

Sample program

Read more…

Arguments

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

Return Value character(len=:), allocatable

public function sha256(str)

function sha256(str)

Read more…

Arguments

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

Return Value character(len=64)


Subroutines

public subroutine test_suite_M_hashkeys()

Arguments

None

public subroutine test_suite_sha256()

Arguments

None