blob: 057a5602aa8f7fe2a59fb75bef07974e5b8394c8 [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
32import System.Posix.Unistd
Jens Geyerd629ea02015-09-23 21:16:50 +020033import qualified Data.ByteString.Lazy as LBS
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070034import qualified Data.HashMap.Strict as Map
35import qualified Data.HashSet as Set
36import qualified Data.Vector as Vector
Jens Geyerd629ea02015-09-23 21:16:50 +020037import qualified System.IO as IO
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070038
39import ThriftTest_Iface
40import ThriftTest_Types
41import qualified ThriftTest_Client as Client
42
43import Thrift.Transport
Jens Geyerd629ea02015-09-23 21:16:50 +020044import Thrift.Transport.Framed
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070045import Thrift.Transport.Handle
Jens Geyerd629ea02015-09-23 21:16:50 +020046import Thrift.Transport.HttpClient
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070047import Thrift.Protocol
48import Thrift.Protocol.Binary
49import Thrift.Protocol.Compact
50import 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
89 deriving (Show, Eq)
90
91getProtocol :: String -> ProtocolType
92getProtocol "binary" = Binary
93getProtocol "compact" = Compact
94getProtocol "json" = JSON
95getProtocol p = error $ "Unsupported Protocol: " ++ p
96
97defaultOptions :: Options
98defaultOptions = Options
99 { port = 9090
100 , domainSocket = ""
101 , host = "localhost"
Jens Geyerd629ea02015-09-23 21:16:50 +0200102 , transport = "buffered"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700103 , protocol = Binary
104 , ssl = False
105 , testLoops = 1
106 }
107
108runClient :: (Protocol p, Transport t) => p t -> IO ()
109runClient p = do
110 let prot = (p,p)
111 putStrLn "Starting Tests"
cdwijayarathnad9217912014-08-15 22:18:30 +0530112
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700113 -- VOID Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200114 putStrLn "testVoid"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700115 Client.testVoid prot
cdwijayarathnad9217912014-08-15 22:18:30 +0530116
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700117 -- String Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200118 putStrLn "testString"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700119 s <- Client.testString prot "Test"
120 when (s /= "Test") exitFailure
121
Jens Geyerd629ea02015-09-23 21:16:50 +0200122 -- Bool Test
123 putStrLn "testBool"
124 bool <- Client.testBool prot True
125 when (not bool) exitFailure
126 putStrLn "testBool"
127 bool <- Client.testBool prot False
128 when (bool) exitFailure
129
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700130 -- Byte Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200131 putStrLn "testByte"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700132 byte <- Client.testByte prot 1
133 when (byte /= 1) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530134
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700135 -- I32 Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200136 putStrLn "testI32"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700137 i32 <- Client.testI32 prot (-1)
138 when (i32 /= -1) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530139
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700140 -- I64 Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200141 putStrLn "testI64"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700142 i64 <- Client.testI64 prot (-34359738368)
143 when (i64 /= -34359738368) exitFailure
144
145 -- Double Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200146 putStrLn "testDouble"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700147 dub <- Client.testDouble prot (-5.2098523)
148 when (abs (dub + 5.2098523) > 0.001) exitFailure
149
Jens Geyerd629ea02015-09-23 21:16:50 +0200150 -- Binary Test
151 putStrLn "testBinary"
152 bin <- Client.testBinary prot (LBS.pack . reverse $ [-128..127])
153 when ((reverse [-128..127]) /= LBS.unpack bin) exitFailure
Jens Geyer8bcfdd92014-12-14 03:14:26 +0100154
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700155 -- Struct Test
156 let structIn = Xtruct{ xtruct_string_thing = "Zero"
157 , xtruct_byte_thing = 1
158 , xtruct_i32_thing = -3
159 , xtruct_i64_thing = -5
160 }
Jens Geyerd629ea02015-09-23 21:16:50 +0200161 putStrLn "testStruct"
cdwijayarathnad9217912014-08-15 22:18:30 +0530162 structOut <- Client.testStruct prot structIn
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700163 when (structIn /= structOut) exitFailure
164
165 -- Nested Struct Test
166 let nestIn = Xtruct2{ xtruct2_byte_thing = 1
167 , xtruct2_struct_thing = structIn
168 , xtruct2_i32_thing = 5
169 }
Jens Geyerd629ea02015-09-23 21:16:50 +0200170 putStrLn "testNest"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700171 nestOut <- Client.testNest prot nestIn
172 when (nestIn /= nestOut) exitSuccess
cdwijayarathnad9217912014-08-15 22:18:30 +0530173
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700174 -- Map Test
175 let mapIn = Map.fromList $ map (\i -> (i, i-10)) [1..5]
Jens Geyerd629ea02015-09-23 21:16:50 +0200176 putStrLn "testMap"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700177 mapOut <- Client.testMap prot mapIn
178 when (mapIn /= mapOut) exitSuccess
cdwijayarathnad9217912014-08-15 22:18:30 +0530179
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700180 -- Set Test
181 let setIn = Set.fromList [-2..3]
Jens Geyerd629ea02015-09-23 21:16:50 +0200182 putStrLn "testSet"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700183 setOut <- Client.testSet prot setIn
184 when (setIn /= setOut) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530185
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700186 -- List Test
187 let listIn = Vector.fromList [-2..3]
Jens Geyerd629ea02015-09-23 21:16:50 +0200188 putStrLn "testList"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700189 listOut <- Client.testList prot listIn
190 when (listIn /= listOut) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530191
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700192 -- Enum Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200193 putStrLn "testEnum"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700194 numz1 <- Client.testEnum prot ONE
195 when (numz1 /= ONE) exitFailure
196
Jens Geyerd629ea02015-09-23 21:16:50 +0200197 putStrLn "testEnum"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700198 numz2 <- Client.testEnum prot TWO
199 when (numz2 /= TWO) exitFailure
200
Jens Geyerd629ea02015-09-23 21:16:50 +0200201 putStrLn "testEnum"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700202 numz5 <- Client.testEnum prot FIVE
203 when (numz5 /= FIVE) exitFailure
204
205 -- Typedef Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200206 putStrLn "testTypedef"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700207 uid <- Client.testTypedef prot 309858235082523
208 when (uid /= 309858235082523) exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530209
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700210 -- Nested Map Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200211 putStrLn "testMapMap"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700212 _ <- Client.testMapMap prot 1
cdwijayarathnad9217912014-08-15 22:18:30 +0530213
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700214 -- Exception Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200215 putStrLn "testException"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700216 exn1 <- try $ Client.testException prot "Xception"
217 case exn1 of
218 Left (Xception _ _) -> return ()
219 _ -> putStrLn (show exn1) >> exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530220
Jens Geyerd629ea02015-09-23 21:16:50 +0200221 putStrLn "testException"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700222 exn2 <- try $ Client.testException prot "TException"
223 case exn2 of
224 Left (_ :: SomeException) -> return ()
225 Right _ -> exitFailure
cdwijayarathnad9217912014-08-15 22:18:30 +0530226
Jens Geyerd629ea02015-09-23 21:16:50 +0200227 putStrLn "testException"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700228 exn3 <- try $ Client.testException prot "success"
229 case exn3 of
230 Left (_ :: SomeException) -> exitFailure
231 Right _ -> return ()
cdwijayarathnad9217912014-08-15 22:18:30 +0530232
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700233 -- Multi Exception Test
Jens Geyerd629ea02015-09-23 21:16:50 +0200234 putStrLn "testMultiException"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700235 multi1 <- try $ Client.testMultiException prot "Xception" "test 1"
236 case multi1 of
237 Left (Xception _ _) -> return ()
238 _ -> exitFailure
239
Jens Geyerd629ea02015-09-23 21:16:50 +0200240 putStrLn "testMultiException"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700241 multi2 <- try $ Client.testMultiException prot "Xception2" "test 2"
242 case multi2 of
243 Left (Xception2 _ _) -> return ()
244 _ -> exitFailure
245
Jens Geyerd629ea02015-09-23 21:16:50 +0200246 putStrLn "testMultiException"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700247 multi3 <- try $ Client.testMultiException prot "success" "test 3"
248 case multi3 of
249 Left (_ :: SomeException) -> exitFailure
250 Right _ -> return ()
251
252
253main :: IO ()
254main = do
255 options <- flip parseFlags defaultOptions <$> getArgs
256 case options of
257 Nothing -> showHelp
258 Just Options{..} -> do
Jens Geyerd629ea02015-09-23 21:16:50 +0200259 trans <- Main.getTransport transport host port
260 case trans of
261 Buffered t -> runTest testLoops protocol t
262 Framed t -> runTest testLoops protocol t
263 Http t -> runTest testLoops protocol t
264 NoTransport err -> putStrLn err
265 where
266 makeClient p t = case p of
267 Binary -> runClient $ BinaryProtocol t
268 Compact -> runClient $ CompactProtocol t
269 JSON -> runClient $ JSONProtocol t
270 runTest loops p t = do
271 let client = makeClient p t
272 replicateM_ loops client
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700273 putStrLn "COMPLETED SUCCESSFULLY"
274
275parseFlags :: [String] -> Options -> Maybe Options
cdwijayarathnad9217912014-08-15 22:18:30 +0530276parseFlags (flag : flags) opts = do
277 let pieces = splitOn "=" flag
278 case pieces of
279 "--port" : arg : _ -> parseFlags flags opts{ port = read arg }
280 "--domain-socket" : arg : _ -> parseFlags flags opts{ domainSocket = read arg }
281 "--host" : arg : _ -> parseFlags flags opts{ host = arg }
282 "--transport" : arg : _ -> parseFlags flags opts{ transport = arg }
283 "--protocol" : arg : _ -> parseFlags flags opts{ protocol = getProtocol arg }
cdwijayarathna7191bc92014-08-16 23:36:07 +0530284 "-n" : arg : _ -> parseFlags flags opts{ testLoops = read arg }
cdwijayarathnad9217912014-08-15 22:18:30 +0530285 "--h" : _ -> Nothing
286 "--help" : _ -> Nothing
287 "--ssl" : _ -> parseFlags flags opts{ ssl = True }
288 "--processor-events" : _ -> parseFlags flags opts
cdwijayarathna7191bc92014-08-16 23:36:07 +0530289 _ -> Nothing
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700290parseFlags [] opts = Just opts
291
292showHelp :: IO ()
293showHelp = putStrLn
294 "Allowed options:\n\
295 \ -h [ --help ] produce help message\n\
296 \ --host arg (=localhost) Host to connect\n\
297 \ --port arg (=9090) Port number to connect\n\
cdwijayarathnad9217912014-08-15 22:18:30 +0530298 \ --domain-socket arg Domain Socket (e.g. /tmp/ThriftTest.thrift),\n\
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700299 \ instead of host and port\n\
Jens Geyerd629ea02015-09-23 21:16:50 +0200300 \ --transport arg (=buffered) Transport: buffered, framed, http\n\
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700301 \ --protocol arg (=binary) Protocol: binary, compact, json\n\
302 \ --ssl Encrypted Transport using SSL\n\
Jens Geyerd629ea02015-09-23 21:16:50 +0200303 \ -n [ --testloops ] arg (=1) Number of Tests"