blob: 839eddc84655a7289ad43ba2a5171fe61c668698 [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{-# LANGUAGE TupleSections #-}
25
26module Thrift.Protocol.JSON
27 ( module Thrift.Protocol
28 , JSONProtocol(..)
29 ) where
30
31import Control.Applicative
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090032import Control.Exception (bracket)
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070033import Control.Monad
34import Data.Attoparsec.ByteString as P
35import Data.Attoparsec.ByteString.Char8 as PC
36import Data.Attoparsec.ByteString.Lazy as LP
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +090037import Data.ByteString.Base64.Lazy as B64C
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070038import Data.ByteString.Lazy.Builder as B
39import Data.ByteString.Internal (c2w, w2c)
40import Data.Functor
41import Data.Int
42import Data.List
43import Data.Maybe (catMaybes)
44import Data.Monoid
45import Data.Text.Lazy.Encoding
46import Data.Word
47import qualified Data.HashMap.Strict as Map
48
49import Thrift.Protocol
50import Thrift.Transport
51import Thrift.Types
52
53import qualified Data.ByteString.Lazy as LBS
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +090054import qualified Data.ByteString.Lazy.Char8 as LBSC
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070055import qualified Data.Text.Lazy as LT
56
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +090057-- | The JSON Protocol data uses the standard 'TJSONProtocol'. Data is
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070058-- encoded as a JSON 'ByteString'
59data JSONProtocol t = JSONProtocol t
60 -- ^ Construct a 'JSONProtocol' with a 'Transport'
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090061getTransport :: Transport t => JSONProtocol t -> t
62getTransport (JSONProtocol t) = t
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070063
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090064instance Transport t => Protocol (JSONProtocol t) where
65 readByte p = tReadAll (getTransport p) 1
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070066
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090067 writeMessage (JSONProtocol t) (s, ty, sq) = bracket readMessageBegin readMessageEnd . const
68 where
69 readMessageBegin = tWrite t $ toLazyByteString $
70 B.char8 '[' <> buildShowable (1 :: Int32) <>
71 B.string8 ",\"" <> escape (encodeUtf8 s) <> B.char8 '\"' <>
72 B.char8 ',' <> buildShowable (fromEnum ty) <>
73 B.char8 ',' <> buildShowable sq <>
74 B.char8 ','
75 readMessageEnd _ = do
76 tWrite t "]"
77 tFlush t
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070078
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090079 readMessage p = bracket readMessageBegin readMessageEnd
80 where
81 readMessageBegin = runParser p $ skipSpace *> do
82 _ver :: Int32 <- lexeme (PC.char8 '[') *> lexeme (signed decimal)
83 bs <- lexeme (PC.char8 ',') *> lexeme escapedString
84 case decodeUtf8' bs of
85 Left _ -> fail "readMessage: invalid text encoding"
86 Right str -> do
87 ty <- toEnum <$> (lexeme (PC.char8 ',') *> lexeme (signed decimal))
88 seqNum <- lexeme (PC.char8 ',') *> lexeme (signed decimal)
89 _ <- PC.char8 ','
90 return (str, ty, seqNum)
91 readMessageEnd _ = void $ runParser p (PC.char8 ']')
92
93 writeVal p = tWrite (getTransport p) . toLazyByteString . buildJSONValue
94 readVal p ty = runParser p $ skipSpace *> parseJSONValue ty
95
96instance Transport t => StatelessProtocol (JSONProtocol t) where
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070097 serializeVal _ = toLazyByteString . buildJSONValue
98 deserializeVal _ ty bs =
99 case LP.eitherResult $ LP.parse (parseJSONValue ty) bs of
100 Left s -> error s
101 Right val -> val
102
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700103-- Writing Functions
104
105buildJSONValue :: ThriftVal -> Builder
106buildJSONValue (TStruct fields) = B.char8 '{' <> buildJSONStruct fields <> B.char8 '}'
107buildJSONValue (TMap kt vt entries) =
108 B.char8 '[' <> B.char8 '"' <> getTypeName kt <> B.char8 '"' <>
109 B.char8 ',' <> B.char8 '"' <> getTypeName vt <> B.char8 '"' <>
110 B.char8 ',' <> buildShowable (length entries) <>
111 B.char8 ',' <> B.char8 '{' <> buildJSONMap entries <> B.char8 '}' <>
112 B.char8 ']'
113buildJSONValue (TList ty entries) =
114 B.char8 '[' <> B.char8 '"' <> getTypeName ty <> B.char8 '"' <>
115 B.char8 ',' <> buildShowable (length entries) <>
116 (if length entries > 0
117 then B.char8 ',' <> buildJSONList entries
118 else mempty) <>
119 B.char8 ']'
120buildJSONValue (TSet ty entries) = buildJSONValue (TList ty entries)
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900121buildJSONValue (TBool b) = if b then B.char8 '1' else B.char8 '0'
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700122buildJSONValue (TByte b) = buildShowable b
123buildJSONValue (TI16 i) = buildShowable i
124buildJSONValue (TI32 i) = buildShowable i
125buildJSONValue (TI64 i) = buildShowable i
126buildJSONValue (TDouble d) = buildShowable d
127buildJSONValue (TString s) = B.char8 '\"' <> escape s <> B.char8 '\"'
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900128buildJSONValue (TBinary s) = B.char8 '\"' <> (B.lazyByteString . B64C.encode $ s) <> B.char8 '\"'
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700129
130buildJSONStruct :: Map.HashMap Int16 (LT.Text, ThriftVal) -> Builder
131buildJSONStruct = mconcat . intersperse (B.char8 ',') . Map.foldrWithKey buildField []
132 where
133 buildField fid (_,val) = (:) $
134 B.char8 '"' <> buildShowable fid <> B.string8 "\":" <>
135 B.char8 '{' <>
136 B.char8 '"' <> getTypeName (getTypeOf val) <> B.string8 "\":" <>
137 buildJSONValue val <>
138 B.char8 '}'
139
140buildJSONMap :: [(ThriftVal, ThriftVal)] -> Builder
141buildJSONMap = mconcat . intersperse (B.char8 ',') . map buildKV
142 where
143 buildKV (key@(TString _), val) =
144 buildJSONValue key <> B.char8 ':' <> buildJSONValue val
145 buildKV (key, val) =
146 B.char8 '\"' <> buildJSONValue key <> B.string8 "\":" <> buildJSONValue val
147buildJSONList :: [ThriftVal] -> Builder
148buildJSONList = mconcat . intersperse (B.char8 ',') . map buildJSONValue
149
150buildShowable :: Show a => a -> Builder
151buildShowable = B.string8 . show
152
153-- Reading Functions
154
155parseJSONValue :: ThriftType -> Parser ThriftVal
156parseJSONValue (T_STRUCT tmap) =
157 TStruct <$> (lexeme (PC.char8 '{') *> parseJSONStruct tmap <* PC.char8 '}')
158parseJSONValue (T_MAP kt vt) = fmap (TMap kt vt) $
159 between '[' ']' $
160 lexeme escapedString *> lexeme (PC.char8 ',') *>
161 lexeme escapedString *> lexeme (PC.char8 ',') *>
162 lexeme decimal *> lexeme (PC.char8 ',') *>
163 between '{' '}' (parseJSONMap kt vt)
164parseJSONValue (T_LIST ty) = fmap (TList ty) $
165 between '[' ']' $ do
Rhys Adamsf48e3392015-05-12 09:51:00 +0900166 len <- lexeme escapedString *> lexeme (PC.char8 ',') *> lexeme decimal
167 if len > 0
168 then lexeme (PC.char8 ',') *> parseJSONList ty
169 else return []
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700170parseJSONValue (T_SET ty) = fmap (TSet ty) $
171 between '[' ']' $ do
Rhys Adamsf48e3392015-05-12 09:51:00 +0900172 len <- lexeme escapedString *> lexeme (PC.char8 ',') *> lexeme decimal
173 if len > 0
174 then lexeme (PC.char8 ',') *> parseJSONList ty
175 else return []
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700176parseJSONValue T_BOOL =
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900177 (TBool True <$ PC.char8 '1') <|> (TBool False <$ PC.char8 '0')
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700178parseJSONValue T_BYTE = TByte <$> signed decimal
179parseJSONValue T_I16 = TI16 <$> signed decimal
180parseJSONValue T_I32 = TI32 <$> signed decimal
181parseJSONValue T_I64 = TI64 <$> signed decimal
182parseJSONValue T_DOUBLE = TDouble <$> double
183parseJSONValue T_STRING = TString <$> escapedString
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900184parseJSONValue T_BINARY = TBinary <$> base64String
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700185parseJSONValue T_STOP = fail "parseJSONValue: cannot parse type T_STOP"
186parseJSONValue T_VOID = fail "parseJSONValue: cannot parse type T_VOID"
187
188parseAnyValue :: Parser ()
189parseAnyValue = choice $
190 skipBetween '{' '}' :
191 skipBetween '[' ']' :
192 map (void . parseJSONValue)
193 [ T_BOOL
194 , T_I16
195 , T_I32
196 , T_I64
197 , T_DOUBLE
198 , T_STRING
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900199 , T_BINARY
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700200 ]
201 where
202 skipBetween :: Char -> Char -> Parser ()
203 skipBetween a b = between a b $ void (PC.satisfy (\c -> c /= a && c /= b))
204 <|> skipBetween a b
205
206parseJSONStruct :: TypeMap -> Parser (Map.HashMap Int16 (LT.Text, ThriftVal))
207parseJSONStruct tmap = Map.fromList . catMaybes <$> parseField
208 `sepBy` lexeme (PC.char8 ',')
209 where
210 parseField = do
211 fid <- lexeme (between '"' '"' decimal) <* lexeme (PC.char8 ':')
212 case Map.lookup fid tmap of
213 Just (str, ftype) -> between '{' '}' $ do
214 _ <- lexeme (escapedString) *> lexeme (PC.char8 ':')
215 val <- lexeme (parseJSONValue ftype)
216 return $ Just (fid, (str, val))
217 Nothing -> lexeme parseAnyValue *> return Nothing
218
219parseJSONMap :: ThriftType -> ThriftType -> Parser [(ThriftVal, ThriftVal)]
220parseJSONMap kt vt =
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900221 ((,) <$> lexeme (parseJSONKey kt) <*>
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700222 (lexeme (PC.char8 ':') *> lexeme (parseJSONValue vt))) `sepBy`
223 lexeme (PC.char8 ',')
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900224 where
225 parseJSONKey T_STRING = parseJSONValue T_STRING
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900226 parseJSONKey T_BINARY = parseJSONValue T_BINARY
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900227 parseJSONKey kt = PC.char8 '"' *> parseJSONValue kt <* PC.char8 '"'
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700228
229parseJSONList :: ThriftType -> Parser [ThriftVal]
230parseJSONList ty = lexeme (parseJSONValue ty) `sepBy` lexeme (PC.char8 ',')
231
232escapedString :: Parser LBS.ByteString
233escapedString = PC.char8 '"' *>
234 (LBS.pack <$> P.many' (escapedChar <|> notChar8 '"')) <*
235 PC.char8 '"'
236
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900237base64String :: Parser LBS.ByteString
238base64String = PC.char8 '"' *>
239 (decodeBase64 . LBSC.pack <$> P.many' (PC.notChar '"')) <*
240 PC.char8 '"'
241 where
242 decodeBase64 b =
243 let padded = case (LBS.length b) `mod` 4 of
244 2 -> LBS.append b "=="
245 3 -> LBS.append b "="
246 _ -> b in
247 case B64C.decode padded of
248 Right s -> s
249 Left x -> error x
250
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700251escapedChar :: Parser Word8
252escapedChar = PC.char8 '\\' *> (c2w <$> choice
253 [ '\SOH' <$ P.string "u0001"
254 , '\STX' <$ P.string "u0002"
255 , '\ETX' <$ P.string "u0003"
256 , '\EOT' <$ P.string "u0004"
257 , '\ENQ' <$ P.string "u0005"
258 , '\ACK' <$ P.string "u0006"
259 , '\BEL' <$ P.string "u0007"
260 , '\BS' <$ P.string "u0008"
261 , '\VT' <$ P.string "u000b"
262 , '\FF' <$ P.string "u000c"
263 , '\CR' <$ P.string "u000d"
264 , '\SO' <$ P.string "u000e"
265 , '\SI' <$ P.string "u000f"
266 , '\DLE' <$ P.string "u0010"
267 , '\DC1' <$ P.string "u0011"
268 , '\DC2' <$ P.string "u0012"
269 , '\DC3' <$ P.string "u0013"
270 , '\DC4' <$ P.string "u0014"
271 , '\NAK' <$ P.string "u0015"
272 , '\SYN' <$ P.string "u0016"
273 , '\ETB' <$ P.string "u0017"
274 , '\CAN' <$ P.string "u0018"
275 , '\EM' <$ P.string "u0019"
276 , '\SUB' <$ P.string "u001a"
277 , '\ESC' <$ P.string "u001b"
278 , '\FS' <$ P.string "u001c"
279 , '\GS' <$ P.string "u001d"
280 , '\RS' <$ P.string "u001e"
281 , '\US' <$ P.string "u001f"
282 , '\DEL' <$ P.string "u007f"
283 , '\0' <$ PC.char '0'
284 , '\a' <$ PC.char 'a'
285 , '\b' <$ PC.char 'b'
286 , '\f' <$ PC.char 'f'
287 , '\n' <$ PC.char 'n'
288 , '\r' <$ PC.char 'r'
289 , '\t' <$ PC.char 't'
290 , '\v' <$ PC.char 'v'
291 , '\"' <$ PC.char '"'
292 , '\'' <$ PC.char '\''
293 , '\\' <$ PC.char '\\'
294 , '/' <$ PC.char '/'
295 ])
296
297escape :: LBS.ByteString -> Builder
298escape = LBS.foldl' escapeChar mempty
299 where
300 escapeChar b w = b <> (B.lazyByteString $ case w2c w of
301 '\0' -> "\\0"
302 '\b' -> "\\b"
303 '\f' -> "\\f"
304 '\n' -> "\\n"
305 '\r' -> "\\r"
306 '\t' -> "\\t"
307 '\"' -> "\\\""
308 '\\' -> "\\\\"
309 '\SOH' -> "\\u0001"
310 '\STX' -> "\\u0002"
311 '\ETX' -> "\\u0003"
312 '\EOT' -> "\\u0004"
313 '\ENQ' -> "\\u0005"
314 '\ACK' -> "\\u0006"
315 '\BEL' -> "\\u0007"
316 '\VT' -> "\\u000b"
317 '\SO' -> "\\u000e"
318 '\SI' -> "\\u000f"
319 '\DLE' -> "\\u0010"
320 '\DC1' -> "\\u0011"
321 '\DC2' -> "\\u0012"
322 '\DC3' -> "\\u0013"
323 '\DC4' -> "\\u0014"
324 '\NAK' -> "\\u0015"
325 '\SYN' -> "\\u0016"
326 '\ETB' -> "\\u0017"
327 '\CAN' -> "\\u0018"
328 '\EM' -> "\\u0019"
329 '\SUB' -> "\\u001a"
330 '\ESC' -> "\\u001b"
331 '\FS' -> "\\u001c"
332 '\GS' -> "\\u001d"
333 '\RS' -> "\\u001e"
334 '\US' -> "\\u001f"
335 '\DEL' -> "\\u007f"
336 _ -> LBS.singleton w)
337
338lexeme :: Parser a -> Parser a
339lexeme = (<* skipSpace)
340
341notChar8 :: Char -> Parser Word8
342notChar8 c = P.satisfy (/= c2w c)
343
344between :: Char -> Char -> Parser a -> Parser a
345between a b p = lexeme (PC.char8 a) *> lexeme p <* lexeme (PC.char8 b)
346
347getTypeName :: ThriftType -> Builder
348getTypeName ty = B.string8 $ case ty of
349 T_STRUCT _ -> "rec"
350 T_MAP _ _ -> "map"
351 T_LIST _ -> "lst"
352 T_SET _ -> "set"
353 T_BOOL -> "tf"
354 T_BYTE -> "i8"
355 T_I16 -> "i16"
356 T_I32 -> "i32"
357 T_I64 -> "i64"
358 T_DOUBLE -> "dbl"
359 T_STRING -> "str"
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900360 T_BINARY -> "str"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700361 _ -> error "Unrecognized Type"
362