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

Description

 
Synopsis

Documentation

sign_bytes :: Int Source #

The maximum size of a signature prepended to a message to form a signed message.

sign_publickeybytes :: Int Source #

The size of a public key for signing verification

sign_secretkeybytes :: Int Source #

The size of a secret key for signing

c_sign_keypair Source #

Arguments

:: Ptr CChar

Public key output buffer

-> Ptr CChar

Secret key output buffer

-> IO CInt

Always 0

c_sign Source #

Arguments

:: Ptr CChar

Signed message output buffer

-> Ptr CULLong

Length of signed message

-> Ptr CChar

Constant message buffer

-> CULLong

Length of message input buffer

-> Ptr CChar

Constant secret key buffer

-> IO CInt

Always 0

c_sign_open Source #

Arguments

:: Ptr CChar

Message output buffer

-> Ptr CULLong

Length of message

-> Ptr CChar

Constant signed message buffer

-> CULLong

Length of signed message buffer

-> Ptr CChar

Public key buffer

-> IO CInt

0 if signature is verifiable, -1 otherwise

c_sign_detached Source #

Arguments

:: Ptr CChar

Signature output buffer

-> Ptr CULLong

Length of the signature

-> Ptr CChar

Constant message buffer

-> CULLong

Length of message buffer

-> Ptr CChar

Constant secret key buffer

-> IO CInt 

c_sign_verify_detached Source #

Arguments

:: Ptr CChar

Signature buffer

-> Ptr CChar

Constant signed message buffer

-> CULLong

Length of signed message buffer

-> Ptr CChar

Public key buffer

-> IO CInt 

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

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

Associated Types

type Rep SecretKey :: Type -> Type #

Show SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

NFData SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Methods

rnf :: SecretKey -> () #

Eq SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Ord SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Hashable SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

IsEncoding SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

type Rep SecretKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

type Rep SecretKey = D1 ('MetaData "SecretKey" "Crypto.Saltine.Internal.Sign" "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.Sign

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

Associated Types

type Rep PublicKey :: Type -> Type #

Show PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

NFData PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Methods

rnf :: PublicKey -> () #

Eq PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Ord PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Hashable PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

IsEncoding PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

type Rep PublicKey Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

type Rep PublicKey = D1 ('MetaData "PublicKey" "Crypto.Saltine.Internal.Sign" "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.Sign

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

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

NFData Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Methods

rnf :: Keypair -> () #

Eq Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Methods

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

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

Ord Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Hashable Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Methods

hashWithSalt :: Int -> Keypair -> Int #

hash :: Keypair -> Int #

type Rep Keypair Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

type Rep Keypair = D1 ('MetaData "Keypair" "Crypto.Saltine.Internal.Sign" "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 Signature Source #

A signature for a Message

Constructors

Signature 

Instances

Instances details
Data Signature Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Methods

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

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

toConstr :: Signature -> Constr #

dataTypeOf :: Signature -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Signature Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Associated Types

type Rep Signature :: Type -> Type #

Show Signature Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

NFData Signature Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Methods

rnf :: Signature -> () #

Eq Signature Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Ord Signature Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

Hashable Signature Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

IsEncoding Signature Source #

Actual signatures may be shorter, but not when generated with saltine.

Instance details

Defined in Crypto.Saltine.Internal.Sign

type Rep Signature Source # 
Instance details

Defined in Crypto.Saltine.Internal.Sign

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