x509-1.7.0: X509 reader and writer

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Data.X509

Contents

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

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

PubKeyUnknown OID ByteString

unrecognized format

data PrivKey Source #

Private key types known and used in X.509

Constructors

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

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

Minimal complete definition

extOID, extEncode, extDecode

Methods

extOID :: a -> OID Source #

extEncode :: a -> [ASN1] Source #

extDecode :: [ASN1] -> Either String a Source #

Common extension usually found in x509v3

data ExtKeyUsageFlag Source #

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

data AltName Source #

Different naming scheme use by the extension.

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

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

Constructors

ExtensionRaw 

Fields

Certificate Revocation List (CRL)

Naming

data DnElement Source #

Elements commonly available in a DistinguishedName structure

Constructors

DnCommonName

CN

DnCountry

Country

DnOrganization

O

DnOrganizationUnit

OU

DnEmailAddress

Email Address (legacy)

getDnElement :: DnElement -> DistinguishedName -> Maybe ASN1CharacterString Source #

Try to get a specific element in a DistinguishedName structure

Certificate Chain

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

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

Methods

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

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

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

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

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