saltine-0.2.1.0: Cryptography that's easy to digest (NaCl/libsodium bindings).
Copyright(c) Max Amanshauser 2021
LicenseMIT
Maintainermax@lambdalifting.org
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Crypto.Saltine.Internal.Hash

Description

 
Synopsis

Documentation

hash_bytes :: Int Source #

The size of a hash resulting from hash.

shorthash_bytes :: Int Source #

The size of a keyed hash resulting from shorthash.

shorthash_keybytes :: Int Source #

The size of a hashing key for the keyed hash function shorthash.

generichash_bytes_max :: Int Source #

The maximum output size of the generic hash function generichash

generichash_keybytes_max :: Int Source #

The maximum key size of the generic hash function generichash

c_hash Source #

Arguments

:: Ptr CChar

Output hash buffer

-> Ptr CChar

Constant message buffer

-> CULLong

Constant message buffer length

-> IO CInt

Always 0

c_shorthash Source #

Arguments

:: Ptr CChar

Output hash buffer

-> Ptr CChar

Constant message buffer

-> CULLong

Message buffer length

-> Ptr CChar

Constant Key buffer

-> IO CInt

Always 0

c_generichash Source #

Arguments

:: Ptr CChar

Output hash buffer

-> CULLong

Output hash length

-> Ptr CChar

Constant message buffer

-> CULLong

Message buffer length

-> Ptr CChar

Constant Key buffer

-> CULLong

Key buffer length

-> IO CInt

Always 0

nullShKey :: ShorthashKey Source #

Used for our Show instances

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

newtype ShorthashKey Source #

An opaque shorthash cryptographic secret key.

Constructors

ShK 

Fields

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)))

newtype GenerichashKey Source #

An opaque generichash cryptographic secret key.

Constructors

GhK 

Fields

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)))

newtype GenerichashOutLen Source #

Constructors

GhOL 

Fields

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)))