{-# LINE 1 "Data/Digest/CRC32.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, FlexibleInstances #-}
module Data.Digest.CRC32 (
CRC32, crc32, crc32Update
) where
import Data.ByteString.Unsafe (unsafeUseAsCStringLen)
import Foreign
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Internal as LI
import qualified System.IO.Unsafe as U
class CRC32 a where
crc32 :: a -> Word32
crc32 = crc32Update 0
crc32Update :: Word32 -> a -> Word32
instance CRC32 S.ByteString where
crc32Update = crc32_s_update
instance CRC32 L.ByteString where
crc32Update = crc32_l_update
instance CRC32 [Word8] where
crc32Update n = (crc32Update n) . L.pack
crc32_s_update :: Word32 -> S.ByteString -> Word32
crc32_s_update seed str
| S.null str = seed
| otherwise =
U.unsafePerformIO $
unsafeUseAsCStringLen str $
\(buf, len) -> fmap fromIntegral $
crc32_c (fromIntegral seed) (castPtr buf) (fromIntegral len)
crc32_l_update :: Word32 -> L.ByteString -> Word32
crc32_l_update = LI.foldlChunks crc32_s_update
foreign import ccall unsafe "zlib.h crc32"
crc32_c :: Word64
{-# LINE 65 "Data/Digest/CRC32.hsc" #-}
-> Ptr Word8
{-# LINE 66 "Data/Digest/CRC32.hsc" #-}
-> Word32
{-# LINE 67 "Data/Digest/CRC32.hsc" #-}
-> IO Word64
{-# LINE 68 "Data/Digest/CRC32.hsc" #-}