saltine-0.1.1.0: 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.OneTimeAuth

Description

Secret-key single-message authentication: Crypto.Saltine.Core.OneTimeAuth

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 after a single message. After the sender authenticates one message, an attacker cannot find authenticators for any other messages.

The sender must not use auth to authenticate more than one message under the same key. Authenticators for two messages under the same key should be expected to reveal enough information to allow forgeries of authenticators on other messages.

Crypto.Saltine.Core.OneTimeAuth is crypto_onetimeauth_poly1305, an authenticator specified in "Cryptography in NaCl" (http://nacl.cr.yp.to/valid.html), Section 9. This authenticator is proven to meet the standard notion of unforgeability after a single message.

This is version 2010.08.30 of the onetimeauth.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.Core.OneTimeAuth

Methods

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

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

Data Key Source # 
Instance details

Defined in Crypto.Saltine.Core.OneTimeAuth

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.Core.OneTimeAuth

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 #

Generic Key Source # 
Instance details

Defined in Crypto.Saltine.Core.OneTimeAuth

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

IsEncoding Key Source # 
Instance details

Defined in Crypto.Saltine.Core.OneTimeAuth

Hashable Key Source # 
Instance details

Defined in Crypto.Saltine.Core.OneTimeAuth

Methods

hashWithSalt :: Int -> Key -> Int

hash :: Key -> Int

type Rep Key Source # 
Instance details

Defined in Crypto.Saltine.Core.OneTimeAuth

type Rep Key = D1 ('MetaData "Key" "Crypto.Saltine.Core.OneTimeAuth" "saltine-0.1.1.0-inplace" 'True) (C1 ('MetaCons "Key" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data Authenticator Source #

An opaque auth authenticator.

Instances

Instances details
Eq Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Core.OneTimeAuth

Data Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Core.OneTimeAuth

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.Core.OneTimeAuth

Generic Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Core.OneTimeAuth

Associated Types

type Rep Authenticator :: Type -> Type #

IsEncoding Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Core.OneTimeAuth

Hashable Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Core.OneTimeAuth

type Rep Authenticator Source # 
Instance details

Defined in Crypto.Saltine.Core.OneTimeAuth

type Rep Authenticator = D1 ('MetaData "Authenticator" "Crypto.Saltine.Core.OneTimeAuth" "saltine-0.1.1.0-inplace" 'True) (C1 ('MetaCons "Au" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) '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 

Builds a keyed Authenticator for a message. This Authenticator is impossible to forge so long as the Key is never used twice.

verify Source #

Arguments

:: Key 
-> Authenticator 
-> ByteString

Message

-> Bool

Is this message authentic?

Verifies that an Authenticator matches a given message and key.