-- |
-- Module      : Data.X509.Signed
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : experimental
-- Portability : unknown
--
-- Exposes helpers for X509 certificate and revocation list, signed structures.
--
-- Signed structures are of the form:
--      Sequence {
--          object              a
--          signatureAlgorithm  AlgorithmIdentifier
--          signatureValue      BitString
--      }
--
-- Unfortunately as lots of signed objects published have been signed on an
-- arbitrary BER ASN1 encoding (instead of using the unique DER encoding) or in
-- a non-valid DER implementation, we need to keep the raw data being signed,
-- as we can't recompute the bytestring used to sign for non compliant cases.
--
-- Signed represent the pure data type for compliant cases, and SignedExact
-- the real world situation of having to deal with compliant and non-compliant cases.
--
module Data.X509.Signed
    (
    -- * Types
      Signed(..)
    , SignedExact
    -- * SignedExact to Signed
    , getSigned
    , getSignedData
    -- * Marshalling function
    , encodeSignedObject
    , decodeSignedObject
    -- * Object to Signed and SignedExact
    , objectToSignedExact
    , objectToSignedExactF
    , 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)

-- | Represent a signed object using a traditional X509 structure.
--
-- When dealing with external certificate, use the SignedExact structure
-- not this one.
data (Show a, Eq a, ASN1Object a) => Signed a = Signed
    { Signed a -> a
signedObject    :: a            -- ^ Object to sign
    , Signed a -> SignatureALG
signedAlg       :: SignatureALG -- ^ Signature Algorithm used
    , Signed a -> ByteString
signedSignature :: B.ByteString -- ^ Signature as bytes
    } deriving (Int -> Signed a -> ShowS
[Signed a] -> ShowS
Signed a -> String
(Int -> Signed a -> ShowS)
-> (Signed a -> String) -> ([Signed a] -> ShowS) -> Show (Signed a)
forall a. (Show a, Eq a, ASN1Object a) => Int -> Signed a -> ShowS
forall a. (Show a, Eq a, ASN1Object a) => [Signed a] -> ShowS
forall a. (Show a, Eq a, ASN1Object a) => Signed a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Signed a] -> ShowS
$cshowList :: forall a. (Show a, Eq a, ASN1Object a) => [Signed a] -> ShowS
show :: Signed a -> String
$cshow :: forall a. (Show a, Eq a, ASN1Object a) => Signed a -> String
showsPrec :: Int -> Signed a -> ShowS
$cshowsPrec :: forall a. (Show a, Eq a, ASN1Object a) => Int -> Signed a -> ShowS
Show, Signed a -> Signed a -> Bool
(Signed a -> Signed a -> Bool)
-> (Signed a -> Signed a -> Bool) -> Eq (Signed a)
forall a.
(Show a, Eq a, ASN1Object a) =>
Signed a -> Signed a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Signed a -> Signed a -> Bool
$c/= :: forall a.
(Show a, Eq a, ASN1Object a) =>
Signed a -> Signed a -> Bool
== :: Signed a -> Signed a -> Bool
$c== :: forall a.
(Show a, Eq a, ASN1Object a) =>
Signed a -> Signed a -> Bool
Eq)

-- | Represent the signed object plus the raw data that we need to
-- keep around for non compliant case to be able to verify signature.
data (Show a, Eq a, ASN1Object a) => SignedExact a = SignedExact
    { SignedExact a -> Signed a
getSigned          :: Signed a     -- ^ get the decoded Signed data
    , SignedExact a -> ByteString
exactObjectRaw     :: B.ByteString -- ^ The raw representation of the object a
                                         -- TODO: in later version, replace with offset in exactRaw
    , SignedExact a -> ByteString
encodeSignedObject :: B.ByteString -- ^ The raw representation of the whole signed structure
    } deriving (Int -> SignedExact a -> ShowS
[SignedExact a] -> ShowS
SignedExact a -> String
(Int -> SignedExact a -> ShowS)
-> (SignedExact a -> String)
-> ([SignedExact a] -> ShowS)
-> Show (SignedExact a)
forall a.
(Show a, Eq a, ASN1Object a) =>
Int -> SignedExact a -> ShowS
forall a. (Show a, Eq a, ASN1Object a) => [SignedExact a] -> ShowS
forall a. (Show a, Eq a, ASN1Object a) => SignedExact a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SignedExact a] -> ShowS
$cshowList :: forall a. (Show a, Eq a, ASN1Object a) => [SignedExact a] -> ShowS
show :: SignedExact a -> String
$cshow :: forall a. (Show a, Eq a, ASN1Object a) => SignedExact a -> String
showsPrec :: Int -> SignedExact a -> ShowS
$cshowsPrec :: forall a.
(Show a, Eq a, ASN1Object a) =>
Int -> SignedExact a -> ShowS
Show, SignedExact a -> SignedExact a -> Bool
(SignedExact a -> SignedExact a -> Bool)
-> (SignedExact a -> SignedExact a -> Bool) -> Eq (SignedExact a)
forall a.
(Show a, Eq a, ASN1Object a) =>
SignedExact a -> SignedExact a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SignedExact a -> SignedExact a -> Bool
$c/= :: forall a.
(Show a, Eq a, ASN1Object a) =>
SignedExact a -> SignedExact a -> Bool
== :: SignedExact a -> SignedExact a -> Bool
$c== :: forall a.
(Show a, Eq a, ASN1Object a) =>
SignedExact a -> SignedExact a -> Bool
Eq)

