Copyright | (c) Max Amanshauser 2021 |
---|---|
License | MIT |
Maintainer | max@lambdalifting.org |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Crypto.Saltine.Internal.Sign
Description
Synopsis
- sign_bytes :: Int
- sign_publickeybytes :: Int
- sign_secretkeybytes :: Int
- c_sign_keypair :: Ptr CChar -> Ptr CChar -> IO CInt
- c_sign :: Ptr CChar -> Ptr CULLong -> Ptr CChar -> CULLong -> Ptr CChar -> IO CInt
- c_sign_open :: Ptr CChar -> Ptr CULLong -> Ptr CChar -> CULLong -> Ptr CChar -> IO CInt
- c_sign_detached :: Ptr CChar -> Ptr CULLong -> Ptr CChar -> CULLong -> Ptr CChar -> IO CInt
- c_sign_verify_detached :: Ptr CChar -> Ptr CChar -> CULLong -> Ptr CChar -> IO CInt
- c_sign_ed25519_pk_to_curve25519 :: Ptr CChar -> Ptr CChar -> IO CInt
- c_sign_ed25519_sk_to_curve25519 :: Ptr CChar -> Ptr CChar -> IO CInt
- newtype SecretKey = SK {
- unSK :: ByteString
- newtype PublicKey = PK {
- unPK :: ByteString
- data Keypair = Keypair {}
- newtype Signature = Signature {}
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
An opaque box
cryptographic secret key.
Constructors
SK | |
Fields
|
Instances
An opaque box
cryptographic public key.
Constructors
PK | |
Fields
|
Instances
NFData PublicKey Source # | |||||
Defined in Crypto.Saltine.Internal.Sign | |||||
Data PublicKey Source # | |||||
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 # | |||||
Defined in Crypto.Saltine.Internal.Sign Associated Types
| |||||
Show PublicKey Source # | |||||
Eq PublicKey Source # | |||||
Ord PublicKey Source # | |||||
Hashable PublicKey Source # | |||||
Defined in Crypto.Saltine.Internal.Sign | |||||
IsEncoding PublicKey Source # | |||||
Defined in Crypto.Saltine.Internal.Sign Methods encode :: PublicKey -> ByteString Source # decode :: ByteString -> Maybe PublicKey Source # encoded :: (Choice p, Applicative f) => p PublicKey (f PublicKey) -> p ByteString (f ByteString) Source # | |||||
type Rep PublicKey Source # | |||||
Defined in Crypto.Saltine.Internal.Sign type Rep PublicKey = D1 ('MetaData "PublicKey" "Crypto.Saltine.Internal.Sign" "saltine-0.2.2.0-inplace" 'True) (C1 ('MetaCons "PK" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPK") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
A convenience type for keypairs
Instances
NFData Keypair Source # | |||||
Defined in Crypto.Saltine.Internal.Sign | |||||
Data Keypair Source # | |||||
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 # | |||||
Defined in Crypto.Saltine.Internal.Sign Associated Types
| |||||
Show Keypair Source # | |||||
Eq Keypair Source # | |||||
Ord Keypair Source # | |||||
Defined in Crypto.Saltine.Internal.Sign | |||||
Hashable Keypair Source # | |||||
Defined in Crypto.Saltine.Internal.Sign | |||||
type Rep Keypair Source # | |||||
Defined in Crypto.Saltine.Internal.Sign type Rep Keypair = D1 ('MetaData "Keypair" "Crypto.Saltine.Internal.Sign" "saltine-0.2.2.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))) |
A signature for a Message
Constructors
Signature | |
Fields |
Instances
NFData Signature Source # | |||||
Defined in Crypto.Saltine.Internal.Sign | |||||
Data Signature Source # | |||||
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 # | |||||
Defined in Crypto.Saltine.Internal.Sign Associated Types
| |||||
Show Signature Source # | |||||
Eq Signature Source # | |||||
Ord Signature Source # | |||||
Hashable Signature Source # | |||||
Defined in Crypto.Saltine.Internal.Sign | |||||
IsEncoding Signature Source # | Actual signatures may be shorter, but not when generated with saltine. | ||||
Defined in Crypto.Saltine.Internal.Sign Methods encode :: Signature -> ByteString Source # decode :: ByteString -> Maybe Signature Source # encoded :: (Choice p, Applicative f) => p Signature (f Signature) -> p ByteString (f ByteString) Source # | |||||
type Rep Signature Source # | |||||
Defined in Crypto.Saltine.Internal.Sign type Rep Signature = D1 ('MetaData "Signature" "Crypto.Saltine.Internal.Sign" "saltine-0.2.2.0-inplace" 'True) (C1 ('MetaCons "Signature" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |