x509-1.7.6: X509 reader and writer
LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Data.X509

Description

Read/Write X509 Certificate, CRL and their signed equivalents.

Follows RFC5280 / RFC6818

Synopsis

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.

Constructors

Certificate 

Fields

Instances

Instances details
Eq Certificate Source # 
Instance details

Defined in Data.X509.Cert

Show Certificate Source # 
Instance details

Defined in Data.X509.Cert

ASN1Object Certificate Source # 
Instance details

Defined in Data.X509.Cert

data PubKey Source #

Public key types known and used in X.509

Constructors

PubKeyRSA PublicKey

RSA public key

PubKeyDSA PublicKey

DSA public key

PubKeyDH (Integer, Integer, Integer, Maybe Integer, ([Word8], Integer))

DH format with (p,g,q,j,(seed,pgenCounter))

PubKeyEC PubKeyEC

EC public key

PubKeyX25519 PublicKey

X25519 public key

PubKeyX448 PublicKey

X448 public key

PubKeyEd25519 PublicKey

Ed25519 public key

PubKeyEd448 PublicKey

Ed448 public key

PubKeyUnknown OID ByteString

unrecognized format

Instances

Instances details
Eq PubKey Source # 
Instance details

Defined in Data.X509.PublicKey

Methods

(==) :: PubKey -> PubKey -> Bool #

(/=) :: PubKey -> PubKey -> Bool #

Show PubKey Source # 
Instance details

Defined in Data.X509.PublicKey

ASN1Object PubKey Source # 
Instance details

Defined in Data.X509.PublicKey

data PubKeyEC Source #

Elliptic Curve Public Key

TODO: missing support for binary curve.

Instances

Instances details
Eq PubKeyEC Source # 
Instance details

Defined in Data.X509.PublicKey

Show PubKeyEC Source # 
Instance details

Defined in Data.X509.PublicKey

newtype SerializedPoint Source #

Serialized Elliptic Curve Point

data PrivKey Source #

Private key types known and used in X.509

Constructors

PrivKeyRSA PrivateKey

RSA private key

PrivKeyDSA PrivateKey

DSA private key

PrivKeyEC PrivKeyEC

EC private key

PrivKeyX25519 SecretKey

X25519 private key

PrivKeyX448 SecretKey

X448 private key

PrivKeyEd25519 SecretKey

Ed25519 private key

PrivKeyEd448 SecretKey

Ed448 private key

Instances

Instances details
Eq PrivKey Source # 
Instance details

Defined in Data.X509.PrivateKey

Methods

(==) :: PrivKey -> PrivKey -> Bool #

(/=) :: PrivKey -> PrivKey -> Bool #

Show PrivKey Source # 
Instance details

Defined in Data.X509.PrivateKey

ASN1Object PrivKey Source # 
Instance details

Defined in Data.X509.PrivateKey

data PrivKeyEC Source #

Elliptic Curve Private Key

TODO: missing support for binary curve.

Instances

Instances details
Eq PrivKeyEC Source # 
Instance details

Defined in Data.X509.PrivateKey

Show PrivKeyEC Source # 
Instance details

Defined in Data.X509.PrivateKey

pubkeyToAlg :: PubKey -> PubKeyALG Source #

Convert a Public key to the Public Key Algorithm type

privkeyToAlg :: PrivKey -> PubKeyALG Source #

Convert a Private key to the Public Key Algorithm type

data HashALG Source #

Hash Algorithm

Instances

Instances details
Eq HashALG Source # 
Instance details

Defined in Data.X509.AlgorithmIdentifier

Methods

(==) :: HashALG -> HashALG -> Bool #

(/=) :: HashALG -> HashALG -> Bool #

Show HashALG Source # 
Instance details

Defined in Data.X509.AlgorithmIdentifier

data PubKeyALG Source #

Public Key Algorithm

Constructors

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_X25519

ECDH 25519 key agreement

PubKeyALG_X448

ECDH 448 key agreement

PubKeyALG_Ed25519

EdDSA 25519 signature algorithm

PubKeyALG_Ed448

EdDSA 448 signature algorithm

PubKeyALG_DH

Diffie Hellman Public Key algorithm

PubKeyALG_Unknown OID

Unknown Public Key algorithm

Instances

Instances details
Eq PubKeyALG Source # 
Instance details

Defined in Data.X509.AlgorithmIdentifier

Show PubKeyALG Source # 
Instance details

Defined in Data.X509.AlgorithmIdentifier

OIDable PubKeyALG Source # 
Instance details

Defined in Data.X509.AlgorithmIdentifier

Methods

getObjectID :: PubKeyALG -> OID #

data SignatureALG Source #

Signature Algorithm, often composed of a public key algorithm and a hash algorithm. For some signature algorithms the hash algorithm is intrinsic to the public key algorithm and is not needed in the data type.

class Extension a where Source #

Extension class.

each extension have a unique OID associated, and a way to encode and decode an ASN1 stream.

Errata: turns out, the content is not necessarily ASN1, it could be data that is only parsable by the extension e.g. raw ascii string. Add method to parse and encode with ByteString

Minimal complete definition

extOID, extHasNestedASN1, extEncode, extDecode

Instances

Instances details
Extension ExtNetscapeComment Source # 
Instance details

Defined in Data.X509.Ext

Extension ExtCrlDistributionPoints Source # 
Instance details

Defined in Data.X509.Ext

Extension ExtAuthorityKeyId Source # 
Instance details

Defined in Data.X509.Ext

Extension ExtSubjectAltName Source # 
Instance details

Defined in Data.X509.Ext

Extension ExtSubjectKeyId Source # 
Instance details

Defined in Data.X509.Ext

Extension ExtExtendedKeyUsage Source # 
Instance details

Defined in Data.X509.Ext

Extension ExtKeyUsage Source # 
Instance details

Defined in Data.X509.Ext

Extension ExtBasicConstraints Source # 
Instance details

Defined in Data.X509.Ext

Common extension usually found in x509v3

data ExtKeyUsageFlag Source #

key usage flag that is found in the key usage extension field.

data ExtSubjectAltName Source #

Provide a way to supply alternate name that can be used for matching host name.

Constructors

ExtSubjectAltName [AltName] 

data AltName Source #

Different naming scheme use by the extension.

Not all name types are available, missing: otherName x400Address directoryName ediPartyName registeredID

Instances

Instances details
Eq AltName Source # 
Instance details

Defined in Data.X509.Ext

Methods

(==) :: AltName -> AltName -> Bool #

(/=) :: AltName -> AltName -> Bool #

Ord AltName Source # 
Instance details

Defined in Data.X509.Ext

Show AltName Source # 
Instance details

Defined in Data.X509.Ext

data DistributionPoint Source #

Distribution point as either some GeneralNames or a DN

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 :: forall a. 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 :: forall a. Extension a => Bool -> a -> ExtensionRaw Source #

Encode an Extension to extensionRaw

data ExtensionRaw Source #

An undecoded extension

Constructors

ExtensionRaw 

Fields

Instances

Instances details
Eq ExtensionRaw Source # 
Instance details

Defined in Data.X509.ExtensionRaw

Show ExtensionRaw Source # 
Instance details

Defined in Data.X509.ExtensionRaw

ASN1Object ExtensionRaw Source # 
Instance details

Defined in Data.X509.ExtensionRaw

extRawASN1 :: ExtensionRaw -> [ASN1] Source #

Deprecated: use tryExtRawASN1 instead

newtype Extensions Source #

a Set of ExtensionRaw

Constructors

Extensions (Maybe [ExtensionRaw]) 

Instances

Instances details
Eq Extensions Source # 
Instance details

Defined in Data.X509.ExtensionRaw

Show Extensions Source # 
Instance details

Defined in Data.X509.ExtensionRaw

ASN1Object Extensions Source # 
Instance details

Defined in Data.X509.ExtensionRaw

Certificate Revocation List (CRL)

data CRL Source #

Describe a Certificate revocation list

Instances

Instances details
Eq CRL Source # 
Instance details

Defined in Data.X509.CRL

Methods

(==) :: CRL -> CRL -> Bool #

(/=) :: CRL -> CRL -> Bool #

Show CRL Source # 
Instance details

Defined in Data.X509.CRL

Methods

showsPrec :: Int -> CRL -> ShowS #

show :: CRL -> String #

showList :: [CRL] -> ShowS #

ASN1Object CRL Source # 
Instance details

Defined in Data.X509.CRL

Methods

toASN1 :: CRL -> ASN1S #

fromASN1 :: [ASN1] -> Either String (CRL, [ASN1]) #

data RevokedCertificate Source #

Describe a revoked certificate identifiable by serial number.

Naming

newtype DistinguishedName Source #

A list of OID and strings.

Instances

Instances details
Eq DistinguishedName Source # 
Instance details

Defined in Data.X509.DistinguishedName

Ord DistinguishedName Source # 
Instance details

Defined in Data.X509.DistinguishedName

Show DistinguishedName Source # 
Instance details

Defined in Data.X509.DistinguishedName

Semigroup DistinguishedName Source # 
Instance details

Defined in Data.X509.DistinguishedName

Monoid DistinguishedName Source # 
Instance details

Defined in Data.X509.DistinguishedName

ASN1Object DistinguishedName Source # 
Instance details

Defined in Data.X509.DistinguishedName

data DnElement Source #

Elements commonly available in a DistinguishedName structure

Constructors

DnCommonName

CN

DnCountry

Country

DnOrganization

O

DnOrganizationUnit

OU

DnEmailAddress

Email Address (legacy)

Instances

Instances details
Eq DnElement Source # 
Instance details

Defined in Data.X509.DistinguishedName

Show DnElement Source # 
Instance details

Defined in Data.X509.DistinguishedName

OIDable DnElement Source # 
Instance details

Defined in Data.X509.DistinguishedName

Methods

getObjectID :: DnElement -> OID #

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.

Constructors

Signed 

Fields

Instances

Instances details
(Show a, Eq a, ASN1Object a) => Eq (Signed a) Source # 
Instance details

Defined in Data.X509.Signed

Methods

(==) :: Signed a -> Signed a -> Bool #

(/=) :: Signed a -> Signed a -> Bool #

(Show a, Eq a, ASN1Object a) => Show (Signed a) Source # 
Instance details

Defined in Data.X509.Signed

Methods

showsPrec :: Int -> Signed a -> ShowS #

show :: Signed a -> String #

showList :: [Signed a] -> ShowS #

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.

Instances

Instances details
(Show a, Eq a, ASN1Object a) => Eq (SignedExact a) Source # 
Instance details

Defined in Data.X509.Signed

(Show a, Eq a, ASN1Object a) => Show (SignedExact a) Source # 
Instance details

Defined in Data.X509.Signed

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

objectToSignedExact Source #

Arguments

:: (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

objectToSignedExactF Source #

Arguments

:: (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

getCRL :: SignedCRL -> CRL Source #

Get the CRL associated to a SignedCRL

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