never executed always true always false
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE MagicHash #-}
3
4 module XXH3 (
5 -- * One shot
6 xxh3_64bit_withSeed_bs,
7 xxh3_64bit_withSeed_ba,
8 xxh3_64bit_withSeed_w64,
9 xxh3_64bit_withSeed_w32,
10 -- * Incremental
11 XXH3_State,
12 xxh3_64bit_createState,
13 xxh3_64bit_reset_withSeed,
14 xxh3_64bit_digest,
15 xxh3_64bit_update_bs,
16 xxh3_64bit_update_ba,
17 xxh3_64bit_update_w64,
18 xxh3_64bit_update_w32,
19 ) where
20
21 import Control.Monad (unless)
22 import Control.Monad.ST (ST)
23 import Control.Monad.ST.Unsafe (unsafeIOToST)
24 import Data.ByteString.Internal (ByteString (..),
25 accursedUnutterablePerformIO)
26 import Data.Coerce (coerce)
27 import qualified Data.Primitive as P
28 import Data.Primitive.ByteArray (ByteArray (..))
29 import Data.Word (Word32, Word64)
30 import Foreign.ForeignPtr
31 import GHC.Exts (MutableByteArray#)
32 import GHC.ForeignPtr
33
34 import FFI
35
36 {-# INLINE withFP #-}
37 withFP :: ForeignPtr a -> (P.Ptr a -> IO b) -> IO b
38 #if MIN_VERSION_GLASGOW_HASKELL(9,0,0,0)
39 withFP = unsafeWithForeignPtr
40 #else
41 withFP = withForeignPtr
42 #endif
43
44 -------------------------------------------------------------------------------
45 -- OneShot
46 -------------------------------------------------------------------------------
47
48 -- | Hash 'ByteString'.
49 xxh3_64bit_withSeed_bs :: ByteString -> Word64 -> Word64
50 xxh3_64bit_withSeed_bs (BS fptr len) !salt = accursedUnutterablePerformIO $
51 withFP fptr $ \ptr ->
52 unsafe_xxh3_64bit_withSeed_ptr ptr (fromIntegral len) salt
53
54 -- | Hash (part of) 'ByteArray'.
55 xxh3_64bit_withSeed_ba :: ByteArray -> Int -> Int -> Word64 -> Word64
56 xxh3_64bit_withSeed_ba (ByteArray ba) !off !len !salt =
57 unsafe_xxh3_64bit_withSeed_ba ba (fromIntegral off) (fromIntegral len) salt
58
59 -- | Hash 'Word64'.
60 xxh3_64bit_withSeed_w64 :: Word64 -> Word64 -> Word64
61 xxh3_64bit_withSeed_w64 !x !salt =
62 unsafe_xxh3_64bit_withSeed_u64 x salt
63
64 -- | Hash 'Word32'.
65 xxh3_64bit_withSeed_w32 :: Word32 -> Word64 -> Word64
66 xxh3_64bit_withSeed_w32 !x !salt =
67 unsafe_xxh3_64bit_withSeed_u32 x salt
68
69 -------------------------------------------------------------------------------
70 -- Incremental
71 -------------------------------------------------------------------------------
72
73 -- | Mutable XXH3 state.
74 data XXH3_State s = XXH3 (MutableByteArray# s)
75
76 -- | Create 'XXH3_State'.
77 xxh3_64bit_createState :: forall s. ST s (XXH3_State s)
78 xxh3_64bit_createState = do
79 -- aligned alloc, otherwise we get segfaults.
80 -- see XXH3_createState implementation
81 P.MutableByteArray ba <- P.newAlignedPinnedByteArray unsafe_xxh3_sizeof_state 64
82 unsafeIOToST (unsafe_xxh3_initState ba)
83 return (XXH3 ba)
84
85 -- | Reset 'XXH3_State' with a seed.
86 xxh3_64bit_reset_withSeed :: XXH3_State s -> Word64 -> ST s ()
87 xxh3_64bit_reset_withSeed (XXH3 s) seed = do
88 unsafeIOToST (unsafe_xxh3_64bit_reset_withSeed s seed)
89
90 -- | Return a hash value from a 'XXH3_State'.
91 --
92 -- Doesn't mutate given state, so you can update, digest and update again.
93 xxh3_64bit_digest :: XXH3_State s -> ST s Word64
94 xxh3_64bit_digest (XXH3 s) =
95 unsafeIOToST (unsafe_xxh3_64bit_digest s)
96
97 -- | Update 'XXH3_State' with 'ByteString'.
98 xxh3_64bit_update_bs :: XXH3_State s -> ByteString -> ST s ()
99 xxh3_64bit_update_bs (XXH3 s) (BS fptr len) = unsafeIOToST $
100 withFP fptr $ \ptr ->
101 unsafe_xxh3_64bit_update_ptr s ptr (fromIntegral len)
102
103 -- | Update 'XXH3_State' with (part of) 'ByteArray'
104 xxh3_64bit_update_ba :: XXH3_State s -> ByteArray -> Int -> Int -> ST s ()
105 xxh3_64bit_update_ba (XXH3 s) (ByteArray ba) !off !len = unsafeIOToST $
106 unsafe_xxh3_64bit_update_ba s ba (fromIntegral off) (fromIntegral len)
107
108 -- | Update 'XXH3_State' with 'Word64'.
109 xxh3_64bit_update_w64 :: XXH3_State s -> Word64 -> ST s ()
110 xxh3_64bit_update_w64 (XXH3 s) w64 = unsafeIOToST $
111 unsafe_xxh3_64bit_update_u64 s w64
112
113 -- | Update 'XXH3_State' with 'Word32'.
114 xxh3_64bit_update_w32 :: XXH3_State s -> Word32 -> ST s ()
115 xxh3_64bit_update_w32 (XXH3 s) w32 = unsafeIOToST $
116 unsafe_xxh3_64bit_update_u32 s w32