| License | BSD-style | 
|---|---|
| Maintainer | Vincent Hanquez <vincent@snarc.org> | 
| Stability | experimental | 
| Portability | Good | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Crypto.PubKey.DSA
Description
An implementation of the Digital Signature Algorithm (DSA)
Synopsis
- data Params = Params {}
- data Signature = Signature {}
- data PublicKey = PublicKey {}
- data PrivateKey = PrivateKey {}
- type PublicNumber = Integer
- type PrivateNumber = Integer
- generatePrivate :: MonadRandom m => Params -> m PrivateNumber
- calculatePublic :: Params -> PrivateNumber -> PublicNumber
- sign :: (ByteArrayAccess msg, HashAlgorithm hash, MonadRandom m) => PrivateKey -> hash -> msg -> m Signature
- signWith :: (ByteArrayAccess msg, HashAlgorithm hash) => Integer -> PrivateKey -> hash -> msg -> Maybe Signature
- verify :: (ByteArrayAccess msg, HashAlgorithm hash) => hash -> PublicKey -> Signature -> msg -> Bool
- data KeyPair = KeyPair Params PublicNumber PrivateNumber
- toPublicKey :: KeyPair -> PublicKey
- toPrivateKey :: KeyPair -> PrivateKey
Documentation
Represent DSA parameters namely P, G, and Q.
Instances
| Eq Params Source # | |
| Data Params Source # | |
| Defined in Crypto.PubKey.DSA Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Params -> c Params # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Params # toConstr :: Params -> Constr # dataTypeOf :: Params -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Params) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Params) # gmapT :: (forall b. Data b => b -> b) -> Params -> Params # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Params -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Params -> r # gmapQ :: (forall d. Data d => d -> u) -> Params -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Params -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Params -> m Params # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Params -> m Params # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Params -> m Params # | |
| Read Params Source # | |
| Show Params Source # | |
| NFData Params Source # | |
| Defined in Crypto.PubKey.DSA | |
Represent a DSA signature namely R and S.
Instances
| Eq Signature Source # | |
| Data Signature Source # | |
| Defined in Crypto.PubKey.DSA 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 :: (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 # | |
| Read Signature Source # | |
| Show Signature Source # | |
| NFData Signature Source # | |
| Defined in Crypto.PubKey.DSA | |
Represent a DSA public key.
Constructors
| PublicKey | |
| Fields 
 | |
Instances
| Eq PublicKey Source # | |
| Data PublicKey Source # | |
| Defined in Crypto.PubKey.DSA 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 :: (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.DSA | |
data PrivateKey Source #
Represent a DSA private key.
Only x need to be secret. the DSA parameters are publicly shared with the other side.
Constructors
| PrivateKey | |
| Fields 
 | |
Instances
| Eq PrivateKey Source # | |
| Defined in Crypto.PubKey.DSA | |
| Data PrivateKey Source # | |
| Defined in Crypto.PubKey.DSA 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 :: (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.DSA Methods readsPrec :: Int -> ReadS PrivateKey # readList :: ReadS [PrivateKey] # readPrec :: ReadPrec PrivateKey # readListPrec :: ReadPrec [PrivateKey] # | |
| Show PrivateKey Source # | |
| Defined in Crypto.PubKey.DSA Methods showsPrec :: Int -> PrivateKey -> ShowS # show :: PrivateKey -> String # showList :: [PrivateKey] -> ShowS # | |
| NFData PrivateKey Source # | |
| Defined in Crypto.PubKey.DSA Methods rnf :: PrivateKey -> () # | |
type PublicNumber = Integer Source #
DSA Public Number, usually embedded in DSA Public Key
type PrivateNumber = Integer Source #
DSA Private Number, usually embedded in DSA Private Key
Generation
generatePrivate :: MonadRandom m => Params -> m PrivateNumber Source #
generate a private number with no specific property this number is usually called X in DSA text.
calculatePublic :: Params -> PrivateNumber -> PublicNumber Source #
Calculate the public number from the parameters and the private key
Signature primitive
sign :: (ByteArrayAccess msg, HashAlgorithm hash, MonadRandom m) => PrivateKey -> hash -> msg -> m Signature Source #
sign message using the private key.
Arguments
| :: (ByteArrayAccess msg, HashAlgorithm hash) | |
| => Integer | k random number | 
| -> PrivateKey | private key | 
| -> hash | hash function | 
| -> msg | message to sign | 
| -> Maybe Signature | 
sign message using the private key and an explicit k number.
Verification primitive
verify :: (ByteArrayAccess msg, HashAlgorithm hash) => hash -> PublicKey -> Signature -> msg -> Bool Source #
verify a bytestring using the public key.
Key pair
Represent a DSA key pair
Constructors
| KeyPair Params PublicNumber PrivateNumber | 
Instances
| Eq KeyPair Source # | |
| Data KeyPair Source # | |
| Defined in Crypto.PubKey.DSA 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 :: (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.DSA | |
toPublicKey :: KeyPair -> PublicKey Source #
Public key of a DSA Key pair
toPrivateKey :: KeyPair -> PrivateKey Source #
Private key of a DSA Key pair