module Data.X509
    (
    
      SignedCertificate
    , SignedCRL
    , Certificate(..)
    , PubKey(..)
    , PubKeyEC(..)
    , SerializedPoint(..)
    , PrivKey(..)
    , PrivKeyEC(..)
    , 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
    , objectToSignedExactF
    , 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 qualified Data.ByteArray as BA
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 Crypto.Hash
type SignedCertificate = SignedExact Certificate
type SignedCRL         = SignedExact CRL
getCertificate :: SignedCertificate -> Certificate
getCertificate :: SignedCertificate -> Certificate
getCertificate = Signed Certificate -> Certificate
forall a. (Show a, Eq a, ASN1Object a) => Signed a -> a
signedObject (Signed Certificate -> Certificate)
-> (SignedCertificate -> Signed Certificate)
-> SignedCertificate
-> Certificate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SignedCertificate -> Signed Certificate
forall a. (Show a, Eq a, ASN1Object a) => SignedExact a -> Signed a
getSigned
getCRL :: SignedCRL -> CRL
getCRL :: SignedCRL -> CRL
getCRL = Signed CRL -> CRL
forall a. (Show a, Eq a, ASN1Object a) => Signed a -> a
signedObject (Signed CRL -> CRL)
-> (SignedCRL -> Signed CRL) -> SignedCRL -> CRL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SignedCRL -> Signed CRL
forall a. (Show a, Eq a, ASN1Object a) => SignedExact a -> Signed a
getSigned
decodeSignedCertificate :: B.ByteString -> Either String SignedCertificate
decodeSignedCertificate :: ByteString -> Either String SignedCertificate
decodeSignedCertificate = ByteString -> Either String SignedCertificate
forall a.
(Show a, Eq a, ASN1Object a) =>
ByteString -> Either String (SignedExact a)
decodeSignedObject
decodeSignedCRL :: B.ByteString -> Either String SignedCRL
decodeSignedCRL :: ByteString -> Either String SignedCRL
decodeSignedCRL = ByteString -> Either String SignedCRL
forall a.
(Show a, Eq a, ASN1Object a) =>
ByteString -> Either String (SignedExact a)
decodeSignedObject
hashDN :: DistinguishedName -> B.ByteString
hashDN :: DistinguishedName -> ByteString
hashDN = Digest SHA1 -> ByteString
forall a. Digest a -> ByteString
shorten (Digest SHA1 -> ByteString)
-> (DistinguishedName -> Digest SHA1)
-> DistinguishedName
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SHA1 -> ByteString -> Digest SHA1
forall ba alg.
(ByteArrayAccess ba, HashAlgorithm alg) =>
alg -> ba -> Digest alg
hashWith SHA1
SHA1 (ByteString -> Digest SHA1)
-> (DistinguishedName -> ByteString)
-> DistinguishedName
-> Digest SHA1
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DER -> [ASN1] -> ByteString
forall a. ASN1Encoding a => a -> [ASN1] -> ByteString
encodeASN1' DER
DER ([ASN1] -> ByteString)
-> (DistinguishedName -> [ASN1]) -> DistinguishedName -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DistinguishedNameInner -> [ASN1] -> [ASN1])
-> [ASN1] -> DistinguishedNameInner -> [ASN1]
forall a b c. (a -> b -> c) -> b -> a -> c
flip DistinguishedNameInner -> [ASN1] -> [ASN1]
forall a. ASN1Object a => a -> [ASN1] -> [ASN1]
toASN1 [] (DistinguishedNameInner -> [ASN1])
-> (DistinguishedName -> DistinguishedNameInner)
-> DistinguishedName
-> [ASN1]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DistinguishedName -> DistinguishedNameInner
DistinguishedNameInner (DistinguishedName -> DistinguishedNameInner)
-> (DistinguishedName -> DistinguishedName)
-> DistinguishedName
-> DistinguishedNameInner
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DistinguishedName -> DistinguishedName
dnLowerUTF8
    where dnLowerUTF8 :: DistinguishedName -> DistinguishedName
