module Data.Digest.XXHash.FFI (
XXHash(..)
) where
import Data.Digest.XXHash.FFI.C
import Data.ByteString.Unsafe (unsafeUseAsCStringLen)
import Data.Word (Word32, Word64)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL
import Foreign.C
import GHC.Exts (realWorld#)
import GHC.IO (IO(IO))
import System.IO.Unsafe (unsafePerformIO)
inlinePerformIO :: IO a -> a
inlinePerformIO (IO m) = case m realWorld# of (# _, r #) -> r
use :: BS.ByteString -> (CString -> CSize -> IO a) -> IO a
use bs k = unsafeUseAsCStringLen bs $ \(ptr,len) -> k ptr (fromIntegral len)
class XXHash t where
xxh32 :: t
-> Word32
-> Word32
xxh64 :: t
-> Word64
-> Word64
instance XXHash BS.ByteString where
xxh32 bs seed = fromIntegral . inlinePerformIO . use bs $
\ptr len -> c_xxh32 ptr len (fromIntegral seed)
xxh64 bs seed = fromIntegral . inlinePerformIO . use bs $
\ptr len -> c_xxh64 ptr len (fromIntegral seed)
instance XXHash BL.ByteString where
xxh32 bs seed = fromIntegral . unsafePerformIO $
allocaXXH32State $ \state -> do
c_xxh32_reset state (fromIntegral seed)
mapM_ (update state) (BL.toChunks bs)
c_xxh32_digest state
where
update state bs' = use bs' $ c_xxh32_update state
xxh64 bs seed = fromIntegral . unsafePerformIO $
allocaXXH64State $ \state -> do
c_xxh64_reset state (fromIntegral seed)
mapM_ (update state) (BL.toChunks bs)
c_xxh64_digest state
where
update state bs' = use bs' $ c_xxh64_update state