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

Crypto.Saltine.Core.Auth

Description

Secret-key message authentication: Crypto.Saltine.Core.Auth

The auth function authenticates a message ByteString using a secret key. The function returns an authenticator. The verify function checks if it's passed a correct authenticator of a message under the given secret key.

The auth function, viewed as a function of the message for a uniform random key, is designed to meet the standard notion of unforgeability. This means that an attacker cannot find authenticators for any messages not authenticated by the sender, even if the attacker has adaptively influenced the messages authenticated by the sender. For a formal definition see, e.g., Section 2.4 of Bellare, Kilian, and Rogaway, "The security of the cipher block chaining message authentication code," Journal of Computer and System Sciences 61 (2000), 362–399; http://www-cse.ucsd.edu/~mihir/papers/cbc.html.

Saltine does not make any promises regarding "strong" unforgeability; perhaps one valid authenticator can be converted into another valid authenticator for the same message. NaCl also does not make any promises regarding "truncated unforgeability."

Crypto.Saltine.Core.Auth is currently an implementation of HMAC-SHA-512-256, i.e., the first 256 bits of HMAC-SHA-512. HMAC-SHA-512-256 is conjectured to meet the standard notion of unforgeability.

This is version 2010.08.30 of the auth.html web page.

Synopsis

Documentation

data Key Source #

An opaque auth cryptographic key.

Instances

Instances details
Eq Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Data Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Methods

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

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

toConstr :: Key -> Constr #

dataTypeOf :: Key -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

(>=) :: Key -> Key -> Bool #

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

NFData Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Methods

rnf :: Key -> () #

Hashable Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Methods

hashWithSalt :: Int -> Key -> Int #

hash :: Key -> Int #

IsEncoding Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

type Rep Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

type Rep Key = D1 ('MetaData "Key" "Crypto.Saltine.Internal.Auth" "saltine-0.2.0.1-inplace" 'True) (C1 ('MetaCons "Key" 'PrefixI 'True) (S1 ('MetaSel ('Just "unKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data Authenticator Source #

An opaque auth authenticator.

Instances

Instances details
Eq Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Data Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Methods

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

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

toConstr :: Authenticator -> Constr #

dataTypeOf :: Authenticator -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Show Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Generic Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Associated Types

type Rep Authenticator :: Type -> Type #

NFData Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

Methods

rnf :: Authenticator -> () #

Hashable Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

IsEncoding Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

type Rep Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Internal.Auth

type Rep Authenticator = D1 ('MetaData "Authenticator" "Crypto.Saltine.Internal.Auth" "saltine-0.2.0.1-inplace" 'True) (C1 ('MetaCons "Au" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAu") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newKey :: IO Key Source #

Creates a random key of the correct size for auth and verify.

auth Source #

Arguments

:: Key 
-> ByteString

Message

-> Authenticator 

Computes an keyed authenticator ByteString from a message. It is infeasible to forge these authenticators without the key, even if an attacker observes many authenticators and messages and has the ability to influence the messages sent.

verify Source #

Arguments

:: Key 
-> Authenticator 
-> ByteString

Message

-> Bool

Is this message authentic?

Checks to see if an authenticator is a correct proof that a message was signed by some key.