Copyright | Dong Han 2021 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
X.509 Certificates read, write and verification.
Synopsis
- data Cert
- withCert :: Cert -> (BotanStructT -> IO r) -> IO r
- loadCert :: HasCallStack => Bytes -> IO Cert
- loadCertFile :: HasCallStack => CBytes -> IO Cert
- dupCert :: HasCallStack => Cert -> IO Cert
- certStart :: Cert -> IO Word64
- certExpire :: Cert -> IO Word64
- certStart' :: Cert -> IO SystemTime
- certExpire' :: Cert -> IO SystemTime
- certStartText :: Cert -> IO Text
- certExpireText :: Cert -> IO Text
- certFingerPrint :: Cert -> HashType -> IO Text
- certSerial :: Cert -> IO Bytes
- certIDAuthority :: Cert -> IO Bytes
- certIDSubject :: Cert -> IO Bytes
- certPubBits :: Cert -> IO Bytes
- certPubKey :: Cert -> IO PubKey
- certDNIssuer :: HasCallStack => Cert -> CBytes -> Int -> IO Text
- certDNSubject :: HasCallStack => Cert -> CBytes -> Int -> IO Text
- certToText :: HasCallStack => Cert -> IO Text
- certUsage :: HasCallStack => Cert -> KeyUsageConstraint -> IO ()
- verifyCert :: HasCallStack => [Cert] -> [Cert] -> Int -> CBytes -> Word64 -> Cert -> IO (Maybe CBytes)
- verifyCertCRL :: HasCallStack => [Cert] -> [Cert] -> [CRL] -> Int -> CBytes -> Word64 -> Cert -> IO (Maybe CBytes)
- verifyCertCRL' :: HasCallStack => [Cert] -> CertStore -> [CRL] -> Int -> CBytes -> Word64 -> Cert -> IO (Maybe CBytes)
- data CRL
- withCRL :: CRL -> (BotanStructT -> IO r) -> IO r
- loadCRL :: HasCallStack => Bytes -> IO CRL
- loadCRLFile :: HasCallStack => CBytes -> IO CRL
- isRevokedX509 :: HasCallStack => CRL -> Cert -> IO Bool
- data CertStore
- withCertStore :: CertStore -> (BotanStructT -> IO r) -> IO r
- loadCertStoreFile :: HasCallStack => CBytes -> IO CertStore
- mozillaCertStore :: CertStore
- systemCertStore :: CertStore
- type KeyUsageConstraint = CUInt
- pattern NO_CONSTRAINTS :: KeyUsageConstraint
- pattern DIGITAL_SIGNATURE :: KeyUsageConstraint
- pattern NON_REPUDIATION :: KeyUsageConstraint
- pattern KEY_ENCIPHERMENT :: KeyUsageConstraint
- pattern DATA_ENCIPHERMENT :: KeyUsageConstraint
- pattern KEY_AGREEMENT :: KeyUsageConstraint
- pattern KEY_CERT_SIGN :: KeyUsageConstraint
- pattern CRL_SIGN :: KeyUsageConstraint
- pattern ENCIPHER_ONLY :: KeyUsageConstraint
- pattern DECIPHER_ONLY :: KeyUsageConstraint
X509 Certificates
An opaque newtype wrapper for an X.509 certificate.
A certificate is a binding between some identifying information (called a subject) and a public key. This binding is asserted by a signature on the certificate, which is placed there by some authority (the issuer) that at least claims that it knows the subject named in the certificate really “owns” the private key corresponding to the public key in the certificate.
The major certificate format in use today is X.509v3, used for instance in the Transport Layer Security (TLS) protocol. A X.509 certificate is represented by the type Cert
.
Instances
Show Cert Source # | |
Generic Cert Source # | |
Print Cert Source # | |
Defined in Z.Crypto.X509 toUTF8BuilderP :: Int -> Cert -> Builder () # | |
type Rep Cert Source # | |
Defined in Z.Crypto.X509 type Rep Cert = D1 ('MetaData "Cert" "Z.Crypto.X509" "Z-Botan-0.4.0.0-Cymuol1BxyD6d85e6LsrR5" 'True) (C1 ('MetaCons "Cert" 'PrefixI 'True) (S1 ('MetaSel ('Just "certStruct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BotanStruct))) |
loadCert :: HasCallStack => Bytes -> IO Cert Source #
Load a certificate from the DER or PEM representation.
loadCertFile :: HasCallStack => CBytes -> IO Cert Source #
Load a certificate from a file.
dupCert :: HasCallStack => Cert -> IO Cert Source #
Create a new object that refers to the same certificate.
read X509 field
certStart :: Cert -> IO Word64 Source #
Return the time the certificate becomes valid, as seconds since epoch.
certExpire :: Cert -> IO Word64 Source #
Return the time the certificate expires, as SystemTime
.
certStart' :: Cert -> IO SystemTime Source #
Return the time the certificate becomes valid.
certExpire' :: Cert -> IO SystemTime Source #
Return the time the certificate expires, as SystemTime
.
certStartText :: Cert -> IO Text Source #
Return the time the certificate becomes valid, as a Text
in form “YYYYMMDDHHMMSSZ” where Z is a literal character reflecting that this time is relative to UTC.
certExpireText :: Cert -> IO Text Source #
Return the time the certificate expires, as a Text
in form “YYYYMMDDHHMMSSZ” where Z is a literal character reflecting that this time is relative to UTC.
certIDAuthority :: Cert -> IO Bytes Source #
Return the authority key ID set in the certificate, which may be empty.
certIDSubject :: Cert -> IO Bytes Source #
Return the subject key ID set in the certificate, which may be empty.
certPubBits :: Cert -> IO Bytes Source #
Get the serialized representation of the public key included in this certificate.
Get a value from the issuer DN field, throw exception if not exists.
Get a value from the subject DN field, throw exception if not exists.
certToText :: HasCallStack => Cert -> IO Text Source #
Format the certificate as a free-form string.
certUsage :: HasCallStack => Cert -> KeyUsageConstraint -> IO () Source #
Change cert's KeyUsageConstraint
.
verify certificate
:: HasCallStack | |
=> [Cert] | Intermediate certificates, set to |
-> [Cert] | Trusted certificates, set to |
-> Int | Set required strength to indicate the minimum key and hash strength that is allowed, set to zero to use default(110). |
-> CBytes | Hostname. |
-> Word64 | Set reference time(seconds since epoch) to be the time which the certificate chain is validated against. Use zero to use the current system clock. |
-> Cert | The certificate to be verified. |
-> IO (Maybe CBytes) |
:: HasCallStack | |
=> [Cert] | Intermediate certificates, set to |
-> [Cert] | Trusted certificates, set to |
-> [CRL] | Certificate Revocation Lists, set to |
-> Int | Set required strength to indicate the minimum key and hash strength that is allowed, set to zero to use default(110). |
-> CBytes | Hostname. |
-> Word64 | Set reference time(seconds since epoch) to be the time which the certificate chain is validated against. Use zero to use the current system clock. |
-> Cert | The certificate to be verified. |
-> IO (Maybe CBytes) |
Certificate path validation supporting Certificate Revocation Lists.
Verify a certificate. Returns Nothing
if validation was successful, 'Just reason' if unsuccessful.
:: HasCallStack | |
=> [Cert] | Intermediate certificates, set to |
-> CertStore | Trusted certificates in |
-> [CRL] | Certificate Revocation Lists, set to |
-> Int | Set required strength to indicate the minimum key and hash strength that is allowed, set to zero to use default(110). |
-> CBytes | Hostname. |
-> Word64 | Set reference time(seconds since epoch) to be the time which the certificate chain is validated against. Use zero to use the current system clock. |
-> Cert | The certificate to be verified. |
-> IO (Maybe CBytes) |
CRL
An opaque newtype wrapper for an X.509 Certificate Revocation Lists.
It will occasionally happen that a certificate must be revoked before its expiration date. Examples of this happening include the private key being compromised, or the user to which it has been assigned leaving an organization. Certificate revocation lists are an answer to this problem (though online certificate validation techniques are starting to become somewhat more popular). Every once in a while the CA will release a new CRL, listing all certificates that have been revoked. Also included is various pieces of information like what time a particular certificate was revoked, and for what reason. In most systems, it is wise to support some form of certificate revocation, and CRLs handle this easily.
Instances
Show CRL Source # | |
Generic CRL Source # | |
Print CRL Source # | |
Defined in Z.Crypto.X509 toUTF8BuilderP :: Int -> CRL -> Builder () # | |
type Rep CRL Source # | |
Defined in Z.Crypto.X509 type Rep CRL = D1 ('MetaData "CRL" "Z.Crypto.X509" "Z-Botan-0.4.0.0-Cymuol1BxyD6d85e6LsrR5" 'True) (C1 ('MetaCons "CRL" 'PrefixI 'True) (S1 ('MetaSel ('Just "crlStruct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BotanStruct))) |
loadCRLFile :: HasCallStack => CBytes -> IO CRL Source #
Load a CRL from a file.
isRevokedX509 :: HasCallStack => CRL -> Cert -> IO Bool Source #
Check whether a given crl contains a given cert. Return True when the certificate is revoked, False otherwise.
CertStore
An opaque newtype wrapper for an X.509 Certificate Store based on botan's FlatFile_Certificate_Store
.
Instances
Show CertStore Source # | |
Generic CertStore Source # | |
Print CertStore Source # | |
Defined in Z.Crypto.X509 toUTF8BuilderP :: Int -> CertStore -> Builder () # | |
type Rep CertStore Source # | |
Defined in Z.Crypto.X509 type Rep CertStore = D1 ('MetaData "CertStore" "Z.Crypto.X509" "Z-Botan-0.4.0.0-Cymuol1BxyD6d85e6LsrR5" 'True) (C1 ('MetaCons "CertStore" 'PrefixI 'True) (S1 ('MetaSel ('Just "certStoreStruct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BotanStruct))) |
withCertStore :: CertStore -> (BotanStructT -> IO r) -> IO r Source #
Use CertStore
as a botan_x509_certstore_t
.
loadCertStoreFile :: HasCallStack => CBytes -> IO CertStore Source #
Load a CertStore from a file.
mozillaCertStore :: CertStore Source #
The built-in mozilla CA CertStore
.
This is a certstore extracted from Mozilla, see https://curl.se/docs/caextract.html.
systemCertStore :: CertStore Source #
The CA CertStore
on your system.
constants
type KeyUsageConstraint = CUInt Source #
Certificate key usage constraints.
pattern NO_CONSTRAINTS :: KeyUsageConstraint Source #
pattern DIGITAL_SIGNATURE :: KeyUsageConstraint Source #
pattern NON_REPUDIATION :: KeyUsageConstraint Source #
pattern KEY_ENCIPHERMENT :: KeyUsageConstraint Source #
pattern DATA_ENCIPHERMENT :: KeyUsageConstraint Source #
pattern KEY_AGREEMENT :: KeyUsageConstraint Source #
pattern KEY_CERT_SIGN :: KeyUsageConstraint Source #
pattern CRL_SIGN :: KeyUsageConstraint Source #
pattern ENCIPHER_ONLY :: KeyUsageConstraint Source #
pattern DECIPHER_ONLY :: KeyUsageConstraint Source #