Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
IO and low level tools.
Synopsis
- hash :: forall len digest bin. (ByteArrayN len digest, ByteArrayAccess bin) => Maybe Key -> [bin] -> IO digest
- init :: Ptr Hasher -> Maybe Key -> IO ()
- update :: forall bin. ByteArrayAccess bin => Ptr Hasher -> [bin] -> IO ()
- finalize :: forall len output. ByteArrayN len output => Ptr Hasher -> IO output
- finalizeSeek :: forall len output. ByteArrayN len output => Ptr Hasher -> Word64 -> IO output
- newtype Digest (len :: Nat) = Digest (SizedByteArray len ScrubbedBytes)
- data Key
- key :: ByteArrayAccess bin => bin -> Maybe Key
- initDerive :: forall context. ByteArrayAccess context => Ptr Hasher -> context -> IO ()
- data Hasher
- modifyHasher :: Hasher -> (Ptr Hasher -> IO a) -> IO a
- type HASHER_ALIGNMENT = 8
- type HASHER_SIZE = 1912
- type KEY_LEN = 32
- type BLOCK_SIZE = 64
- type DEFAULT_DIGEST_LEN = 32
- type CHUNK_LEN = 1024
- type MAX_DEPTH = 54
- type MAX_SIMD_DEGREE = 16
- c_init :: Ptr Hasher -> IO ()
- c_init_keyed :: Ptr Hasher -> Ptr Word8 -> IO ()
- c_init_derive_key_raw :: Ptr Hasher -> Ptr Word8 -> CSize -> IO ()
- c_update :: Ptr Hasher -> Ptr Word8 -> CSize -> IO ()
- c_finalize :: Ptr Hasher -> Ptr Word8 -> CSize -> IO ()
- c_finalize_seek :: Ptr Hasher -> Word64 -> Ptr Word8 -> CSize -> IO ()
Hashing
:: 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 |
BLAKE3 hashing.
:: Ptr Hasher | Obtain with |
-> Maybe Key | Whether to use keyed hashing mode (for MAC, PRF). |
-> IO () |
Initialize a Hasher
.
:: forall bin. ByteArrayAccess bin | |
=> Ptr Hasher | Obtain with |
-> [bin] | |
-> IO () |
Update Hasher
state with new data.
:: forall len output. ByteArrayN len output | |
=> Ptr Hasher | Obtain with |
-> IO output | The |
Finalize incremental hashing and obtain a the BLAKE3 output of the
specified len
gth.
:: forall len output. ByteArrayN len output | |
=> Ptr Hasher | Obtain with |
-> Word64 | BLAKE3 output offset. |
-> IO output |
Finalize incremental hashing and obtain the specified len
gth 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
.
Instances
KnownNat len => ByteArrayN len (Digest len) Source # | |
KnownNat len => Storable (Digest len) Source # | When allocating a |
Defined in BLAKE3.IO | |
Show (Digest len) Source # | Base 16 (hexadecimal). |
Eq (Digest len) Source # | Constant time. |
Ord (Digest len) Source # | |
KnownNat len => ByteArrayAccess (Digest len) Source # | |
Keyed hashing
Instances
Storable Key Source # | When allocating a |
Defined in BLAKE3.IO | |
Show Key Source # | Base 16 (hexadecimal). |
Eq Key Source # | Constant time. |
ByteArrayAccess Key Source # | Length is |
ByteArrayN KEY_LEN Key Source # | Allocate a The memory is wiped and freed as soon as the |
:: ByteArrayAccess bin | |
=> bin | Key bytes. Must have length |
-> Maybe Key |
Key derivation
:: forall context. ByteArrayAccess context | |
=> Ptr Hasher | Obtain with |
-> context | |
-> IO () |
Hasher
BLAKE3 internal state.
Obtain with hasher
, hasherKeyed
.
Instances
Storable Hasher Source # | When allocating a |
Show Hasher Source # | Base 16 (hexadecimal). |
Eq Hasher Source # | Constant time. |
ByteArrayAccess Hasher Source # | Length is |
ByteArrayN HASHER_SIZE Hasher Source # | Allocate a |
Obtain a
to use with functions like Ptr
Hasher
initDerive
, etc.
Constants
type HASHER_ALIGNMENT = 8 Source #
type HASHER_SIZE = 1912 Source #
In bytes.
type BLOCK_SIZE = 64 Source #
In bytes.
type DEFAULT_DIGEST_LEN = 32 Source #
In bytes.
type MAX_SIMD_DEGREE = 16 Source #
Low-level C bindings
:: Ptr Hasher | You can obtain with |
-> IO () |
void blake3_hasher_init(blake3_hasher *self)
:: Ptr Hasher | You can obtain with |
-> Ptr Word8 | You can obtain with |
-> IO () |
void blake3_hasher_init_keyed(blake3_hasher *self, const uint8_t key[KEY_LEN
])
c_init_derive_key_raw Source #
:: Ptr Hasher | You can obtain with |
-> Ptr Word8 | Context. |
-> CSize | Context length. |
-> IO () |
void blake3_hasher_init_derive_key_raw(blake3_hasher *self, const void *context, size_t context_len)
:: Ptr Hasher | Must have been previously initializedi. See |
-> Ptr Word8 | Data. |
-> CSize | Data length. |
-> IO () |
void blake3_hasher_update(blake3_hasher *self, const void *input, size_t input_len)