{-# LANGUAGE CPP, ForeignFunctionInterface #-} -- Private interface to a C implementation of SHA 256. Originally based on code -- by Zooko O'Whielacronx, but rewritten since. Therefore, BSD applies, as for -- the rest of hashed-storage. module Bundled.SHA256 ( sha256 ) where import Foreign import Foreign.C.Types import Data.ByteString.Unsafe (unsafeUseAsCStringLen) import qualified Data.ByteString.Internal as BSI sha256 :: BSI.ByteString -> BSI.ByteString sha256 p = unsafePerformIO $ do digest <- BSI.create 32 $ \digest -> unsafeUseAsCStringLen p $ \(ptr,n) -> c_sha256 ptr (fromIntegral n) digest return $! digest -- void sha256sum(const unsigned char *d, size_t n, unsigned char *md); foreign import ccall unsafe "sha2.h hashed_storage_sha256" c_sha256 :: Ptr CChar -> CSize -> Ptr Word8 -> IO ()