hashes-0.2.3: Hash functions
CopyrightCopyright © 2021 Lars Kuhtz <lakuhtz@gmail.com>
LicenseMIT
MaintainerLars Kuhtz <lakuhtz@gmail.com>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Hash.SipHash

Description

 
Synopsis

Documentation

data SipHashKey Source #

The Word46 constructor parameters represent the 128 bit key in little endian encoding.

Constructors

SipHashKey !Word64 !Word64 

newtype SipHash (c :: Nat) (d :: Nat) Source #

SipHash with c compression rounds and d finalization rounds.

cf. http://cr.yp.to/siphash/siphash-20120918.pdf

Constructors

SipHash Word64 

Instances

Instances details
Show (SipHash c d) Source # 
Instance details

Defined in Data.Hash.SipHash

Methods

showsPrec :: Int -> SipHash c d -> ShowS #

show :: SipHash c d -> String #

showList :: [SipHash c d] -> ShowS #

Eq (SipHash c d) Source # 
Instance details

Defined in Data.Hash.SipHash

Methods

(==) :: SipHash c d -> SipHash c d -> Bool #

(/=) :: SipHash c d -> SipHash c d -> Bool #

Ord (SipHash c d) Source # 
Instance details

Defined in Data.Hash.SipHash

Methods

compare :: SipHash c d -> SipHash c d -> Ordering #

(<) :: SipHash c d -> SipHash c d -> Bool #

(<=) :: SipHash c d -> SipHash c d -> Bool #

(>) :: SipHash c d -> SipHash c d -> Bool #

(>=) :: SipHash c d -> SipHash c d -> Bool #

max :: SipHash c d -> SipHash c d -> SipHash c d #

min :: SipHash c d -> SipHash c d -> SipHash c d #

(SipHashParam c, SipHashParam d) => IncrementalHash (SipHash c d) Source # 
Instance details

Defined in Data.Hash.SipHash

Associated Types

type Context (SipHash c d) Source #

Methods

update :: Context (SipHash c d) -> Ptr Word8 -> Int -> IO (Context (SipHash c d)) Source #

finalize :: Context (SipHash c d) -> SipHash c d Source #

(SipHashParam c, SipHashParam d) => Hash (SipHash c d) Source # 
Instance details

Defined in Data.Hash.SipHash

Associated Types

type Salt (SipHash c d) Source #

Methods

initialize :: Salt (SipHash c d) -> Context (SipHash c d) Source #

type Context (SipHash c d) Source # 
Instance details

Defined in Data.Hash.SipHash

type Context (SipHash c d) = SipHashContext c d
type Salt (SipHash c d) Source # 
Instance details

Defined in Data.Hash.SipHash

type Salt (SipHash c d) = SipHashKey

sipHash :: SipHashKey -> Ptr Word8 -> Int -> IO (SipHash 2 4) Source #

SipHash, with recommended default parameters of c=2 and d=4.

The first and second argument is the 128 bit key, represented as two 64 bit words.

SipHash-c-d

sipHashCD :: forall c d. SipHashParam c => SipHashParam d => SipHashKey -> Ptr Word8 -> Int -> IO (SipHash c d) Source #

Generic SipHash with c rounds per block and d finalization rounds.

The first and second argument is the 128 bit key, represented as two 64 bit words.

sipHash24 :: SipHashKey -> Ptr Word8 -> Int -> IO (SipHash 2 4) Source #

SipHash-2-4

The first and second argument is the 128 bit key, represented as two 64 bit words.

sipHash13 :: SipHashKey -> Ptr Word8 -> Int -> IO (SipHash 1 3) Source #

SipHash-1-3

The first and second argument is the 128 bit key, represented as two 64 bit words.

sipHash48 :: SipHashKey -> Ptr Word8 -> Int -> IO (SipHash 4 8) Source #

SipHash-4-8

The first and second argument is the 128 bit key, represented as two 64 bit words.

Incremental SipHash

data SipHashContext (c :: Nat) (d :: Nat) Source #

Internal mutable SipHashContext.

The first four arguments are the internal state values \(v_{0..3}\) and the last argument represents the pending bytes from an incomplete word of the last chunk of input.

sipHashInitialize :: SipHashKey -> SipHashContext c d Source #

Initialize a new SipHashContext

sipHashUpdate :: forall (c :: Nat) (d :: Nat). SipHashParam c => SipHashContext c d -> Ptr Word8 -> Int -> IO (SipHashContext c d) Source #

Incrementally add input bytes to an SipHash computation and update the internal context.

sipHashFinalize :: forall (c :: Nat) (d :: Nat). SipHashParam c => SipHashParam d => SipHashContext c d -> SipHash c d Source #

Utils