{-# LANGUAGE OverloadedStrings #-} module TLSA ( TLSA(..) , CertUsage(..) , Selector(..) , MatchingType(..) , fromByteString , toByteString , match ) where import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as L import qualified Crypto.Hash.SHA256 as SHA256 import qualified Crypto.Hash.SHA512 as SHA512 import Data.X509 ( certPubKey, Certificate ) import Data.ASN1.Types ( toASN1 ) import Data.ASN1.Encoding ( encodeASN1 ) import Data.ASN1.BinaryEncoding import Control.Applicative import Data.Word import Data.Maybe import Data.Monoid {- INLINE fromWord8 #-} fromWord8 :: Enum a => Word8 -> a fromWord8 = toEnum . fromEnum {- INLINE toWord8 -} toWord8 :: Enum a => a -> Word8 toWord8 = toEnum . fromEnum -- | The Certificate Usage Field as described in RFC 6698, section 2.1.1. data CertUsage -- | This usage limits which CA can be used to issue certificates for a -- given service on a host. PKIX-validated TLS connections for the domain -- should be considered invalid if the certification path does not include -- at least one certificate that 'match'es the 'TLSA' record. = CAConstraint -- | This usage limits which end entity certificate can be used by a given -- service on a host. The TLS connection for the domain should be -- considered invalid if the end entity certificate does not 'match' the -- 'TLSA' record. | ServiceCertificateConstraint -- | This usage allows a domain name administrator to specify a new trust -- anchor. This is useful if the domain issues its own certificates under -- its own CA that is not expected to be in the end users' collection of -- trust anchors. When conducting PKIX validation for the domain, any -- certificate 'match'ing the 'TLSA' record can be treated as a trust -- anchor that does not require further validation. | TrustAnchorAssertion -- | This usage allows for a domain name administrator to issue -- certificates for a domain without involving a third-party CA. The end -- entity certificate MUST 'match' the 'TLSA' record. Unlike for a -- 'ServiceCertificateConstraint', PKIX validation should not be performed. | DomainIssued | CertUsage Word8 deriving (Eq, Ord, Show, Read) instance Enum CertUsage where fromEnum CAConstraint = 0 fromEnum ServiceCertificateConstraint = 1 fromEnum TrustAnchorAssertion = 2 fromEnum DomainIssued = 3 fromEnum (CertUsage n) = fromEnum n toEnum 0 = CAConstraint toEnum 1 = ServiceCertificateConstraint toEnum 2 = TrustAnchorAssertion toEnum 3 = DomainIssued toEnum n = CertUsage (toEnum n) -- | Indicates what sort of object should be compared with 'associationData'. data Selector = FullCertificate -- ^ x.509 certificate | SubjectPublicKeyInfo -- ^ PKCS #8 formatted public key | Selector Word8 -- ^ value 255 reserved for private use deriving (Eq,Ord,Show) instance Enum Selector where fromEnum FullCertificate = 0 fromEnum SubjectPublicKeyInfo = 1 fromEnum (Selector n) = fromEnum n toEnum 0 = FullCertificate toEnum 1 = SubjectPublicKeyInfo toEnum n = Selector (toEnum n) -- | Is 'associationData' an object of the form specified by 'Selector' or is -- it only a hash of it? data MatchingType = Match_Exact | Match_SHA256 | Match_SHA512 | Match Word8 -- ^ value 255 is reserved for private use deriving (Eq,Ord,Show) instance Enum MatchingType where fromEnum Match_Exact = 0 fromEnum Match_SHA256 = 1 fromEnum Match_SHA512 = 2 fromEnum (Match n) = fromEnum n toEnum 0 = Match_Exact toEnum 1 = Match_SHA256 toEnum 2 = Match_SHA512 toEnum n = Match (toEnum n) -- | The parsed RDATA field of a TLSA DNS resource record (type 52) as -- described in RFC 6698. -- -- The 'match' function uses 'selector', 'matchingType' and 'associationData' -- to implement a predicate on certificates obtained via the TLS protocol. The -- 'certUsage' field indicates what that predicate means. data TLSA = TLSA { certUsage :: CertUsage , selector :: Selector , matchingType :: MatchingType , associationData :: BS.ByteString } deriving (Eq, Ord, Show) -- | Parse RDATA for a TLSA resource record. fromByteString :: BS.ByteString -> TLSA fromByteString bs = TLSA (fromWord8 cu) (fromWord8 sel) (fromWord8 mat) dta where (csm,dta) = BS.splitAt 3 bs (cu,sel,mat) = case BS.unpack csm of [cu,sel,mat] -> (cu,sel,mat) [cu,sel] -> (cu,sel,0) [cu] -> (cu,0,0) [] -> (0,0,0) -- | Encode a valid RDATA field for a TLSA DNS record. toByteString :: TLSA -> BS.ByteString toByteString (TLSA cu sel mat dta) = csm <> dta where csm = BS.pack [ toWord8 cu , toWord8 sel , toWord8 mat ] -- | Returns 'True' if the given certificate matches the given 'TLSA' object. -- The algorithm for matching depends on the values of 'selector' and -- 'matchingType' as described in RFC 6698. match :: TLSA -> Certificate -> Bool match tlsa cert = fromMaybe False $ (== associationData tlsa) <$> (hash <*> material) where encode obj = encodeASN1 DER (toASN1 obj []) material = case selector tlsa of FullCertificate -> Just $ encode cert SubjectPublicKeyInfo -> Just $ encode $ certPubKey cert _ -> Nothing hash = case matchingType tlsa of Match_Exact -> Just L.toStrict Match_SHA256 -> Just SHA256.hashlazy Match_SHA512 -> Just SHA512.hashlazy _ -> Nothing