blob: 2d35305dcda222ef381ad4817dbf6a7066ed39ce [file] [log] [blame]
Bryan Duxbury0781f2b2009-04-07 23:29:42 +00001--
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
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070020{-# LANGUAGE CPP #-}
21{-# LANGUAGE ExistentialQuantification #-}
22{-# LANGUAGE OverloadedStrings #-}
23{-# LANGUAGE ScopedTypeVariables #-}
24
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000025module Thrift.Protocol.Binary
26 ( module Thrift.Protocol
27 , BinaryProtocol(..)
28 ) where
29
30import Control.Exception ( throw )
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070031import Control.Monad
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000032import Data.Bits
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070033import Data.ByteString.Lazy.Builder
34import Data.Functor
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000035import Data.Int
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070036import Data.Monoid
Roger Meier6849f202012-05-18 07:35:19 +000037import Data.Text.Lazy.Encoding ( decodeUtf8, encodeUtf8 )
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000038
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000039import Thrift.Protocol
40import Thrift.Transport
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070041import Thrift.Types
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000042
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070043import qualified Data.Attoparsec.ByteString as P
44import qualified Data.Attoparsec.ByteString.Lazy as LP
45import qualified Data.Binary as Binary
Bryan Duxbury75a33e82010-09-22 00:48:56 +000046import qualified Data.ByteString.Lazy as LBS
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070047import qualified Data.HashMap.Strict as Map
48import qualified Data.Text.Lazy as LT
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000049
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070050data BinaryProtocol a = BinaryProtocol a
Bryan Duxburye59a80f2010-09-20 15:21:37 +000051
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070052-- NOTE: Reading and Writing functions rely on Builders and Data.Binary to
53-- encode and decode data. Data.Binary assumes that the binary values it is
54-- encoding to and decoding from are in BIG ENDIAN format, and converts the
55-- endianness as necessary to match the local machine.
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000056instance Protocol BinaryProtocol where
57 getTransport (BinaryProtocol t) = t
58
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070059 writeMessageBegin p (n, t, s) = tWrite (getTransport p) $ toLazyByteString $
60 buildBinaryValue (TI32 (version1 .|. fromIntegral (fromEnum t))) <>
61 buildBinaryValue (TString $ encodeUtf8 n) <>
62 buildBinaryValue (TI32 s)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000063
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070064 readMessageBegin p = runParser p $ do
65 TI32 ver <- parseBinaryValue T_I32
66 if ver .&. versionMask /= version1
67 then throw $ ProtocolExn PE_BAD_VERSION "Missing version identifier"
68 else do
69 TString s <- parseBinaryValue T_STRING
70 TI32 sz <- parseBinaryValue T_I32
71 return (decodeUtf8 s, toEnum $ fromIntegral $ ver .&. 0xFF, sz)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000072
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070073 serializeVal _ = toLazyByteString . buildBinaryValue
74 deserializeVal _ ty bs =
75 case LP.eitherResult $ LP.parse (parseBinaryValue ty) bs of
76 Left s -> error s
77 Right val -> val
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000078
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070079 readVal p = runParser p . parseBinaryValue
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000080
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070081-- | Writing Functions
82buildBinaryValue :: ThriftVal -> Builder
83buildBinaryValue (TStruct fields) = buildBinaryStruct fields <> buildType T_STOP
84buildBinaryValue (TMap ky vt entries) =
85 buildType ky <>
86 buildType vt <>
87 int32BE (fromIntegral (length entries)) <>
88 buildBinaryMap entries
89buildBinaryValue (TList ty entries) =
90 buildType ty <>
91 int32BE (fromIntegral (length entries)) <>
92 buildBinaryList entries
93buildBinaryValue (TSet ty entries) =
94 buildType ty <>
95 int32BE (fromIntegral (length entries)) <>
96 buildBinaryList entries
97buildBinaryValue (TBool b) =
98 word8 $ toEnum $ if b then 1 else 0
99buildBinaryValue (TByte b) = int8 b
100buildBinaryValue (TI16 i) = int16BE i
101buildBinaryValue (TI32 i) = int32BE i
102buildBinaryValue (TI64 i) = int64BE i
103buildBinaryValue (TDouble d) = doubleBE d
104buildBinaryValue (TString s) = int32BE len <> lazyByteString s
105 where
106 len :: Int32 = fromIntegral (LBS.length s)
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900107buildBinaryValue (TBinary s) = buildBinaryValue (TString s)
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000108
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700109buildBinaryStruct :: Map.HashMap Int16 (LT.Text, ThriftVal) -> Builder
110buildBinaryStruct = Map.foldrWithKey combine mempty
111 where
112 combine fid (_,val) s =
113 buildTypeOf val <> int16BE fid <> buildBinaryValue val <> s
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000114
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700115buildBinaryMap :: [(ThriftVal, ThriftVal)] -> Builder
116buildBinaryMap = foldl combine mempty
117 where
118 combine s (key, val) = s <> buildBinaryValue key <> buildBinaryValue val
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000119
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700120buildBinaryList :: [ThriftVal] -> Builder
121buildBinaryList = foldr (mappend . buildBinaryValue) mempty
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000122
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700123-- | Reading Functions
124parseBinaryValue :: ThriftType -> P.Parser ThriftVal
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900125parseBinaryValue (T_STRUCT tmap) = TStruct <$> parseBinaryStruct tmap
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700126parseBinaryValue (T_MAP _ _) = do
127 kt <- parseType
128 vt <- parseType
129 n <- Binary.decode . LBS.fromStrict <$> P.take 4
130 TMap kt vt <$> parseBinaryMap kt vt n
131parseBinaryValue (T_LIST _) = do
132 t <- parseType
133 n <- Binary.decode . LBS.fromStrict <$> P.take 4
134 TList t <$> parseBinaryList t n
135parseBinaryValue (T_SET _) = do
136 t <- parseType
137 n <- Binary.decode . LBS.fromStrict <$> P.take 4
138 TSet t <$> parseBinaryList t n
139parseBinaryValue T_BOOL = TBool . (/=0) <$> P.anyWord8
140parseBinaryValue T_BYTE = TByte . Binary.decode . LBS.fromStrict <$> P.take 1
141parseBinaryValue T_I16 = TI16 . Binary.decode . LBS.fromStrict <$> P.take 2
142parseBinaryValue T_I32 = TI32 . Binary.decode . LBS.fromStrict <$> P.take 4
143parseBinaryValue T_I64 = TI64 . Binary.decode . LBS.fromStrict <$> P.take 8
144parseBinaryValue T_DOUBLE = TDouble . bsToDouble <$> P.take 8
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900145parseBinaryValue T_STRING = parseBinaryString TString
146parseBinaryValue T_BINARY = parseBinaryString TBinary
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700147parseBinaryValue ty = error $ "Cannot read value of type " ++ show ty
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000148
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900149parseBinaryString ty = do
150 i :: Int32 <- Binary.decode . LBS.fromStrict <$> P.take 4
151 ty . LBS.fromStrict <$> P.take (fromIntegral i)
152
153parseBinaryStruct :: TypeMap -> P.Parser (Map.HashMap Int16 (LT.Text, ThriftVal))
154parseBinaryStruct tmap = Map.fromList <$> P.manyTill parseField (matchType T_STOP)
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700155 where
156 parseField = do
157 t <- parseType
158 n <- Binary.decode . LBS.fromStrict <$> P.take 2
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900159 v <- case (t, Map.lookup n tmap) of
160 (T_STRING, Just (_, T_BINARY)) -> parseBinaryValue T_BINARY
161 _ -> parseBinaryValue t
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700162 return (n, ("", v))
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000163
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700164parseBinaryMap :: ThriftType -> ThriftType -> Int32 -> P.Parser [(ThriftVal, ThriftVal)]
165parseBinaryMap kt vt n | n <= 0 = return []
166 | otherwise = do
167 k <- parseBinaryValue kt
168 v <- parseBinaryValue vt
169 ((k,v) :) <$> parseBinaryMap kt vt (n-1)
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000170
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700171parseBinaryList :: ThriftType -> Int32 -> P.Parser [ThriftVal]
172parseBinaryList ty n | n <= 0 = return []
173 | otherwise = liftM2 (:) (parseBinaryValue ty)
174 (parseBinaryList ty (n-1))
175
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000176
177
178-- | Write a type as a byte
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700179buildType :: ThriftType -> Builder
180buildType t = word8 $ fromIntegral $ fromEnum t
181
182-- | Write type of a ThriftVal as a byte
183buildTypeOf :: ThriftVal -> Builder
184buildTypeOf = buildType . getTypeOf
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000185
186-- | Read a byte as though it were a ThriftType
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700187parseType :: P.Parser ThriftType
188parseType = toEnum . fromIntegral <$> P.anyWord8
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000189
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700190matchType :: ThriftType -> P.Parser ThriftType
191matchType t = t <$ P.word8 (fromIntegral $ fromEnum t)