dnLowerUTF8 (DistinguishedName [(OID, ASN1CharacterString)]
l) = [(OID, ASN1CharacterString)] -> DistinguishedName
DistinguishedName ([(OID, ASN1CharacterString)] -> DistinguishedName)
-> [(OID, ASN1CharacterString)] -> DistinguishedName
forall a b. (a -> b) -> a -> b
$ ((OID, ASN1CharacterString) -> (OID, ASN1CharacterString))
-> [(OID, ASN1CharacterString)] -> [(OID, ASN1CharacterString)]
forall a b. (a -> b) -> [a] -> [b]
map ((ASN1CharacterString -> ASN1CharacterString)
-> (OID, ASN1CharacterString) -> (OID, ASN1CharacterString)
forall b c d. (b -> c) -> (d, b) -> (d, c)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second ASN1CharacterString -> ASN1CharacterString
toLowerUTF8) [(OID, ASN1CharacterString)]
l
          toLowerUTF8 :: ASN1CharacterString -> ASN1CharacterString
toLowerUTF8 (ASN1CharacterString ASN1StringEncoding
_ ByteString
s) = ASN1StringEncoding -> ByteString -> ASN1CharacterString
ASN1CharacterString ASN1StringEncoding
UTF8 ((Word8 -> Word8) -> ByteString -> ByteString
B.map Word8 -> Word8
asciiToLower ByteString
s)
          asciiToLower :: Word8 -> Word8
asciiToLower Word8
c
            | Word8
c Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
w8A Bool -> Bool -> Bool
&& Word8
c Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word8
w8Z = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Char -> Int
forall a. Enum a => a -> Int
fromEnum Char
'A' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Char -> Int
forall a. Enum a => a -> Int
fromEnum Char
'a')
            | Bool
otherwise            = Word8
c
          w8A :: Word8
w8A = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word8) -> Int -> Word8
forall a b. (a -> b) -> a -> b
$ Char -> Int
forall a. Enum a => a -> Int
fromEnum Char
'A'
          w8Z :: Word8
w8Z = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word8) -> Int -> Word8
forall a b. (a -> b) -> a -> b
$ Char -> Int
forall a. Enum a => a -> Int
fromEnum Char
'Z'
hashDN_old :: DistinguishedName -> B.ByteString
hashDN_old :: DistinguishedName -> ByteString
hashDN_old = Digest MD5 -> ByteString
forall a. Digest a -> ByteString
shorten (Digest MD5 -> ByteString)
-> (DistinguishedName -> Digest MD5)
-> DistinguishedName
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MD5 -> ByteString -> Digest MD5
forall ba alg.
(ByteArrayAccess ba, HashAlgorithm alg) =>
alg -> ba -> Digest alg
hashWith MD5
MD5 (ByteString -> Digest MD5)
-> (DistinguishedName -> ByteString)
-> DistinguishedName
-> Digest MD5
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DER -> [ASN1] -> ByteString
forall a. ASN1Encoding a => a -> [ASN1] -> ByteString
encodeASN1' DER
DER ([ASN1] -> ByteString)
-> (DistinguishedName -> [ASN1]) -> DistinguishedName -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DistinguishedName -> [ASN1] -> [ASN1])
-> [ASN1] -> DistinguishedName -> [ASN1]
forall a b c. (a -> b -> c) -> b -> a -> c
flip DistinguishedName -> [ASN1] -> [ASN1]
forall a. ASN1Object a => a -> [ASN1] -> [ASN1]
toASN1 []
shorten :: Digest a -> B.ByteString
shorten :: forall a. Digest a -> ByteString
shorten Digest a
b = [Word8] -> ByteString
B.pack ([Word8] -> ByteString) -> [Word8] -> ByteString
forall a b. (a -> b) -> a -> b
$ (Int -> Word8) -> [Int] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Word8
i [Int
3,Int
2,Int
1,Int
0]
    where i :: Int -> Word8
i Int
n = Digest a -> Int -> Word8
forall a. ByteArrayAccess a => a -> Int -> Word8
BA.index Digest a
b Int
n