-- | Get the signed data for the signature
getSignedData :: (Show a, Eq a, ASN1Object a)
              => SignedExact a
              -> B.ByteString
getSignedData :: SignedExact a -> ByteString
getSignedData = SignedExact a -> ByteString
forall a.
(Show a, Eq a, ASN1Object a) =>
SignedExact a -> ByteString
exactObjectRaw

-- | make a 'SignedExact' copy of a 'Signed' object
--
-- As the signature is already generated, expect the
-- encoded object to have been made on a compliant DER ASN1 implementation.
--
-- It's better to use 'objectToSignedExact' instead of this.
signedToExact :: (Show a, Eq a, ASN1Object a)
              => Signed a
              -> SignedExact a
signedToExact :: Signed a -> SignedExact a
signedToExact Signed a
signed = SignedExact a
sExact
  where (SignedExact a
sExact, ())      = (ByteString -> (ByteString, SignatureALG, ()))
-> a -> (SignedExact a, ())
forall a r.
(Show a, Eq a, ASN1Object a) =>
(ByteString -> (ByteString, SignatureALG, r))
-> a -> (SignedExact a, r)
objectToSignedExact ByteString -> (ByteString, SignatureALG, ())
forall p. p -> (ByteString, SignatureALG, ())
fakeSigFunction (Signed a -> a
forall a. (Show a, Eq a, ASN1Object a) => Signed a -> a
signedObject Signed a
signed)
        fakeSigFunction :: p -> (ByteString, SignatureALG, ())
fakeSigFunction p
_ = (Signed a -> ByteString
forall a. (Show a, Eq a, ASN1Object a) => Signed a -> ByteString
signedSignature Signed a
signed, Signed a -> SignatureALG
forall a. (Show a, Eq a, ASN1Object a) => Signed a -> SignatureALG
signedAlg Signed a
signed, ())

-- | Transform an object into a 'SignedExact' object
objectToSignedExact :: (Show a, Eq a, ASN1Object a)
                    => (ByteString -> (ByteString, SignatureALG, r)) -- ^ signature function
                    -> a                                             -- ^ object to sign
                    -> (SignedExact a, r)
objectToSignedExact :: (ByteString -> (ByteString, SignatureALG, r))
-> a -> (SignedExact a, r)
objectToSignedExact ByteString -> (ByteString, SignatureALG, r)
signatureFunction a
object = (SignedExact a
signedExact, r
val)
  where
    (r
val, SignedExact a
signedExact) = (ByteString -> (r, (ByteString, SignatureALG)))
-> a -> (r, SignedExact a)
forall (f :: * -> *) a.
(Functor f, Show a, Eq a, ASN1Object a) =>
(ByteString -> f (ByteString, SignatureALG))
-> a -> f (SignedExact a)
objectToSignedExactF ((ByteString, SignatureALG, r) -> (r, (ByteString, SignatureALG))
forall a b a. (a, b, a) -> (a, (a, b))
wrap ((ByteString, SignatureALG, r) -> (r, (ByteString, SignatureALG)))
-> (ByteString -> (ByteString, SignatureALG, r))
-> ByteString
-> (r, (ByteString, SignatureALG))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> (ByteString, SignatureALG, r)
signatureFunction) a
object
    wrap :: (a, b, a) -> (a, (a, b))
wrap (a
b, b
s, a
r) = (a
r, (a
b, b
s))

-- | A generalization of 'objectToSignedExact' where the signature function
-- runs in an arbitrary functor.  This allows for example to sign using an
-- algorithm needing random values.
objectToSignedExactF :: (Functor f, Show a, Eq a, ASN1Object a)
                     => (ByteString -> f (ByteString, SignatureALG)) -- ^ signature function
                     -> a                                            -- ^ object to sign
                     -> f (SignedExact a)
