module Data.X509
(
SignedCertificate
, SignedCRL
, Certificate(..)
, PubKey(..)
, PrivKey(..)
, pubkeyToAlg
, privkeyToAlg
, module Data.X509.AlgorithmIdentifier
, module Data.X509.Ext
, module Data.X509.ExtensionRaw
, module Data.X509.CRL
, DistinguishedName(..)
, DnElement(..)
, ASN1CharacterString(..)
, getDnElement
, module Data.X509.CertificateChain
, Signed(..)
, SignedExact
, getSigned
, getSignedData
, objectToSignedExact
, encodeSignedObject
, decodeSignedObject
, getCertificate
, getCRL
, decodeSignedCertificate
, decodeSignedCRL
, hashDN
, hashDN_old
) where
import Control.Arrow (second)
import Data.ASN1.Types
import Data.ASN1.Encoding
import Data.ASN1.BinaryEncoding
import qualified Data.ByteString as B
import Data.X509.Cert
import Data.X509.Ext
import Data.X509.ExtensionRaw
import Data.X509.CRL
import Data.X509.CertificateChain
import Data.X509.DistinguishedName
import Data.X509.Signed
import Data.X509.PublicKey
import Data.X509.PrivateKey
import Data.X509.AlgorithmIdentifier
import qualified Crypto.Hash.MD5 as MD5
import qualified Crypto.Hash.SHA1 as SHA1
type SignedCertificate = SignedExact Certificate
type SignedCRL = SignedExact CRL
getCertificate :: SignedCertificate -> Certificate
getCertificate = signedObject . getSigned
getCRL :: SignedCRL -> CRL
getCRL = signedObject . getSigned
decodeSignedCertificate :: B.ByteString -> Either String SignedCertificate
decodeSignedCertificate = decodeSignedObject
decodeSignedCRL :: B.ByteString -> Either String SignedCRL
decodeSignedCRL = decodeSignedObject
hashDN :: DistinguishedName -> B.ByteString
hashDN = shorten . SHA1.hash . encodeASN1' DER . flip toASN1 [] . DistinguishedNameInner . dnLowerUTF8
where dnLowerUTF8 (DistinguishedName l) = DistinguishedName $ map (second toLowerUTF8) l
toLowerUTF8 (ASN1CharacterString _ s) = ASN1CharacterString UTF8 (B.map asciiToLower s)
asciiToLower c
| c >= w8A && c <= w8Z = fromIntegral (fromIntegral c fromEnum 'A' + fromEnum 'a')
| otherwise = c
w8A = fromIntegral $ fromEnum 'A'
w8Z = fromIntegral $ fromEnum 'Z'
hashDN_old :: DistinguishedName -> B.ByteString
hashDN_old = shorten . MD5.hash . encodeASN1' DER . flip toASN1 []
shorten :: B.ByteString -> B.ByteString
shorten b = B.pack $ map i [3,2,1,0]
where i n = B.index b n