blob: d991de15416a91f0f958cf054f22217aa36b6b4c [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 #-}
21module Main where
22
23import Control.Exception
24import Control.Monad
25import Data.Functor
26import Data.HashMap.Strict (HashMap)
27import Data.List
cdwijayarathnad9217912014-08-15 22:18:30 +053028import Data.List.Split
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070029import Data.String
30import Network
31import System.Environment
32import System.Exit
33import System.IO
34import System.Posix.Unistd
35import qualified Data.HashMap.Strict as Map
36import qualified Data.HashSet as Set
37import qualified Data.Text.Lazy as Text
38import qualified Data.Vector as Vector
39
40import ThriftTest
41import ThriftTest_Iface
42import ThriftTest_Types
43
44import Thrift
45import Thrift.Server
46import Thrift.Transport.Framed
47import Thrift.Transport.Handle
48import Thrift.Protocol.Binary
49import Thrift.Protocol.Compact
50import Thrift.Protocol.JSON
51
52data Options = Options
53 { port :: Int
54 , domainSocket :: String
55 , serverType :: ServerType
56 , transport :: String
57 , protocol :: ProtocolType
58 , ssl :: Bool
59 , workers :: Int
60 }
cdwijayarathnad9217912014-08-15 22:18:30 +053061
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070062data ServerType = Simple
63 | ThreadPool
64 | Threaded
65 | NonBlocking
66 deriving (Show, Eq)
67
68instance IsString ServerType where
69 fromString "simple" = Simple
70 fromString "thread-pool" = ThreadPool
71 fromString "threaded" = Threaded
72 fromString "nonblocking" = NonBlocking
73 fromString _ = error "not a valid server type"
74
75data ProtocolType = Binary
76 | Compact
77 | JSON
78
79getProtocol :: String -> ProtocolType
80getProtocol "binary" = Binary
81getProtocol "compact" = Compact
82getProtocol "json" = JSON
83getProtocol p = error $"Unsupported Protocol: " ++ p
84
85defaultOptions :: Options
86defaultOptions = Options
87 { port = 9090
88 , domainSocket = ""
89 , serverType = Threaded
90 , transport = "framed"
91 , protocol = Binary
92 , ssl = False
93 , workers = 4
94 }
95
96stringifyMap :: (Show a, Show b) => Map.HashMap a b -> String
cdwijayarathnad9217912014-08-15 22:18:30 +053097stringifyMap = Data.List.intercalate ", " . Data.List.map joinKV . Map.toList
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070098 where joinKV (k, v) = show k ++ " => " ++ show v
99
100stringifySet :: Show a => Set.HashSet a -> String
cdwijayarathnad9217912014-08-15 22:18:30 +0530101stringifySet = Data.List.intercalate ", " . Data.List.map show . Set.toList
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700102
103stringifyList :: Show a => Vector.Vector a -> String
cdwijayarathnad9217912014-08-15 22:18:30 +0530104stringifyList = Data.List.intercalate ", " . Data.List.map show . Vector.toList
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700105
106data TestHandler = TestHandler
cdwijayarathnad9217912014-08-15 22:18:30 +0530107instance ThriftTest_Iface TestHandler where
108 testVoid _ = System.IO.putStrLn "testVoid()"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700109
110 testString _ s = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530111 System.IO.putStrLn $ "testString(" ++ show s ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700112 return s
113
114 testByte _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530115 System.IO.putStrLn $ "testByte(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700116 return x
117
118 testI32 _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530119 System.IO.putStrLn $ "testI32(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700120 return x
121
122 testI64 _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530123 System.IO.putStrLn $ "testI64(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700124 return x
cdwijayarathnad9217912014-08-15 22:18:30 +0530125
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700126 testDouble _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530127 System.IO.putStrLn $ "testDouble(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700128 return x
129
Jens Geyer8bcfdd92014-12-14 03:14:26 +0100130 testBinary _ x = do
131 System.IO.putStrLn $ "testBinary(" ++ show x ++ ")"
132 return x
133
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700134 testStruct _ struct@Xtruct{..} = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530135 System.IO.putStrLn $ "testStruct({" ++ show xtruct_string_thing
136 ++ ", " ++ show xtruct_byte_thing
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700137 ++ ", " ++ show xtruct_i32_thing
138 ++ ", " ++ show xtruct_i64_thing
139 ++ "})"
140 return struct
141
142 testNest _ nest@Xtruct2{..} = do
143 let Xtruct{..} = xtruct2_struct_thing
cdwijayarathnad9217912014-08-15 22:18:30 +0530144 System.IO.putStrLn $ "testNest({" ++ show xtruct2_byte_thing
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700145 ++ "{, " ++ show xtruct_string_thing
146 ++ ", " ++ show xtruct_byte_thing
147 ++ ", " ++ show xtruct_i32_thing
148 ++ ", " ++ show xtruct_i64_thing
149 ++ "}, " ++ show xtruct2_i32_thing
150 return nest
151
152 testMap _ m = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530153 System.IO.putStrLn $ "testMap({" ++ stringifyMap m ++ "})"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700154 return m
cdwijayarathnad9217912014-08-15 22:18:30 +0530155
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700156 testStringMap _ m = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530157 System.IO.putStrLn $ "testStringMap(" ++ stringifyMap m ++ "})"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700158 return m
159
160 testSet _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530161 System.IO.putStrLn $ "testSet({" ++ stringifySet x ++ "})"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700162 return x
163
164 testList _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530165 System.IO.putStrLn $ "testList(" ++ stringifyList x ++ "})"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700166 return x
167
168 testEnum _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530169 System.IO.putStrLn $ "testEnum(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700170 return x
171
172 testTypedef _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530173 System.IO.putStrLn $ "testTypedef(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700174 return x
175
176 testMapMap _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530177 System.IO.putStrLn $ "testMapMap(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700178 return $ Map.fromList [ (-4, Map.fromList [ (-4, -4)
179 , (-3, -3)
180 , (-2, -2)
181 , (-1, -1)
182 ])
183 , (4, Map.fromList [ (1, 1)
184 , (2, 2)
185 , (3, 3)
186 , (4, 4)
187 ])
188 ]
189
190 testInsanity _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530191 System.IO.putStrLn "testInsanity()"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700192 return $ Map.fromList [ (1, Map.fromList [ (TWO , x)
193 , (THREE, x)
194 ])
195 , (2, Map.fromList [ (SIX, default_Insanity)
196 ])
197 ]
198
199 testMulti _ byte i32 i64 _ _ _ = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530200 System.IO.putStrLn "testMulti()"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700201 return Xtruct{ xtruct_string_thing = Text.pack "Hello2"
202 , xtruct_byte_thing = byte
203 , xtruct_i32_thing = i32
204 , xtruct_i64_thing = i64
205 }
cdwijayarathnad9217912014-08-15 22:18:30 +0530206
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700207 testException _ s = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530208 System.IO.putStrLn $ "testException(" ++ show s ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700209 case s of
210 "Xception" -> throw $ Xception 1001 s
211 "TException" -> throw ThriftException
212 _ -> return ()
213
214 testMultiException _ s1 s2 = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530215 System.IO.putStrLn $ "testMultiException(" ++ show s1 ++ ", " ++ show s2 ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700216 case s1 of
cdwijayarathnad9217912014-08-15 22:18:30 +0530217 "Xception" -> throw $ Xception 1001 "This is an Xception"
218 "Xception2" -> throw $ Xception2 2002 default_Xtruct
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700219 "TException" -> throw ThriftException
220 _ -> return default_Xtruct{ xtruct_string_thing = s2 }
221
222 testOneway _ i = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530223 System.IO.putStrLn $ "testOneway(" ++ show i ++ "): Sleeping..."
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700224 sleep (fromIntegral i)
cdwijayarathnad9217912014-08-15 22:18:30 +0530225 System.IO.putStrLn $ "testOneway(" ++ show i ++ "): done sleeping!"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700226
227main :: IO ()
228main = do
229 options <- flip parseFlags defaultOptions <$> getArgs
230 case options of
231 Nothing -> showHelp
232 Just Options{..} -> do
cdwijayarathnad9217912014-08-15 22:18:30 +0530233 System.IO.putStrLn $ "Starting \"" ++ show serverType ++ "\" server (" ++
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700234 show transport ++ ") listen on: " ++ domainSocket ++ show port
235 case protocol of
236 Binary -> runServer BinaryProtocol port
237 Compact -> runServer CompactProtocol port
238 JSON -> runServer JSONProtocol port
239 where
240 runServer p = runThreadedServer (accepter p) TestHandler ThriftTest.process . PortNumber . fromIntegral
241 accepter p s = do
242 (h, _, _) <- accept s
243 return (p h, p h)
244
245parseFlags :: [String] -> Options -> Maybe Options
cdwijayarathnad9217912014-08-15 22:18:30 +0530246parseFlags (flag : flags) opts = do
247 let pieces = splitOn "=" flag
248 case pieces of
249 "--port" : arg : _ -> parseFlags flags opts{ port = read arg }
250 "--domain-socket" : arg : _ -> parseFlags flags opts{ domainSocket = read arg }
251 "--server-type" : arg : _ -> parseFlags flags opts{ serverType = fromString arg }
252 "--transport" : arg : _ -> parseFlags flags opts{ transport = arg }
253 "--protocol" : arg : _ -> parseFlags flags opts{ protocol = getProtocol arg }
254 "--workers" : arg : _ -> parseFlags flags opts{ workers = read arg }
cdwijayarathna7191bc92014-08-16 23:36:07 +0530255 "-n" : arg : _ -> parseFlags flags opts{ workers = read arg }
cdwijayarathnad9217912014-08-15 22:18:30 +0530256 "--h" : _ -> Nothing
257 "--help" : _ -> Nothing
258 "--ssl" : _ -> parseFlags flags opts{ ssl = True }
259 "--processor-events" : _ -> parseFlags flags opts
cdwijayarathna7191bc92014-08-16 23:36:07 +0530260 _ -> Nothing
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700261parseFlags [] opts = Just opts
262
263showHelp :: IO ()
cdwijayarathnad9217912014-08-15 22:18:30 +0530264showHelp = System.IO.putStrLn
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700265 "Allowed options:\n\
266 \ -h [ --help ] produce help message\n\
267 \ --port arg (=9090) Port number to listen\n\
268 \ --domain-socket arg Unix Domain Socket (e.g. /tmp/ThriftTest.thrift)\n\
269 \ --server-type arg (=simple) type of server, \"simple\", \"thread-pool\",\n\
270 \ \"threaded\", or \"nonblocking\"\n\
271 \ --transport arg (=buffered) transport: buffered, framed, http\n\
272 \ --protocol arg (=binary) protocol: binary, compact, json\n\
273 \ --ssl Encrypted Transport using SSL\n\
274 \ --processor-events processor-events\n\
cdwijayarathnad9217912014-08-15 22:18:30 +0530275 \ -n [ --workers ] arg (=4) Number of thread pools workers. Only valid for\n\
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700276 \ thread-pool server type"