License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | Haskell98 |
- Types
- Common extension usually found in x509v3
- Accessor turning extension into a specific one
- Certificate Revocation List (CRL)
- Naming
- Certificate Chain
- marshall between CertificateChain and CertificateChainRaw
- Signed types and marshalling
- Parametrized Signed accessor
- Hash distinguished names related function
Read/Write X509 Certificate, CRL and their signed equivalents.
Follows RFC5280 / RFC6818
- type SignedCertificate = SignedExact Certificate
- type SignedCRL = SignedExact CRL
- data Certificate = Certificate {}
- data PubKey
- data PubKeyEC
- = PubKeyEC_Prime { }
- | PubKeyEC_Named { }
- newtype SerializedPoint = SerializedPoint ByteString
- data PrivKey
- pubkeyToAlg :: PubKey -> PubKeyALG
- privkeyToAlg :: PrivKey -> PubKeyALG
- data HashALG
- data PubKeyALG
- data SignatureALG
- class Extension a where
- data ExtBasicConstraints = ExtBasicConstraints Bool (Maybe Integer)
- data ExtKeyUsage = ExtKeyUsage [ExtKeyUsageFlag]
- data ExtKeyUsageFlag
- data ExtExtendedKeyUsage = ExtExtendedKeyUsage [ExtKeyUsagePurpose]
- data ExtKeyUsagePurpose
- data ExtSubjectKeyId = ExtSubjectKeyId ByteString
- data ExtSubjectAltName = ExtSubjectAltName [AltName]
- data ExtAuthorityKeyId = ExtAuthorityKeyId ByteString
- data ExtCrlDistributionPoints = ExtCrlDistributionPoints [DistributionPoint]
- data AltName
- data DistributionPoint
- data ReasonFlag
- extensionGet :: Extension a => Extensions -> Maybe a
- extensionGetE :: Extension a => Extensions -> Maybe (Either String a)
- extensionDecode :: Extension a => ExtensionRaw -> Maybe (Either String a)
- extensionEncode :: Extension a => Bool -> a -> ExtensionRaw
- data ExtensionRaw = ExtensionRaw {
- extRawOID :: OID
- extRawCritical :: Bool
- extRawASN1 :: [ASN1]
- newtype Extensions = Extensions (Maybe [ExtensionRaw])
- data CRL = CRL {}
- data RevokedCertificate = RevokedCertificate {}
- newtype DistinguishedName = DistinguishedName {}
- data DnElement
- data ASN1CharacterString :: * = ASN1CharacterString {}
- getDnElement :: DnElement -> DistinguishedName -> Maybe ASN1CharacterString
- newtype CertificateChain = CertificateChain [SignedExact Certificate]
- newtype CertificateChainRaw = CertificateChainRaw [ByteString]
- decodeCertificateChain :: CertificateChainRaw -> Either (Int, String) CertificateChain
- encodeCertificateChain :: CertificateChain -> CertificateChainRaw
- data (Show a, Eq a, ASN1Object a) => Signed a = Signed {}
- data (Show a, Eq a, ASN1Object a) => SignedExact a
- getSigned :: SignedExact a -> Signed a
- getSignedData :: (Show a, Eq a, ASN1Object a) => SignedExact a -> ByteString
- objectToSignedExact :: (Show a, Eq a, ASN1Object a) => (ByteString -> (ByteString, SignatureALG, r)) -> a -> (SignedExact a, r)
- objectToSignedExactF :: (Functor f, Show a, Eq a, ASN1Object a) => (ByteString -> f (ByteString, SignatureALG)) -> a -> f (SignedExact a)
- encodeSignedObject :: SignedExact a -> ByteString
- decodeSignedObject :: (Show a, Eq a, ASN1Object a) => ByteString -> Either String (SignedExact a)
- getCertificate :: SignedCertificate -> Certificate
- getCRL :: SignedCRL -> CRL
- decodeSignedCertificate :: ByteString -> Either String SignedCertificate
- decodeSignedCRL :: ByteString -> Either String SignedCRL
- hashDN :: DistinguishedName -> ByteString
- hashDN_old :: DistinguishedName -> ByteString
Types
type SignedCertificate = SignedExact Certificate Source #
A Signed Certificate
type SignedCRL = SignedExact CRL Source #
A Signed CRL
data Certificate Source #
X.509 Certificate type.
This type doesn't include the signature, it's describe in the RFC as tbsCertificate.
Certificate | |
|
Public key types known and used in X.509
Elliptic Curve Public Key
TODO: missing support for binary curve.
newtype SerializedPoint Source #
Serialized Elliptic Curve Point
Private key types known and used in X.509
PrivKeyRSA PrivateKey | RSA private key |
PrivKeyDSA PrivateKey | DSA private key |
pubkeyToAlg :: PubKey -> PubKeyALG Source #
Convert a Public key to the Public Key Algorithm type
privkeyToAlg :: PrivKey -> PubKeyALG Source #
Convert a Public key to the Public Key Algorithm type
Hash Algorithm
Public Key Algorithm
PubKeyALG_RSA | RSA Public Key algorithm |
PubKeyALG_RSAPSS | RSA PSS Key algorithm (RFC 3447) |
PubKeyALG_DSA | DSA Public Key algorithm |
PubKeyALG_EC | ECDSA & ECDH Public Key algorithm |
PubKeyALG_DH | Diffie Hellman Public Key algorithm |
PubKeyALG_Unknown OID | Unknown Public Key algorithm |
data SignatureALG Source #
Signature Algorithm often composed of a public key algorithm and a hash algorithm
class Extension a where Source #
Extension class.
each extension have a unique OID associated, and a way to encode and decode an ASN1 stream.
Common extension usually found in x509v3
data ExtBasicConstraints Source #
Basic Constraints
data ExtKeyUsage Source #
Describe key usage
data ExtKeyUsageFlag Source #
key usage flag that is found in the key usage extension field.
data ExtExtendedKeyUsage Source #
Extended key usage extension
data ExtKeyUsagePurpose Source #
Key usage purposes for the ExtendedKeyUsage extension
data ExtSubjectKeyId Source #
Provide a way to identify a public key by a short hash.
data ExtSubjectAltName Source #
Provide a way to supply alternate name that can be used for matching host name.
data ExtAuthorityKeyId Source #
Provide a mean to identify the public key corresponding to the private key used to signed a certificate.
data ExtCrlDistributionPoints Source #
Identify how CRL information is obtained
Different naming scheme use by the extension.
Not all name types are available, missing: otherName x400Address directoryName ediPartyName registeredID
data DistributionPoint Source #
Distribution point as either some GeneralNames or a DN
data ReasonFlag Source #
Reason flag for the CRL
Accessor turning extension into a specific one
extensionGet :: Extension a => Extensions -> Maybe a Source #
Get a specific extension from a lists of raw extensions
extensionGetE :: Extension a => Extensions -> Maybe (Either String a) Source #
Get a specific extension from a lists of raw extensions
extensionDecode :: Extension a => ExtensionRaw -> Maybe (Either String a) Source #
Try to decode an ExtensionRaw.
If this function return: * Nothing, the OID doesn't match * Just Left, the OID matched, but the extension couldn't be decoded * Just Right, the OID matched, and the extension has been succesfully decoded
extensionEncode :: Extension a => Bool -> a -> ExtensionRaw Source #
Encode an Extension to extensionRaw
data ExtensionRaw Source #
An undecoded extension
ExtensionRaw | |
|
newtype Extensions Source #
a Set of ExtensionRaw
Certificate Revocation List (CRL)
Describe a Certificate revocation list
data RevokedCertificate Source #
Describe a revoked certificate identifiable by serial number.
Naming
newtype DistinguishedName Source #
A list of OID and strings.
Elements commonly available in a DistinguishedName
structure
DnCommonName | CN |
DnCountry | Country |
DnOrganization | O |
DnOrganizationUnit | OU |
DnEmailAddress | Email Address (legacy) |
data ASN1CharacterString :: * #
ASN1 Character String with encoding
getDnElement :: DnElement -> DistinguishedName -> Maybe ASN1CharacterString Source #
Try to get a specific element in a DistinguishedName
structure
Certificate Chain
newtype CertificateChain Source #
A chain of X.509 certificates in exact form.
newtype CertificateChainRaw Source #
Represent a chain of X.509 certificates in bytestring form.
marshall between CertificateChain and CertificateChainRaw
decodeCertificateChain :: CertificateChainRaw -> Either (Int, String) CertificateChain Source #
Decode a CertificateChainRaw into a CertificateChain if every raw certificate are decoded correctly, otherwise return the index of the failed certificate and the error associated.
encodeCertificateChain :: CertificateChain -> CertificateChainRaw Source #
Convert a CertificateChain into a CertificateChainRaw
Signed types and marshalling
data (Show a, Eq a, ASN1Object a) => Signed a Source #
Represent a signed object using a traditional X509 structure.
When dealing with external certificate, use the SignedExact structure not this one.
Signed | |
|
data (Show a, Eq a, ASN1Object a) => SignedExact a Source #
Represent the signed object plus the raw data that we need to keep around for non compliant case to be able to verify signature.
(ASN1Object a, Eq a, Show a) => Eq (SignedExact a) Source # | |
(ASN1Object a, Eq a, Show a) => Show (SignedExact a) Source # | |
getSigned :: SignedExact a -> Signed a Source #
get the decoded Signed data
getSignedData :: (Show a, Eq a, ASN1Object a) => SignedExact a -> ByteString Source #
Get the signed data for the signature
:: (Show a, Eq a, ASN1Object a) | |
=> (ByteString -> (ByteString, SignatureALG, r)) | signature function |
-> a | object to sign |
-> (SignedExact a, r) |
Transform an object into a SignedExact
object
:: (Functor f, Show a, Eq a, ASN1Object a) | |
=> (ByteString -> f (ByteString, SignatureALG)) | signature function |
-> a | object to sign |
-> f (SignedExact a) |
A generalization of objectToSignedExact
where the signature function
runs in an arbitrary functor. This allows for example to sign using an
algorithm needing random values.
encodeSignedObject :: SignedExact a -> ByteString Source #
The raw representation of the whole signed structure
decodeSignedObject :: (Show a, Eq a, ASN1Object a) => ByteString -> Either String (SignedExact a) Source #
Try to parse a bytestring that use the typical X509 signed structure format
Parametrized Signed accessor
getCertificate :: SignedCertificate -> Certificate Source #
Get the Certificate associated to a SignedCertificate
decodeSignedCertificate :: ByteString -> Either String SignedCertificate Source #
Try to decode a bytestring to a SignedCertificate
decodeSignedCRL :: ByteString -> Either String SignedCRL Source #
Try to decode a bytestring to a SignedCRL
Hash distinguished names related function
hashDN :: DistinguishedName -> ByteString Source #
Make an OpenSSL style hash of distinguished name
OpenSSL algorithm is odd, and has been replicated here somewhat. only lower the case of ascii character.
hashDN_old :: DistinguishedName -> ByteString Source #
Create an openssl style old hash of distinguished name