{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE Unsafe #-}
{-# OPTIONS_GHC -O0
-fdo-lambda-eta-expansion
-fcase-merge
-fstrictness
-fno-omit-interface-pragmas
-fno-ignore-interface-pragmas #-}
{-# OPTIONS_GHC -optc-Wall -optc-O3 #-}
module Crypto.Hash.SHA256.FFI where
import Data.ByteString (ByteString)
import Data.Word
import Foreign.C.Types
import Foreign.Ptr
newtype Ctx = Ctx ByteString
deriving (Ctx -> Ctx -> Bool
(Ctx -> Ctx -> Bool) -> (Ctx -> Ctx -> Bool) -> Eq Ctx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ctx -> Ctx -> Bool
$c/= :: Ctx -> Ctx -> Bool
== :: Ctx -> Ctx -> Bool
$c== :: Ctx -> Ctx -> Bool
Eq)
foreign import capi unsafe "hs_sha256.h hs_cryptohash_sha256_init"
c_sha256_init :: Ptr Ctx -> IO ()
foreign import capi unsafe "hs_sha256.h hs_cryptohash_sha256_update"
c_sha256_update_unsafe :: Ptr Ctx -> Ptr Word8 -> CSize -> IO ()
foreign import capi safe "hs_sha256.h hs_cryptohash_sha256_update"
c_sha256_update_safe :: Ptr Ctx -> Ptr Word8 -> CSize -> IO ()
foreign import capi unsafe "hs_sha256.h hs_cryptohash_sha256_finalize"
c_sha256_finalize_len :: Ptr Ctx -> Ptr Word8 -> IO Word64
foreign import capi unsafe "hs_sha256.h hs_cryptohash_sha256_finalize"
c_sha256_finalize :: Ptr Ctx -> Ptr Word8 -> IO ()
foreign import capi unsafe "hs_sha256.h hs_cryptohash_sha256_hash"
c_sha256_hash_unsafe :: Ptr Word8 -> CSize -> Ptr Word8 -> IO ()
foreign import capi safe "hs_sha256.h hs_cryptohash_sha256_hash"
c_sha256_hash_safe :: Ptr Word8 -> CSize -> Ptr Word8 -> IO ()