saltine-0.2.1.0: Cryptography that's easy to digest (NaCl/libsodium bindings).
Copyright(c) Joseph Abrahamson 2013
LicenseMIT
Maintainerme@jspha.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Crypto.Saltine.Core.Hash

Description

The hash function hashes a message ByteString and returns a hash. Hashes are always of length hash. The shorthash function hashes a message ByteString with respect to a secret key and returns a very short hash. Short hashes are always of length shorthash.

The hash function is designed to be usable as a strong component of DSA, RSA-PSS, key derivation, hash-based message-authentication codes, hash-based ciphers, and various other common applications. Strong means that the security of these applications, when instantiated with hash, is the same as the security of the applications against generic attacks. In particular, the hash function is designed to make finding collisions difficult.

hash is currently an implementation of SHA-512. shorthash is currently an implementation of SipHash-2-4 (https://131002.net/siphash/).

There has been considerable degradation of public confidence in the security conjectures for many hash functions, including SHA-512. However, for the moment, there do not appear to be alternatives that inspire satisfactory levels of confidence. One can hope that NIST's SHA-3 competition will improve the situation.

Sodium includes an implementation of the Blake2b hash function (https://blake2.net/) and is bound here as the generichash function.

This is version 2010.08.30 of the hash.html web page. Information about SipHash has been added.

Synopsis

Documentation

data ShorthashKey Source #

An opaque shorthash cryptographic secret key.

Instances

Instances details
Data ShorthashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShorthashKey -> c ShorthashKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShorthashKey #

toConstr :: ShorthashKey -> Constr #

dataTypeOf :: ShorthashKey -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ShorthashKey) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShorthashKey) #

gmapT :: (forall b. Data b => b -> b) -> ShorthashKey -> ShorthashKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShorthashKey -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShorthashKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> ShorthashKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ShorthashKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShorthashKey -> m ShorthashKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShorthashKey -> m ShorthashKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShorthashKey -> m ShorthashKey #

Generic ShorthashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Associated Types

type Rep ShorthashKey :: Type -> Type #

Show ShorthashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

NFData ShorthashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Methods

rnf :: ShorthashKey -> () #

Eq ShorthashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Ord ShorthashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Hashable ShorthashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

IsEncoding ShorthashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

type Rep ShorthashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

type Rep ShorthashKey = D1 ('MetaData "ShorthashKey" "Crypto.Saltine.Internal.Hash" "saltine-0.2.1.0-inplace" 'True) (C1 ('MetaCons "ShK" 'PrefixI 'True) (S1 ('MetaSel ('Just "unShK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

hash Source #

Arguments

:: ByteString

Message

-> ByteString

Hash

Computes a cryptographically collision-resistant hash making hash m == hash m' ==> m == m' highly likely even when under attack.

shorthash Source #

Arguments

:: ShorthashKey 
-> ByteString

Message

-> ByteString

Hash

Computes a very short, fast keyed hash. This function is defined here to break circulat module imports

newShorthashKey :: IO ShorthashKey Source #

Randomly generates a new key for shorthash.

data GenerichashKey Source #

An opaque generichash cryptographic secret key.

Instances

Instances details
Data GenerichashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenerichashKey -> c GenerichashKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GenerichashKey #

toConstr :: GenerichashKey -> Constr #

dataTypeOf :: GenerichashKey -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GenerichashKey) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GenerichashKey) #

gmapT :: (forall b. Data b => b -> b) -> GenerichashKey -> GenerichashKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenerichashKey -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenerichashKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> GenerichashKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenerichashKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenerichashKey -> m GenerichashKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenerichashKey -> m GenerichashKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenerichashKey -> m GenerichashKey #

Generic GenerichashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Associated Types

type Rep GenerichashKey :: Type -> Type #

Show GenerichashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

NFData GenerichashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Methods

rnf :: GenerichashKey -> () #

Eq GenerichashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Ord GenerichashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Hashable GenerichashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

IsEncoding GenerichashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

type Rep GenerichashKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

type Rep GenerichashKey = D1 ('MetaData "GenerichashKey" "Crypto.Saltine.Internal.Hash" "saltine-0.2.1.0-inplace" 'True) (C1 ('MetaCons "GhK" 'PrefixI 'True) (S1 ('MetaSel ('Just "unGhK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newGenerichashKey :: Int -> IO (Maybe GenerichashKey) Source #

Randomly generates a new key for generichash of the given length.

data GenerichashOutLen Source #

Instances

Instances details
Data GenerichashOutLen Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenerichashOutLen -> c GenerichashOutLen #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GenerichashOutLen #

toConstr :: GenerichashOutLen -> Constr #

dataTypeOf :: GenerichashOutLen -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GenerichashOutLen) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GenerichashOutLen) #

gmapT :: (forall b. Data b => b -> b) -> GenerichashOutLen -> GenerichashOutLen #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenerichashOutLen -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenerichashOutLen -> r #

gmapQ :: (forall d. Data d => d -> u) -> GenerichashOutLen -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenerichashOutLen -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenerichashOutLen -> m GenerichashOutLen #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenerichashOutLen -> m GenerichashOutLen #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenerichashOutLen -> m GenerichashOutLen #

Generic GenerichashOutLen Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Associated Types

type Rep GenerichashOutLen :: Type -> Type #

NFData GenerichashOutLen Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Methods

rnf :: GenerichashOutLen -> () #

Eq GenerichashOutLen Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Ord GenerichashOutLen Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

Hashable GenerichashOutLen Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

type Rep GenerichashOutLen Source # 
Instance details

Defined in Crypto.Saltine.Internal.Hash

type Rep GenerichashOutLen = D1 ('MetaData "GenerichashOutLen" "Crypto.Saltine.Internal.Hash" "saltine-0.2.1.0-inplace" 'True) (C1 ('MetaCons "GhOL" 'PrefixI 'True) (S1 ('MetaSel ('Just "unGhOL") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

generichashOutLen :: Int -> Maybe GenerichashOutLen Source #

Create a validated Generichash output length

generichash Source #

Arguments

:: GenerichashKey 
-> ByteString

Message

-> GenerichashOutLen

Desired output hash length

-> ByteString

Hash

Computes a generic, keyed hash.