{-# LINE 1 "Data/Digest/CRC32.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, FlexibleInstances #-}
{-# LINE 2 "Data/Digest/CRC32.hsc" #-}
------------------------------------------------------------
-- |
-- Copyright    :   (c) 2008 Eugene Kirpichov
-- License      :   BSD-style
--
-- Maintainer   :   ekirpichov@gmail.com
-- Stability    :   experimental
-- Portability  :   portable (H98 + FFI)
--
-- CRC32 wrapper
--
------------------------------------------------------------

module Data.Digest.CRC32 (
    CRC32, crc32
) where

import Foreign
import Foreign.C.Types
import Foreign.ForeignPtr
import GHC.Ptr

import qualified Data.ByteString as S
import qualified Data.ByteString.Internal as BI
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Internal as LI


{-# LINE 30 "Data/Digest/CRC32.hsc" #-}

-- | The class of values for which CRC32 may be computed
class CRC32 a where
    -- | Compute CRC32 checksum
    crc32 :: a -> Word32

instance CRC32 S.ByteString where
    crc32 = crc32_s

instance CRC32 L.ByteString where
    crc32 = crc32_l

instance CRC32 [Word8] where
    crc32 = crc32 . L.pack


crc32_s :: S.ByteString -> Word32
crc32_s s = crc32_l (LI.Chunk s LI.Empty)

crc32_l :: L.ByteString -> Word32
crc32_l = LI.foldlChunks updateCRC 0 
    where updateCRC crc bs = fromIntegral $ crc32_c (fromIntegral crc) buf (fromIntegral len)
              where (ptr, offset, len) = BI.toForeignPtr bs
                    buf = (unsafeForeignPtrToPtr ptr) `plusPtr` offset

foreign import ccall unsafe "zlib.h crc32"
    crc32_c :: CInt -> Ptr Word8 -> CInt -> CInt -- crc, buf, len -> crc'