-- |
-- Module      : Network.TLS.Util.ASN1
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : experimental
-- Portability : unknown
--
-- ASN1 utils for TLS
--
module Network.TLS.Util.ASN1
    ( decodeASN1Object
    , encodeASN1Object
    ) where

import Network.TLS.Imports
import Data.ASN1.Types (fromASN1, toASN1, ASN1Object)
import Data.ASN1.Encoding (decodeASN1', encodeASN1')
import Data.ASN1.BinaryEncoding (DER(..))

-- | Attempt to decode a bytestring representing
-- an DER ASN.1 serialized object into the object.
decodeASN1Object :: ASN1Object a
                 => String
                 -> ByteString
                 -> Either String a
decodeASN1Object :: forall a. ASN1Object a => String -> ByteString -> Either String a
decodeASN1Object String
name ByteString
bs =
    case forall a.
ASN1Decoding a =>
a -> ByteString -> Either ASN1Error [ASN1]
decodeASN1' DER
DER ByteString
bs of
        Left ASN1Error
e     -> forall a b. a -> Either a b
Left (String
name forall a. [a] -> [a] -> [a]
++ String
": cannot decode ASN1: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show ASN1Error
e)
        Right [ASN1]
asn1 -> case forall a. ASN1Object a => [ASN1] -> Either String (a, [ASN1])
fromASN1 [ASN1]
asn1 of
                            Left String
e      -> forall a b. a -> Either a b
Left (String
name forall a. [a] -> [a] -> [a]
++ String
": cannot parse ASN1: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show String
e)
                            Right (a
d,[ASN1]
_) -> forall a b. b -> Either a b
Right a
d

-- | Encode an ASN.1 Object to the DER serialized bytestring
encodeASN1Object :: ASN1Object a
                 => a
                 -> ByteString
encodeASN1Object :: forall a. ASN1Object a => a -> ByteString
encodeASN1Object a
obj = forall a. ASN1Encoding a => a -> [ASN1] -> ByteString
encodeASN1' DER
DER forall a b. (a -> b) -> a -> b
$ forall a. ASN1Object a => a -> ASN1S
toASN1 a
obj []