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

Crypto.Saltine.Core.AEAD.AES256GCM

Description

Secret-key authenticated encryption with additional data (AEAD): Crypto.Saltine.Core.AEAD.AES256GCM

Using this module is not recommended. Don't use unless you have to. Keep in mind its limitations: https://doc.libsodium.org/secret-key_cryptography/aead

Unless you know for certain the CPU your program will run on supports Intel SSSE3, AES-NI and CLMUL, you should run aead_aes256gcm_available first and only proceed if the result is True.

Generating nonces for the functions in this module randomly is not recommended, due to the risk of generating collisions.

Synopsis

Documentation

data Key Source #

An opaque AES256GCM cryptographic key.

Instances

Instances details
Data Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

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 #

Generic Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Show Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

NFData Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

Methods

rnf :: Key -> () #

Eq Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

Methods

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

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

Ord Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

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 #

Hashable Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

Methods

hashWithSalt :: Int -> Key -> Int #

hash :: Key -> Int #

IsEncoding Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

type Rep Key Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

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

data Nonce Source #

An opaque AES256GCM nonce.

Instances

Instances details
Data Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

Methods

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

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

toConstr :: Nonce -> Constr #

dataTypeOf :: Nonce -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

Associated Types

type Rep Nonce :: Type -> Type #

Methods

from :: Nonce -> Rep Nonce x #

to :: Rep Nonce x -> Nonce #

Show Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

Methods

showsPrec :: Int -> Nonce -> ShowS #

show :: Nonce -> String #

showList :: [Nonce] -> ShowS #

NFData Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

Methods

rnf :: Nonce -> () #

Eq Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

Methods

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

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

Ord Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

Methods

compare :: Nonce -> Nonce -> Ordering #

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

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

(>) :: Nonce -> Nonce -> Bool #

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

max :: Nonce -> Nonce -> Nonce #

min :: Nonce -> Nonce -> Nonce #

Hashable Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

Methods

hashWithSalt :: Int -> Nonce -> Int #

hash :: Nonce -> Int #

IsEncoding Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

IsNonce Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

type Rep Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.AEAD.AES256GCM

type Rep Nonce = D1 ('MetaData "Nonce" "Crypto.Saltine.Internal.AEAD.AES256GCM" "saltine-0.2.1.0-inplace" 'True) (C1 ('MetaCons "Nonce" 'PrefixI 'True) (S1 ('MetaSel ('Just "unNonce") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

aead Source #

Arguments

:: Key 
-> Nonce 
-> ByteString

Message

-> ByteString

AAD

-> ByteString

Ciphertext

Encrypts a message. It is infeasible for an attacker to decrypt the message so long as the Nonce is never repeated.

aeadOpen Source #

Arguments

:: Key 
-> Nonce 
-> ByteString

Ciphertext

-> ByteString

AAD

-> Maybe ByteString

Message

Decrypts a message. Returns Nothing if the keys and message do not match.

aeadDetached Source #

Arguments

:: Key 
-> Nonce 
-> ByteString

Message

-> ByteString

AAD

-> (ByteString, ByteString)

Tag, Ciphertext

Encrypts a message. It is infeasible for an attacker to decrypt the message so long as the Nonce is never repeated.

aeadOpenDetached Source #

Arguments

:: Key 
-> Nonce 
-> ByteString

Tag

-> ByteString

Ciphertext

-> ByteString

AAD

-> Maybe ByteString

Message

Decrypts a message. Returns Nothing if the keys and message do not match.

newKey :: IO Key Source #

Creates a random AES256GCM key

newNonce :: IO Nonce Source #

Creates a random AES256GCM nonce