-- | 32-bit FNV-1a (Fowler-Noll-Vo) hash {-# LANGUAGE CPP #-} module Data.Generics.Fixplate.Util.Hash.FNV.FNV32 ( FNV32(..) , unFNV32 ) where -------------------------------------------------------------------------------- import Data.Char import Data.Word import Data.Bits -- import Data.Int -- import Data.List import Data.Generics.Fixplate.Util.Hash.Class -------------------------------------------------------------------------------- newtype FNV32 = FNV32 Word32 deriving (Eq,Ord,Show) unFNV32 :: FNV32 -> Word32 unFNV32 (FNV32 x) = x instance Hashable FNV32 where hashDigest (FNV32 w) = hashDigest w instance HashValue FNV32 where emptyHash = FNV32 fnv32_offset hashHash (FNV32 w) = hashWord32 w showHex (FNV32 w) = showHex32 w hashWord8 x (FNV32 w) = FNV32 (fnv32_octet x w) hashWord16 x (FNV32 w) = FNV32 (fnv32_word16 x w) hashWord32 x (FNV32 w) = FNV32 (fnv32_word32 x w) hashWord64 x (FNV32 w) = FNV32 (fnv32_word64 x w) -------------------------------------------------------------------------------- showHex32 :: Word32 -> String showHex32 h = reverse $ worker 8 h where worker :: Int -> Word32 -> String worker 0 0 = [] worker 0 _ = error "Hash/FNV32/showHex: shouldn't happen" worker i w = hexdigit (w .&. 15) : worker (i-1) (shiftR w 4) hexdigit :: Word32 -> Char hexdigit n | k>=0 && k<=9 = chr (k+48) | otherwise = chr (k+55) where k = fromIntegral n -------------------------------------------------------------------------------- -- FNV-1a hash fnv32_prime, fnv32_offset :: Word32 fnv32_prime = 16777619 fnv32_offset = 2166136261 fnv32_octet :: Word8 -> Word32 -> Word32 fnv32_octet octet old = fnv32_prime * (old `xor` fromIntegral octet) -------------------------------------------------------------------------------- -- 32 bit fnv32_word32 :: Word32 -> Word32 -> Word32 fnv32_word32 w = fnv32_octet a . fnv32_octet b . fnv32_octet c . fnv32_octet d where a = fromIntegral (255 .&. ( w )) b = fromIntegral (255 .&. (shiftR w 8)) c = fromIntegral (255 .&. (shiftR w 16)) d = fromIntegral (255 .&. (shiftR w 24)) {- fnv32_word24 :: Word32 -> Word32 -> Word32 fnv32_word24 w = fnv32_octet a . fnv32_octet b . fnv32_octet c where a = fromIntegral (255 .&. ( w )) b = fromIntegral (255 .&. (shiftR w 8)) c = fromIntegral (255 .&. (shiftR w 16)) -} fnv32_word16 :: Word16 -> Word32 -> Word32 fnv32_word16 w = fnv32_octet a . fnv32_octet b where a = fromIntegral (255 .&. ( w )) b = fromIntegral (255 .&. (shiftR w 8)) fnv32_word64 :: Word64 -> Word32 -> Word32 fnv32_word64 w = fnv32_word32 a . fnv32_word32 b where a = fromIntegral (0xffffffff .&. ( w )) b = fromIntegral (0xffffffff .&. (shiftR w 32)) --------------------------------------------------------------------------------