Safe Haskell | None |
---|---|
Language | Haskell2010 |
An interface to asymmetric cipher keypair.
Synopsis
- class (Eq k, Typeable k, PKey k) => PublicKey k where
- fromPublicKey :: k -> SomePublicKey
- toPublicKey :: SomePublicKey -> Maybe k
- class PublicKey a => KeyPair a where
- fromKeyPair :: a -> SomeKeyPair
- toKeyPair :: SomeKeyPair -> Maybe a
- data SomePublicKey
- data SomeKeyPair
Documentation
class (Eq k, Typeable k, PKey k) => PublicKey k where Source #
Instances of this class has at least public portion of a keypair. They might or might not have the private key.
Nothing
fromPublicKey :: k -> SomePublicKey Source #
Wrap an arbitrary public key into polymorphic type
SomePublicKey
.
toPublicKey :: SomePublicKey -> Maybe k Source #
Cast from the polymorphic type SomePublicKey
to the concrete
type. Return Nothing
if failed.
Instances
PublicKey RSAKeyPair Source # | |
Defined in OpenSSL.EVP.PKey | |
PublicKey RSAPubKey Source # | |
Defined in OpenSSL.EVP.PKey | |
PublicKey DSAKeyPair Source # | |
Defined in OpenSSL.EVP.PKey | |
PublicKey DSAPubKey Source # | |
Defined in OpenSSL.EVP.PKey | |
PublicKey SomeKeyPair Source # | |
Defined in OpenSSL.EVP.PKey | |
PublicKey SomePublicKey Source # | |
Defined in OpenSSL.EVP.PKey |
class PublicKey a => KeyPair a where Source #
Instances of this class has both of public and private portions of a keypair.
Nothing
fromKeyPair :: a -> SomeKeyPair Source #
Wrap an arbitrary keypair into polymorphic type SomeKeyPair
.
toKeyPair :: SomeKeyPair -> Maybe a Source #
Cast from the polymorphic type SomeKeyPair
to the concrete
type. Return Nothing
if failed.
Instances
KeyPair RSAKeyPair Source # | |
Defined in OpenSSL.EVP.PKey fromKeyPair :: RSAKeyPair -> SomeKeyPair Source # toKeyPair :: SomeKeyPair -> Maybe RSAKeyPair Source # | |
KeyPair DSAKeyPair Source # | |
Defined in OpenSSL.EVP.PKey fromKeyPair :: DSAKeyPair -> SomeKeyPair Source # toKeyPair :: SomeKeyPair -> Maybe DSAKeyPair Source # | |
KeyPair SomeKeyPair Source # | |
Defined in OpenSSL.EVP.PKey fromKeyPair :: SomeKeyPair -> SomeKeyPair Source # toKeyPair :: SomeKeyPair -> Maybe SomeKeyPair Source # |
data SomePublicKey Source #
This is an opaque type to hold an arbitrary public key in it. The
actual key type can be safelly type-casted using toPublicKey
.
Instances
Eq SomePublicKey Source # | |
Defined in OpenSSL.EVP.PKey (==) :: SomePublicKey -> SomePublicKey -> Bool # (/=) :: SomePublicKey -> SomePublicKey -> Bool # | |
PKey SomePublicKey Source # | |
Defined in OpenSSL.EVP.PKey toPKey :: SomePublicKey -> IO VaguePKey Source # fromPKey :: VaguePKey -> IO (Maybe SomePublicKey) Source # pkeySize :: SomePublicKey -> Int Source # pkeyDefaultMD :: SomePublicKey -> IO Digest Source # | |
PublicKey SomePublicKey Source # | |
Defined in OpenSSL.EVP.PKey |
data SomeKeyPair Source #
This is an opaque type to hold an arbitrary keypair in it. The
actual key type can be safelly type-casted using toKeyPair
.
Instances
Eq SomeKeyPair Source # | |
Defined in OpenSSL.EVP.PKey (==) :: SomeKeyPair -> SomeKeyPair -> Bool # (/=) :: SomeKeyPair -> SomeKeyPair -> Bool # | |
PKey SomeKeyPair Source # | |
Defined in OpenSSL.EVP.PKey toPKey :: SomeKeyPair -> IO VaguePKey Source # fromPKey :: VaguePKey -> IO (Maybe SomeKeyPair) Source # pkeySize :: SomeKeyPair -> Int Source # pkeyDefaultMD :: SomeKeyPair -> IO Digest Source # | |
KeyPair SomeKeyPair Source # | |
Defined in OpenSSL.EVP.PKey fromKeyPair :: SomeKeyPair -> SomeKeyPair Source # toKeyPair :: SomeKeyPair -> Maybe SomeKeyPair Source # | |
PublicKey SomeKeyPair Source # | |
Defined in OpenSSL.EVP.PKey |
Orphan instances
PKey RSAKeyPair Source # | |
toPKey :: RSAKeyPair -> IO VaguePKey Source # fromPKey :: VaguePKey -> IO (Maybe RSAKeyPair) Source # pkeySize :: RSAKeyPair -> Int Source # pkeyDefaultMD :: RSAKeyPair -> IO Digest Source # | |
PKey RSAPubKey Source # | |
PKey DSAKeyPair Source # | |
toPKey :: DSAKeyPair -> IO VaguePKey Source # fromPKey :: VaguePKey -> IO (Maybe DSAKeyPair) Source # pkeySize :: DSAKeyPair -> Int Source # pkeyDefaultMD :: DSAKeyPair -> IO Digest Source # | |
PKey DSAPubKey Source # | |