objectToSignedExactF :: (ByteString -> f (ByteString, SignatureALG))
-> a -> f (SignedExact a)
objectToSignedExactF ByteString -> f (ByteString, SignatureALG)
signatureFunction a
object = ((ByteString, SignatureALG) -> SignedExact a)
-> f (ByteString, SignatureALG) -> f (SignedExact a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ByteString, SignatureALG) -> SignedExact a
buildSignedExact (ByteString -> f (ByteString, SignatureALG)
signatureFunction ByteString
objRaw)
  where buildSignedExact :: (ByteString, SignatureALG) -> SignedExact a
buildSignedExact (ByteString
sigBits,SignatureALG
sigAlg) =
            let signed :: Signed a
signed     = Signed :: forall a. a -> SignatureALG -> ByteString -> Signed a
Signed { signedObject :: a
signedObject    = a
object
                                    , signedAlg :: SignatureALG
signedAlg       = SignatureALG
sigAlg
                                    , signedSignature :: ByteString
signedSignature = ByteString
sigBits
                                    }
                signedRaw :: ByteString
signedRaw  = DER -> [ASN1] -> ByteString
forall a. ASN1Encoding a => a -> [ASN1] -> ByteString
encodeASN1' DER
DER [ASN1]
signedASN1
                signedASN1 :: [ASN1]
signedASN1 = ASN1ConstructionType -> ASN1
Start ASN1ConstructionType
Sequence
                               ASN1 -> [ASN1] -> [ASN1]
forall a. a -> [a] -> [a]
: [ASN1] -> [ASN1]
objASN1
                               (SignatureALG -> [ASN1] -> [ASN1]
forall a. ASN1Object a => a -> [ASN1] -> [ASN1]
toASN1 SignatureALG
sigAlg
                               (BitArray -> ASN1
BitString (ByteString -> Int -> BitArray
toBitArray ByteString
sigBits Int
0)
                           ASN1 -> [ASN1] -> [ASN1]
forall a. a -> [a] -> [a]
: ASN1ConstructionType -> ASN1
End ASN1ConstructionType
Sequence
                           ASN1 -> [ASN1] -> [ASN1]
forall a. a -> [a] -> [a]
: []))
            in Signed a -> ByteString -> ByteString -> SignedExact a
forall a. Signed a -> ByteString -> ByteString -> SignedExact a
SignedExact Signed a
signed ByteString
objRaw ByteString
signedRaw
        objASN1 :: [ASN1] -> [ASN1]
objASN1            = \[ASN1]
xs -> ASN1ConstructionType -> ASN1
Start ASN1ConstructionType
Sequence ASN1 -> [ASN1] -> [ASN1]
forall a. a -> [a] -> [a]
: a -> [ASN1] -> [ASN1]
forall a. ASN1Object a => a -> [ASN1] -> [ASN1]
toASN1 a
object (ASN1ConstructionType -> ASN1
End ASN1ConstructionType
Sequence ASN1 -> [ASN1] -> [ASN1]
forall a. a -> [a] -> [a]
: [ASN1]
xs)
        objRaw :: ByteString
objRaw             = DER -> [ASN1] -> ByteString
forall a. ASN1Encoding a => a -> [ASN1] -> ByteString
encodeASN1' DER
DER ([ASN1] -> [ASN1]
objASN1 [])

-- | Transform an object into a 'Signed' object.
--
-- It's recommended to use the SignedExact object instead of Signed.
objectToSigned :: (Show a, Eq a, ASN1Object a)
               => (ByteString
               -> (ByteString, SignatureALG, r))
               -> a
               -> (Signed a, r)
objectToSigned :: (ByteString -> (ByteString, SignatureALG, r)) -> a -> (Signed a, r)
objectToSigned ByteString -> (ByteString, SignatureALG, r)
signatureFunction a
object = (SignedExact a -> Signed a) -> (SignedExact a, r) -> (Signed a, r)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first SignedExact a -> Signed a
forall a. (Show a, Eq a, ASN1Object a) => SignedExact a -> Signed a
getSigned ((SignedExact a, r) -> (Signed a, r))
-> (SignedExact a, r) -> (Signed a, r)
forall a b. (a -> b) -> a -> b
$ (ByteString -> (ByteString, SignatureALG, r))
-> a -> (SignedExact a, r)
forall a r.
(Show a, Eq a, ASN1Object a) =>
(ByteString -> (ByteString, SignatureALG, r))
-> a -> (SignedExact a, r)
objectToSignedExact ByteString -> (ByteString, SignatureALG, r)
signatureFunction a
object

