-- |
-- Module      : Data.ASN1.Serialize
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : experimental
-- Portability : unknown
--
module Data.ASN1.Serialize (getHeader, putHeader) where

import qualified Data.ByteString as B
import Data.ASN1.Get
import Data.ASN1.Internal
import Data.ASN1.Types
import Data.ASN1.Types.Lowlevel
import Data.Bits
import Data.Word
import Control.Applicative ((<$>))
import Control.Monad

-- | parse an ASN1 header
getHeader :: Get ASN1Header
getHeader :: Get ASN1Header
getHeader = do
    (ASN1Class
cl,Bool
pc,Int
t1) <- Word8 -> (ASN1Class, Bool, Int)
parseFirstWord forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
    Int
tag        <- if Int
t1 forall a. Eq a => a -> a -> Bool
== Int
0x1f then Get Int
getTagLong else forall (m :: * -> *) a. Monad m => a -> m a
return Int
t1
    ASN1Length
len        <- Get ASN1Length
getLength
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ASN1Class -> Int -> Bool -> ASN1Length -> ASN1Header
ASN1Header ASN1Class
cl Int
tag Bool
pc ASN1Length
len

-- | Parse the first word of an header
parseFirstWord :: Word8 -> (ASN1Class, Bool, ASN1Tag)
parseFirstWord :: Word8 -> (ASN1Class, Bool, Int)
parseFirstWord Word8
w = (ASN1Class
cl,Bool
pc,Int
t1)
  where cl :: ASN1Class
cl = forall a. Enum a => Int -> a
toEnum forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ (Word8
w forall a. Bits a => a -> Int -> a
`shiftR` Int
6)
        pc :: Bool
pc = forall a. Bits a => a -> Int -> Bool
testBit Word8
w Int
5
        t1 :: Int
t1 = forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
w forall a. Bits a => a -> a -> a
.&. Word8
0x1f)

{- when the first tag is 0x1f, the tag is in long form, where
 - we get bytes while the 7th bit is set. -}
getTagLong :: Get ASN1Tag
getTagLong :: Get Int
getTagLong = do
    Int
t <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
t forall a. Eq a => a -> a -> Bool
== Int
0x80) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"non canonical encoding of long tag"
    if forall a. Bits a => a -> Int -> Bool
testBit Int
t Int
7
        then forall {b}. (Num b, Bits b) => b -> Get b
loop (forall a. Bits a => a -> Int -> a
clearBit Int
t Int
7)
        else forall (m :: * -> *) a. Monad m => a -> m a
return Int
t
  where loop :: b -> Get b
loop b
n = do
            b
t <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
            if forall a. Bits a => a -> Int -> Bool
testBit b
t Int
7
                then b -> Get b
loop (b
n forall a. Bits a => a -> Int -> a
`shiftL` Int
7 forall a. Num a => a -> a -> a
+ forall a. Bits a => a -> Int -> a
clearBit b
t Int
7)
                else forall (m :: * -> *) a. Monad m => a -> m a
return (b
n forall a. Bits a => a -> Int -> a
`shiftL` Int
7 forall a. Num a => a -> a -> a
+ b
t)


{- get the asn1 length which is either short form if 7th bit is not set,
 - indefinite form is the 7 bit is set and every other bits clear,
 - or long form otherwise, where the next bytes will represent the length
 -}
getLength :: Get ASN1Length
getLength :: Get ASN1Length
getLength = do
    Int
l1 <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
    if forall a. Bits a => a -> Int -> Bool
testBit Int
l1 Int
7
        then case forall a. Bits a => a -> Int -> a
clearBit Int
l1 Int
7 of
            Int
0   -> forall (m :: * -> *) a. Monad m => a -> m a
return ASN1Length
LenIndefinite
            Int
len -> do
                ByteString
lw <- Int -> Get ByteString
getBytes Int
len
                forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Int -> ASN1Length
LenLong Int
len forall a b. (a -> b) -> a -> b
$ ByteString -> Int
uintbs ByteString
lw)
        else
            forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ASN1Length
LenShort Int
l1)
  where
        {- uintbs return the unsigned int represented by the bytes -}
        uintbs :: ByteString -> Int
uintbs = forall a. (a -> Word8 -> a) -> a -> ByteString -> a
B.foldl (\Int
acc Word8
n -> (Int
acc forall a. Bits a => a -> Int -> a
`shiftL` Int
8) forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
n) Int
0

-- | putIdentifier encode an ASN1 Identifier into a marshalled value
putHeader :: ASN1Header -> B.ByteString
putHeader :: ASN1Header -> ByteString
putHeader (ASN1Header ASN1Class
cl Int
tag Bool
pc ASN1Length
len) = [ByteString] -> ByteString
B.concat
    [ Word8 -> ByteString
B.singleton Word8
word1
    , if Int
tag forall a. Ord a => a -> a -> Bool
< Int
0x1f then ByteString
B.empty else ByteString
tagBS
    , ByteString
lenBS]
  where cli :: Word8
cli   = forall a. Bits a => a -> Int -> a
shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum ASN1Class
cl) Int
6
        pcval :: Word8
pcval = forall a. Bits a => a -> Int -> a
shiftL (if Bool
pc then Word8
0x1 else Word8
0x0) Int
5
        tag0 :: Word8
tag0  = if Int
tag forall a. Ord a => a -> a -> Bool
< Int
0x1f then forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
tag else Word8
0x1f
        word1 :: Word8
word1 = Word8
cli forall a. Bits a => a -> a -> a
.|. Word8
pcval forall a. Bits a => a -> a -> a
.|. Word8
tag0
        lenBS :: ByteString
lenBS = [Word8] -> ByteString
B.pack forall a b. (a -> b) -> a -> b
$ ASN1Length -> [Word8]
putLength ASN1Length
len
        tagBS :: ByteString
tagBS = forall i. (Bits i, Integral i) => i -> ByteString
putVarEncodingIntegral Int
tag

{- | putLength encode a length into a ASN1 length.
 - see getLength for the encoding rules -}
putLength :: ASN1Length -> [Word8]
putLength :: ASN1Length -> [Word8]
putLength (LenShort Int
i)
    | Int
i forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
i forall a. Ord a => a -> a -> Bool
> Int
0x7f = forall a. HasCallStack => String -> a
error String
"putLength: short length is not between 0x0 and 0x80"
    | Bool
otherwise         = [forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i]
putLength (LenLong Int
_ Int
i)
    | Int
i forall a. Ord a => a -> a -> Bool
< Int
0     = forall a. HasCallStack => String -> a
error String
"putLength: long length is negative"
    | Bool
otherwise = Word8
lenbytes forall a. a -> [a] -> [a]
: [Word8]
lw
        where
            lw :: [Word8]
lw       = Integer -> [Word8]
bytesOfUInt forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i
            lenbytes :: Word8
lenbytes = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Word8]
lw forall a. Bits a => a -> a -> a
.|. Int
0x80)
putLength (ASN1Length
LenIndefinite) = [Word8
0x80]