Z-Botan-0.3.1.0: Crypto for Haskell
CopyrightDong Han 2021
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Crypto.X509

Description

X.509 Certificates read, write and verification.

Synopsis

X509 Certificates

data Cert Source #

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

Instances details
Show Cert Source # 
Instance details

Defined in Z.Crypto.X509

Methods

showsPrec :: Int -> Cert -> ShowS #

show :: Cert -> String #

showList :: [Cert] -> ShowS #

Generic Cert Source # 
Instance details

Defined in Z.Crypto.X509

Associated Types

type Rep Cert :: Type -> Type #

Methods

from :: Cert -> Rep Cert x #

to :: Rep Cert x -> Cert #

Print Cert Source # 
Instance details

Defined in Z.Crypto.X509

Methods

toUTF8BuilderP :: Int -> Cert -> Builder () #

type Rep Cert Source # 
Instance details

Defined in Z.Crypto.X509

type Rep Cert = D1 ('MetaData "Cert" "Z.Crypto.X509" "Z-Botan-0.3.1.0-GbapUVQUdq6A2uFR3TMVx6" 'True) (C1 ('MetaCons "Cert" 'PrefixI 'True) (S1 ('MetaSel ('Just "certStruct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BotanStruct)))

withCert :: Cert -> (BotanStructT -> IO r) -> IO r Source #

Use Cert as a botan_cert_t.

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.

certFingerPrint :: Cert -> HashType -> IO Text Source #

Return the finger print of the certificate.

certSerial :: Cert -> IO Bytes Source #

Return the serial number of the certificate.

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.

certPubKey :: Cert -> IO PubKey Source #

Get the public key included in this certificate.

certDNIssuer Source #

Arguments

:: HasCallStack 
=> Cert 
-> CBytes

key

-> Int

index

-> IO Text 

Get a value from the issuer DN field, throw exception if not exists.

certDNSubject Source #

Arguments

:: HasCallStack 
=> Cert 
-> CBytes

key

-> Int

index

-> IO Text 

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.

verify certificate

verifyCert Source #

Arguments

:: HasCallStack 
=> [Cert]

Intermediate certificates, set to [] if not needed.

-> [Cert]

Trusted certificates, set to [] if not needed.

-> 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) 

verifyCertCRL Source #

Arguments

:: HasCallStack 
=> [Cert]

Intermediate certificates, set to [] if not needed.

-> [Cert]

Trusted certificates, set to [] if not needed.

-> [CRL]

Certificate Revocation Lists, set to [] if not needed.

-> 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.

verifyCertCRL' Source #

Arguments

:: HasCallStack 
=> [Cert]

Intermediate certificates, set to [] if not needed.

-> CertStore

Trusted certificates in CertStore

-> [CRL]

Certificate Revocation Lists, set to [] if not needed.

-> 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 with a CertStore.

Verify a certificate. Returns Nothing if validation was successful, 'Just reason' if unsuccessful.

CRL

data CRL Source #

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

Instances details
Show CRL Source # 
Instance details

Defined in Z.Crypto.X509

Methods

showsPrec :: Int -> CRL -> ShowS #

show :: CRL -> String #

showList :: [CRL] -> ShowS #

Generic CRL Source # 
Instance details

Defined in Z.Crypto.X509

Associated Types

type Rep CRL :: Type -> Type #

Methods

from :: CRL -> Rep CRL x #

to :: Rep CRL x -> CRL #

Print CRL Source # 
Instance details

Defined in Z.Crypto.X509

Methods

toUTF8BuilderP :: Int -> CRL -> Builder () #

type Rep CRL Source # 
Instance details

Defined in Z.Crypto.X509

type Rep CRL = D1 ('MetaData "CRL" "Z.Crypto.X509" "Z-Botan-0.3.1.0-GbapUVQUdq6A2uFR3TMVx6" 'True) (C1 ('MetaCons "CRL" 'PrefixI 'True) (S1 ('MetaSel ('Just "crlStruct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BotanStruct)))

withCRL :: CRL -> (BotanStructT -> IO r) -> IO r Source #

Use CRL as a botan_crl_t.

loadCRL :: HasCallStack => Bytes -> IO CRL Source #

Load a CRL from the DER or PEM representation.

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

data CertStore Source #

An opaque newtype wrapper for an X.509 Certificate Store based on botan's FlatFile_Certificate_Store.

Instances

Instances details
Show CertStore Source # 
Instance details

Defined in Z.Crypto.X509

Generic CertStore Source # 
Instance details

Defined in Z.Crypto.X509

Associated Types

type Rep CertStore :: Type -> Type #

Print CertStore Source # 
Instance details

Defined in Z.Crypto.X509

Methods

toUTF8BuilderP :: Int -> CertStore -> Builder () #

type Rep CertStore Source # 
Instance details

Defined in Z.Crypto.X509

type Rep CertStore = D1 ('MetaData "CertStore" "Z.Crypto.X509" "Z-Botan-0.3.1.0-GbapUVQUdq6A2uFR3TMVx6" '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.