-- | Try to parse a bytestring that use the typical X509 signed structure format
decodeSignedObject :: (Show a, Eq a, ASN1Object a)
                   => ByteString
                   -> Either String (SignedExact a)
decodeSignedObject :: ByteString -> Either String (SignedExact a)
decodeSignedObject ByteString
b = (ASN1Error -> Either String (SignedExact a))
-> ([ASN1Repr] -> Either String (SignedExact a))
-> Either ASN1Error [ASN1Repr]
-> Either String (SignedExact a)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Either String (SignedExact a)
forall a b. a -> Either a b
Left (String -> Either String (SignedExact a))
-> (ASN1Error -> String)
-> ASN1Error
-> Either String (SignedExact a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ASN1Error -> String
forall a. Show a => a -> String
show) [ASN1Repr] -> Either String (SignedExact a)
forall a.
(Show a, Eq a, ASN1Object a) =>
[ASN1Repr] -> Either String (SignedExact a)
parseSigned (Either ASN1Error [ASN1Repr] -> Either String (SignedExact a))
-> Either ASN1Error [ASN1Repr] -> Either String (SignedExact a)
forall a b. (a -> b) -> a -> b
$ BER -> ByteString -> Either ASN1Error [ASN1Repr]
forall a.
ASN1DecodingRepr a =>
a -> ByteString -> Either ASN1Error [ASN1Repr]
decodeASN1Repr' BER
BER ByteString
b
  where -- the following implementation is very inefficient.
        -- uses reverse and containing, move to a better solution eventually
        parseSigned :: [ASN1Repr] -> Either String (SignedExact a)
parseSigned [ASN1Repr]
l = [ASN1Repr]
-> ([ASN1Repr] -> Either String (SignedExact a))
-> Either String (SignedExact a)
forall b p. [(ASN1, b)] -> ([(ASN1, b)] -> p) -> p
onContainer (([ASN1Repr], [ASN1Repr]) -> [ASN1Repr]
forall a b. (a, b) -> a
fst (([ASN1Repr], [ASN1Repr]) -> [ASN1Repr])
-> ([ASN1Repr], [ASN1Repr]) -> [ASN1Repr]
forall a b. (a -> b) -> a -> b
$ [ASN1Repr] -> ([ASN1Repr], [ASN1Repr])
getConstructedEndRepr [ASN1Repr]
l) (([ASN1Repr] -> Either String (SignedExact a))
 -> Either String (SignedExact a))
-> ([ASN1Repr] -> Either String (SignedExact a))
-> Either String (SignedExact a)
forall a b. (a -> b) -> a -> b
$ \[ASN1Repr]
l2 ->
            let ([ASN1Repr]
objRepr,[ASN1Repr]
rem1)   = [ASN1Repr] -> ([ASN1Repr], [ASN1Repr])
getConstructedEndRepr [ASN1Repr]
l2
                ([ASN1Repr]
sigAlgSeq,[ASN1Repr]
rem2) = [ASN1Repr] -> ([ASN1Repr], [ASN1Repr])
getConstructedEndRepr [ASN1Repr]
rem1
                ([ASN1Repr]
sigSeq,[ASN1Repr]
_)       = [ASN1Repr] -> ([ASN1Repr], [ASN1Repr])
getConstructedEndRepr [ASN1Repr]
rem2
                obj :: Either String (a, [ASN1])
obj              = [ASN1Repr]
-> ([ASN1Repr] -> Either String (a, [ASN1]))
-> Either String (a, [ASN1])
forall b p. [(ASN1, b)] -> ([(ASN1, b)] -> p) -> p
onContainer [ASN1Repr]
objRepr ((String -> Either String (a, [ASN1]))
-> ((a, [ASN1]) -> Either String (a, [ASN1]))
-> Either String (a, [ASN1])
-> Either String (a, [ASN1])
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Either String (a, [ASN1])
forall a b. a -> Either a b
Left (a, [ASN1]) -> Either String (a, [ASN1])
forall a b. b -> Either a b
Right (Either String (a, [ASN1]) -> Either String (a, [ASN1]))
-> ([ASN1Repr] -> Either String (a, [ASN1]))
-> [ASN1Repr]
-> Either String (a, [ASN1])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ASN1] -> Either String (a, [ASN1])
forall a. ASN1Object a => [ASN1] -> Either String (a, [ASN1])
fromASN1 ([ASN1] -> Either String (a, [ASN1]))
-> ([ASN1Repr] -> [ASN1])
-> [ASN1Repr]
-> Either String (a, [ASN1])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ASN1Repr -> ASN1) -> [ASN1Repr] -> [ASN1]
forall a b. (a -> b) -> [a] -> [b]
map ASN1Repr -> ASN1
forall a b. (a, b) -> a
fst)
             in case (Either String (a, [ASN1])
obj, (ASN1Repr -> ASN1) -> [ASN1Repr] -> [ASN1]
forall a b. (a -> b) -> [a] -> [b]
map ASN1Repr -> ASN1
forall a b. (a, b) -> a
fst [ASN1Repr]
sigSeq) of
                    (Right (a
o,[]), [BitString BitArray
signature]) ->
                        let rawObj :: ByteString
