module Data.Byteable
( Byteable(..)
, constEqBytes
) where
import Foreign.Ptr (Ptr, plusPtr)
import Foreign.ForeignPtr (withForeignPtr)
import Data.ByteString (ByteString)
import Data.List (foldl')
import Data.Word (Word8)
import qualified Data.ByteString as B (length, zipWith)
import qualified Data.ByteString.Internal as B (toForeignPtr)
class Byteable a where
toBytes :: a -> ByteString
byteableLength :: a -> Int
byteableLength = B.length . toBytes
withBytePtr :: a -> (Ptr Word8 -> IO b) -> IO b
withBytePtr a f = withForeignPtr fptr $ \ptr -> f (ptr `plusPtr` off)
where (fptr, off, _) = B.toForeignPtr $ toBytes a
instance Byteable ByteString where
toBytes bs = bs
constEqBytes :: Byteable a => a -> a -> Bool
constEqBytes a b = constEqByteString (toBytes a) (toBytes b)
constEqByteString :: ByteString -> ByteString -> Bool
constEqByteString a b
| len /= B.length b = False
| otherwise = foldl' (&&!) True $ B.zipWith (==) a b
where len = B.length a
(&&!) :: Bool -> Bool -> Bool
True &&! True = True
True &&! False = False
False &&! True = False
False &&! False = False