blob: ea6bcf3bbcc7261a2abf71f9453061b3cc76c4f0 [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
36import Data.ByteString.Lazy.Builder as B
37import Data.ByteString.Internal (c2w, w2c)
38import Data.Functor
39import Data.Int
40import Data.List
41import Data.Maybe (catMaybes)
42import Data.Monoid
43import Data.Text.Lazy.Encoding
44import Data.Word
45import qualified Data.HashMap.Strict as Map
46
47import Thrift.Protocol
48import Thrift.Transport
49import Thrift.Types
50
51import qualified Data.ByteString.Lazy as LBS
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +090052import qualified Data.ByteString.Lazy.Char8 as LBSC
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070053import qualified Data.Text.Lazy as LT
54
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +090055-- | The JSON Protocol data uses the standard 'TJSONProtocol'. Data is
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070056-- encoded as a JSON 'ByteString'
57data JSONProtocol t = JSONProtocol t
58 -- ^ Construct a 'JSONProtocol' with a 'Transport'
59
60instance Protocol JSONProtocol where
61 getTransport (JSONProtocol t) = t
62
63 writeMessageBegin (JSONProtocol t) (s, ty, sq) = tWrite t $ toLazyByteString $
64 B.char8 '[' <> buildShowable (1 :: Int32) <>
65 B.string8 ",\"" <> escape (encodeUtf8 s) <> B.char8 '\"' <>
66 B.char8 ',' <> buildShowable (fromEnum ty) <>
67 B.char8 ',' <> buildShowable sq <>
68 B.char8 ','
69 writeMessageEnd (JSONProtocol t) = tWrite t "]"
70 readMessageBegin p = runParser p $ skipSpace *> do
71 _ver :: Int32 <- lexeme (PC.char8 '[') *> lexeme (signed decimal)
72 bs <- lexeme (PC.char8 ',') *> lexeme escapedString
73 case decodeUtf8' bs of
74 Left _ -> fail "readMessage: invalid text encoding"
75 Right str -> do
76 ty <- toEnum <$> (lexeme (PC.char8 ',') *> lexeme (signed decimal))
77 seqNum <- lexeme (PC.char8 ',') *> lexeme (signed decimal)
78 _ <- PC.char8 ','
79 return (str, ty, seqNum)
80 readMessageEnd p = void $ runParser p (PC.char8 ']')
81
82 serializeVal _ = toLazyByteString . buildJSONValue
83 deserializeVal _ ty bs =
84 case LP.eitherResult $ LP.parse (parseJSONValue ty) bs of
85 Left s -> error s
86 Right val -> val
87
88 readVal p ty = runParser p $ skipSpace *> parseJSONValue ty
89
90
91-- Writing Functions
92
93buildJSONValue :: ThriftVal -> Builder
94buildJSONValue (TStruct fields) = B.char8 '{' <> buildJSONStruct fields <> B.char8 '}'
95buildJSONValue (TMap kt vt entries) =
96 B.char8 '[' <> B.char8 '"' <> getTypeName kt <> B.char8 '"' <>
97 B.char8 ',' <> B.char8 '"' <> getTypeName vt <> B.char8 '"' <>
98 B.char8 ',' <> buildShowable (length entries) <>
99 B.char8 ',' <> B.char8 '{' <> buildJSONMap entries <> B.char8 '}' <>
100 B.char8 ']'
101buildJSONValue (TList ty entries) =
102 B.char8 '[' <> B.char8 '"' <> getTypeName ty <> B.char8 '"' <>
103 B.char8 ',' <> buildShowable (length entries) <>
104 (if length entries > 0
105 then B.char8 ',' <> buildJSONList entries
106 else mempty) <>
107 B.char8 ']'
108buildJSONValue (TSet ty entries) = buildJSONValue (TList ty entries)
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900109buildJSONValue (TBool b) = if b then B.char8 '1' else B.char8 '0'
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700110buildJSONValue (TByte b) = buildShowable b
111buildJSONValue (TI16 i) = buildShowable i
112buildJSONValue (TI32 i) = buildShowable i
113buildJSONValue (TI64 i) = buildShowable i
114buildJSONValue (TDouble d) = buildShowable d
115buildJSONValue (TString s) = B.char8 '\"' <> escape s <> B.char8 '\"'
116
117buildJSONStruct :: Map.HashMap Int16 (LT.Text, ThriftVal) -> Builder
118buildJSONStruct = mconcat . intersperse (B.char8 ',') . Map.foldrWithKey buildField []
119 where
120 buildField fid (_,val) = (:) $
121 B.char8 '"' <> buildShowable fid <> B.string8 "\":" <>
122 B.char8 '{' <>
123 B.char8 '"' <> getTypeName (getTypeOf val) <> B.string8 "\":" <>
124 buildJSONValue val <>
125 B.char8 '}'
126
127buildJSONMap :: [(ThriftVal, ThriftVal)] -> Builder
128buildJSONMap = mconcat . intersperse (B.char8 ',') . map buildKV
129 where
130 buildKV (key@(TString _), val) =
131 buildJSONValue key <> B.char8 ':' <> buildJSONValue val
132 buildKV (key, val) =
133 B.char8 '\"' <> buildJSONValue key <> B.string8 "\":" <> buildJSONValue val
134buildJSONList :: [ThriftVal] -> Builder
135buildJSONList = mconcat . intersperse (B.char8 ',') . map buildJSONValue
136
137buildShowable :: Show a => a -> Builder
138buildShowable = B.string8 . show
139
140-- Reading Functions
141
142parseJSONValue :: ThriftType -> Parser ThriftVal
143parseJSONValue (T_STRUCT tmap) =
144 TStruct <$> (lexeme (PC.char8 '{') *> parseJSONStruct tmap <* PC.char8 '}')
145parseJSONValue (T_MAP kt vt) = fmap (TMap kt vt) $
146 between '[' ']' $
147 lexeme escapedString *> lexeme (PC.char8 ',') *>
148 lexeme escapedString *> lexeme (PC.char8 ',') *>
149 lexeme decimal *> lexeme (PC.char8 ',') *>
150 between '{' '}' (parseJSONMap kt vt)
151parseJSONValue (T_LIST ty) = fmap (TList ty) $
152 between '[' ']' $ do
Rhys Adamsf48e3392015-05-12 09:51:00 +0900153 len <- lexeme escapedString *> lexeme (PC.char8 ',') *> lexeme decimal
154 if len > 0
155 then lexeme (PC.char8 ',') *> parseJSONList ty
156 else return []
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700157parseJSONValue (T_SET ty) = fmap (TSet ty) $
158 between '[' ']' $ do
Rhys Adamsf48e3392015-05-12 09:51:00 +0900159 len <- lexeme escapedString *> lexeme (PC.char8 ',') *> lexeme decimal
160 if len > 0
161 then lexeme (PC.char8 ',') *> parseJSONList ty
162 else return []
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700163parseJSONValue T_BOOL =
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900164 (TBool True <$ PC.char8 '1') <|> (TBool False <$ PC.char8 '0')
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700165parseJSONValue T_BYTE = TByte <$> signed decimal
166parseJSONValue T_I16 = TI16 <$> signed decimal
167parseJSONValue T_I32 = TI32 <$> signed decimal
168parseJSONValue T_I64 = TI64 <$> signed decimal
169parseJSONValue T_DOUBLE = TDouble <$> double
170parseJSONValue T_STRING = TString <$> escapedString
171parseJSONValue T_STOP = fail "parseJSONValue: cannot parse type T_STOP"
172parseJSONValue T_VOID = fail "parseJSONValue: cannot parse type T_VOID"
173
174parseAnyValue :: Parser ()
175parseAnyValue = choice $
176 skipBetween '{' '}' :
177 skipBetween '[' ']' :
178 map (void . parseJSONValue)
179 [ T_BOOL
180 , T_I16
181 , T_I32
182 , T_I64
183 , T_DOUBLE
184 , T_STRING
185 ]
186 where
187 skipBetween :: Char -> Char -> Parser ()
188 skipBetween a b = between a b $ void (PC.satisfy (\c -> c /= a && c /= b))
189 <|> skipBetween a b
190
191parseJSONStruct :: TypeMap -> Parser (Map.HashMap Int16 (LT.Text, ThriftVal))
192parseJSONStruct tmap = Map.fromList . catMaybes <$> parseField
193 `sepBy` lexeme (PC.char8 ',')
194 where
195 parseField = do
196 fid <- lexeme (between '"' '"' decimal) <* lexeme (PC.char8 ':')
197 case Map.lookup fid tmap of
198 Just (str, ftype) -> between '{' '}' $ do
199 _ <- lexeme (escapedString) *> lexeme (PC.char8 ':')
200 val <- lexeme (parseJSONValue ftype)
201 return $ Just (fid, (str, val))
202 Nothing -> lexeme parseAnyValue *> return Nothing
203
204parseJSONMap :: ThriftType -> ThriftType -> Parser [(ThriftVal, ThriftVal)]
205parseJSONMap kt vt =
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900206 ((,) <$> lexeme (parseJSONKey kt) <*>
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700207 (lexeme (PC.char8 ':') *> lexeme (parseJSONValue vt))) `sepBy`
208 lexeme (PC.char8 ',')
Nobuaki Sukegawaef2b5282015-12-11 02:24:17 +0900209 where
210 parseJSONKey T_STRING = parseJSONValue T_STRING
211 parseJSONKey kt = PC.char8 '"' *> parseJSONValue kt <* PC.char8 '"'
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700212
213parseJSONList :: ThriftType -> Parser [ThriftVal]
214parseJSONList ty = lexeme (parseJSONValue ty) `sepBy` lexeme (PC.char8 ',')
215
216escapedString :: Parser LBS.ByteString
217escapedString = PC.char8 '"' *>
218 (LBS.pack <$> P.many' (escapedChar <|> notChar8 '"')) <*
219 PC.char8 '"'
220
221escapedChar :: Parser Word8
222escapedChar = PC.char8 '\\' *> (c2w <$> choice
223 [ '\SOH' <$ P.string "u0001"
224 , '\STX' <$ P.string "u0002"
225 , '\ETX' <$ P.string "u0003"
226 , '\EOT' <$ P.string "u0004"
227 , '\ENQ' <$ P.string "u0005"
228 , '\ACK' <$ P.string "u0006"
229 , '\BEL' <$ P.string "u0007"
230 , '\BS' <$ P.string "u0008"
231 , '\VT' <$ P.string "u000b"
232 , '\FF' <$ P.string "u000c"
233 , '\CR' <$ P.string "u000d"
234 , '\SO' <$ P.string "u000e"
235 , '\SI' <$ P.string "u000f"
236 , '\DLE' <$ P.string "u0010"
237 , '\DC1' <$ P.string "u0011"
238 , '\DC2' <$ P.string "u0012"
239 , '\DC3' <$ P.string "u0013"
240 , '\DC4' <$ P.string "u0014"
241 , '\NAK' <$ P.string "u0015"
242 , '\SYN' <$ P.string "u0016"
243 , '\ETB' <$ P.string "u0017"
244 , '\CAN' <$ P.string "u0018"
245 , '\EM' <$ P.string "u0019"
246 , '\SUB' <$ P.string "u001a"
247 , '\ESC' <$ P.string "u001b"
248 , '\FS' <$ P.string "u001c"
249 , '\GS' <$ P.string "u001d"
250 , '\RS' <$ P.string "u001e"
251 , '\US' <$ P.string "u001f"
252 , '\DEL' <$ P.string "u007f"
253 , '\0' <$ PC.char '0'
254 , '\a' <$ PC.char 'a'
255 , '\b' <$ PC.char 'b'
256 , '\f' <$ PC.char 'f'
257 , '\n' <$ PC.char 'n'
258 , '\r' <$ PC.char 'r'
259 , '\t' <$ PC.char 't'
260 , '\v' <$ PC.char 'v'
261 , '\"' <$ PC.char '"'
262 , '\'' <$ PC.char '\''
263 , '\\' <$ PC.char '\\'
264 , '/' <$ PC.char '/'
265 ])
266
267escape :: LBS.ByteString -> Builder
268escape = LBS.foldl' escapeChar mempty
269 where
270 escapeChar b w = b <> (B.lazyByteString $ case w2c w of
271 '\0' -> "\\0"
272 '\b' -> "\\b"
273 '\f' -> "\\f"
274 '\n' -> "\\n"
275 '\r' -> "\\r"
276 '\t' -> "\\t"
277 '\"' -> "\\\""
278 '\\' -> "\\\\"
279 '\SOH' -> "\\u0001"
280 '\STX' -> "\\u0002"
281 '\ETX' -> "\\u0003"
282 '\EOT' -> "\\u0004"
283 '\ENQ' -> "\\u0005"
284 '\ACK' -> "\\u0006"
285 '\BEL' -> "\\u0007"
286 '\VT' -> "\\u000b"
287 '\SO' -> "\\u000e"
288 '\SI' -> "\\u000f"
289 '\DLE' -> "\\u0010"
290 '\DC1' -> "\\u0011"
291 '\DC2' -> "\\u0012"
292 '\DC3' -> "\\u0013"
293 '\DC4' -> "\\u0014"
294 '\NAK' -> "\\u0015"
295 '\SYN' -> "\\u0016"
296 '\ETB' -> "\\u0017"
297 '\CAN' -> "\\u0018"
298 '\EM' -> "\\u0019"
299 '\SUB' -> "\\u001a"
300 '\ESC' -> "\\u001b"
301 '\FS' -> "\\u001c"
302 '\GS' -> "\\u001d"
303 '\RS' -> "\\u001e"
304 '\US' -> "\\u001f"
305 '\DEL' -> "\\u007f"
306 _ -> LBS.singleton w)
307
308lexeme :: Parser a -> Parser a
309lexeme = (<* skipSpace)
310
311notChar8 :: Char -> Parser Word8
312notChar8 c = P.satisfy (/= c2w c)
313
314between :: Char -> Char -> Parser a -> Parser a
315between a b p = lexeme (PC.char8 a) *> lexeme p <* lexeme (PC.char8 b)
316
317getTypeName :: ThriftType -> Builder
318getTypeName ty = B.string8 $ case ty of
319 T_STRUCT _ -> "rec"
320 T_MAP _ _ -> "map"
321 T_LIST _ -> "lst"
322 T_SET _ -> "set"
323 T_BOOL -> "tf"
324 T_BYTE -> "i8"
325 T_I16 -> "i16"
326 T_I32 -> "i32"
327 T_I64 -> "i64"
328 T_DOUBLE -> "dbl"
329 T_STRING -> "str"
330 _ -> error "Unrecognized Type"
331