blob: 2f9fc4a86daff82c1de248490649f3874e57d287 [file] [log] [blame]
Bryan Duxburyc6574472010-10-06 00:12:33 +00001{-# LANGUAGE ScopedTypeVariables #-}
2--
3-- Licensed to the Apache Software Foundation (ASF) under one
4-- or more contributor license agreements. See the NOTICE file
5-- distributed with this work for additional information
6-- regarding copyright ownership. The ASF licenses this file
7-- to you under the Apache License, Version 2.0 (the
8-- "License"); you may not use this file except in compliance
9-- with the License. You may obtain a copy of the License at
10--
11-- http://www.apache.org/licenses/LICENSE-2.0
12--
13-- Unless required by applicable law or agreed to in writing,
14-- software distributed under the License is distributed on an
15-- "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
16-- KIND, either express or implied. See the License for the
17-- specific language governing permissions and limitations
18-- under the License.
19--
20
21module Main where
22
23
24import qualified Control.Exception
25import qualified Data.Map as Map
26import qualified Data.Set as Set
27import qualified Network
28
29import Thrift
30import Thrift.Protocol.Binary
31import Thrift.Server
32import Thrift.Transport.Handle
33
34import qualified ThriftTestUtils
35
36import qualified ThriftTest
37import qualified ThriftTest_Client as Client
38import qualified ThriftTest_Iface as Iface
39import qualified ThriftTest_Types as Types
40
41
42data TestHandler = TestHandler
43instance Iface.ThriftTest_Iface TestHandler where
44 testVoid _ = return ()
45
46 testString _ (Just s) = do
47 ThriftTestUtils.serverLog s
48 return s
49
50 testString _ Nothing = do
51 error $ "Unsupported testString form"
52
53 testByte _ (Just x) = do
54 ThriftTestUtils.serverLog $ show x
55 return x
56
57 testByte _ Nothing = do
58 error $ "Unsupported testByte form"
59
60 testI32 _ (Just x) = do
61 ThriftTestUtils.serverLog $ show x
62 return x
63
64 testI32 _ Nothing = do
65 error $ "Unsupported testI32 form"
66
67 testI64 _ (Just x) = do
68 ThriftTestUtils.serverLog $ show x
69 return x
70
71 testI64 _ Nothing = do
72 error $ "Unsupported testI64 form"
73
74 testDouble _ (Just x) = do
75 ThriftTestUtils.serverLog $ show x
76 return x
77
78 testDouble _ Nothing = do
79 error $ "Unsupported testDouble form"
80
81 testStruct _ (Just x) = do
82 ThriftTestUtils.serverLog $ show x
83 return x
84
85 testStruct _ Nothing = do
86 error $ "Unsupported testStruct form"
87
88 testNest _ (Just x) = do
89 ThriftTestUtils.serverLog $ show x
90 return x
91
92 testNest _ Nothing = do
93 error $ "Unsupported testNest form"
94
95 testMap _ (Just x) = do
96 ThriftTestUtils.serverLog $ show x
97 return x
98
99 testMap _ Nothing = do
100 error $ "Unsupported testMap form"
101
Roger Meier0680a832011-06-21 04:42:43 +0000102 testStringMap _ (Just x) = do
103 ThriftTestUtils.serverLog $ show x
104 return x
105
106 testStringMap _ Nothing = do
107 error $ "Unsupported testMap form"
108
Bryan Duxburyc6574472010-10-06 00:12:33 +0000109 testSet _ (Just x) = do
110 ThriftTestUtils.serverLog $ show x
111 return x
112
113 testSet _ Nothing = do
114 error $ "Unsupported testSet form"
115
116 testList _ (Just x) = do
117 ThriftTestUtils.serverLog $ show x
118 return x
119
120 testList _ Nothing = do
121 error $ "Unsupported testList form"
122
123 testEnum _ (Just x) = do
124 ThriftTestUtils.serverLog $ show x
125 return x
126
127 testEnum _ Nothing = do
128 error $ "Unsupported testEnum form"
129
130 testTypedef _ (Just x) = do
131 ThriftTestUtils.serverLog $ show x
132 return x
133
134 testTypedef _ Nothing = do
135 error $ "Unsupported testTypedef form"
136
137 testMapMap _ (Just _) = do
138 return (Map.fromList [(1, Map.fromList [(2, 2)])])
139
140 testMapMap _ Nothing = do
141 error $ "Unsupported testMapMap form"
142
143 testInsanity _ (Just x) = do
144 return (Map.fromList [(1, Map.fromList [(Types.ONE, x)])])
145
146 testInsanity _ Nothing = do
147 error $ "Unsupported testInsanity form"
148
149 testMulti _ _ _ _ _ _ _ = do
150 return (Types.Xtruct Nothing Nothing Nothing Nothing)
151
152 testException _ _ = do
153 Control.Exception.throw (Types.Xception (Just 1) (Just "bya"))
154
155 testMultiException _ _ _ = do
156 Control.Exception.throw (Types.Xception (Just 1) (Just "xyz"))
157
158 testOneway _ (Just i) = do
159 ThriftTestUtils.serverLog $ show i
160
161 testOneway _ Nothing = do
162 error $ "Unsupported testOneway form"
163
164
165client :: (String, Network.PortID) -> IO ()
166client addr = do
167 to <- hOpen addr
168 let ps = (BinaryProtocol to, BinaryProtocol to)
169
170 v1 <- Client.testString ps "bya"
171 ThriftTestUtils.clientLog v1
172
173 v2 <- Client.testByte ps 8
174 ThriftTestUtils.clientLog $ show v2
175
176 v3 <- Client.testByte ps (-8)
177 ThriftTestUtils.clientLog $ show v3
178
179 v4 <- Client.testI32 ps 32
180 ThriftTestUtils.clientLog $ show v4
181
182 v5 <- Client.testI32 ps (-32)
183 ThriftTestUtils.clientLog $ show v5
184
185 v6 <- Client.testI64 ps 64
186 ThriftTestUtils.clientLog $ show v6
187
188 v7 <- Client.testI64 ps (-64)
189 ThriftTestUtils.clientLog $ show v7
190
191 v8 <- Client.testDouble ps 3.14
192 ThriftTestUtils.clientLog $ show v8
193
194 v9 <- Client.testDouble ps (-3.14)
195 ThriftTestUtils.clientLog $ show v9
196
197 v10 <- Client.testMap ps (Map.fromList [(1,1),(2,2),(3,3)])
198 ThriftTestUtils.clientLog $ show v10
199
Roger Meier0680a832011-06-21 04:42:43 +0000200 v11 <- Client.testStringMap ps (Map.fromList [("a","123"),("a b","with spaces "),("same","same"),("0","numeric key")])
Bryan Duxburyc6574472010-10-06 00:12:33 +0000201 ThriftTestUtils.clientLog $ show v11
202
Roger Meier0680a832011-06-21 04:42:43 +0000203 v12 <- Client.testList ps [1,2,3,4,5]
Bryan Duxburyc6574472010-10-06 00:12:33 +0000204 ThriftTestUtils.clientLog $ show v12
205
Roger Meier0680a832011-06-21 04:42:43 +0000206 v13 <- Client.testSet ps (Set.fromList [1,2,3,4,5])
Bryan Duxburyc6574472010-10-06 00:12:33 +0000207 ThriftTestUtils.clientLog $ show v13
208
Roger Meier0680a832011-06-21 04:42:43 +0000209 v14 <- Client.testStruct ps (Types.Xtruct (Just "hi") (Just 4) (Just 5) Nothing)
210 ThriftTestUtils.clientLog $ show v14
211
Bryan Duxburyc6574472010-10-06 00:12:33 +0000212 (testException ps "bad") `Control.Exception.catch` testExceptionHandler
213
214 (testMultiException ps "ok") `Control.Exception.catch` testMultiExceptionHandler1
215 (testMultiException ps "bad") `Control.Exception.catch` testMultiExceptionHandler2 `Control.Exception.catch` testMultiExceptionHandler3
216
217 -- ( (Client.testMultiException ps "e" "e2">> ThriftTestUtils.clientLog "bad") `Control.Exception.catch`
218
219 tClose to
220 where testException ps msg = do
221 Client.testException ps "e"
222 ThriftTestUtils.clientLog msg
223 return ()
224
225 testExceptionHandler (e :: Types.Xception) = do
226 ThriftTestUtils.clientLog $ show e
227
228 testMultiException ps msg = do
229 _ <- Client.testMultiException ps "e" "e2"
230 ThriftTestUtils.clientLog msg
231 return ()
232
233 testMultiExceptionHandler1 (e :: Types.Xception) = do
234 ThriftTestUtils.clientLog $ show e
235
236 testMultiExceptionHandler2 (e :: Types.Xception2) = do
237 ThriftTestUtils.clientLog $ show e
238
239 testMultiExceptionHandler3 (_ :: Control.Exception.SomeException) = do
240 ThriftTestUtils.clientLog "ok"
241
242
243server :: Network.PortNumber -> IO ()
244server port = do
245 ThriftTestUtils.serverLog "Ready..."
246 (runBasicServer TestHandler ThriftTest.process port)
247 `Control.Exception.catch`
248 (\(TransportExn s _) -> error $ "FAILURE: " ++ s)
249
250
251main :: IO ()
252main = ThriftTestUtils.runTest server client