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

Crypto.Saltine.Internal.Box

Description

 
Synopsis

Documentation

box_publickeybytes :: Int Source #

Size of a crypto_box public key

box_secretkeybytes :: Int Source #

Size of a crypto_box secret key

box_noncebytes :: Int Source #

Size of a crypto_box nonce

box_zerobytes :: Int Source #

Size of 0-padding prepended to messages before using crypto_box or after using crypto_box_open

box_boxzerobytes :: Int Source #

Size of 0-padding prepended to ciphertext before using crypto_box_open or after using crypto_box.

box_beforenmbytes :: Int Source #

Size of a crypto_box_beforenm-generated combined key

box_sealbytes :: Int Source #

Amount by which ciphertext is longer than plaintext in sealed boxes

c_box_keypair Source #

Arguments

:: Ptr CChar

Public key

-> Ptr CChar

Secret key

-> IO CInt

Always 0

Should always return a 0.

c_box_easy Source #

Arguments

:: Ptr CChar

Cipher output buffer

-> Ptr CChar

Constant message input buffer

-> CULLong

Length of message input buffer

-> Ptr CChar

Constant nonce buffer

-> Ptr CChar

Constant public key buffer

-> Ptr CChar

Constant secret key buffer

-> IO CInt

Always 0

The secretbox C API uses C strings.

c_box_open_easy Source #

Arguments

:: Ptr CChar

Message output buffer

-> Ptr CChar

Constant ciphertext input buffer

-> CULLong

Length of message input buffer

-> Ptr CChar

Constant nonce buffer

-> Ptr CChar

Constant public key buffer

-> Ptr CChar

Constant secret key buffer

-> IO CInt

0 for success, -1 for failure to verify

The secretbox C API uses C strings.

c_box_beforenm Source #

Arguments

:: Ptr CChar

Combined key output buffer

-> Ptr CChar

Constant public key buffer

-> Ptr CChar

Constant secret key buffer

-> IO CInt

Always 0

Single target key precompilation.

c_box_easy_afternm Source #

Arguments

:: Ptr CChar

Cipher output buffer

-> Ptr CChar

Constant message input buffer

-> CULLong

Length of message input buffer (incl. 0s)

-> Ptr CChar

Constant nonce buffer

-> Ptr CChar

Constant combined key buffer

-> IO CInt

Always 0

Precompiled key crypto box. Uses C strings.

c_box_open_easy_afternm Source #

Arguments

:: Ptr CChar

Message output buffer

-> Ptr CChar

Constant ciphertext input buffer

-> CULLong

Length of message input buffer (incl. 0s)

-> Ptr CChar

Constant nonce buffer

-> Ptr CChar

Constant combined key buffer

-> IO CInt

0 for success, -1 for failure to verify

The secretbox C API uses C strings.

c_box_seal Source #

Arguments

:: Ptr CChar

Cipher output buffer

-> Ptr CChar

Constant message input buffer

-> CULLong

Length of message input buffer

-> Ptr CChar

Constant public key buffer

-> IO CInt

Always 0

The sealedbox C API uses C strings.

c_box_seal_open Source #

Arguments

:: Ptr CChar

Message output buffer

-> Ptr CChar

Constant ciphertext input buffer

-> CULLong

Length of message input buffer

-> Ptr CChar

Constant public key buffer

-> Ptr CChar

Constant secret key buffer

-> IO CInt

0 for success, -1 for failure to decrypt

The sealedbox C API uses C strings.

newtype SecretKey Source #

An opaque box cryptographic secret key.

Constructors

SK 

Fields

Instances

Instances details
Data SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Methods

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

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

toConstr :: SecretKey -> Constr #

dataTypeOf :: SecretKey -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Associated Types

type Rep SecretKey :: Type -> Type #

Show SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

NFData SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Methods

rnf :: SecretKey -> () #

Eq SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Ord SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Hashable SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

IsEncoding SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

type Rep SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

type Rep SecretKey = D1 ('MetaData "SecretKey" "Crypto.Saltine.Internal.Box" "saltine-0.2.1.0-inplace" 'True) (C1 ('MetaCons "SK" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype PublicKey Source #

An opaque box cryptographic public key.

Constructors

PK 

Fields

Instances

Instances details
Data PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Methods

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

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

toConstr :: PublicKey -> Constr #

dataTypeOf :: PublicKey -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Associated Types

type Rep PublicKey :: Type -> Type #

Show PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

NFData PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Methods

rnf :: PublicKey -> () #

Eq PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Ord PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Hashable PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

IsEncoding PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

type Rep PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

type Rep PublicKey = D1 ('MetaData "PublicKey" "Crypto.Saltine.Internal.Box" "saltine-0.2.1.0-inplace" 'True) (C1 ('MetaCons "PK" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data Keypair Source #

A convenience type for keypairs

Constructors

Keypair 

Instances

Instances details
Data Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Methods

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

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

toConstr :: Keypair -> Constr #

dataTypeOf :: Keypair -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Associated Types

type Rep Keypair :: Type -> Type #

Methods

from :: Keypair -> Rep Keypair x #

to :: Rep Keypair x -> Keypair #

Show Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

NFData Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Methods

rnf :: Keypair -> () #

Eq Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Methods

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

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

Ord Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Hashable Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Methods

hashWithSalt :: Int -> Keypair -> Int #

hash :: Keypair -> Int #

type Rep Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

type Rep Keypair = D1 ('MetaData "Keypair" "Crypto.Saltine.Internal.Box" "saltine-0.2.1.0-inplace" 'False) (C1 ('MetaCons "Keypair" 'PrefixI 'True) (S1 ('MetaSel ('Just "secretKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SecretKey) :*: S1 ('MetaSel ('Just "publicKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PublicKey)))

newtype CombinedKey Source #

An opaque boxAfterNM cryptographic combined key.

Constructors

CK 

Fields

Instances

Instances details
Data CombinedKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Methods

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

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

toConstr :: CombinedKey -> Constr #

dataTypeOf :: CombinedKey -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic CombinedKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Associated Types

type Rep CombinedKey :: Type -> Type #

Show CombinedKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

NFData CombinedKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Methods

rnf :: CombinedKey -> () #

Eq CombinedKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Ord CombinedKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Hashable CombinedKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

IsEncoding CombinedKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

type Rep CombinedKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

type Rep CombinedKey = D1 ('MetaData "CombinedKey" "Crypto.Saltine.Internal.Box" "saltine-0.2.1.0-inplace" 'True) (C1 ('MetaCons "CK" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype Nonce Source #

An opaque box nonce.

Constructors

Nonce 

Fields

Instances

Instances details
Data Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

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.Box

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.Box

Methods

showsPrec :: Int -> Nonce -> ShowS #

show :: Nonce -> String #

showList :: [Nonce] -> ShowS #

NFData Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Methods

rnf :: Nonce -> () #

Eq Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

Methods

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

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

Ord Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

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.Box

Methods

hashWithSalt :: Int -> Nonce -> Int #

hash :: Nonce -> Int #

IsEncoding Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

IsNonce Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

type Rep Nonce Source # 
Instance details

Defined in Crypto.Saltine.Internal.Box

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