blob: 03314ed2de484c141846d2cfb59c80c2df39d772 [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
cdwijayarathnad9217912014-08-15 22:18:30 +053026import Data.List.Split
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070027import Data.String
28import Network
29import System.Environment
30import System.Exit
31import System.Posix.Unistd
32import qualified Data.HashMap.Strict as Map
33import qualified Data.HashSet as Set
34import qualified Data.Vector as Vector
35
36import ThriftTest_Iface
37import ThriftTest_Types
38import qualified ThriftTest_Client as Client
39
40import Thrift.Transport
41import Thrift.Transport.Handle
42import Thrift.Protocol
43import Thrift.Protocol.Binary
44import Thrift.Protocol.Compact
45import Thrift.Protocol.JSON
46
47data Options = Options
48 { host :: String
49 , port :: Int
50 , domainSocket :: String
51 , transport :: String
52 , protocol :: ProtocolType
53 , ssl :: Bool
54 , testLoops :: Int
55 }
56 deriving (Show, Eq)
57
58data ProtocolType = Binary
59 | Compact
60 | JSON
61 deriving (Show, Eq)
62
63getProtocol :: String -> ProtocolType
64getProtocol "binary" = Binary
65getProtocol "compact" = Compact
66getProtocol "json" = JSON
67getProtocol p = error $ "Unsupported Protocol: " ++ p
68
69defaultOptions :: Options
70defaultOptions = Options
71 { port = 9090
72 , domainSocket = ""
73 , host = "localhost"
74 , transport = "framed"
75 , protocol = Binary
76 , ssl = False
77 , testLoops = 1
78 }
79
80runClient :: (Protocol p, Transport t) => p t -> IO ()
81runClient p = do
82 let prot = (p,p)
83 putStrLn "Starting Tests"
cdwijayarathnad9217912014-08-15 22:18:30 +053084
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070085 -- VOID Test
86 Client.testVoid prot
cdwijayarathnad9217912014-08-15 22:18:30 +053087
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070088 -- String Test
89 s <- Client.testString prot "Test"
90 when (s /= "Test") exitFailure
91
92 -- Byte Test
93 byte <- Client.testByte prot 1
94 when (byte /= 1) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +053095
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070096 -- I32 Test
97 i32 <- Client.testI32 prot (-1)
98 when (i32 /= -1) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +053099
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700100 -- I64 Test
101 i64 <- Client.testI64 prot (-34359738368)
102 when (i64 /= -34359738368) exitFailure
103
104 -- Double Test
105 dub <- Client.testDouble prot (-5.2098523)
106 when (abs (dub + 5.2098523) > 0.001) exitFailure
107
108 -- Struct Test
109 let structIn = Xtruct{ xtruct_string_thing = "Zero"
110 , xtruct_byte_thing = 1
111 , xtruct_i32_thing = -3
112 , xtruct_i64_thing = -5
113 }
cdwijayarathnad9217912014-08-15 22:18:30 +0530114 structOut <- Client.testStruct prot structIn
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700115 when (structIn /= structOut) exitFailure
116
117 -- Nested Struct Test
118 let nestIn = Xtruct2{ xtruct2_byte_thing = 1
119 , xtruct2_struct_thing = structIn
120 , xtruct2_i32_thing = 5
121 }
122 nestOut <- Client.testNest prot nestIn
123 when (nestIn /= nestOut) exitSuccess
cdwijayarathnad9217912014-08-15 22:18:30 +0530124
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700125 -- Map Test
126 let mapIn = Map.fromList $ map (\i -> (i, i-10)) [1..5]
127 mapOut <- Client.testMap prot mapIn
128 when (mapIn /= mapOut) exitSuccess
cdwijayarathnad9217912014-08-15 22:18:30 +0530129
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700130 -- Set Test
131 let setIn = Set.fromList [-2..3]
132 setOut <- Client.testSet prot setIn
133 when (setIn /= setOut) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530134
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700135 -- List Test
136 let listIn = Vector.fromList [-2..3]
137 listOut <- Client.testList prot listIn
138 when (listIn /= listOut) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530139
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700140 -- Enum Test
141 numz1 <- Client.testEnum prot ONE
142 when (numz1 /= ONE) exitFailure
143
144 numz2 <- Client.testEnum prot TWO
145 when (numz2 /= TWO) exitFailure
146
147 numz5 <- Client.testEnum prot FIVE
148 when (numz5 /= FIVE) exitFailure
149
150 -- Typedef Test
151 uid <- Client.testTypedef prot 309858235082523
152 when (uid /= 309858235082523) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530153
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700154 -- Nested Map Test
155 _ <- Client.testMapMap prot 1
cdwijayarathnad9217912014-08-15 22:18:30 +0530156
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700157 -- Exception Test
158 exn1 <- try $ Client.testException prot "Xception"
159 case exn1 of
160 Left (Xception _ _) -> return ()
161 _ -> putStrLn (show exn1) >> exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530162
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700163 exn2 <- try $ Client.testException prot "TException"
164 case exn2 of
165 Left (_ :: SomeException) -> return ()
166 Right _ -> exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530167
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700168 exn3 <- try $ Client.testException prot "success"
169 case exn3 of
170 Left (_ :: SomeException) -> exitFailure
171 Right _ -> return ()
cdwijayarathnad9217912014-08-15 22:18:30 +0530172
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700173 -- Multi Exception Test
174 multi1 <- try $ Client.testMultiException prot "Xception" "test 1"
175 case multi1 of
176 Left (Xception _ _) -> return ()
177 _ -> exitFailure
178
179 multi2 <- try $ Client.testMultiException prot "Xception2" "test 2"
180 case multi2 of
181 Left (Xception2 _ _) -> return ()
182 _ -> exitFailure
183
184 multi3 <- try $ Client.testMultiException prot "success" "test 3"
185 case multi3 of
186 Left (_ :: SomeException) -> exitFailure
187 Right _ -> return ()
188
189
190main :: IO ()
191main = do
192 options <- flip parseFlags defaultOptions <$> getArgs
193 case options of
194 Nothing -> showHelp
195 Just Options{..} -> do
196 handle <- hOpen (host, PortNumber $ fromIntegral port)
197 let client = case protocol of
198 Binary -> runClient $ BinaryProtocol handle
199 Compact -> runClient $ CompactProtocol handle
200 JSON -> runClient $ JSONProtocol handle
cdwijayarathnad9217912014-08-15 22:18:30 +0530201 replicateM_ testLoops client
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700202 putStrLn "COMPLETED SUCCESSFULLY"
203
204parseFlags :: [String] -> Options -> Maybe Options
cdwijayarathnad9217912014-08-15 22:18:30 +0530205parseFlags (flag : flags) opts = do
206 let pieces = splitOn "=" flag
207 case pieces of
208 "--port" : arg : _ -> parseFlags flags opts{ port = read arg }
209 "--domain-socket" : arg : _ -> parseFlags flags opts{ domainSocket = read arg }
210 "--host" : arg : _ -> parseFlags flags opts{ host = arg }
211 "--transport" : arg : _ -> parseFlags flags opts{ transport = arg }
212 "--protocol" : arg : _ -> parseFlags flags opts{ protocol = getProtocol arg }
cdwijayarathna7191bc92014-08-16 23:36:07 +0530213 "-n" : arg : _ -> parseFlags flags opts{ testLoops = read arg }
cdwijayarathnad9217912014-08-15 22:18:30 +0530214 "--h" : _ -> Nothing
215 "--help" : _ -> Nothing
216 "--ssl" : _ -> parseFlags flags opts{ ssl = True }
217 "--processor-events" : _ -> parseFlags flags opts
cdwijayarathna7191bc92014-08-16 23:36:07 +0530218 _ -> Nothing
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700219parseFlags [] opts = Just opts
220
221showHelp :: IO ()
222showHelp = putStrLn
223 "Allowed options:\n\
224 \ -h [ --help ] produce help message\n\
225 \ --host arg (=localhost) Host to connect\n\
226 \ --port arg (=9090) Port number to connect\n\
cdwijayarathnad9217912014-08-15 22:18:30 +0530227 \ --domain-socket arg Domain Socket (e.g. /tmp/ThriftTest.thrift),\n\
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700228 \ instead of host and port\n\
229 \ --transport arg (=buffered) Transport: buffered, framed, http, evhttp\n\
230 \ --protocol arg (=binary) Protocol: binary, compact, json\n\
231 \ --ssl Encrypted Transport using SSL\n\
232 \ -n [ --testloops ] arg (=1) Number of Tests"