blob: 759466b53dc65033e8e269220283616ae6c626ef [file] [log] [blame]
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -07001--
2-- Licensed to the Apache Software Foundation (ASF) under one
3-- or more contributor license agreements. See the NOTICE file
4-- distributed with this work for additional information
5-- regarding copyright ownership. The ASF licenses this file
6-- to you under the Apache License, Version 2.0 (the
7-- "License"); you may not use this file except in compliance
8-- with the License. You may obtain a copy of the License at
9--
10-- http://www.apache.org/licenses/LICENSE-2.0
11--
12-- Unless required by applicable law or agreed to in writing,
13-- software distributed under the License is distributed on an
14-- "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
15-- KIND, either express or implied. See the License for the
16-- specific language governing permissions and limitations
17-- under the License.
18--
19
20{-# LANGUAGE CPP #-}
21{-# LANGUAGE ExistentialQuantification #-}
22{-# LANGUAGE OverloadedStrings #-}
23{-# LANGUAGE ScopedTypeVariables #-}
24
25module Thrift.Protocol.Compact
26 ( module Thrift.Protocol
27 , CompactProtocol(..)
28 ) where
29
30import Control.Applicative
31import Control.Exception ( throw )
32import Control.Monad
33import Data.Attoparsec.ByteString as P
34import Data.Attoparsec.ByteString.Lazy as LP
35import Data.Bits
36import Data.ByteString.Lazy.Builder as B
37import Data.Int
38import Data.List as List
39import Data.Monoid
40import Data.Word
41import Data.Text.Lazy.Encoding ( decodeUtf8, encodeUtf8 )
42
43import Thrift.Protocol hiding (versionMask)
44import Thrift.Transport
45import Thrift.Types
46
47import qualified Data.ByteString as BS
48import qualified Data.ByteString.Lazy as LBS
49import qualified Data.HashMap.Strict as Map
50import qualified Data.Text.Lazy as LT
51
52-- | the Compact Protocol implements the standard Thrift 'TCompactProcotol'
53-- which is similar to the 'TBinaryProtocol', but takes less space on the wire.
54-- Integral types are encoded using as varints.
55data CompactProtocol a = CompactProtocol a
56 -- ^ Constuct a 'CompactProtocol' with a 'Transport'
57
Nobuaki Sukegawa7c7d6792015-12-09 03:22:35 +090058protocolID, version, versionMask, typeMask, typeBits :: Word8
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070059protocolID = 0x82 -- 1000 0010
60version = 0x01
61versionMask = 0x1f -- 0001 1111
62typeMask = 0xe0 -- 1110 0000
Jens Geyera86886e2014-09-17 22:25:48 +020063typeBits = 0x07 -- 0000 0111
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070064typeShiftAmount :: Int
65typeShiftAmount = 5
66
67
68instance Protocol CompactProtocol where
69 getTransport (CompactProtocol t) = t
70
71 writeMessageBegin p (n, t, s) = tWrite (getTransport p) $ toLazyByteString $
Nobuaki Sukegawa7c7d6792015-12-09 03:22:35 +090072 B.word8 protocolID <>
73 B.word8 ((version .&. versionMask) .|.
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070074 (((fromIntegral $ fromEnum t) `shiftL`
75 typeShiftAmount) .&. typeMask)) <>
76 buildVarint (i32ToZigZag s) <>
77 buildCompactValue (TString $ encodeUtf8 n)
78
79 readMessageBegin p = runParser p $ do
80 pid <- fromIntegral <$> P.anyWord8
81 when (pid /= protocolID) $ error "Bad Protocol ID"
82 w <- fromIntegral <$> P.anyWord8
83 let ver = w .&. versionMask
84 when (ver /= version) $ error "Bad Protocol version"
Jens Geyera86886e2014-09-17 22:25:48 +020085 let typ = (w `shiftR` typeShiftAmount) .&. typeBits
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070086 seqId <- parseVarint zigZagToI32
87 TString name <- parseCompactValue T_STRING
88 return (decodeUtf8 name, toEnum $ fromIntegral $ typ, seqId)
89
90 serializeVal _ = toLazyByteString . buildCompactValue
91 deserializeVal _ ty bs =
92 case LP.eitherResult $ LP.parse (parseCompactValue ty) bs of
93 Left s -> error s
94 Right val -> val
95
96 readVal p ty = runParser p $ parseCompactValue ty
97
98
99-- | Writing Functions
100buildCompactValue :: ThriftVal -> Builder
101buildCompactValue (TStruct fields) = buildCompactStruct fields
102buildCompactValue (TMap kt vt entries) =
103 let len = fromIntegral $ length entries :: Word32 in
104 if len == 0
105 then B.word8 0x00
106 else buildVarint len <>
107 B.word8 (fromTType kt `shiftL` 4 .|. fromTType vt) <>
108 buildCompactMap entries
109buildCompactValue (TList ty entries) =
110 let len = length entries in
111 (if len < 15
112 then B.word8 $ (fromIntegral len `shiftL` 4) .|. fromTType ty
113 else B.word8 (0xF0 .|. fromTType ty) <>
114 buildVarint (fromIntegral len :: Word32)) <>
115 buildCompactList entries
116buildCompactValue (TSet ty entries) = buildCompactValue (TList ty entries)
117buildCompactValue (TBool b) =
118 B.word8 $ toEnum $ if b then 1 else 0
119buildCompactValue (TByte b) = int8 b
120buildCompactValue (TI16 i) = buildVarint $ i16ToZigZag i
121buildCompactValue (TI32 i) = buildVarint $ i32ToZigZag i
122buildCompactValue (TI64 i) = buildVarint $ i64ToZigZag i
Nobuaki Sukegawa7c7d6792015-12-09 03:22:35 +0900123buildCompactValue (TDouble d) = doubleLE d
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700124buildCompactValue (TString s) = buildVarint len <> lazyByteString s
125 where
126 len = fromIntegral (LBS.length s) :: Word32
127
128buildCompactStruct :: Map.HashMap Int16 (LT.Text, ThriftVal) -> Builder
129buildCompactStruct = flip (loop 0) mempty . Map.toList
130 where
131 loop _ [] acc = acc <> B.word8 (fromTType T_STOP)
132 loop lastId ((fid, (_,val)) : fields) acc = loop fid fields $ acc <>
133 (if fid > lastId && fid - lastId <= 15
134 then B.word8 $ fromIntegral ((fid - lastId) `shiftL` 4) .|. typeOf val
135 else B.word8 (typeOf val) <> buildVarint (i16ToZigZag fid)) <>
136 (if typeOf val > 0x02 -- Not a T_BOOL
137 then buildCompactValue val
138 else mempty) -- T_BOOLs are encoded in the type
139buildCompactMap :: [(ThriftVal, ThriftVal)] -> Builder
140buildCompactMap = foldl combine mempty
141 where
142 combine s (key, val) = buildCompactValue key <> buildCompactValue val <> s
143
144buildCompactList :: [ThriftVal] -> Builder
145buildCompactList = foldr (mappend . buildCompactValue) mempty
146
147-- | Reading Functions
148parseCompactValue :: ThriftType -> Parser ThriftVal
149parseCompactValue (T_STRUCT _) = TStruct <$> parseCompactStruct
150parseCompactValue (T_MAP kt' vt') = do
151 n <- parseVarint id
152 if n == 0
153 then return $ TMap kt' vt' []
154 else do
155 w <- P.anyWord8
156 let kt = typeFrom $ w `shiftR` 4
157 vt = typeFrom $ w .&. 0x0F
158 TMap kt vt <$> parseCompactMap kt vt n
159parseCompactValue (T_LIST ty) = TList ty <$> parseCompactList
160parseCompactValue (T_SET ty) = TSet ty <$> parseCompactList
161parseCompactValue T_BOOL = TBool . (/=0) <$> P.anyWord8
162parseCompactValue T_BYTE = TByte . fromIntegral <$> P.anyWord8
163parseCompactValue T_I16 = TI16 <$> parseVarint zigZagToI16
164parseCompactValue T_I32 = TI32 <$> parseVarint zigZagToI32
165parseCompactValue T_I64 = TI64 <$> parseVarint zigZagToI64
Nobuaki Sukegawa7c7d6792015-12-09 03:22:35 +0900166parseCompactValue T_DOUBLE = TDouble . bsToDoubleLE <$> P.take 8
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700167parseCompactValue T_STRING = do
168 len :: Word32 <- parseVarint id
169 TString . LBS.fromStrict <$> P.take (fromIntegral len)
170parseCompactValue ty = error $ "Cannot read value of type " ++ show ty
171
172parseCompactStruct :: Parser (Map.HashMap Int16 (LT.Text, ThriftVal))
173parseCompactStruct = Map.fromList <$> parseFields 0
174 where
175 parseFields :: Int16 -> Parser [(Int16, (LT.Text, ThriftVal))]
176 parseFields lastId = do
177 w <- P.anyWord8
178 if w == 0x00
179 then return []
180 else do
181 let ty = typeFrom (w .&. 0x0F)
182 modifier = (w .&. 0xF0) `shiftR` 4
183 fid <- if modifier /= 0
184 then return (lastId + fromIntegral modifier)
185 else parseVarint zigZagToI16
186 val <- if ty == T_BOOL
187 then return (TBool $ (w .&. 0x0F) == 0x01)
188 else parseCompactValue ty
189 ((fid, (LT.empty, val)) : ) <$> parseFields fid
190
191parseCompactMap :: ThriftType -> ThriftType -> Int32 ->
192 Parser [(ThriftVal, ThriftVal)]
193parseCompactMap kt vt n | n <= 0 = return []
194 | otherwise = do
195 k <- parseCompactValue kt
196 v <- parseCompactValue vt
197 ((k,v) :) <$> parseCompactMap kt vt (n-1)
198
199parseCompactList :: Parser [ThriftVal]
200parseCompactList = do
201 w <- P.anyWord8
202 let ty = typeFrom $ w .&. 0x0F
203 lsize = w `shiftR` 4
204 size <- if lsize == 0xF
205 then parseVarint id
206 else return $ fromIntegral lsize
207 loop ty size
208 where
209 loop :: ThriftType -> Int32 -> Parser [ThriftVal]
210 loop ty n | n <= 0 = return []
211 | otherwise = liftM2 (:) (parseCompactValue ty)
212 (loop ty (n-1))
213
214-- Signed numbers must be converted to "Zig Zag" format before they can be
215-- serialized in the Varint format
216i16ToZigZag :: Int16 -> Word16
217i16ToZigZag n = fromIntegral $ (n `shiftL` 1) `xor` (n `shiftR` 15)
218
219zigZagToI16 :: Word16 -> Int16
220zigZagToI16 n = fromIntegral $ (n `shiftR` 1) `xor` negate (n .&. 0x1)
221
222i32ToZigZag :: Int32 -> Word32
223i32ToZigZag n = fromIntegral $ (n `shiftL` 1) `xor` (n `shiftR` 31)
224
225zigZagToI32 :: Word32 -> Int32
226zigZagToI32 n = fromIntegral $ (n `shiftR` 1) `xor` negate (n .&. 0x1)
227
228i64ToZigZag :: Int64 -> Word64
229i64ToZigZag n = fromIntegral $ (n `shiftL` 1) `xor` (n `shiftR` 63)
230
231zigZagToI64 :: Word64 -> Int64
232zigZagToI64 n = fromIntegral $ (n `shiftR` 1) `xor` negate (n .&. 0x1)
233
234buildVarint :: (Bits a, Integral a) => a -> Builder
235buildVarint n | n .&. complement 0x7F == 0 = B.word8 $ fromIntegral n
236 | otherwise = B.word8 (0x80 .|. (fromIntegral n .&. 0x7F)) <>
237 buildVarint (n `shiftR` 7)
238
239parseVarint :: (Bits a, Integral a, Ord a) => (a -> b) -> Parser b
240parseVarint fromZigZag = do
241 bytestemp <- BS.unpack <$> P.takeTill (not . flip testBit 7)
242 lsb <- P.anyWord8
243 let bytes = lsb : List.reverse bytestemp
244 return $ fromZigZag $ List.foldl' combine 0x00 bytes
245 where combine a b = (a `shiftL` 7) .|. (fromIntegral b .&. 0x7f)
246
247-- | Compute the Compact Type
248fromTType :: ThriftType -> Word8
249fromTType ty = case ty of
250 T_STOP -> 0x00
251 T_BOOL -> 0x01
252 T_BYTE -> 0x03
253 T_I16 -> 0x04
254 T_I32 -> 0x05
255 T_I64 -> 0x06
256 T_DOUBLE -> 0x07
257 T_STRING -> 0x08
258 T_LIST{} -> 0x09
259 T_SET{} -> 0x0A
260 T_MAP{} -> 0x0B
261 T_STRUCT{} -> 0x0C
262 T_VOID -> error "No Compact type for T_VOID"
263
264typeOf :: ThriftVal -> Word8
265typeOf v = case v of
266 TBool True -> 0x01
267 TBool False -> 0x02
268 TByte _ -> 0x03
269 TI16 _ -> 0x04
270 TI32 _ -> 0x05
271 TI64 _ -> 0x06
272 TDouble _ -> 0x07
273 TString _ -> 0x08
274 TList{} -> 0x09
275 TSet{} -> 0x0A
276 TMap{} -> 0x0B
277 TStruct{} -> 0x0C
278
279typeFrom :: Word8 -> ThriftType
280typeFrom w = case w of
281 0x01 -> T_BOOL
282 0x02 -> T_BOOL
283 0x03 -> T_BYTE
284 0x04 -> T_I16
285 0x05 -> T_I32
286 0x06 -> T_I64
287 0x07 -> T_DOUBLE
288 0x08 -> T_STRING
289 0x09 -> T_LIST T_VOID
290 0x0A -> T_SET T_VOID
291 0x0B -> T_MAP T_VOID T_VOID
292 0x0C -> T_STRUCT Map.empty
293 n -> error $ "typeFrom: " ++ show n ++ " is not a compact type"