blob: f6a031cfed4e9b766cbe2bcc59d1e6501c86019a [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
27import qualified Maybe
28import qualified Network
29
30import Thrift.Protocol.Binary
31import Thrift.Server
32import Thrift.Transport.Handle
33
34import qualified ThriftTestUtils
35
36import qualified DebugProtoTest_Types as Types
37import qualified Inherited
38import qualified Inherited_Client as IClient
39import qualified Inherited_Iface as IIface
40import qualified Srv_Client as SClient
41import qualified Srv_Iface as SIface
42
43-- we don't actually need this import, but force it to check the code generator exports proper Haskell syntax
44import qualified Srv()
45
46
47data InheritedHandler = InheritedHandler
48instance SIface.Srv_Iface InheritedHandler where
49 janky _ arg = do
50 ThriftTestUtils.serverLog $ "Got janky method call: " ++ show arg
51 return $ 31
52
53 voidMethod _ = do
54 ThriftTestUtils.serverLog "Got voidMethod method call"
55 return ()
56
57 primitiveMethod _ = do
58 ThriftTestUtils.serverLog "Got primitiveMethod call"
59 return $ 42
60
61 structMethod _ = do
62 ThriftTestUtils.serverLog "Got structMethod call"
63 return $ Types.CompactProtoTestStruct {
64 Types.f_CompactProtoTestStruct_a_byte = Just 0x01,
65 Types.f_CompactProtoTestStruct_a_i16 = Just 0x02,
66 Types.f_CompactProtoTestStruct_a_i32 = Just 0x03,
67 Types.f_CompactProtoTestStruct_a_i64 = Just 0x04,
68 Types.f_CompactProtoTestStruct_a_double = Just 0.1,
69 Types.f_CompactProtoTestStruct_a_string = Just "abcdef",
70 Types.f_CompactProtoTestStruct_a_binary = Just DBL.empty,
71 Types.f_CompactProtoTestStruct_true_field = Just True,
72 Types.f_CompactProtoTestStruct_false_field = Just False,
73 Types.f_CompactProtoTestStruct_empty_struct_field = Just Types.Empty,
74
75 Types.f_CompactProtoTestStruct_byte_list = Nothing,
76 Types.f_CompactProtoTestStruct_i16_list = Nothing,
77 Types.f_CompactProtoTestStruct_i32_list = Nothing,
78 Types.f_CompactProtoTestStruct_i64_list = Nothing,
79 Types.f_CompactProtoTestStruct_double_list = Nothing,
80 Types.f_CompactProtoTestStruct_string_list = Nothing,
81 Types.f_CompactProtoTestStruct_binary_list = Nothing,
82 Types.f_CompactProtoTestStruct_boolean_list = Nothing,
Roger Meierda74ff42012-05-18 09:25:02 +000083 Types.f_CompactProtoTestStruct_struct_list = Nothing,
Bryan Duxburyc6574472010-10-06 00:12:33 +000084
85 Types.f_CompactProtoTestStruct_byte_set = Nothing,
86 Types.f_CompactProtoTestStruct_i16_set = Nothing,
87 Types.f_CompactProtoTestStruct_i32_set = Nothing,
88 Types.f_CompactProtoTestStruct_i64_set = Nothing,
89 Types.f_CompactProtoTestStruct_double_set = Nothing,
90 Types.f_CompactProtoTestStruct_string_set = Nothing,
91 Types.f_CompactProtoTestStruct_binary_set = Nothing,
92 Types.f_CompactProtoTestStruct_boolean_set = Nothing,
93 Types.f_CompactProtoTestStruct_struct_set = Nothing,
94
95 Types.f_CompactProtoTestStruct_byte_byte_map = Nothing,
96 Types.f_CompactProtoTestStruct_i16_byte_map = Nothing,
97 Types.f_CompactProtoTestStruct_i32_byte_map = Nothing,
98 Types.f_CompactProtoTestStruct_i64_byte_map = Nothing,
99 Types.f_CompactProtoTestStruct_double_byte_map = Nothing,
100 Types.f_CompactProtoTestStruct_string_byte_map = Nothing,
101 Types.f_CompactProtoTestStruct_binary_byte_map = Nothing,
102 Types.f_CompactProtoTestStruct_boolean_byte_map = Nothing,
103
104 Types.f_CompactProtoTestStruct_byte_i16_map = Nothing,
105 Types.f_CompactProtoTestStruct_byte_i32_map = Nothing,
106 Types.f_CompactProtoTestStruct_byte_i64_map = Nothing,
107 Types.f_CompactProtoTestStruct_byte_double_map = Nothing,
108 Types.f_CompactProtoTestStruct_byte_string_map = Nothing,
109 Types.f_CompactProtoTestStruct_byte_binary_map = Nothing,
110 Types.f_CompactProtoTestStruct_byte_boolean_map = Nothing,
111
112 Types.f_CompactProtoTestStruct_list_byte_map = Nothing,
113 Types.f_CompactProtoTestStruct_set_byte_map = Nothing,
114 Types.f_CompactProtoTestStruct_map_byte_map = Nothing,
115
116 Types.f_CompactProtoTestStruct_byte_map_map = Nothing,
117 Types.f_CompactProtoTestStruct_byte_set_map = Nothing,
118 Types.f_CompactProtoTestStruct_byte_list_map = Nothing }
119
120 methodWithDefaultArgs _ arg = do
121 ThriftTestUtils.serverLog $ "Got methodWithDefaultArgs: " ++ show arg
122 return ()
123
124 onewayMethod _ = do
125 ThriftTestUtils.serverLog "Got onewayMethod"
126
127instance IIface.Inherited_Iface InheritedHandler where
128 identity _ arg = do
129 ThriftTestUtils.serverLog $ "Got identity method: " ++ show arg
130 return $ Maybe.fromJust arg
131
132client :: (String, Network.PortID) -> IO ()
133client addr = do
134 to <- hOpen addr
135 let p = BinaryProtocol to
136 let ps = (p,p)
137
138 v1 <- SClient.janky ps 42
139 ThriftTestUtils.clientLog $ show v1
140
141 SClient.voidMethod ps
142
143 v2 <- SClient.primitiveMethod ps
144 ThriftTestUtils.clientLog $ show v2
145
146 v3 <- SClient.structMethod ps
147 ThriftTestUtils.clientLog $ show v3
148
149 SClient.methodWithDefaultArgs ps 42
150
151 SClient.onewayMethod ps
152
153 v4 <- IClient.identity ps 42
154 ThriftTestUtils.clientLog $ show v4
155
156 return ()
157
158server :: Network.PortNumber -> IO ()
159server port = do
160 ThriftTestUtils.serverLog "Ready..."
161 (runBasicServer InheritedHandler Inherited.process port)
162 `Control.Exception.catch`
163 (\(TransportExn s _) -> error $ "FAILURE: " ++ show s)
164
165main :: IO ()
166main = ThriftTestUtils.runTest server client