blob: 93fb591b343a64c587b2cb411d5e1597d59233c0 [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
Jens Geyerd629ea02015-09-23 21:16:50 +020029import Network.URI
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070030import System.Environment
31import System.Exit
Jens Geyerd629ea02015-09-23 21:16:50 +020032import qualified Data.ByteString.Lazy as LBS
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070033import qualified Data.HashMap.Strict as Map
34import qualified Data.HashSet as Set
35import qualified Data.Vector as Vector
Jens Geyerd629ea02015-09-23 21:16:50 +020036import qualified System.IO as IO
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070037
38import ThriftTest_Iface
39import ThriftTest_Types
40import qualified ThriftTest_Client as Client
41
42import Thrift.Transport
Jens Geyerd629ea02015-09-23 21:16:50 +020043import Thrift.Transport.Framed
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070044import Thrift.Transport.Handle
Jens Geyerd629ea02015-09-23 21:16:50 +020045import Thrift.Transport.HttpClient
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070046import Thrift.Protocol
47import Thrift.Protocol.Binary
48import Thrift.Protocol.Compact
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090049import Thrift.Protocol.Header
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070050import Thrift.Protocol.JSON
51
52data Options = Options
53 { host :: String
54 , port :: Int
55 , domainSocket :: String
56 , transport :: String
57 , protocol :: ProtocolType
Jens Geyerd629ea02015-09-23 21:16:50 +020058 -- TODO: Haskell lib does not have SSL support
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070059 , ssl :: Bool
60 , testLoops :: Int
61 }
62 deriving (Show, Eq)
63
Jens Geyerd629ea02015-09-23 21:16:50 +020064data TransportType = Buffered IO.Handle
65 | Framed (FramedTransport IO.Handle)
66 | Http HttpClient
67 | NoTransport String
68
69getTransport :: String -> String -> Int -> (IO TransportType)
70getTransport "buffered" host port = do
71 h <- hOpen (host, PortNumber $ fromIntegral port)
72 IO.hSetBuffering h $ IO.BlockBuffering Nothing
73 return $ Buffered h
74getTransport "framed" host port = do
75 h <- hOpen (host, PortNumber $ fromIntegral port)
76 t <- openFramedTransport h
77 return $ Framed t
78getTransport "http" host port = let uriStr = "http://" ++ host ++ ":" ++ show port in
79 case parseURI uriStr of
80 Nothing -> do return (NoTransport $ "Failed to parse URI: " ++ uriStr)
81 Just(uri) -> do
82 t <- openHttpClient uri
83 return $ Http t
84getTransport t host port = do return (NoTransport $ "Unsupported transport: " ++ t)
85
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070086data ProtocolType = Binary
87 | Compact
88 | JSON
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090089 | Header
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070090 deriving (Show, Eq)
91
92getProtocol :: String -> ProtocolType
93getProtocol "binary" = Binary
94getProtocol "compact" = Compact
95getProtocol "json" = JSON
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090096getProtocol "header" = Header
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070097getProtocol p = error $ "Unsupported Protocol: " ++ p
98
99defaultOptions :: Options
100defaultOptions = Options
101 { port = 9090
102 , domainSocket = ""
103 , host = "localhost"
Jens Geyerd629ea02015-09-23 21:16:50 +0200104 , transport = "buffered"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700105 , protocol = Binary
106 , ssl = False
107 , testLoops = 1
108 }
109
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +0900110runClient :: Protocol p => p -> IO ()
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700111runClient p = do
112 let prot = (p,p)
113 putStrLn "Starting Tests"
cdwijayarathnad9217912014-08-15 22:18:30 +0530114
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700115 -- VOID Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200116 putStrLn "testVoid"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700117 Client.testVoid prot
cdwijayarathnad9217912014-08-15 22:18:30 +0530118
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700119 -- String Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200120 putStrLn "testString"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700121 s <- Client.testString prot "Test"
122 when (s /= "Test") exitFailure
123
Jens Geyerd629ea02015-09-23 21:16:50 +0200124 -- Bool Test
125 putStrLn "testBool"
126 bool <- Client.testBool prot True
127 when (not bool) exitFailure
128 putStrLn "testBool"
129 bool <- Client.testBool prot False
130 when (bool) exitFailure
131
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700132 -- Byte Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200133 putStrLn "testByte"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700134 byte <- Client.testByte prot 1
135 when (byte /= 1) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530136
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700137 -- I32 Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200138 putStrLn "testI32"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700139 i32 <- Client.testI32 prot (-1)
140 when (i32 /= -1) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530141
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700142 -- I64 Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200143 putStrLn "testI64"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700144 i64 <- Client.testI64 prot (-34359738368)
145 when (i64 /= -34359738368) exitFailure
146
147 -- Double Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200148 putStrLn "testDouble"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700149 dub <- Client.testDouble prot (-5.2098523)
150 when (abs (dub + 5.2098523) > 0.001) exitFailure
151
Jens Geyerd629ea02015-09-23 21:16:50 +0200152 -- Binary Test
153 putStrLn "testBinary"
154 bin <- Client.testBinary prot (LBS.pack . reverse $ [-128..127])
155 when ((reverse [-128..127]) /= LBS.unpack bin) exitFailure
Jens Geyer8bcfdd92014-12-14 03:14:26 +0100156
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700157 -- Struct Test
158 let structIn = Xtruct{ xtruct_string_thing = "Zero"
159 , xtruct_byte_thing = 1
160 , xtruct_i32_thing = -3
161 , xtruct_i64_thing = -5
162 }
Jens Geyerd629ea02015-09-23 21:16:50 +0200163 putStrLn "testStruct"
cdwijayarathnad9217912014-08-15 22:18:30 +0530164 structOut <- Client.testStruct prot structIn
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700165 when (structIn /= structOut) exitFailure
166
167 -- Nested Struct Test
168 let nestIn = Xtruct2{ xtruct2_byte_thing = 1
169 , xtruct2_struct_thing = structIn
170 , xtruct2_i32_thing = 5
171 }
Jens Geyerd629ea02015-09-23 21:16:50 +0200172 putStrLn "testNest"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700173 nestOut <- Client.testNest prot nestIn
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900174 when (nestIn /= nestOut) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530175
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700176 -- Map Test
177 let mapIn = Map.fromList $ map (\i -> (i, i-10)) [1..5]
Jens Geyerd629ea02015-09-23 21:16:50 +0200178 putStrLn "testMap"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700179 mapOut <- Client.testMap prot mapIn
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +0900180 when (mapIn /= mapOut) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530181
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700182 -- Set Test
183 let setIn = Set.fromList [-2..3]
Jens Geyerd629ea02015-09-23 21:16:50 +0200184 putStrLn "testSet"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700185 setOut <- Client.testSet prot setIn
186 when (setIn /= setOut) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530187
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700188 -- List Test
189 let listIn = Vector.fromList [-2..3]
Jens Geyerd629ea02015-09-23 21:16:50 +0200190 putStrLn "testList"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700191 listOut <- Client.testList prot listIn
192 when (listIn /= listOut) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530193
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700194 -- Enum Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200195 putStrLn "testEnum"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700196 numz1 <- Client.testEnum prot ONE
197 when (numz1 /= ONE) exitFailure
198
Jens Geyerd629ea02015-09-23 21:16:50 +0200199 putStrLn "testEnum"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700200 numz2 <- Client.testEnum prot TWO
201 when (numz2 /= TWO) exitFailure
202
Jens Geyerd629ea02015-09-23 21:16:50 +0200203 putStrLn "testEnum"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700204 numz5 <- Client.testEnum prot FIVE
205 when (numz5 /= FIVE) exitFailure
206
207 -- Typedef Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200208 putStrLn "testTypedef"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700209 uid <- Client.testTypedef prot 309858235082523
210 when (uid /= 309858235082523) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530211
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700212 -- Nested Map Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200213 putStrLn "testMapMap"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700214 _ <- Client.testMapMap prot 1
cdwijayarathnad9217912014-08-15 22:18:30 +0530215
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700216 -- Exception Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200217 putStrLn "testException"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700218 exn1 <- try $ Client.testException prot "Xception"
219 case exn1 of
220 Left (Xception _ _) -> return ()
221 _ -> putStrLn (show exn1) >> exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530222
Jens Geyerd629ea02015-09-23 21:16:50 +0200223 putStrLn "testException"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700224 exn2 <- try $ Client.testException prot "TException"
225 case exn2 of
226 Left (_ :: SomeException) -> return ()
227 Right _ -> exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530228
Jens Geyerd629ea02015-09-23 21:16:50 +0200229 putStrLn "testException"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700230 exn3 <- try $ Client.testException prot "success"
231 case exn3 of
232 Left (_ :: SomeException) -> exitFailure
233 Right _ -> return ()
cdwijayarathnad9217912014-08-15 22:18:30 +0530234
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700235 -- Multi Exception Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200236 putStrLn "testMultiException"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700237 multi1 <- try $ Client.testMultiException prot "Xception" "test 1"
238 case multi1 of
239 Left (Xception _ _) -> return ()
240 _ -> exitFailure
241
Jens Geyerd629ea02015-09-23 21:16:50 +0200242 putStrLn "testMultiException"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700243 multi2 <- try $ Client.testMultiException prot "Xception2" "test 2"
244 case multi2 of
245 Left (Xception2 _ _) -> return ()
246 _ -> exitFailure
247
Jens Geyerd629ea02015-09-23 21:16:50 +0200248 putStrLn "testMultiException"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700249 multi3 <- try $ Client.testMultiException prot "success" "test 3"
250 case multi3 of
251 Left (_ :: SomeException) -> exitFailure
252 Right _ -> return ()
253
254
255main :: IO ()
256main = do
257 options <- flip parseFlags defaultOptions <$> getArgs
258 case options of
259 Nothing -> showHelp
260 Just Options{..} -> do
Jens Geyerd629ea02015-09-23 21:16:50 +0200261 trans <- Main.getTransport transport host port
262 case trans of
263 Buffered t -> runTest testLoops protocol t
264 Framed t -> runTest testLoops protocol t
265 Http t -> runTest testLoops protocol t
266 NoTransport err -> putStrLn err
267 where
268 makeClient p t = case p of
269 Binary -> runClient $ BinaryProtocol t
270 Compact -> runClient $ CompactProtocol t
271 JSON -> runClient $ JSONProtocol t
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +0900272 Header -> createHeaderProtocol t t >>= runClient
Jens Geyerd629ea02015-09-23 21:16:50 +0200273 runTest loops p t = do
274 let client = makeClient p t
275 replicateM_ loops client
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700276 putStrLn "COMPLETED SUCCESSFULLY"
277
278parseFlags :: [String] -> Options -> Maybe Options
cdwijayarathnad9217912014-08-15 22:18:30 +0530279parseFlags (flag : flags) opts = do
280 let pieces = splitOn "=" flag
281 case pieces of
282 "--port" : arg : _ -> parseFlags flags opts{ port = read arg }
283 "--domain-socket" : arg : _ -> parseFlags flags opts{ domainSocket = read arg }
284 "--host" : arg : _ -> parseFlags flags opts{ host = arg }
285 "--transport" : arg : _ -> parseFlags flags opts{ transport = arg }
286 "--protocol" : arg : _ -> parseFlags flags opts{ protocol = getProtocol arg }
cdwijayarathna7191bc92014-08-16 23:36:07 +0530287 "-n" : arg : _ -> parseFlags flags opts{ testLoops = read arg }
cdwijayarathnad9217912014-08-15 22:18:30 +0530288 "--h" : _ -> Nothing
289 "--help" : _ -> Nothing
290 "--ssl" : _ -> parseFlags flags opts{ ssl = True }
291 "--processor-events" : _ -> parseFlags flags opts
cdwijayarathna7191bc92014-08-16 23:36:07 +0530292 _ -> Nothing
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700293parseFlags [] opts = Just opts
294
295showHelp :: IO ()
296showHelp = putStrLn
297 "Allowed options:\n\
298 \ -h [ --help ] produce help message\n\
299 \ --host arg (=localhost) Host to connect\n\
300 \ --port arg (=9090) Port number to connect\n\
cdwijayarathnad9217912014-08-15 22:18:30 +0530301 \ --domain-socket arg Domain Socket (e.g. /tmp/ThriftTest.thrift),\n\
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700302 \ instead of host and port\n\
Jens Geyerd629ea02015-09-23 21:16:50 +0200303 \ --transport arg (=buffered) Transport: buffered, framed, http\n\
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700304 \ --protocol arg (=binary) Protocol: binary, compact, json\n\
305 \ --ssl Encrypted Transport using SSL\n\
Jens Geyerd629ea02015-09-23 21:16:50 +0200306 \ -n [ --testloops ] arg (=1) Number of Tests"