blake3-0.3: BLAKE3 hashing algorithm
Safe HaskellSafe-Inferred
LanguageHaskell2010

BLAKE3.IO

Description

IO and low level tools.

Synopsis

Hashing

hash Source #

Arguments

:: forall len digest bin. (ByteArrayN len digest, ByteArrayAccess bin) 
=> Maybe Key

Whether to use keyed hashing mode (for MAC, PRF).

-> [bin]

Data to hash.

-> IO digest

The digest type could be Digest len.

BLAKE3 hashing.

init Source #

Arguments

:: Ptr Hasher

Obtain with alloc or similar. It will be mutated.

-> Maybe Key

Whether to use keyed hashing mode (for MAC, PRF).

-> IO () 

Initialize a Hasher.

update Source #

Arguments

:: forall bin. ByteArrayAccess bin 
=> Ptr Hasher

Obtain with modifyHasher. It will be mutated.

-> [bin] 
-> IO () 

Update Hasher state with new data.

finalize Source #

Arguments

:: forall len output. ByteArrayN len output 
=> Ptr Hasher

Obtain with modifyHasher. It will be mutated.

-> IO output

The output type could be Digest len.

Finalize incremental hashing and obtain a the BLAKE3 output of the specified length.

finalizeSeek Source #

Arguments

:: forall len output. ByteArrayN len output 
=> Ptr Hasher

Obtain with modifyHasher. It will be mutated.

-> Word64

BLAKE3 output offset.

-> IO output 

Finalize incremental hashing and obtain the specified length of BLAKE3 output starting at the specified offset.

finalize h = finalizeSeek h 0

Digest

newtype Digest (len :: Nat) Source #

Output from BLAKE3 algorithm, of len bytes.

The default digest length for BLAKE3 is DEFAULT_DIGEST_LEN.

Constructors

Digest (SizedByteArray len ScrubbedBytes) 

Instances

Instances details
KnownNat len => ByteArrayN len (Digest len) Source # 
Instance details

Defined in BLAKE3.IO

Methods

allocRet :: Proxy len -> (Ptr p -> IO a) -> IO (a, Digest len) #

KnownNat len => Storable (Digest len) Source #

When allocating a Digest, prefer to use alloc, which wipes and releases the memory as soon it becomes unused.

Instance details

Defined in BLAKE3.IO

Methods

sizeOf :: Digest len -> Int #

alignment :: Digest len -> Int #

peekElemOff :: Ptr (Digest len) -> Int -> IO (Digest len) #

pokeElemOff :: Ptr (Digest len) -> Int -> Digest len -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Digest len) #

pokeByteOff :: Ptr b -> Int -> Digest len -> IO () #

peek :: Ptr (Digest len) -> IO (Digest len) #

poke :: Ptr (Digest len) -> Digest len -> IO () #

Show (Digest len) Source #

Base 16 (hexadecimal).

Instance details

Defined in BLAKE3.IO

Methods

showsPrec :: Int -> Digest len -> ShowS #

show :: Digest len -> String #

showList :: [Digest len] -> ShowS #

Eq (Digest len) Source #

Constant time.

Instance details

Defined in BLAKE3.IO

Methods

(==) :: Digest len -> Digest len -> Bool #

(/=) :: Digest len -> Digest len -> Bool #

Ord (Digest len) Source # 
Instance details

Defined in BLAKE3.IO

Methods

compare :: Digest len -> Digest len -> Ordering #

(<) :: Digest len -> Digest len -> Bool #

(<=) :: Digest len -> Digest len -> Bool #

(>) :: Digest len -> Digest len -> Bool #

(>=) :: Digest len -> Digest len -> Bool #

max :: Digest len -> Digest len -> Digest len #

min :: Digest len -> Digest len -> Digest len #

KnownNat len => ByteArrayAccess (Digest len) Source # 
Instance details

Defined in BLAKE3.IO

Methods

length :: Digest len -> Int #

withByteArray :: Digest len -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Digest len -> Ptr p -> IO () #

Keyed hashing

data Key Source #

Key used for keyed hashing mode.

Obtain with key.

See hashKeyed.

Instances

Instances details
Storable Key Source #

When allocating a Key, prefer to use alloc, which wipes and releases the memory as soon it becomes unused.

Instance details

Defined in BLAKE3.IO

Methods

sizeOf :: Key -> Int #

alignment :: Key -> Int #

peekElemOff :: Ptr Key -> Int -> IO Key #

pokeElemOff :: Ptr Key -> Int -> Key -> IO () #

peekByteOff :: Ptr b -> Int -> IO Key #

pokeByteOff :: Ptr b -> Int -> Key -> IO () #

peek :: Ptr Key -> IO Key #

poke :: Ptr Key -> Key -> IO () #

Show Key Source #

Base 16 (hexadecimal).

Instance details

Defined in BLAKE3.IO

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Eq Key Source #

Constant time.

Instance details

Defined in BLAKE3.IO

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

ByteArrayAccess Key Source #

