| License | BSD-style | 
|---|---|
| Maintainer | Vincent Hanquez <vincent@snarc.org> | 
| Stability | experimental | 
| Portability | Good | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Crypto.PubKey.RSA.Types
Description
Synopsis
- data Error
- data Blinder = Blinder !Integer !Integer
- data PublicKey = PublicKey {}
- data PrivateKey = PrivateKey {}
- newtype KeyPair = KeyPair PrivateKey
- toPublicKey :: KeyPair -> PublicKey
- toPrivateKey :: KeyPair -> PrivateKey
- private_size :: PrivateKey -> Int
- private_n :: PrivateKey -> Integer
- private_e :: PrivateKey -> Integer
Documentation
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. | 
Blinder which is used to obfuscate the timing of the decryption primitive (used by decryption and signing).
Instances
Represent a RSA public key
Constructors
| PublicKey | |
Instances
| Data PublicKey Source # | |
| 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 # | |
| Show PublicKey Source # | |
| NFData PublicKey Source # | |
| Defined in Crypto.PubKey.RSA.Types | |
| Eq PublicKey Source # | |
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
| Data PrivateKey Source # | |
| 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 # | |
| Defined in Crypto.PubKey.RSA.Types Methods readsPrec :: Int -> ReadS PrivateKey # readList :: ReadS [PrivateKey] # readPrec :: ReadPrec PrivateKey # readListPrec :: ReadPrec [PrivateKey] # | |
| Show PrivateKey Source # | |
| Defined in Crypto.PubKey.RSA.Types Methods showsPrec :: Int -> PrivateKey -> ShowS # show :: PrivateKey -> String # showList :: [PrivateKey] -> ShowS # | |
| NFData PrivateKey Source # | |
| Defined in Crypto.PubKey.RSA.Types Methods rnf :: PrivateKey -> () # | |
| Eq PrivateKey Source # | |
| Defined in Crypto.PubKey.RSA.Types | |
Represent RSA KeyPair
note the RSA private key contains already an instance of public key for efficiency
Constructors
| KeyPair PrivateKey | 
Instances
| Data KeyPair Source # | |
| Defined in Crypto.PubKey.RSA.Types 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 # | |
| Read KeyPair Source # | |
| Show KeyPair Source # | |
| NFData KeyPair Source # | |
| Defined in Crypto.PubKey.RSA.Types | |
| Eq KeyPair Source # | |
toPublicKey :: KeyPair -> PublicKey Source #
Public key of a RSA KeyPair
toPrivateKey :: KeyPair -> PrivateKey Source #
Private key of a RSA KeyPair
private_size :: PrivateKey -> Int Source #
get the size in bytes from a private key
private_n :: PrivateKey -> Integer Source #
get n from a private key
private_e :: PrivateKey -> Integer Source #
get e from a private key