symbolic-base-0.1.0.0: ZkFold Symbolic compiler and zero-knowledge proof protocols
Safe HaskellSafe-Inferred
LanguageHaskell2010

ZkFold.Symbolic.Algorithms.Hash.SHA2

Synopsis

Documentation

class (Symbolic context, NFData (context (Vector (WordSize algorithm))), KnownNat (ChunkSize algorithm), KnownNat (WordSize algorithm), Mod (ChunkSize algorithm) (WordSize algorithm) ~ 0, (Div (ChunkSize algorithm) (WordSize algorithm) * WordSize algorithm) ~ ChunkSize algorithm, (Div (8 * WordSize algorithm) (WordSize algorithm) * WordSize algorithm) ~ (8 * WordSize algorithm)) => AlgorithmSetup (algorithm :: Symbol) (context :: (Type -> Type) -> Type) where Source #

SHA2 is a family of hashing functions with almost identical implementations but different constants and parameters. This class links these varying parts with the appropriate algorithm.

Associated Types

type WordSize algorithm :: Natural Source #

The length of words the algorithm operates internally, in bits.

type ChunkSize algorithm :: Natural Source #

Hashing algorithms from SHA2 family require splitting the input message into blocks. This type describes the size of these blocks, in bits.

type ResultSize algorithm :: Natural Source #

The length of the resulting hash, in bits.

Methods

initialHashes :: Vector (ByteString (WordSize algorithm) context) Source #

Initial hash values which will be mixed with the message bits.

roundConstants :: Vector (ByteString (WordSize algorithm) context) Source #

Constants used in the internal loop, one per each round.

truncateResult :: ByteString (8 * WordSize algorithm) context -> ByteString (ResultSize algorithm) context Source #

A function to postprocess the hash. For example, SHA224 requires dropping the last 32 bits of a SHA256 hash.

sigmaShifts :: (Natural, Natural, Natural, Natural, Natural, Natural) Source #

Round rotation values for Sigma in the internal loop.

sumShifts :: (Natural, Natural, Natural, Natural, Natural, Natural) Source #

Round rotation values for Sum in the internal loop.

Instances

Instances details
(Symbolic c, NFData (c (Vector (WordSize "SHA224")))) => AlgorithmSetup "SHA224" c Source # 
Instance details

Defined in ZkFold.Symbolic.Algorithms.Hash.SHA2

Associated Types

type WordSize "SHA224" :: Natural Source #

type ChunkSize "SHA224" :: Natural Source #

type ResultSize "SHA224" :: Natural Source #

(Symbolic c, NFData (c (Vector (WordSize "SHA256")))) => AlgorithmSetup "SHA256" c Source # 
Instance details

Defined in ZkFold.Symbolic.Algorithms.Hash.SHA2

Associated Types

type WordSize "SHA256" :: Natural Source #

type ChunkSize "SHA256" :: Natural Source #

type ResultSize "SHA256" :: Natural Source #

(Symbolic c, NFData (c (Vector (WordSize "SHA384")))) => AlgorithmSetup "SHA384" c Source # 
Instance details

Defined in ZkFold.Symbolic.Algorithms.Hash.SHA2

Associated Types

type WordSize "SHA384" :: Natural Source #

type ChunkSize "SHA384" :: Natural Source #

type ResultSize "SHA384" :: Natural Source #

(Symbolic c, NFData (c (Vector (WordSize "SHA512")))) => AlgorithmSetup "SHA512" c Source # 
Instance details

Defined in ZkFold.Symbolic.Algorithms.Hash.SHA2

Associated Types

type WordSize "SHA512" :: Natural Source #

type ChunkSize "SHA512" :: Natural Source #

type ResultSize "SHA512" :: Natural Source #

(Symbolic c, NFData (c (Vector (WordSize "SHA512/224")))) => AlgorithmSetup "SHA512/224" c Source # 
Instance details

Defined in ZkFold.Symbolic.Algorithms.Hash.SHA2

Associated Types

type WordSize "SHA512/224" :: Natural Source #

type ChunkSize "SHA512/224" :: Natural Source #

type ResultSize "SHA512/224" :: Natural Source #

(Symbolic c, NFData (c (Vector (WordSize "SHA512/256")))) => AlgorithmSetup "SHA512/256" c Source # 
Instance details

Defined in ZkFold.Symbolic.Algorithms.Hash.SHA2

Associated Types

type WordSize "SHA512/256" :: Natural Source #

type ChunkSize "SHA512/256" :: Natural Source #

type ResultSize "SHA512/256" :: Natural Source #

type SHA2 algorithm context k = (AlgorithmSetup algorithm context, KnownNat k) Source #

Constraints required for a type-safe SHA2

sha2 :: forall (algorithm :: Symbol) context k {d}. SHA2 algorithm context k => d ~ Div (PaddedLength k (ChunkSize algorithm) (2 * WordSize algorithm)) (ChunkSize algorithm) => ByteString k context -> ByteString (ResultSize algorithm) context Source #

A generalised version of SHA2. It is agnostic of the ByteString base field. Sample usage:

>>> bs = fromConstant (42 :: Natural) :: ByteString 8 (Zp BLS12_381_Scalar)
>>> hash = sha2 @"SHA256" bs

type SHA2N algorithm context = AlgorithmSetup algorithm context Source #

Constraints required for a SHA2 of a Natural number.

sha2Natural :: forall (algorithm :: Symbol) (context :: (Type -> Type) -> Type). SHA2N algorithm context => Natural -> Natural -> ByteString (ResultSize algorithm) context Source #

Same as sha2 but accepts a Natural number and length of message in bits instead of a ByteString. Only used for testing.

type family PaddedLength (msg :: Natural) (block :: Natural) (lenBits :: Natural) :: Natural where ... Source #

On type level, determine the length of the message after padding. Padding algorithm is described below:

  1. begin with the original message of length L bits
  2. append a single '1' bit
  3. append K '0' bits, where K is the minimum number >= 0 such that (L + 1 + K + 64) is a multiple of 512
  4. append L as a 64-bit big-endian integer, making the total post-processed length a multiple of 512 bits

such that the bits in the message are: message of length L 1 zeros as 64 bit integer

For SHA384, SHA512 and SHA512/t, replace 512 with 1024 and 64 with 128.

Equations

PaddedLength msg block lenBits = If ((NextMultiple msg block - msg) <=? lenBits) (block + NextMultiple msg block) (NextMultiple msg block)