raaz-0.3.5: Fast and type safe cryptography.
Copyright(c) Piyush P Kurur 2019
LicenseApache-2.0 OR BSD-3-Clause
MaintainerPiyush P Kurur <ppk@iitpkd.ac.in>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Raaz.Primitive.Keyed.Internal

Description

 
Synopsis

Keyed Hashing.

The keyed version of a cryptographic hash. Certain hashes like blake2 can be used for message authentication where the message is essentially appended to the key and hashed. This module is meant to handle such keyed primitives. Note that this naive message authentication is vulnerable to length extension attack when combined with a Merkel-Damgrad like hash like the sha2 family of hashes; they require a more complicated HMAC construction.

newtype Keyed prim Source #

The message authentication code associated with the hashes.

Constructors

Keyed prim 

Instances

Instances details
Eq prim => Eq (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

(==) :: Keyed prim -> Keyed prim -> Bool #

(/=) :: Keyed prim -> Keyed prim -> Bool #

Show (Key (Keyed prim)) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

showsPrec :: Int -> Key (Keyed prim) -> ShowS #

show :: Key (Keyed prim) -> String #

showList :: [Key (Keyed prim)] -> ShowS #

Show prim => Show (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

showsPrec :: Int -> Keyed prim -> ShowS #

show :: Keyed prim -> String #

showList :: [Keyed prim] -> ShowS #

IsString (Key (Keyed prim)) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

fromString :: String -> Key (Keyed prim) #

IsString prim => IsString (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

fromString :: String -> Keyed prim #

Storable prim => Storable (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

sizeOf :: Keyed prim -> Int #

alignment :: Keyed prim -> Int #

peekElemOff :: Ptr (Keyed prim) -> Int -> IO (Keyed prim) #

pokeElemOff :: Ptr (Keyed prim) -> Int -> Keyed prim -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Keyed prim) #

pokeByteOff :: Ptr b -> Int -> Keyed prim -> IO () #

peek :: Ptr (Keyed prim) -> IO (Keyed prim) #

poke :: Ptr (Keyed prim) -> Keyed prim -> IO () #

Equality prim => Equality (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

eq :: Keyed prim -> Keyed prim -> Result Source #

EndianStore prim => EndianStore (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

store :: Ptr (Keyed prim) -> Keyed prim -> IO () Source #

load :: Ptr (Keyed prim) -> IO (Keyed prim) Source #

adjustEndian :: Ptr (Keyed prim) -> Int -> IO () Source #

Encodable (Key (Keyed prim)) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Encodable prim => Encodable (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Primitive prim => Primitive (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Associated Types

type WordType (Keyed prim) Source #

type WordsPerBlock (Keyed prim) :: Nat Source #

newtype Key (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

newtype Key (Keyed prim) = Key ByteString
type WordType (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

type WordType (Keyed prim) = WordType prim
type WordsPerBlock (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

type WordsPerBlock (Keyed prim) = WordsPerBlock prim

class KeyedHash prim where Source #

Class of primitives, typically cryptographic hashes, that when used as a keyed hash gives a safe MAC.

Methods

hashInit :: BYTES Int -> prim Source #

Instances

Instances details
KeyedHash Blake2s Source # 
Instance details

Defined in Raaz.Primitive.Blake2.Internal

KeyedHash Blake2b Source # 
Instance details

Defined in Raaz.Primitive.Blake2.Internal

data family Key p :: Type Source #

The type family that captures the key of a keyed primitive.

Instances

Instances details
Initialisable ChaCha20Mem (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Eq (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Show (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Show (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Show (Key (Keyed prim)) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

showsPrec :: Int -> Key (Keyed prim) -> ShowS #

show :: Key (Keyed prim) -> String #

showList :: [Key (Keyed prim)] -> ShowS #

Show (Key Poly1305) Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

IsString (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

IsString (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

IsString (Key (Keyed prim)) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

fromString :: String -> Key (Keyed prim) #

Storable (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Storable (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Equality (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

EndianStore (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

EndianStore (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Encodable (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Encodable (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Encodable (Key (Keyed prim)) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Initialisable (MemoryCell (Key ChaCha20)) (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Key XChaCha20 Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Key XChaCha20 = XKey KEY
newtype Key ChaCha20 Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Key ChaCha20 = Key KEY
data Key Poly1305 Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

data Key Poly1305 = Key R S
newtype Key (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

newtype Key (Keyed prim) = Key ByteString

unsafeToKeyed :: prim -> Keyed prim Source #

Converts the hash value to the corresponding Keyed value. This function violates the principle that semantically distinct values should be of distinct types and hence should be considered unsafe.

unsafeToPrim :: Keyed prim -> prim Source #

Converts a Keyed value to the corresponding hash value. This function violates the principle that semantically distinct values should be of distinct types and hence should be considered unsafe