| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 1 | -- | 
|  | 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 |  | 
|  | 26 | module Thrift.Protocol.JSON | 
|  | 27 | ( module Thrift.Protocol | 
|  | 28 | , JSONProtocol(..) | 
|  | 29 | ) where | 
|  | 30 |  | 
|  | 31 | import Control.Applicative | 
|  | 32 | import Control.Monad | 
|  | 33 | import Data.Attoparsec.ByteString as P | 
|  | 34 | import Data.Attoparsec.ByteString.Char8 as PC | 
|  | 35 | import Data.Attoparsec.ByteString.Lazy as LP | 
| Nobuaki Sukegawa | e68ccc2 | 2015-12-13 21:45:39 +0900 | [diff] [blame] | 36 | import Data.ByteString.Base64.Lazy as B64C | 
|  | 37 | import Data.ByteString.Base64 as B64 | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 38 | import Data.ByteString.Lazy.Builder as B | 
|  | 39 | import Data.ByteString.Internal (c2w, w2c) | 
|  | 40 | import Data.Functor | 
|  | 41 | import Data.Int | 
|  | 42 | import Data.List | 
|  | 43 | import Data.Maybe (catMaybes) | 
|  | 44 | import Data.Monoid | 
|  | 45 | import Data.Text.Lazy.Encoding | 
|  | 46 | import Data.Word | 
|  | 47 | import qualified Data.HashMap.Strict as Map | 
|  | 48 |  | 
|  | 49 | import Thrift.Protocol | 
|  | 50 | import Thrift.Transport | 
|  | 51 | import Thrift.Types | 
|  | 52 |  | 
|  | 53 | import qualified Data.ByteString.Lazy as LBS | 
| Nobuaki Sukegawa | ef2b528 | 2015-12-11 02:24:17 +0900 | [diff] [blame] | 54 | import qualified Data.ByteString.Lazy.Char8 as LBSC | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 55 | import qualified Data.Text.Lazy as LT | 
|  | 56 |  | 
| Nobuaki Sukegawa | ef2b528 | 2015-12-11 02:24:17 +0900 | [diff] [blame] | 57 | -- | The JSON Protocol data uses the standard 'TJSONProtocol'.  Data is | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 58 | -- encoded as a JSON 'ByteString' | 
|  | 59 | data JSONProtocol t = JSONProtocol t | 
|  | 60 | -- ^ Construct a 'JSONProtocol' with a 'Transport' | 
|  | 61 |  | 
|  | 62 | instance 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 |  | 
|  | 95 | buildJSONValue :: ThriftVal -> Builder | 
|  | 96 | buildJSONValue (TStruct fields) = B.char8 '{' <> buildJSONStruct fields <> B.char8 '}' | 
|  | 97 | buildJSONValue (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 ']' | 
|  | 103 | buildJSONValue (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 ']' | 
|  | 110 | buildJSONValue (TSet ty entries) = buildJSONValue (TList ty entries) | 
| Nobuaki Sukegawa | ef2b528 | 2015-12-11 02:24:17 +0900 | [diff] [blame] | 111 | buildJSONValue (TBool b) = if b then B.char8 '1' else B.char8 '0' | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 112 | buildJSONValue (TByte b) = buildShowable b | 
|  | 113 | buildJSONValue (TI16 i) = buildShowable i | 
|  | 114 | buildJSONValue (TI32 i) = buildShowable i | 
|  | 115 | buildJSONValue (TI64 i) = buildShowable i | 
|  | 116 | buildJSONValue (TDouble d) = buildShowable d | 
|  | 117 | buildJSONValue (TString s) = B.char8 '\"' <> escape s <> B.char8 '\"' | 
| Nobuaki Sukegawa | e68ccc2 | 2015-12-13 21:45:39 +0900 | [diff] [blame] | 118 | buildJSONValue (TBinary s) = B.char8 '\"' <> (B.lazyByteString . B64C.encode $ s) <> B.char8 '\"' | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 119 |  | 
|  | 120 | buildJSONStruct :: Map.HashMap Int16 (LT.Text, ThriftVal) -> Builder | 
|  | 121 | buildJSONStruct = 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 |  | 
|  | 130 | buildJSONMap :: [(ThriftVal, ThriftVal)] -> Builder | 
|  | 131 | buildJSONMap = 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 | 
|  | 137 | buildJSONList :: [ThriftVal] -> Builder | 
|  | 138 | buildJSONList = mconcat . intersperse (B.char8 ',') . map buildJSONValue | 
|  | 139 |  | 
|  | 140 | buildShowable :: Show a => a ->  Builder | 
|  | 141 | buildShowable = B.string8 . show | 
|  | 142 |  | 
|  | 143 | -- Reading Functions | 
|  | 144 |  | 
|  | 145 | parseJSONValue :: ThriftType -> Parser ThriftVal | 
|  | 146 | parseJSONValue (T_STRUCT tmap) = | 
|  | 147 | TStruct <$> (lexeme (PC.char8 '{') *> parseJSONStruct tmap <* PC.char8 '}') | 
|  | 148 | parseJSONValue (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) | 
|  | 154 | parseJSONValue (T_LIST ty) = fmap (TList ty) $ | 
|  | 155 | between '[' ']' $ do | 
| Rhys Adams | f48e339 | 2015-05-12 09:51:00 +0900 | [diff] [blame] | 156 | len <- lexeme escapedString *> lexeme (PC.char8 ',') *> lexeme decimal | 
|  | 157 | if len > 0 | 
|  | 158 | then lexeme (PC.char8 ',') *> parseJSONList ty | 
|  | 159 | else return [] | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 160 | parseJSONValue (T_SET ty) = fmap (TSet ty) $ | 
|  | 161 | between '[' ']' $ do | 
| Rhys Adams | f48e339 | 2015-05-12 09:51:00 +0900 | [diff] [blame] | 162 | len <- lexeme escapedString *> lexeme (PC.char8 ',') *> lexeme decimal | 
|  | 163 | if len > 0 | 
|  | 164 | then  lexeme (PC.char8 ',') *> parseJSONList ty | 
|  | 165 | else return [] | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 166 | parseJSONValue T_BOOL = | 
| Nobuaki Sukegawa | ef2b528 | 2015-12-11 02:24:17 +0900 | [diff] [blame] | 167 | (TBool True <$ PC.char8 '1') <|> (TBool False <$ PC.char8 '0') | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 168 | parseJSONValue T_BYTE = TByte <$> signed decimal | 
|  | 169 | parseJSONValue T_I16 = TI16 <$> signed decimal | 
|  | 170 | parseJSONValue T_I32 = TI32 <$> signed decimal | 
|  | 171 | parseJSONValue T_I64 = TI64 <$> signed decimal | 
|  | 172 | parseJSONValue T_DOUBLE = TDouble <$> double | 
|  | 173 | parseJSONValue T_STRING = TString <$> escapedString | 
| Nobuaki Sukegawa | e68ccc2 | 2015-12-13 21:45:39 +0900 | [diff] [blame] | 174 | parseJSONValue T_BINARY = TBinary <$> base64String | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 175 | parseJSONValue T_STOP = fail "parseJSONValue: cannot parse type T_STOP" | 
|  | 176 | parseJSONValue T_VOID = fail "parseJSONValue: cannot parse type T_VOID" | 
|  | 177 |  | 
|  | 178 | parseAnyValue :: Parser () | 
|  | 179 | parseAnyValue = 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 Sukegawa | e68ccc2 | 2015-12-13 21:45:39 +0900 | [diff] [blame] | 189 | , T_BINARY | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 190 | ] | 
|  | 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 |  | 
|  | 196 | parseJSONStruct :: TypeMap -> Parser (Map.HashMap Int16 (LT.Text, ThriftVal)) | 
|  | 197 | parseJSONStruct 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 |  | 
|  | 209 | parseJSONMap :: ThriftType -> ThriftType -> Parser [(ThriftVal, ThriftVal)] | 
|  | 210 | parseJSONMap kt vt = | 
| Nobuaki Sukegawa | ef2b528 | 2015-12-11 02:24:17 +0900 | [diff] [blame] | 211 | ((,) <$> lexeme (parseJSONKey kt) <*> | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 212 | (lexeme (PC.char8 ':') *> lexeme (parseJSONValue vt))) `sepBy` | 
|  | 213 | lexeme (PC.char8 ',') | 
| Nobuaki Sukegawa | ef2b528 | 2015-12-11 02:24:17 +0900 | [diff] [blame] | 214 | where | 
|  | 215 | parseJSONKey T_STRING = parseJSONValue T_STRING | 
| Nobuaki Sukegawa | e68ccc2 | 2015-12-13 21:45:39 +0900 | [diff] [blame] | 216 | parseJSONKey T_BINARY = parseJSONValue T_BINARY | 
| Nobuaki Sukegawa | ef2b528 | 2015-12-11 02:24:17 +0900 | [diff] [blame] | 217 | parseJSONKey kt = PC.char8 '"' *> parseJSONValue kt <* PC.char8 '"' | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 218 |  | 
|  | 219 | parseJSONList :: ThriftType -> Parser [ThriftVal] | 
|  | 220 | parseJSONList ty = lexeme (parseJSONValue ty) `sepBy` lexeme (PC.char8 ',') | 
|  | 221 |  | 
|  | 222 | escapedString :: Parser LBS.ByteString | 
|  | 223 | escapedString = PC.char8 '"' *> | 
|  | 224 | (LBS.pack <$> P.many' (escapedChar <|> notChar8 '"')) <* | 
|  | 225 | PC.char8 '"' | 
|  | 226 |  | 
| Nobuaki Sukegawa | e68ccc2 | 2015-12-13 21:45:39 +0900 | [diff] [blame] | 227 | base64String :: Parser LBS.ByteString | 
|  | 228 | base64String = 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 Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 241 | escapedChar :: Parser Word8 | 
|  | 242 | escapedChar = 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 |  | 
|  | 287 | escape :: LBS.ByteString -> Builder | 
|  | 288 | escape = 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 |  | 
|  | 328 | lexeme :: Parser a -> Parser a | 
|  | 329 | lexeme = (<* skipSpace) | 
|  | 330 |  | 
|  | 331 | notChar8 :: Char -> Parser Word8 | 
|  | 332 | notChar8 c = P.satisfy (/= c2w c) | 
|  | 333 |  | 
|  | 334 | between :: Char -> Char -> Parser a -> Parser a | 
|  | 335 | between a b p = lexeme (PC.char8 a) *> lexeme p <* lexeme (PC.char8 b) | 
|  | 336 |  | 
|  | 337 | getTypeName :: ThriftType -> Builder | 
|  | 338 | getTypeName 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 Sukegawa | e68ccc2 | 2015-12-13 21:45:39 +0900 | [diff] [blame] | 350 | T_BINARY   -> "str" | 
| Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 351 | _ -> error "Unrecognized Type" | 
|  | 352 |  |