module Data.X509.CertificateChain
    ( CertificateChain(..)
    , CertificateChainRaw(..)
    
    , decodeCertificateChain
    , encodeCertificateChain
    ) where
import Data.X509.Cert (Certificate)
import Data.X509.Signed (SignedExact, decodeSignedObject, encodeSignedObject)
import Data.ByteString (ByteString)
newtype CertificateChain = CertificateChain [SignedExact Certificate]
    deriving (Show,Eq)
newtype CertificateChainRaw = CertificateChainRaw [ByteString]
    deriving (Show,Eq)
decodeCertificateChain :: CertificateChainRaw -> Either (Int, String) CertificateChain
decodeCertificateChain (CertificateChainRaw l) =
    either Left (Right . CertificateChain) $ loop 0 l
  where loop _ []     = Right []
        loop i (r:rs) = case decodeSignedObject r of
                         Left err -> Left (i, err)
                         Right o  -> either Left (Right . (o :)) $ loop (i+1) rs
encodeCertificateChain :: CertificateChain -> CertificateChainRaw
encodeCertificateChain (CertificateChain chain) =
    CertificateChainRaw $ map encodeSignedObject chain