Copyright | (c) Joseph Abrahamson 2013 |
---|---|
License | MIT |
Maintainer | me@jspha.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
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
- data Key
- data Authenticator
- newKey :: IO Key
- auth :: Key -> ByteString -> Authenticator
- verify :: Key -> Authenticator -> ByteString -> Bool
Documentation
An opaque auth
cryptographic key.
Instances
Eq Key Source # | |
Data Key Source # | |
Defined in Crypto.Saltine.Core.OneTimeAuth 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 # 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 # | |
Generic Key Source # | |
Hashable Key Source # | |
Defined in Crypto.Saltine.Core.OneTimeAuth | |
IsEncoding Key Source # | |
Defined in Crypto.Saltine.Core.OneTimeAuth encode :: Key -> ByteString Source # decode :: ByteString -> Maybe Key Source # encoded :: (Choice p, Applicative f) => p Key (f Key) -> p ByteString (f ByteString) Source # | |
type Rep Key Source # | |
Defined in Crypto.Saltine.Core.OneTimeAuth type Rep Key = D1 ('MetaData "Key" "Crypto.Saltine.Core.OneTimeAuth" "saltine-0.1.1.1-KbVmRAcWBV25w8Dlelbdig" 'True) (C1 ('MetaCons "Key" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
data Authenticator Source #
An opaque auth
authenticator.
Instances
:: 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.
:: Key | |
-> Authenticator | |
-> ByteString | Message |
-> Bool | Is this message authentic? |
Verifies that an Authenticator
matches a given message and key.