Blame src/Crypto/Hash/SHA256/FFI.hs

Packit f46cda
{-# LANGUAGE CApiFFI #-}
Packit f46cda
{-# LANGUAGE Unsafe  #-}
Packit f46cda
Packit f46cda
-- Ugly hack to workaround https://ghc.haskell.org/trac/ghc/ticket/14452
Packit f46cda
{-# OPTIONS_GHC -O0
Packit f46cda
                -fdo-lambda-eta-expansion
Packit f46cda
                -fcase-merge
Packit f46cda
                -fstrictness
Packit f46cda
                -fno-omit-interface-pragmas
Packit f46cda
                -fno-ignore-interface-pragmas #-}
Packit f46cda
Packit f46cda
{-# OPTIONS_GHC -optc-Wall -optc-O3 #-}
Packit f46cda
Packit f46cda
-- |
Packit f46cda
-- Module      : Crypto.Hash.SHA256.FFI
Packit f46cda
-- License     : BSD-3
Packit f46cda
-- Maintainer  : Herbert Valerio Riedel <hvr@gnu.org>
Packit f46cda
--
Packit f46cda
module Crypto.Hash.SHA256.FFI where
Packit f46cda
Packit f46cda
import           Data.ByteString (ByteString)
Packit f46cda
import           Data.Word
Packit f46cda
import           Foreign.C.Types
Packit f46cda
import           Foreign.Ptr
Packit f46cda
Packit f46cda
-- | SHA-256 Context
Packit f46cda
--
Packit f46cda
-- The context data is exactly 104 bytes long, however
Packit f46cda
-- the data in the context is stored in host-endianness.
Packit f46cda
--
Packit f46cda
-- The context data is made up of
Packit f46cda
--
Packit f46cda
--  * a 'Word64' representing the number of bytes already feed to hash algorithm so far,
Packit f46cda
--
Packit f46cda
--  * a 64-element 'Word8' buffer holding partial input-chunks, and finally
Packit f46cda
--
Packit f46cda
--  * a 8-element 'Word32' array holding the current work-in-progress digest-value.
Packit f46cda
--
Packit f46cda
-- Consequently, a SHA-256 digest as produced by 'hash', 'hashlazy', or 'finalize' is 32 bytes long.
Packit f46cda
newtype Ctx = Ctx ByteString
Packit f46cda
Packit f46cda
foreign import capi unsafe "hs_sha256.h hs_cryptohash_sha256_init"
Packit f46cda
    c_sha256_init :: Ptr Ctx -> IO ()
Packit f46cda
Packit f46cda
foreign import capi unsafe "hs_sha256.h hs_cryptohash_sha256_update"
Packit f46cda
    c_sha256_update_unsafe :: Ptr Ctx -> Ptr Word8 -> CSize -> IO ()
Packit f46cda
Packit f46cda
foreign import capi safe "hs_sha256.h hs_cryptohash_sha256_update"
Packit f46cda
    c_sha256_update_safe :: Ptr Ctx -> Ptr Word8 -> CSize -> IO ()
Packit f46cda
Packit f46cda
foreign import capi unsafe "hs_sha256.h hs_cryptohash_sha256_finalize"
Packit f46cda
    c_sha256_finalize_len :: Ptr Ctx -> Ptr Word8 -> IO Word64
Packit f46cda
Packit f46cda
foreign import capi unsafe "hs_sha256.h hs_cryptohash_sha256_finalize"
Packit f46cda
    c_sha256_finalize :: Ptr Ctx -> Ptr Word8 -> IO ()
Packit f46cda
Packit f46cda
foreign import capi unsafe "hs_sha256.h hs_cryptohash_sha256_hash"
Packit f46cda
    c_sha256_hash_unsafe :: Ptr Word8 -> CSize -> Ptr Word8 -> IO ()
Packit f46cda
Packit f46cda
foreign import capi safe "hs_sha256.h hs_cryptohash_sha256_hash"
Packit f46cda
    c_sha256_hash_safe :: Ptr Word8 -> CSize -> Ptr Word8 -> IO ()