Length is KEY_LEN.

Instance details

Defined in BLAKE3.IO

Methods

length :: Key -> Int #

withByteArray :: Key -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Key -> Ptr p -> IO () #

ByteArrayN KEY_LEN Key Source #

Allocate a Key.

The memory is wiped and freed as soon as the Key becomes unused.

Instance details

Defined in BLAKE3.IO

Methods

allocRet :: Proxy KEY_LEN -> (Ptr p -> IO a) -> IO (a, Key) #

key Source #

Arguments

:: ByteArrayAccess bin 
=> bin

Key bytes. Must have length KEY_LEN.

-> Maybe Key 

Obtain a Key for use in BLAKE3 keyed hashing.

See hashKeyed.

Key derivation

initDerive Source #

Arguments

:: forall context. ByteArrayAccess context 
=> Ptr Hasher

Obtain with alloc or similar. It will be mutated.

-> context 
-> IO () 

Initialize a Hasher in derivation mode.

The input key material must be provided afterwards, using update.

Hasher

data Hasher Source #

BLAKE3 internal state.

Obtain with hasher, hasherKeyed.

Instances

Instances details
Storable Hasher Source #

When allocating a Hasher, prefer to use alloc, which wipes and releases the memory as soon it becomes unused.

Instance details

Defined in BLAKE3.IO

Show Hasher Source #

Base 16 (hexadecimal).

Instance details

Defined in BLAKE3.IO

Eq Hasher Source #

Constant time.

Instance details

Defined in BLAKE3.IO

Methods

(==) :: Hasher -> Hasher -> Bool #

(/=) :: Hasher -> Hasher -> Bool #

ByteArrayAccess Hasher Source #

Length is HASHER_SIZE.

Instance details

Defined in BLAKE3.IO

Methods

length :: Hasher -> Int #

withByteArray :: Hasher -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Hasher -> Ptr p -> IO () #

ByteArrayN HASHER_SIZE Hasher Source #

Allocate a Hasher. The memory is wiped and freed as soon as the Hasher becomes unused.

Instance details

Defined in BLAKE3.IO

Methods

allocRet :: Proxy HASHER_SIZE -> (Ptr p -> IO a) -> IO (a, Hasher) #

modifyHasher Source #

Arguments

:: Hasher 
-> (Ptr Hasher -> IO a)

HASHER_SIZE bytes.

-> IO a 

Obtain a Ptr Hasher to use with functions like initDerive, etc.

Constants

type HASHER_SIZE = 1912 Source #

In bytes.

type KEY_LEN = 32 Source #

In bytes.

type BLOCK_SIZE = 64 Source #

In bytes.

type DEFAULT_DIGEST_LEN = 32 Source #

In bytes.

type CHUNK_LEN = 1024 Source #

type MAX_DEPTH = 54 Source #

Low-level C bindings

c_init Source #

Arguments

:: Ptr Hasher

You can obtain with alloc. Otherwise, any chunk of HASHER_SIZE bytes aligned to HASHER_ALIGNMENT will do.

-> IO () 
void blake3_hasher_init(blake3_hasher *self)

c_init_keyed Source #

Arguments

:: Ptr Hasher

You can obtain with alloc. Otherwise, any chunk of HASHER_SIZE bytes aligned to HASHER_ALIGNMENT will do.

-> Ptr Word8

You can obtain with alloc. Otherwise, any chunk of length KEY_LEN will do.

-> IO () 
void blake3_hasher_init_keyed(blake3_hasher *self, const uint8_t key[KEY_LEN])

c_init_derive_key_raw Source #

Arguments

:: Ptr Hasher

You can obtain with alloc. Otherwise, any chunk of HASHER_SIZE bytes aligned to HASHER_ALIGNMENT will do.

-> Ptr Word8

Context.

-> CSize

Context length.

-> IO () 
void blake3_hasher_init_derive_key_raw(blake3_hasher *self, const void *context, size_t context_len)

c_update Source #

Arguments

:: Ptr Hasher

Must have been previously initializedi. See c_init, c_init_keyed, c_init_derive_key.

-> Ptr Word8

Data.

-> CSize

Data length.

-> IO () 
void blake3_hasher_update(blake3_hasher *self, const void *input, size_t input_len)

c_finalize Source #

Arguments

:: Ptr Hasher

Must have been previously initializedi. See c_init, c_init_keyed, c_init_derive_key.

-> Ptr Word8

Out.

-> CSize

Out length.

-> IO () 
void blake3_hasher_finalize(const blake3_hasher *self, uint8_t *out, size_t out_len)

c_finalize_seek Source #

Arguments

:: Ptr Hasher

Must have been previously initializedi. See c_init, c_init_keyed, c_init_derive_key.

-> Word64

Seek position.

-> Ptr Word8

Out.

-> CSize

Out length.

-> IO () 
void blake3_hasher_finalize_seek(const blake3_hasher *self, uint64_t seek, uint8_t *out, size_t out_len)