rawObj = [ASN1Event] -> ByteString
Raw.toByteString ([ASN1Event] -> ByteString) -> [ASN1Event] -> ByteString
forall a b. (a -> b) -> a -> b
$ (ASN1Repr -> [ASN1Event]) -> [ASN1Repr] -> [ASN1Event]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ASN1Repr -> [ASN1Event]
forall a b. (a, b) -> b
snd [ASN1Repr]
objRepr
                         in case [ASN1] -> Either String (SignatureALG, [ASN1])
forall a. ASN1Object a => [ASN1] -> Either String (a, [ASN1])
fromASN1 ([ASN1] -> Either String (SignatureALG, [ASN1]))
-> [ASN1] -> Either String (SignatureALG, [ASN1])
forall a b. (a -> b) -> a -> b
$ (ASN1Repr -> ASN1) -> [ASN1Repr] -> [ASN1]
forall a b. (a -> b) -> [a] -> [b]
map ASN1Repr -> ASN1
forall a b. (a, b) -> a
fst [ASN1Repr]
sigAlgSeq of
                                Left String
s           -> String -> Either String (SignedExact a)
forall a b. a -> Either a b
Left (String
"signed object error sigalg: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
s)
                                Right (SignatureALG
sigAlg,[ASN1]
_) ->
                                    let signed :: Signed a
signed = Signed :: forall a. a -> SignatureALG -> ByteString -> Signed a
Signed
                                                    { signedObject :: a
signedObject    = a
o
                                                    , signedAlg :: SignatureALG
signedAlg       = SignatureALG
sigAlg
                                                    , signedSignature :: ByteString
signedSignature = BitArray -> ByteString
bitArrayGetData BitArray
signature
                                                    }
                                     in SignedExact a -> Either String (SignedExact a)
forall a b. b -> Either a b
Right (SignedExact a -> Either String (SignedExact a))
-> SignedExact a -> Either String (SignedExact a)
forall a b. (a -> b) -> a -> b
$ SignedExact :: forall a. Signed a -> ByteString -> ByteString -> SignedExact a
SignedExact
                                                { getSigned :: Signed a
getSigned          = Signed a
signed
                                                , exactObjectRaw :: ByteString
exactObjectRaw     = ByteString
rawObj
                                                , encodeSignedObject :: ByteString
encodeSignedObject = ByteString
b
                                                }
                    (Right (a
_,[ASN1]
remObj), [ASN1]
_) ->
                        String -> Either String (SignedExact a)
forall a b. a -> Either a b
Left (String -> Either String (SignedExact a))
-> String -> Either String (SignedExact a)
forall a b. (a -> b) -> a -> b
$ (String
"signed object error: remaining stream in object: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [ASN1] -> String
forall a. Show a => a -> String
show [ASN1]
remObj)
                    (Left String
err, [ASN1]
_) -> String -> Either String (SignedExact a)
forall a b. a -> Either a b
Left (String -> Either String (SignedExact a))
-> String -> Either String (SignedExact a)
forall a b. (a -> b) -> a -> b
$ (String
"signed object error: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
err)
        onContainer :: [(ASN1, b)] -> ([(ASN1, b)] -> p) -> p
onContainer ((Start ASN1ConstructionType
_, b
_) : [(ASN1, b)]
l) [(ASN1, b)] -> p
f =
            case [(ASN1, b)] -> [(ASN1, b)]
forall a. [a] -> [a]
reverse [(ASN1, b)]
l of
                ((End ASN1ConstructionType
_, b
_) : [(ASN1, b)]
l2) -> [(ASN1, b)] -> p
f ([(ASN1, b)] -> p) -> [(ASN1, b)] -> p
forall a b. (a -> b) -> a -> b
$ [(ASN1, b)] -> [(ASN1, b)]
forall a. [a] -> [a]
reverse [(ASN1, b)]
l2
                [(ASN1, b)]
_                 -> [(ASN1, b)] -> p
f []
        onContainer [(ASN1, b)]
_ [(ASN1, b)] -> p
f = [(ASN1, b)] -> p
f []