blob: 35e8397fd99f767ddeff52799a07bc239f0b01c1 [file] [log] [blame]
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -07001--
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{-# LANGUAGE OverloadedStrings, RecordWildCards, ScopedTypeVariables #-}
21module Main where
22
23import Control.Exception
24import Control.Monad
25import Data.Functor
26import Data.String
27import Network
28import System.Environment
29import System.Exit
30import System.Posix.Unistd
31import qualified Data.HashMap.Strict as Map
32import qualified Data.HashSet as Set
33import qualified Data.Vector as Vector
34
35import ThriftTest_Iface
36import ThriftTest_Types
37import qualified ThriftTest_Client as Client
38
39import Thrift.Transport
40import Thrift.Transport.Handle
41import Thrift.Protocol
42import Thrift.Protocol.Binary
43import Thrift.Protocol.Compact
44import Thrift.Protocol.JSON
45
46data Options = Options
47 { host :: String
48 , port :: Int
49 , domainSocket :: String
50 , transport :: String
51 , protocol :: ProtocolType
52 , ssl :: Bool
53 , testLoops :: Int
54 }
55 deriving (Show, Eq)
56
57data ProtocolType = Binary
58 | Compact
59 | JSON
60 deriving (Show, Eq)
61
62getProtocol :: String -> ProtocolType
63getProtocol "binary" = Binary
64getProtocol "compact" = Compact
65getProtocol "json" = JSON
66getProtocol p = error $ "Unsupported Protocol: " ++ p
67
68defaultOptions :: Options
69defaultOptions = Options
70 { port = 9090
71 , domainSocket = ""
72 , host = "localhost"
73 , transport = "framed"
74 , protocol = Binary
75 , ssl = False
76 , testLoops = 1
77 }
78
79runClient :: (Protocol p, Transport t) => p t -> IO ()
80runClient p = do
81 let prot = (p,p)
82 putStrLn "Starting Tests"
83
84 -- VOID Test
85 Client.testVoid prot
86
87 -- String Test
88 s <- Client.testString prot "Test"
89 when (s /= "Test") exitFailure
90
91 -- Byte Test
92 byte <- Client.testByte prot 1
93 when (byte /= 1) exitFailure
94
95 -- I32 Test
96 i32 <- Client.testI32 prot (-1)
97 when (i32 /= -1) exitFailure
98
99 -- I64 Test
100 i64 <- Client.testI64 prot (-34359738368)
101 when (i64 /= -34359738368) exitFailure
102
103 -- Double Test
104 dub <- Client.testDouble prot (-5.2098523)
105 when (abs (dub + 5.2098523) > 0.001) exitFailure
106
107 -- Struct Test
108 let structIn = Xtruct{ xtruct_string_thing = "Zero"
109 , xtruct_byte_thing = 1
110 , xtruct_i32_thing = -3
111 , xtruct_i64_thing = -5
112 }
113 structOut <- Client.testStruct prot structIn
114 when (structIn /= structOut) exitFailure
115
116 -- Nested Struct Test
117 let nestIn = Xtruct2{ xtruct2_byte_thing = 1
118 , xtruct2_struct_thing = structIn
119 , xtruct2_i32_thing = 5
120 }
121 nestOut <- Client.testNest prot nestIn
122 when (nestIn /= nestOut) exitSuccess
123
124 -- Map Test
125 let mapIn = Map.fromList $ map (\i -> (i, i-10)) [1..5]
126 mapOut <- Client.testMap prot mapIn
127 when (mapIn /= mapOut) exitSuccess
128
129 -- Set Test
130 let setIn = Set.fromList [-2..3]
131 setOut <- Client.testSet prot setIn
132 when (setIn /= setOut) exitFailure
133
134 -- List Test
135 let listIn = Vector.fromList [-2..3]
136 listOut <- Client.testList prot listIn
137 when (listIn /= listOut) exitFailure
138
139 -- Enum Test
140 numz1 <- Client.testEnum prot ONE
141 when (numz1 /= ONE) exitFailure
142
143 numz2 <- Client.testEnum prot TWO
144 when (numz2 /= TWO) exitFailure
145
146 numz5 <- Client.testEnum prot FIVE
147 when (numz5 /= FIVE) exitFailure
148
149 -- Typedef Test
150 uid <- Client.testTypedef prot 309858235082523
151 when (uid /= 309858235082523) exitFailure
152
153 -- Nested Map Test
154 _ <- Client.testMapMap prot 1
155
156 -- Exception Test
157 exn1 <- try $ Client.testException prot "Xception"
158 case exn1 of
159 Left (Xception _ _) -> return ()
160 _ -> putStrLn (show exn1) >> exitFailure
161
162 exn2 <- try $ Client.testException prot "TException"
163 case exn2 of
164 Left (_ :: SomeException) -> return ()
165 Right _ -> exitFailure
166
167 exn3 <- try $ Client.testException prot "success"
168 case exn3 of
169 Left (_ :: SomeException) -> exitFailure
170 Right _ -> return ()
171
172 -- Multi Exception Test
173 multi1 <- try $ Client.testMultiException prot "Xception" "test 1"
174 case multi1 of
175 Left (Xception _ _) -> return ()
176 _ -> exitFailure
177
178 multi2 <- try $ Client.testMultiException prot "Xception2" "test 2"
179 case multi2 of
180 Left (Xception2 _ _) -> return ()
181 _ -> exitFailure
182
183 multi3 <- try $ Client.testMultiException prot "success" "test 3"
184 case multi3 of
185 Left (_ :: SomeException) -> exitFailure
186 Right _ -> return ()
187
188
189main :: IO ()
190main = do
191 options <- flip parseFlags defaultOptions <$> getArgs
192 case options of
193 Nothing -> showHelp
194 Just Options{..} -> do
195 handle <- hOpen (host, PortNumber $ fromIntegral port)
196 let client = case protocol of
197 Binary -> runClient $ BinaryProtocol handle
198 Compact -> runClient $ CompactProtocol handle
199 JSON -> runClient $ JSONProtocol handle
200 replicateM_ testLoops client
201 putStrLn "COMPLETED SUCCESSFULLY"
202
203parseFlags :: [String] -> Options -> Maybe Options
204parseFlags (flag : arg : flags) opts
205 | flag == "--port" = parseFlags flags opts{ port = read arg }
206 | flag == "--domain-socket" = parseFlags flags opts{ domainSocket = arg }
207 | flag == "--host" = parseFlags flags opts{ host = arg }
208 | flag == "--transport" = parseFlags flags opts{ transport = arg }
209 | flag == "--protocol" = parseFlags flags opts{ protocol = getProtocol arg }
210 | flag == "-n" ||
211 flag == "--testloops" = parseFlags flags opts{ testLoops = read arg }
212parseFlags (flag : flags) opts
213 | flag == "-h" = Nothing
214 | flag == "--help" = Nothing
215 | flag == "--ssl" = parseFlags flags opts{ ssl = True }
216 | flag == "--processor-events" ||
217 otherwise = parseFlags flags opts
218parseFlags [] opts = Just opts
219
220showHelp :: IO ()
221showHelp = putStrLn
222 "Allowed options:\n\
223 \ -h [ --help ] produce help message\n\
224 \ --host arg (=localhost) Host to connect\n\
225 \ --port arg (=9090) Port number to connect\n\
226 \ --domain-socket arg Domain Socket (e.g. /tmp/ThriftTest.thrift),\n\
227 \ instead of host and port\n\
228 \ --transport arg (=buffered) Transport: buffered, framed, http, evhttp\n\
229 \ --protocol arg (=binary) Protocol: binary, compact, json\n\
230 \ --ssl Encrypted Transport using SSL\n\
231 \ -n [ --testloops ] arg (=1) Number of Tests"