blob: 4160c17935b4cbfe60a2951e291824e8d3e09d54 [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
102 testSet _ (Just x) = do
103 ThriftTestUtils.serverLog $ show x
104 return x
105
106 testSet _ Nothing = do
107 error $ "Unsupported testSet form"
108
109 testList _ (Just x) = do
110 ThriftTestUtils.serverLog $ show x
111 return x
112
113 testList _ Nothing = do
114 error $ "Unsupported testList form"
115
116 testEnum _ (Just x) = do
117 ThriftTestUtils.serverLog $ show x
118 return x
119
120 testEnum _ Nothing = do
121 error $ "Unsupported testEnum form"
122
123 testTypedef _ (Just x) = do
124 ThriftTestUtils.serverLog $ show x
125 return x
126
127 testTypedef _ Nothing = do
128 error $ "Unsupported testTypedef form"
129
130 testMapMap _ (Just _) = do
131 return (Map.fromList [(1, Map.fromList [(2, 2)])])
132
133 testMapMap _ Nothing = do
134 error $ "Unsupported testMapMap form"
135
136 testInsanity _ (Just x) = do
137 return (Map.fromList [(1, Map.fromList [(Types.ONE, x)])])
138
139 testInsanity _ Nothing = do
140 error $ "Unsupported testInsanity form"
141
142 testMulti _ _ _ _ _ _ _ = do
143 return (Types.Xtruct Nothing Nothing Nothing Nothing)
144
145 testException _ _ = do
146 Control.Exception.throw (Types.Xception (Just 1) (Just "bya"))
147
148 testMultiException _ _ _ = do
149 Control.Exception.throw (Types.Xception (Just 1) (Just "xyz"))
150
151 testOneway _ (Just i) = do
152 ThriftTestUtils.serverLog $ show i
153
154 testOneway _ Nothing = do
155 error $ "Unsupported testOneway form"
156
157
158client :: (String, Network.PortID) -> IO ()
159client addr = do
160 to <- hOpen addr
161 let ps = (BinaryProtocol to, BinaryProtocol to)
162
163 v1 <- Client.testString ps "bya"
164 ThriftTestUtils.clientLog v1
165
166 v2 <- Client.testByte ps 8
167 ThriftTestUtils.clientLog $ show v2
168
169 v3 <- Client.testByte ps (-8)
170 ThriftTestUtils.clientLog $ show v3
171
172 v4 <- Client.testI32 ps 32
173 ThriftTestUtils.clientLog $ show v4
174
175 v5 <- Client.testI32 ps (-32)
176 ThriftTestUtils.clientLog $ show v5
177
178 v6 <- Client.testI64 ps 64
179 ThriftTestUtils.clientLog $ show v6
180
181 v7 <- Client.testI64 ps (-64)
182 ThriftTestUtils.clientLog $ show v7
183
184 v8 <- Client.testDouble ps 3.14
185 ThriftTestUtils.clientLog $ show v8
186
187 v9 <- Client.testDouble ps (-3.14)
188 ThriftTestUtils.clientLog $ show v9
189
190 v10 <- Client.testMap ps (Map.fromList [(1,1),(2,2),(3,3)])
191 ThriftTestUtils.clientLog $ show v10
192
193 v11 <- Client.testList ps [1,2,3,4,5]
194 ThriftTestUtils.clientLog $ show v11
195
196 v12 <- Client.testSet ps (Set.fromList [1,2,3,4,5])
197 ThriftTestUtils.clientLog $ show v12
198
199 v13 <- Client.testStruct ps (Types.Xtruct (Just "hi") (Just 4) (Just 5) Nothing)
200 ThriftTestUtils.clientLog $ show v13
201
202 (testException ps "bad") `Control.Exception.catch` testExceptionHandler
203
204 (testMultiException ps "ok") `Control.Exception.catch` testMultiExceptionHandler1
205 (testMultiException ps "bad") `Control.Exception.catch` testMultiExceptionHandler2 `Control.Exception.catch` testMultiExceptionHandler3
206
207 -- ( (Client.testMultiException ps "e" "e2">> ThriftTestUtils.clientLog "bad") `Control.Exception.catch`
208
209 tClose to
210 where testException ps msg = do
211 Client.testException ps "e"
212 ThriftTestUtils.clientLog msg
213 return ()
214
215 testExceptionHandler (e :: Types.Xception) = do
216 ThriftTestUtils.clientLog $ show e
217
218 testMultiException ps msg = do
219 _ <- Client.testMultiException ps "e" "e2"
220 ThriftTestUtils.clientLog msg
221 return ()
222
223 testMultiExceptionHandler1 (e :: Types.Xception) = do
224 ThriftTestUtils.clientLog $ show e
225
226 testMultiExceptionHandler2 (e :: Types.Xception2) = do
227 ThriftTestUtils.clientLog $ show e
228
229 testMultiExceptionHandler3 (_ :: Control.Exception.SomeException) = do
230 ThriftTestUtils.clientLog "ok"
231
232
233server :: Network.PortNumber -> IO ()
234server port = do
235 ThriftTestUtils.serverLog "Ready..."
236 (runBasicServer TestHandler ThriftTest.process port)
237 `Control.Exception.catch`
238 (\(TransportExn s _) -> error $ "FAILURE: " ++ s)
239
240
241main :: IO ()
242main = ThriftTestUtils.runTest server client