module Data.X509.Signed
    (
    
      Signed(..)
    , SignedExact
    
    , getSigned
    , getSignedData
    
    , encodeSignedObject
    , decodeSignedObject
    
    , objectToSignedExact
    , objectToSigned
    , signedToExact
    ) where
import Control.Arrow (first)
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import Data.X509.AlgorithmIdentifier
import Data.ASN1.Types
import Data.ASN1.Encoding
import Data.ASN1.BinaryEncoding
import Data.ASN1.Stream
import Data.ASN1.BitArray
import qualified Data.ASN1.BinaryEncoding.Raw as Raw (toByteString)
data (Show a, Eq a, ASN1Object a) => Signed a = Signed
    { signedObject    :: a            
    , signedAlg       :: SignatureALG 
    , signedSignature :: B.ByteString 
    } deriving (Show, Eq)
data (Show a, Eq a, ASN1Object a) => SignedExact a = SignedExact
    { getSigned          :: Signed a     
    , exactObjectRaw     :: B.ByteString 
                                         
    , encodeSignedObject :: B.ByteString 
    } deriving (Show, Eq)
getSignedData :: (Show a, Eq a, ASN1Object a)
              => SignedExact a
              -> B.ByteString
getSignedData = exactObjectRaw
signedToExact :: (Show a, Eq a, ASN1Object a)
              => Signed a
              -> SignedExact a
signedToExact signed = sExact
  where (sExact, ())      = objectToSignedExact fakeSigFunction (signedObject signed)
        fakeSigFunction _ = (signedSignature signed, signedAlg signed, ())
objectToSignedExact :: (Show a, Eq a, ASN1Object a)
                    => (ByteString -> (ByteString, SignatureALG, r)) 
                    -> a                                             
                    -> (SignedExact a, r)
objectToSignedExact signatureFunction object = (SignedExact signed objRaw signedRaw, r)
  where signed     = Signed { signedObject    = object
                            , signedAlg       = sigAlg
                            , signedSignature = sigBits
                            }
        signedRaw  = encodeASN1' DER signedASN1
        signedASN1 = Start Sequence
                       : objASN1
                       (toASN1 sigAlg
                       (BitString (toBitArray sigBits 0)
                   : End Sequence
                   : []))
        objASN1            = \xs -> Start Sequence : toASN1 object (End Sequence : xs)
        objRaw             = encodeASN1' DER (objASN1 [])
        (sigBits,sigAlg,r) = signatureFunction objRaw
objectToSigned :: (Show a, Eq a, ASN1Object a)
               => (ByteString
               -> (ByteString, SignatureALG, r))
               -> a
               -> (Signed a, r)
objectToSigned signatureFunction object = first getSigned $ objectToSignedExact signatureFunction object
decodeSignedObject :: (Show a, Eq a, ASN1Object a)
                   => ByteString
                   -> Either String (SignedExact a)
decodeSignedObject b = either (Left . show) parseSigned $ decodeASN1Repr' BER b
  where 
        
        parseSigned l = onContainer (fst $ getConstructedEndRepr l) $ \l2 ->
            let (objRepr,rem1)   = getConstructedEndRepr l2
                (sigAlgSeq,rem2) = getConstructedEndRepr rem1
                (sigSeq,_)       = getConstructedEndRepr rem2
                obj              = onContainer objRepr (either Left Right . fromASN1 . map fst)
             in case (obj, map fst sigSeq) of
                    (Right (o,[]), [BitString signature]) ->
                        let rawObj = Raw.toByteString $ concatMap snd objRepr
                         in case fromASN1 $ map fst sigAlgSeq of
                                Left s           -> Left ("signed object error sigalg: " ++ s)
                                Right (sigAlg,_) ->
                                    let signed = Signed
                                                    { signedObject    = o
                                                    , signedAlg       = sigAlg
                                                    , signedSignature = bitArrayGetData signature
                                                    }
                                     in Right $ SignedExact
                                                { getSigned          = signed
                                                , exactObjectRaw     = rawObj
                                                , encodeSignedObject = b
                                                }
                    (Right (_,remObj), _) ->
                        Left $ ("signed object error: remaining stream in object: " ++ show remObj)
                    (Left err, _) -> Left $ ("signed object error: " ++ show err)
        onContainer ((Start _, _) : l) f =
            case reverse l of
                ((End _, _) : l2) -> f $ reverse l2
                _                 -> f []
        onContainer _ f = f []