blob: 7f619e8cbf1126ebb3adff00abb03661e001420d [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
32import Control.Monad
33import Data.Attoparsec.ByteString as P
34import Data.Attoparsec.ByteString.Char8 as PC
35import Data.Attoparsec.ByteString.Lazy as LP
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +090036import Data.ByteString.Base64.Lazy as B64C
37import Data.ByteString.Base64 as B64
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'
61
62instance Protocol JSONProtocol where
63 getTransport (JSONProtocol t) = t
64
65 writeMessageBegin (JSONProtocol t) (s, ty, sq) = tWrite t $ toLazyByteString $
66 B.char8 '[' <> buildShowable (1 :: Int32) <>
67 B.string8 ",\"" <> escape (encodeUtf8 s) <> B.char8 '\"' <>
68 B.char8 ',' <> buildShowable (fromEnum ty) <>
69 B.char8 ',' <> buildShowable sq <>
70 B.char8 ','
71 writeMessageEnd (JSONProtocol t) = tWrite t "]"
72 readMessageBegin p = runParser p $ skipSpace *> do
73 _ver :: Int32 <- lexeme (PC.char8 '[') *> lexeme (signed decimal)
74 bs <- lexeme (PC.char8 ',') *> lexeme escapedString
75 case decodeUtf8' bs of
76 Left _ -> fail "readMessage: invalid text encoding"
77 Right str -> do
78 ty <- toEnum <$> (lexeme (PC.char8 ',') *> lexeme (signed decimal))
79 seqNum <- lexeme (PC.char8 ',') *> lexeme (signed decimal)
80 _ <- PC.char8 ','
81 return (str, ty, seqNum)
82 readMessageEnd p = void $ runParser p (PC.char8 ']')
83
84 serializeVal _ = toLazyByteString . buildJSONValue
85 deserializeVal _ ty bs =
86 case LP.eitherResult $ LP.parse (parseJSONValue ty) bs of
87 Left s -> error s
88 Right val -> val
89
90 readVal p ty = runParser p $ skipSpace *> parseJSONValue ty
91
92
93-- Writing Functions
94
95buildJSONValue :: ThriftVal -> Builder
96buildJSONValue (TStruct fields) = B.char8 '{' <> buildJSONStruct fields <> B.char8 '}'
97buildJSONValue (TMap kt vt entries) =
98 B.char8 '[' <> B.char8 '"' <> getTypeName kt <> B.char8 '"' <>
99 B.char8 ',' <> B.char8 '"' <> getTypeName vt <> B.char8 '"' <>
100 B.char8 ',' <> buildShowable (length entries) <>
101 B.char8 ',' <> B.char8 '{' <> buildJSONMap entries <> B.char8 '}' <>
102 B.char8 ']'
103buildJSONValue (TList ty entries) =
104 B.char8 '[' <> B.char8 '"' <> getTypeName ty <> B.char8 '"' <>
105 B.char8 ',' <> buildShowable (length entries) <>
106 (if length entries > 0
107 then B.char8 ',' <> buildJSONList entries
108 else mempty) <>
109 B.char8 ']'
110buildJSONValue (TSet ty entries) = buildJSONValue (TList ty entries)
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900111buildJSONValue (TBool b) = if b then B.char8 '1' else B.char8 '0'
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700112buildJSONValue (TByte b) = buildShowable b
113buildJSONValue (TI16 i) = buildShowable i
114buildJSONValue (TI32 i) = buildShowable i
115buildJSONValue (TI64 i) = buildShowable i
116buildJSONValue (TDouble d) = buildShowable d
117buildJSONValue (TString s) = B.char8 '\"' <> escape s <> B.char8 '\"'
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900118buildJSONValue (TBinary s) = B.char8 '\"' <> (B.lazyByteString . B64C.encode $ s) <> B.char8 '\"'
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700119
120buildJSONStruct :: Map.HashMap Int16 (LT.Text, ThriftVal) -> Builder
121buildJSONStruct = mconcat . intersperse (B.char8 ',') . Map.foldrWithKey buildField []
122 where
123 buildField fid (_,val) = (:) $
124 B.char8 '"' <> buildShowable fid <> B.string8 "\":" <>
125 B.char8 '{' <>
126 B.char8 '"' <> getTypeName (getTypeOf val) <> B.string8 "\":" <>
127 buildJSONValue val <>
128 B.char8 '}'
129
130buildJSONMap :: [(ThriftVal, ThriftVal)] -> Builder
131buildJSONMap = mconcat . intersperse (B.char8 ',') . map buildKV
132 where
133 buildKV (key@(TString _), val) =
134 buildJSONValue key <> B.char8 ':' <> buildJSONValue val
135 buildKV (key, val) =
136 B.char8 '\"' <> buildJSONValue key <> B.string8 "\":" <> buildJSONValue val
137buildJSONList :: [ThriftVal] -> Builder
138buildJSONList = mconcat . intersperse (B.char8 ',') . map buildJSONValue
139
140buildShowable :: Show a => a -> Builder
141buildShowable = B.string8 . show
142
143-- Reading Functions
144
145parseJSONValue :: ThriftType -> Parser ThriftVal
146parseJSONValue (T_STRUCT tmap) =
147 TStruct <$> (lexeme (PC.char8 '{') *> parseJSONStruct tmap <* PC.char8 '}')
148parseJSONValue (T_MAP kt vt) = fmap (TMap kt vt) $
149 between '[' ']' $
150 lexeme escapedString *> lexeme (PC.char8 ',') *>
151 lexeme escapedString *> lexeme (PC.char8 ',') *>
152 lexeme decimal *> lexeme (PC.char8 ',') *>
153 between '{' '}' (parseJSONMap kt vt)
154parseJSONValue (T_LIST ty) = fmap (TList ty) $
155 between '[' ']' $ do
Rhys Adamsf48e3392015-05-12 09:51:00 +0900156 len <- lexeme escapedString *> lexeme (PC.char8 ',') *> lexeme decimal
157 if len > 0
158 then lexeme (PC.char8 ',') *> parseJSONList ty
159 else return []
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700160parseJSONValue (T_SET ty) = fmap (TSet ty) $
161 between '[' ']' $ do
Rhys Adamsf48e3392015-05-12 09:51:00 +0900162 len <- lexeme escapedString *> lexeme (PC.char8 ',') *> lexeme decimal
163 if len > 0
164 then lexeme (PC.char8 ',') *> parseJSONList ty
165 else return []
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700166parseJSONValue T_BOOL =
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900167 (TBool True <$ PC.char8 '1') <|> (TBool False <$ PC.char8 '0')
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700168parseJSONValue T_BYTE = TByte <$> signed decimal
169parseJSONValue T_I16 = TI16 <$> signed decimal
170parseJSONValue T_I32 = TI32 <$> signed decimal
171parseJSONValue T_I64 = TI64 <$> signed decimal
172parseJSONValue T_DOUBLE = TDouble <$> double
173parseJSONValue T_STRING = TString <$> escapedString
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900174parseJSONValue T_BINARY = TBinary <$> base64String
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700175parseJSONValue T_STOP = fail "parseJSONValue: cannot parse type T_STOP"
176parseJSONValue T_VOID = fail "parseJSONValue: cannot parse type T_VOID"
177
178parseAnyValue :: Parser ()
179parseAnyValue = choice $
180 skipBetween '{' '}' :
181 skipBetween '[' ']' :
182 map (void . parseJSONValue)
183 [ T_BOOL
184 , T_I16
185 , T_I32
186 , T_I64
187 , T_DOUBLE
188 , T_STRING
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900189 , T_BINARY
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700190 ]
191 where
192 skipBetween :: Char -> Char -> Parser ()
193 skipBetween a b = between a b $ void (PC.satisfy (\c -> c /= a && c /= b))
194 <|> skipBetween a b
195
196parseJSONStruct :: TypeMap -> Parser (Map.HashMap Int16 (LT.Text, ThriftVal))
197parseJSONStruct tmap = Map.fromList . catMaybes <$> parseField
198 `sepBy` lexeme (PC.char8 ',')
199 where
200 parseField = do
201 fid <- lexeme (between '"' '"' decimal) <* lexeme (PC.char8 ':')
202 case Map.lookup fid tmap of
203 Just (str, ftype) -> between '{' '}' $ do
204 _ <- lexeme (escapedString) *> lexeme (PC.char8 ':')
205 val <- lexeme (parseJSONValue ftype)
206 return $ Just (fid, (str, val))
207 Nothing -> lexeme parseAnyValue *> return Nothing
208
209parseJSONMap :: ThriftType -> ThriftType -> Parser [(ThriftVal, ThriftVal)]
210parseJSONMap kt vt =
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900211 ((,) <$> lexeme (parseJSONKey kt) <*>
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700212 (lexeme (PC.char8 ':') *> lexeme (parseJSONValue vt))) `sepBy`
213 lexeme (PC.char8 ',')
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900214 where
215 parseJSONKey T_STRING = parseJSONValue T_STRING
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900216 parseJSONKey T_BINARY = parseJSONValue T_BINARY
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900217 parseJSONKey kt = PC.char8 '"' *> parseJSONValue kt <* PC.char8 '"'
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700218
219parseJSONList :: ThriftType -> Parser [ThriftVal]
220parseJSONList ty = lexeme (parseJSONValue ty) `sepBy` lexeme (PC.char8 ',')
221
222escapedString :: Parser LBS.ByteString
223escapedString = PC.char8 '"' *>
224 (LBS.pack <$> P.many' (escapedChar <|> notChar8 '"')) <*
225 PC.char8 '"'
226
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900227base64String :: Parser LBS.ByteString
228base64String = PC.char8 '"' *>
229 (decodeBase64 . LBSC.pack <$> P.many' (PC.notChar '"')) <*
230 PC.char8 '"'
231 where
232 decodeBase64 b =
233 let padded = case (LBS.length b) `mod` 4 of
234 2 -> LBS.append b "=="
235 3 -> LBS.append b "="
236 _ -> b in
237 case B64C.decode padded of
238 Right s -> s
239 Left x -> error x
240
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700241escapedChar :: Parser Word8
242escapedChar = PC.char8 '\\' *> (c2w <$> choice
243 [ '\SOH' <$ P.string "u0001"
244 , '\STX' <$ P.string "u0002"
245 , '\ETX' <$ P.string "u0003"
246 , '\EOT' <$ P.string "u0004"
247 , '\ENQ' <$ P.string "u0005"
248 , '\ACK' <$ P.string "u0006"
249 , '\BEL' <$ P.string "u0007"
250 , '\BS' <$ P.string "u0008"
251 , '\VT' <$ P.string "u000b"
252 , '\FF' <$ P.string "u000c"
253 , '\CR' <$ P.string "u000d"
254 , '\SO' <$ P.string "u000e"
255 , '\SI' <$ P.string "u000f"
256 , '\DLE' <$ P.string "u0010"
257 , '\DC1' <$ P.string "u0011"
258 , '\DC2' <$ P.string "u0012"
259 , '\DC3' <$ P.string "u0013"
260 , '\DC4' <$ P.string "u0014"
261 , '\NAK' <$ P.string "u0015"
262 , '\SYN' <$ P.string "u0016"
263 , '\ETB' <$ P.string "u0017"
264 , '\CAN' <$ P.string "u0018"
265 , '\EM' <$ P.string "u0019"
266 , '\SUB' <$ P.string "u001a"
267 , '\ESC' <$ P.string "u001b"
268 , '\FS' <$ P.string "u001c"
269 , '\GS' <$ P.string "u001d"
270 , '\RS' <$ P.string "u001e"
271 , '\US' <$ P.string "u001f"
272 , '\DEL' <$ P.string "u007f"
273 , '\0' <$ PC.char '0'
274 , '\a' <$ PC.char 'a'
275 , '\b' <$ PC.char 'b'
276 , '\f' <$ PC.char 'f'
277 , '\n' <$ PC.char 'n'
278 , '\r' <$ PC.char 'r'
279 , '\t' <$ PC.char 't'
280 , '\v' <$ PC.char 'v'
281 , '\"' <$ PC.char '"'
282 , '\'' <$ PC.char '\''
283 , '\\' <$ PC.char '\\'
284 , '/' <$ PC.char '/'
285 ])
286
287escape :: LBS.ByteString -> Builder
288escape = LBS.foldl' escapeChar mempty
289 where
290 escapeChar b w = b <> (B.lazyByteString $ case w2c w of
291 '\0' -> "\\0"
292 '\b' -> "\\b"
293 '\f' -> "\\f"
294 '\n' -> "\\n"
295 '\r' -> "\\r"
296 '\t' -> "\\t"
297 '\"' -> "\\\""
298 '\\' -> "\\\\"
299 '\SOH' -> "\\u0001"
300 '\STX' -> "\\u0002"
301 '\ETX' -> "\\u0003"
302 '\EOT' -> "\\u0004"
303 '\ENQ' -> "\\u0005"
304 '\ACK' -> "\\u0006"
305 '\BEL' -> "\\u0007"
306 '\VT' -> "\\u000b"
307 '\SO' -> "\\u000e"
308 '\SI' -> "\\u000f"
309 '\DLE' -> "\\u0010"
310 '\DC1' -> "\\u0011"
311 '\DC2' -> "\\u0012"
312 '\DC3' -> "\\u0013"
313 '\DC4' -> "\\u0014"
314 '\NAK' -> "\\u0015"
315 '\SYN' -> "\\u0016"
316 '\ETB' -> "\\u0017"
317 '\CAN' -> "\\u0018"
318 '\EM' -> "\\u0019"
319 '\SUB' -> "\\u001a"
320 '\ESC' -> "\\u001b"
321 '\FS' -> "\\u001c"
322 '\GS' -> "\\u001d"
323 '\RS' -> "\\u001e"
324 '\US' -> "\\u001f"
325 '\DEL' -> "\\u007f"
326 _ -> LBS.singleton w)
327
328lexeme :: Parser a -> Parser a
329lexeme = (<* skipSpace)
330
331notChar8 :: Char -> Parser Word8
332notChar8 c = P.satisfy (/= c2w c)
333
334between :: Char -> Char -> Parser a -> Parser a
335between a b p = lexeme (PC.char8 a) *> lexeme p <* lexeme (PC.char8 b)
336
337getTypeName :: ThriftType -> Builder
338getTypeName ty = B.string8 $ case ty of
339 T_STRUCT _ -> "rec"
340 T_MAP _ _ -> "map"
341 T_LIST _ -> "lst"
342 T_SET _ -> "set"
343 T_BOOL -> "tf"
344 T_BYTE -> "i8"
345 T_I16 -> "i16"
346 T_I32 -> "i32"
347 T_I64 -> "i64"
348 T_DOUBLE -> "dbl"
349 T_STRING -> "str"
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900350 T_BINARY -> "str"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700351 _ -> error "Unrecognized Type"
352