crypton-1.0.0: Cryptography Primitives sink
LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
PortabilityGood
Safe HaskellSafe-Inferred
LanguageHaskell2010

Crypto.PubKey.RSA

Description

 
Synopsis

Documentation

data Error Source #

error possible during encryption, decryption or signing.

Constructors

MessageSizeIncorrect

the message to decrypt is not of the correct size (need to be == private_size)

MessageTooLong

the message to encrypt is too long

MessageNotRecognized

the message decrypted doesn't have a PKCS15 structure (0 2 .. 0 msg)

SignatureTooLong

the message's digest is too long

InvalidParameters

some parameters lead to breaking assumptions.

Instances

Instances details
Show Error Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Eq Error Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

Methods

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

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

data PublicKey Source #

Represent a RSA public key

Constructors

PublicKey 

Fields

Instances

Instances details
Data PublicKey Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

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 #

Read PublicKey Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

Show PublicKey Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

NFData PublicKey Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

Methods

rnf :: PublicKey -> () #

Eq PublicKey Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

data PrivateKey Source #

Represent a RSA private key.

Only the pub, d fields are mandatory to fill.

p, q, dP, dQ, qinv are by-product during RSA generation, but are useful to record here to speed up massively the decrypt and sign operation.

implementations can leave optional fields to 0.

Constructors

PrivateKey 

Fields

Instances

Instances details
Data PrivateKey Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

Methods

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

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

toConstr :: PrivateKey -> Constr #

dataTypeOf :: PrivateKey -> DataType #

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

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

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

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

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

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

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

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

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

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

Read PrivateKey Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

Show PrivateKey Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

NFData PrivateKey Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

Methods

rnf :: PrivateKey -> () #

Eq PrivateKey Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

data Blinder Source #

Blinder which is used to obfuscate the timing of the decryption primitive (used by decryption and signing).

Constructors

Blinder !Integer !Integer 

Instances

Instances details
Show Blinder Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

Eq Blinder Source # 
Instance details

Defined in Crypto.PubKey.RSA.Types

Methods

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

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

Generation function

generateWith Source #

Arguments

:: (Integer, Integer)

chosen distinct primes p and q

-> Int

size in bytes

-> Integer

RSA public exponent e

-> Maybe (PublicKey, PrivateKey) 

Generate a key pair given p and q.

p and q need to be distinct prime numbers.

e need to be coprime to phi=(p-1)*(q-1). If that's not the case, the function will not return a key pair. A small hamming weight results in better performance.

  • e=0x10001 is a popular choice
  • e=3 is popular as well, but proven to not be as secure for some cases.

generate Source #

Arguments

:: MonadRandom m 
=> Int

size in bytes

-> Integer

RSA public exponent e

-> m (PublicKey, PrivateKey) 

generate a pair of (private, public) key of size in bytes.

generateBlinder Source #

Arguments

:: MonadRandom m 
=> Integer

RSA public N parameter.

-> m Blinder 

Generate a blinder to use with decryption and signing operation

the unique parameter apart from the random number generator is the public key value N.