{-# LANGUAGE DataKinds #-}
{-# OPTIONS_HADDOCK hide not_home #-}
module BLAKE3.Raw where
import Data.Word
import Foreign.C.Types
import Foreign.C.String
import Foreign.Ptr
import Prelude hiding (init)
type HASHER_ALIGNMENT = 8
type HASHER_SIZE = 1912
type KEY_LEN = 32
type DEFAULT_DIGEST_LEN = 32
type BLOCK_SIZE = 64
type CHUNK_LEN = 1024
type MAX_DEPTH = 54
type MAX_SIMD_DEGREE = 16
data HasherInternal
foreign import ccall unsafe
  "blake3.h blake3_hasher_init"
  init
    :: Ptr HasherInternal
    -> IO () 
foreign import ccall unsafe
  "blake3.h blake3_hasher_init_keyed"
  init_keyed
    :: Ptr HasherInternal
    -> Ptr Word8   
    -> IO ()
foreign import ccall unsafe
  "blake3.h blake3_hasher_init_derive_key"
  init_derive_key
    :: Ptr HasherInternal
    -> CString  
    -> IO ()    
foreign import ccall unsafe
  "blake3.h blake3_hasher_update"
  update
    :: Ptr HasherInternal
    -> Ptr Word8 
    -> CSize     
    -> IO () 
foreign import ccall unsafe
  "blake3.h blake3_hasher_finalize"
  finalize
    :: Ptr HasherInternal
    -> Ptr Word8 
    -> CSize     
    -> IO () 
foreign import ccall unsafe
  "blake3.h blake3_hasher_finalize"
  finalize_seek
    :: Ptr HasherInternal
    -> Word64      
    -> Ptr Word8   
    -> CSize       
    -> IO ()