stdlib_hash_64bit_fnv.fypp 源文件

FNV_1_HASHFNV_1A_HASH 是 Glenn Fowler、Landon Curt Noll 和 Phong Vo 的 FNV-1FNV-1a 哈希函数的 Fortran 2008 翻译版本,该函数已发布到公共领域。 Landon Curt Noll 已授权在 Fortran 标准库中使用这些算法。 这些函数的描述可以在 https://en.wikipedia.org/wiki/Fowler–Noll–Vo_hash_function 找到。 这些函数已从其标准形式修改,以在哈希中也编码结构的大小。




源代码

!!------------------------------------------------------------------------------
!! `FNV_1_HASH` and  `FNV_1A_HASH` are translations to Fortran 2008 of the
!! `FNV-1` and `FNV-1a` hash functions of Glenn Fowler, Landon Curt Noll,
!! and Phong Vo, that has been released into the public domain. Permission
!! has been granted, by Landon Curt Noll, for the use of these algorithms
!! in the Fortran Standard Library. A description of these functions is
!! available at https://en.wikipedia.org/wiki/Fowler–Noll–Vo_hash_function.
!! The functions have been modified from their normal form to also encode
!! the size of the structure in the hash.
!!------------------------------------------------------------------------------

#! Integer kinds to be considered during templating
#:set INT_KINDS = ["int16", "int32", "int64"]

submodule(stdlib_hash_64bit) stdlib_hash_64bit_fnv
! An implementation of the FNV hashes 1 and 1a of Glenn Fowler, Landon Curt
! Noll, and Kiem-Phong-Vo,
! https://en.wikipedia.org/wiki/Fowler–Noll–Vo_hash_function
    implicit none

    integer(int_hash), parameter ::                          &
        offset_basis = int( z'CBF29CE484222325', int_hash ), &
        prime        = int( z'100000001B3', int_hash )

contains

    pure module function int8_fnv_1( key ) result(hash_code)
        integer(int8), intent(in)     :: key(:)
        integer(int_hash)             :: hash_code

        integer(int64) :: i

        hash_code = offset_basis
        do i=1_int64, size(key, kind=int64)
            hash_code = hash_code * prime
            if ( little_endian ) then
                hash_code = ieor( hash_code, &
                                  transfer( [key(i), 0_int8, 0_int8, 0_int8,  &
                                             0_int8, 0_int8, 0_int8, 0_int8], &
                                            0_int_hash ) )
            else
                hash_code = ieor( hash_code, &
                                  transfer( [0_int8, 0_int8, 0_int8, 0_int8,  &
                                             0_int8, 0_int8, 0_int8, key(i)], &
                                            0_int_hash ) )
            end if
        end do

    end function int8_fnv_1


#:for k1 in INT_KINDS
    pure module function ${k1}$_fnv_1( key ) result(hash_code)
        integer(${k1}$), intent(in)   :: key(:)
        integer(int_hash)             :: hash_code

        hash_code = int8_fnv_1( transfer( key, 0_int8,                      &
                                          bytes_${k1}$*                     &
                                          size( key, kind=int64 ) ) )

    end function ${k1}$_fnv_1

#:endfor

    elemental module function character_fnv_1( key ) result(hash_code)
        character(*), intent(in)      :: key
        integer(int_hash)             :: hash_code

        hash_code = int8_fnv_1( transfer( key,                           &
                                          0_int8,                        &
                                          bytes_char*                    &
                                          len(key, kind=int64) ) )

    end function character_fnv_1


    pure module function int8_fnv_1a( key ) result(hash_code)
        integer(int8), intent(in)     :: key(:)
        integer(int_hash)             :: hash_code

        integer(int64) :: i

        hash_code = offset_basis
        do i=1_int64, size(key, kind=int64)
            if ( little_endian ) then
                hash_code = ieor( hash_code, &
                                  transfer( [key(i), 0_int8, 0_int8, 0_int8,  &
                                             0_int8, 0_int8, 0_int8, 0_int8], &
                                            0_int_hash ) )
            else
                hash_code = ieor( hash_code, &
                                  transfer( [0_int8, 0_int8, 0_int8, 0_int8,  &
                                             0_int8, 0_int8, 0_int8, key(i)], &
                                            0_int_hash ) )
            end if
            hash_code = hash_code * prime
        end do

    end function int8_fnv_1a


#:for k1 in INT_KINDS
    pure module function ${k1}$_fnv_1a( key ) result(hash_code)
        integer(${k1}$), intent(in)   :: key(:)
        integer(int_hash)             :: hash_code

        hash_code = int8_fnv_1a( transfer( key, 0_int8,                   &
                                           bytes_${k1}$*                  &
                                           size(key, kind=int64)))

    end function ${k1}$_fnv_1a

#:endfor

    elemental module function character_fnv_1a( key ) result(hash_code)
        character(*), intent(in)      :: key
        integer(int_hash)             :: hash_code

        hash_code = int8_fnv_1a( transfer( key, 0_int8,                   &
                                           (bits_char/bits_int8)*         &
                                           len(key, kind=int64) ) )

    end function character_fnv_1a

end submodule stdlib_hash_64bit_fnv