]> git.proxmox.com Git - ceph.git/blob - ceph/src/jaegertracing/thrift/lib/hs/test/JSONSpec.hs
buildsys: switch source download to quincy
[ceph.git] / ceph / src / jaegertracing / thrift / lib / hs / test / JSONSpec.hs
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 module JSONSpec where
21
22 import Test.Hspec
23 import Test.Hspec.QuickCheck (prop)
24
25 import qualified Data.ByteString.Lazy as LBS
26 import qualified Data.ByteString.Lazy.Char8 as C
27
28 import Thrift.Types
29 import Thrift.Transport
30 import Thrift.Transport.Memory
31 import Thrift.Protocol
32 import Thrift.Protocol.JSON
33
34 tString :: [Char] -> ThriftVal
35 tString = TString . C.pack
36
37 spec :: Spec
38 spec = do
39 describe "JSONProtocol" $ do
40 describe "bool" $ do
41 it "writes true as 1" $ do
42 let val = True
43 trans <- openMemoryBuffer
44 let proto = JSONProtocol trans
45 writeVal proto (TBool val)
46 bin <-tRead trans 100
47 (C.unpack bin) `shouldBe` ['1']
48
49 it "writes false as 0" $ do
50 let val = False
51 trans <- openMemoryBuffer
52 let proto = JSONProtocol trans
53 writeVal proto (TBool val)
54 bin <- tRead trans 100
55 (C.unpack bin) `shouldBe` ['0']
56
57 prop "round trip" $ \val -> do
58 trans <- openMemoryBuffer
59 let proto = JSONProtocol trans
60 writeVal proto $ TBool val
61 val2 <- readVal proto T_BOOL
62 val2 `shouldBe` (TBool val)
63
64 describe "string" $ do
65 it "writes" $ do
66 trans <- openMemoryBuffer
67 let proto = JSONProtocol trans
68 writeVal proto (TString $ C.pack "\"a")
69 bin <- tRead trans 100
70 (C.unpack bin) `shouldBe` "\"\\\"a\""
71
72 it "reads" $ do
73 trans <- openMemoryBuffer
74 let proto = JSONProtocol trans
75 tWrite trans $ C.pack "\"\\\"a\""
76 val <- readVal proto (T_STRING)
77 val `shouldBe` (TString $ C.pack "\"a")
78
79 prop "round trip" $ \val -> do
80 trans <- openMemoryBuffer
81 let proto = JSONProtocol trans
82 writeVal proto (TString $ C.pack val)
83 val2 <- readVal proto (T_STRING)
84 val2 `shouldBe` (TString $ C.pack val)
85
86 describe "binary" $ do
87 it "writes with padding" $ do
88 trans <- openMemoryBuffer
89 let proto = JSONProtocol trans
90 writeVal proto (TBinary $ LBS.pack [1])
91 bin <- tRead trans 100
92 (C.unpack bin) `shouldBe` "\"AQ==\""
93
94 it "reads with padding" $ do
95 trans <- openMemoryBuffer
96 let proto = JSONProtocol trans
97 tWrite trans $ C.pack "\"AQ==\""
98 val <- readVal proto (T_BINARY)
99 val `shouldBe` (TBinary $ LBS.pack [1])
100
101 it "reads without padding" $ do
102 trans <- openMemoryBuffer
103 let proto = JSONProtocol trans
104 tWrite trans $ C.pack "\"AQ\""
105 val <- readVal proto (T_BINARY)
106 val `shouldBe` (TBinary $ LBS.pack [1])
107
108 prop "round trip" $ \val -> do
109 trans <- openMemoryBuffer
110 let proto = JSONProtocol trans
111 writeVal proto (TBinary $ LBS.pack val)
112 val2 <- readVal proto (T_BINARY)
113 val2 `shouldBe` (TBinary $ LBS.pack val)
114
115 describe "list" $ do
116 it "writes empty list" $ do
117 trans <- openMemoryBuffer
118 let proto = JSONProtocol trans
119 writeVal proto (TList T_BYTE [])
120 bin <- tRead trans 100
121 (C.unpack bin) `shouldBe` "[\"i8\",0]"
122
123 it "reads empty" $ do
124 trans <- openMemoryBuffer
125 let proto = JSONProtocol trans
126 tWrite trans (C.pack "[\"i8\",0]")
127 val <- readVal proto (T_LIST T_BYTE)
128 val `shouldBe` (TList T_BYTE [])
129
130 it "writes single element" $ do
131 trans <- openMemoryBuffer
132 let proto = JSONProtocol trans
133 writeVal proto (TList T_BYTE [TByte 0])
134 bin <- tRead trans 100
135 (C.unpack bin) `shouldBe` "[\"i8\",1,0]"
136
137 it "reads single element" $ do
138 trans <- openMemoryBuffer
139 let proto = JSONProtocol trans
140 tWrite trans (C.pack "[\"i8\",1,0]")
141 val <- readVal proto (T_LIST T_BYTE)
142 val `shouldBe` (TList T_BYTE [TByte 0])
143
144 it "reads elements" $ do
145 trans <- openMemoryBuffer
146 let proto = JSONProtocol trans
147 tWrite trans (C.pack "[\"i8\",2,42, 43]")
148 val <- readVal proto (T_LIST T_BYTE)
149 val `shouldBe` (TList T_BYTE [TByte 42, TByte 43])
150
151 prop "round trip" $ \val -> do
152 trans <- openMemoryBuffer
153 let proto = JSONProtocol trans
154 writeVal proto $ (TList T_STRING $ map tString val)
155 val2 <- readVal proto $ T_LIST T_STRING
156 val2 `shouldBe` (TList T_STRING $ map tString val)
157
158 describe "set" $ do
159 it "writes empty" $ do
160 trans <- openMemoryBuffer
161 let proto = JSONProtocol trans
162 writeVal proto (TSet T_BYTE [])
163 bin <- tRead trans 100
164 (C.unpack bin) `shouldBe` "[\"i8\",0]"
165
166 it "reads empty" $ do
167 trans <- openMemoryBuffer
168 let proto = JSONProtocol trans
169 tWrite trans (C.pack "[\"i8\",0]")
170 val <- readVal proto (T_SET T_BYTE)
171 val `shouldBe` (TSet T_BYTE [])
172
173 it "reads single element" $ do
174 trans <- openMemoryBuffer
175 let proto = JSONProtocol trans
176 tWrite trans (C.pack "[\"i8\",1,0]")
177 val <- readVal proto (T_SET T_BYTE)
178 val `shouldBe` (TSet T_BYTE [TByte 0])
179
180 it "reads elements" $ do
181 trans <- openMemoryBuffer
182 let proto = JSONProtocol trans
183 tWrite trans (C.pack "[\"i8\",2,42, 43]")
184 val <- readVal proto (T_SET T_BYTE)
185 val `shouldBe` (TSet T_BYTE [TByte 42, TByte 43])
186
187 prop "round trip" $ \val -> do
188 trans <- openMemoryBuffer
189 let proto = JSONProtocol trans
190 writeVal proto $ (TSet T_STRING $ map tString val)
191 val2 <- readVal proto $ T_SET T_STRING
192 val2 `shouldBe` (TSet T_STRING $ map tString val)
193
194 describe "map" $ do
195 it "writes empty" $ do
196 trans <- openMemoryBuffer
197 let proto = JSONProtocol trans
198 writeVal proto (TMap T_BYTE T_BYTE [])
199 bin <- tRead trans 100
200 (C.unpack bin) `shouldBe`"[\"i8\",\"i8\",0,{}]"
201
202 it "reads empty" $ do
203 trans <- openMemoryBuffer
204 let proto = JSONProtocol trans
205 tWrite trans (C.pack "[\"i8\",\"i8\",0,{}]")
206 val <- readVal proto (T_MAP T_BYTE T_BYTE)
207 val `shouldBe` (TMap T_BYTE T_BYTE [])
208
209 it "reads string-string" $ do
210 let bin = "[\"str\",\"str\",2,{\"a\":\"2\",\"b\":\"blah\"}]"
211 trans <- openMemoryBuffer
212 let proto = JSONProtocol trans
213 tWrite trans (C.pack bin)
214 val <- readVal proto (T_MAP T_STRING T_STRING)
215 val`shouldBe` (TMap T_STRING T_STRING [(tString "a", tString "2"), (tString "b", tString "blah")])
216
217 prop "round trip" $ \val -> do
218 trans <- openMemoryBuffer
219 let proto = JSONProtocol trans
220 writeVal proto $ (TMap T_STRING T_STRING $ map toKV val)
221 val2 <- readVal proto $ T_MAP T_STRING T_STRING
222 val2 `shouldBe` (TMap T_STRING T_STRING $ map toKV val)
223 where
224 toKV v = (tString v, tString v)
225