blob: fb28963f68750988130c7c60813fdca9c6bdf3d6 [file] [log] [blame]
Bryan Duxburyc6574472010-10-06 00:12:33 +00001--
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
Roger Meierda74ff42012-05-18 09:25:02 +000020{-# LANGUAGE OverloadedStrings #-}
21
Bryan Duxburyc6574472010-10-06 00:12:33 +000022module Main where
23
24
25import qualified Control.Exception
26import qualified Data.ByteString.Lazy as DBL
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070027import qualified Data.HashMap.Strict as Map
28import qualified Data.HashSet as Set
29import qualified Data.Vector as Vector
Bryan Duxburyc6574472010-10-06 00:12:33 +000030import qualified Network
31
32import Thrift.Protocol.Binary
33import Thrift.Server
34import Thrift.Transport.Handle
35
36import qualified ThriftTestUtils
37
38import qualified DebugProtoTest_Types as Types
39import qualified Inherited
40import qualified Inherited_Client as IClient
41import qualified Inherited_Iface as IIface
42import qualified Srv_Client as SClient
43import qualified Srv_Iface as SIface
44
45-- we don't actually need this import, but force it to check the code generator exports proper Haskell syntax
46import qualified Srv()
47
48
49data InheritedHandler = InheritedHandler
50instance SIface.Srv_Iface InheritedHandler where
51 janky _ arg = do
52 ThriftTestUtils.serverLog $ "Got janky method call: " ++ show arg
53 return $ 31
54
55 voidMethod _ = do
56 ThriftTestUtils.serverLog "Got voidMethod method call"
57 return ()
58
59 primitiveMethod _ = do
60 ThriftTestUtils.serverLog "Got primitiveMethod call"
61 return $ 42
62
63 structMethod _ = do
64 ThriftTestUtils.serverLog "Got structMethod call"
65 return $ Types.CompactProtoTestStruct {
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070066 Types.compactProtoTestStruct_a_byte = 0x01,
67 Types.compactProtoTestStruct_a_i16 = 0x02,
68 Types.compactProtoTestStruct_a_i32 = 0x03,
69 Types.compactProtoTestStruct_a_i64 = 0x04,
70 Types.compactProtoTestStruct_a_double = 0.1,
71 Types.compactProtoTestStruct_a_string = "abcdef",
72 Types.compactProtoTestStruct_a_binary = DBL.empty,
73 Types.compactProtoTestStruct_true_field = True,
74 Types.compactProtoTestStruct_false_field = False,
75 Types.compactProtoTestStruct_empty_struct_field = Types.Empty,
Bryan Duxburyc6574472010-10-06 00:12:33 +000076
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070077 Types.compactProtoTestStruct_byte_list = Vector.empty,
78 Types.compactProtoTestStruct_i16_list = Vector.empty,
79 Types.compactProtoTestStruct_i32_list = Vector.empty,
80 Types.compactProtoTestStruct_i64_list = Vector.empty,
81 Types.compactProtoTestStruct_double_list = Vector.empty,
82 Types.compactProtoTestStruct_string_list = Vector.empty,
83 Types.compactProtoTestStruct_binary_list = Vector.empty,
84 Types.compactProtoTestStruct_boolean_list = Vector.empty,
85 Types.compactProtoTestStruct_struct_list = Vector.empty,
Bryan Duxburyc6574472010-10-06 00:12:33 +000086
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070087 Types.compactProtoTestStruct_byte_set = Set.empty,
88 Types.compactProtoTestStruct_i16_set = Set.empty,
89 Types.compactProtoTestStruct_i32_set = Set.empty,
90 Types.compactProtoTestStruct_i64_set = Set.empty,
91 Types.compactProtoTestStruct_double_set = Set.empty,
92 Types.compactProtoTestStruct_string_set = Set.empty,
93 Types.compactProtoTestStruct_binary_set = Set.empty,
94 Types.compactProtoTestStruct_boolean_set = Set.empty,
95 Types.compactProtoTestStruct_struct_set = Set.empty,
Bryan Duxburyc6574472010-10-06 00:12:33 +000096
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070097 Types.compactProtoTestStruct_byte_byte_map = Map.empty,
98 Types.compactProtoTestStruct_i16_byte_map = Map.empty,
99 Types.compactProtoTestStruct_i32_byte_map = Map.empty,
100 Types.compactProtoTestStruct_i64_byte_map = Map.empty,
101 Types.compactProtoTestStruct_double_byte_map = Map.empty,
102 Types.compactProtoTestStruct_string_byte_map = Map.empty,
103 Types.compactProtoTestStruct_binary_byte_map = Map.empty,
104 Types.compactProtoTestStruct_boolean_byte_map = Map.empty,
Bryan Duxburyc6574472010-10-06 00:12:33 +0000105
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700106 Types.compactProtoTestStruct_byte_i16_map = Map.empty,
107 Types.compactProtoTestStruct_byte_i32_map = Map.empty,
108 Types.compactProtoTestStruct_byte_i64_map = Map.empty,
109 Types.compactProtoTestStruct_byte_double_map = Map.empty,
110 Types.compactProtoTestStruct_byte_string_map = Map.empty,
111 Types.compactProtoTestStruct_byte_binary_map = Map.empty,
112 Types.compactProtoTestStruct_byte_boolean_map = Map.empty,
Bryan Duxburyc6574472010-10-06 00:12:33 +0000113
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700114 Types.compactProtoTestStruct_list_byte_map = Map.empty,
115 Types.compactProtoTestStruct_set_byte_map = Map.empty,
116 Types.compactProtoTestStruct_map_byte_map = Map.empty,
Bryan Duxburyc6574472010-10-06 00:12:33 +0000117
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700118 Types.compactProtoTestStruct_byte_map_map = Map.empty,
119 Types.compactProtoTestStruct_byte_set_map = Map.empty,
120 Types.compactProtoTestStruct_byte_list_map = Map.empty }
Bryan Duxburyc6574472010-10-06 00:12:33 +0000121
122 methodWithDefaultArgs _ arg = do
123 ThriftTestUtils.serverLog $ "Got methodWithDefaultArgs: " ++ show arg
124 return ()
125
126 onewayMethod _ = do
127 ThriftTestUtils.serverLog "Got onewayMethod"
128
129instance IIface.Inherited_Iface InheritedHandler where
130 identity _ arg = do
131 ThriftTestUtils.serverLog $ "Got identity method: " ++ show arg
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700132 return arg
Bryan Duxburyc6574472010-10-06 00:12:33 +0000133
134client :: (String, Network.PortID) -> IO ()
135client addr = do
136 to <- hOpen addr
137 let p = BinaryProtocol to
138 let ps = (p,p)
139
140 v1 <- SClient.janky ps 42
141 ThriftTestUtils.clientLog $ show v1
142
143 SClient.voidMethod ps
144
145 v2 <- SClient.primitiveMethod ps
146 ThriftTestUtils.clientLog $ show v2
147
148 v3 <- SClient.structMethod ps
149 ThriftTestUtils.clientLog $ show v3
150
151 SClient.methodWithDefaultArgs ps 42
152
153 SClient.onewayMethod ps
154
155 v4 <- IClient.identity ps 42
156 ThriftTestUtils.clientLog $ show v4
157
158 return ()
159
160server :: Network.PortNumber -> IO ()
161server port = do
162 ThriftTestUtils.serverLog "Ready..."
163 (runBasicServer InheritedHandler Inherited.process port)
164 `Control.Exception.catch`
165 (\(TransportExn s _) -> error $ "FAILURE: " ++ show s)
166
167main :: IO ()
168main = ThriftTestUtils.runTest server client