module Data.Hash.SL2.Mutable ( eq , unit , concat , append, prepend , foldAppend, foldPrepend , serialize, unserialize , withNew, withCopy ) where import Prelude hiding (concat) import Foreign import Foreign.C.String import Data.ByteString (ByteString) import Data.ByteString.Unsafe import Data.Foldable (Foldable, foldlM, foldrM) import Data.Hash.SL2.Internal import Data.Hash.SL2.Unsafe import qualified Data.Hash.SL2.Internal.Imports as Imports instance Storable Hash where sizeOf = const hashSize alignment = const 0 peek p = fmap fst $ withNew $ \hp -> copyBytes hp (castPtr p) hashSize poke p h = unsafeUseAsPtr h $ \hp -> copyBytes (castPtr p) hp hashSize -- | /O(1)/ Compare the two hashes for equality. eq :: Ptr Hash -> Ptr Hash -> IO Bool eq a b = fmap toBool $ Imports.eq a b -- | /O(1)/ Set the 'Hash' to the empty value. unit :: Ptr Hash -> IO () unit h = Imports.unit h -- | /O(1)/ Concatenate the second and third 'Hash', store the result in the first. concat :: Ptr Hash -> Ptr Hash -> Ptr Hash -> IO () concat c a b = Imports.concat c a b -- | /O(n)/ Append the hash of the 'ByteString' to the existing 'Hash'. append :: ByteString -> Ptr Hash -> IO () append s p = unsafeUseAsCStringLen s $ \(s', len) -> Imports.append (castPtr p) s' (fromIntegral len) -- | /O(n)/ Prepend the hash of the 'ByteString' to the existing 'Hash'. prepend :: ByteString -> Ptr Hash -> IO () prepend s p = unsafeUseAsCStringLen s $ \(s', len) -> Imports.prepend (castPtr p) s' (fromIntegral len) -- | /O(n)/ Append the hash of every 'ByteString' to the existing 'Hash', from left to right. foldAppend :: Foldable t => t ByteString -> Ptr Hash -> IO () foldAppend ss p = foldlM (const $ flip append p) () ss -- | /O(n)/ Prepend the hash of every 'ByteString' to the existing 'Hash', from right to left. foldPrepend :: Foldable t => t ByteString -> Ptr Hash -> IO () foldPrepend ss p = foldrM (const . flip prepend p) () ss -- | /O(1)/ Serialize the hash into a url-safe base64 representation. serialize :: Ptr Hash -> IO String serialize h = allocaBytes hashLen $ \p -> Imports.serialize h p >> peekCStringLen (p, hashLen) -- | /O(1)/ Unserialize the hash from the representation generated by 'serialize'. unserialize :: String -> Ptr Hash -> IO (Maybe ()) unserialize s p = withCAStringLen s $ \(s', len) -> if len == hashLen then Just `fmap` Imports.unserialize p s' else return Nothing withNew :: (Ptr Hash -> IO a) -> IO (Hash, a) withNew f = mallocForeignPtrBytes hashSize >>= \fp -> (\r -> (H fp, r)) `fmap` withForeignPtr fp (f . castPtr) withCopy :: Hash -> (Ptr Hash -> IO a) -> IO (Hash, a) withCopy h f = withNew $ \p -> poke p h >> f p