sel-0.0.1.0: Cryptography for the casual user
Copyright(C) Hécate Moonlight 2022
LicenseBSD-3-Clause
MaintainerThe Haskell Cryptography Group
PortabilityGHC only
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sel.Hashing

Description

 
Synopsis

Introduction

This API computes a fixed-length fingerprint for an arbitrarily long message. It is backed by the BLAKE2b algorithm.

Sample use cases:

  • File integrity checking
  • Creating unique identifiers to index arbitrarily long data

⚠️ Do not use this module to hash passwords! ⚠️ Please use the Sel.Hashing.Password module instead.

If you need to deviate from the defaults enforced by this module, please use the underlying bindings at LibSodium.Bindings.GenericHashing.

Hashing a message

data HashKey Source #

The HashKey is used to produce distinct fingerprints for the same message. It is optional to use, and hashByteString will always produce the same fingerprint for the same message if a HashKey is not given. This behaviour is similar to MD5 and SHA-1 functions, for which hashByteString is a faster and more secure alternative.

Create a new HashKey with newHashKey.

Since: 0.0.1.0

Instances

Instances details
Eq HashKey Source # 
Instance details

Defined in Sel.Hashing

Methods

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

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

Ord HashKey Source # 
Instance details

Defined in Sel.Hashing

newHashKey :: IO HashKey Source #

Create a new HashKey of size cryptoGenericHashKeyBytes.

Since: 0.0.1.0

data Hash Source #

The fingerprint computed by hashByteString. It is produced by the BLAKE2b algorithm, and is of size cryptoGenericHashBytes, as recommended.

You can produce a human-readable string representation of a Hash by using the display function.

Since: 0.0.1.0

Instances

Instances details
Storable Hash Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing

Methods

sizeOf :: Hash -> Int #

alignment :: Hash -> Int #

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

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

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

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

peek :: Ptr Hash -> IO Hash #

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

Show Hash Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing

Methods

showsPrec :: Int -> Hash -> ShowS #

show :: Hash -> String #

showList :: [Hash] -> ShowS #

Eq Hash Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing

Methods

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

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

Ord Hash Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing

Methods

compare :: Hash -> Hash -> Ordering #

(<) :: Hash -> Hash -> Bool #

(<=) :: Hash -> Hash -> Bool #

(>) :: Hash -> Hash -> Bool #

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

max :: Hash -> Hash -> Hash #

min :: Hash -> Hash -> Hash #

Display Hash Source #

Since: 0.0.1.0

Instance details

Defined in Sel.Hashing

hashByteString :: Maybe HashKey -> StrictByteString -> IO Hash Source #

Hash a StrictByteString with the BLAKE2b algorithm, and an optional key.

Without a HashKey, hashing the same data twice will give the same result.

Since: 0.0.1.0

Hashing a multi-part message

data Multipart s Source #

Multipart is a cryptographic context for streaming hashing. This API can be used when a message is too big to fit in memory or when the message is received in portions.

Use it like this:

>>> hashKey <- Hashing.newHashKey
>>> hash <- Hashing.withMultipart (Just hashKey) $ \multipartState -> do -- we are in MonadIO
...   message1 <- getMessage
...   Hashing.updateMultipart multipartState message1
...   message2 <- getMessage
...   Hashing.updateMultipart multipartState message2

Since: 0.0.1.0

withMultipart Source #

Arguments

:: forall (a :: Type) (m :: Type -> Type). MonadIO m 
=> Maybe HashKey

Optional cryptographic key

-> (forall s. Multipart s -> m a)

Continuation that gives you access to a Multipart cryptographic context

-> m Hash 

Perform streaming hashing with a Multipart cryptographic context. If there is no HashKey, you will get the same output for the same input all the time.

Use updateMultipart within the continuation to add more message parts to be hashed.

The context is safely allocated first, then the continuation is run and then it is deallocated after that.

Since: 0.0.1.0

updateMultipart :: forall (m :: Type -> Type) (s :: Type). MonadIO m => Multipart s -> StrictByteString -> m () Source #

Add a message portion to be hashed.

This function is to be used within withMultipart.

Since: 0.0.1.0

Conversion

hashToHexText :: Hash -> Text Source #

Convert a Hash to a strict, hexadecimal-encoded Text.

Since: 0.0.1.0

hashToHexByteString :: Hash -> StrictByteString Source #

Convert a Hash to a strict, hexadecimal-encoded StrictByteString.

Since: 0.0.1.0

hashToBinary :: Hash -> StrictByteString Source #

Convert a Hash to a strict binary StrictByteString.

Since: 0.0.1.0