blob: 4a88649b81d64387164cd9892ef98515e83c08c5 [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
Nobuaki Sukegawae8c71d82015-11-23 19:51:37 +090034import Control.Concurrent (threadDelay)
Jens Geyerd629ea02015-09-23 21:16:50 +020035import qualified System.IO as IO
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070036import qualified Data.HashMap.Strict as Map
37import qualified Data.HashSet as Set
38import qualified Data.Text.Lazy as Text
39import qualified Data.Vector as Vector
40
41import ThriftTest
42import ThriftTest_Iface
43import ThriftTest_Types
44
45import Thrift
46import Thrift.Server
47import Thrift.Transport.Framed
48import Thrift.Transport.Handle
49import Thrift.Protocol.Binary
50import Thrift.Protocol.Compact
51import Thrift.Protocol.JSON
52
53data Options = Options
54 { port :: Int
55 , domainSocket :: String
56 , serverType :: ServerType
57 , transport :: String
58 , protocol :: ProtocolType
59 , ssl :: Bool
60 , workers :: Int
61 }
cdwijayarathnad9217912014-08-15 22:18:30 +053062
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070063data ServerType = Simple
64 | ThreadPool
65 | Threaded
66 | NonBlocking
67 deriving (Show, Eq)
68
69instance IsString ServerType where
70 fromString "simple" = Simple
71 fromString "thread-pool" = ThreadPool
72 fromString "threaded" = Threaded
73 fromString "nonblocking" = NonBlocking
74 fromString _ = error "not a valid server type"
75
Jens Geyerd629ea02015-09-23 21:16:50 +020076data TransportType = Buffered (Socket -> (IO IO.Handle))
77 | Framed (Socket -> (IO (FramedTransport IO.Handle)))
78 | NoTransport String
79
80getTransport :: String -> TransportType
81getTransport "buffered" = Buffered $ \s -> do
82 (h, _, _) <- (accept s)
83 IO.hSetBuffering h $ IO.BlockBuffering Nothing
84 return h
85getTransport "framed" = Framed $ \s -> do
86 (h, _, _) <- (accept s)
87 openFramedTransport h
88getTransport t = NoTransport $ "Unsupported transport: " ++ t
89
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070090data ProtocolType = Binary
91 | Compact
92 | JSON
93
94getProtocol :: String -> ProtocolType
95getProtocol "binary" = Binary
96getProtocol "compact" = Compact
97getProtocol "json" = JSON
98getProtocol p = error $"Unsupported Protocol: " ++ p
99
100defaultOptions :: Options
101defaultOptions = Options
102 { port = 9090
103 , domainSocket = ""
104 , serverType = Threaded
Jens Geyerd629ea02015-09-23 21:16:50 +0200105 , transport = "buffered"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700106 , protocol = Binary
Jens Geyerd629ea02015-09-23 21:16:50 +0200107 -- TODO: Haskell lib does not have SSL support
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700108 , ssl = False
109 , workers = 4
110 }
111
112stringifyMap :: (Show a, Show b) => Map.HashMap a b -> String
cdwijayarathnad9217912014-08-15 22:18:30 +0530113stringifyMap = Data.List.intercalate ", " . Data.List.map joinKV . Map.toList
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700114 where joinKV (k, v) = show k ++ " => " ++ show v
115
116stringifySet :: Show a => Set.HashSet a -> String
cdwijayarathnad9217912014-08-15 22:18:30 +0530117stringifySet = Data.List.intercalate ", " . Data.List.map show . Set.toList
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700118
119stringifyList :: Show a => Vector.Vector a -> String
cdwijayarathnad9217912014-08-15 22:18:30 +0530120stringifyList = Data.List.intercalate ", " . Data.List.map show . Vector.toList
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700121
122data TestHandler = TestHandler
cdwijayarathnad9217912014-08-15 22:18:30 +0530123instance ThriftTest_Iface TestHandler where
124 testVoid _ = System.IO.putStrLn "testVoid()"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700125
126 testString _ s = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530127 System.IO.putStrLn $ "testString(" ++ show s ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700128 return s
129
Nobuaki Sukegawaa649e742015-09-21 13:53:25 +0900130 testBool _ x = do
131 System.IO.putStrLn $ "testBool(" ++ show x ++ ")"
132 return x
133
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700134 testByte _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530135 System.IO.putStrLn $ "testByte(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700136 return x
137
138 testI32 _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530139 System.IO.putStrLn $ "testI32(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700140 return x
141
142 testI64 _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530143 System.IO.putStrLn $ "testI64(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700144 return x
cdwijayarathnad9217912014-08-15 22:18:30 +0530145
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700146 testDouble _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530147 System.IO.putStrLn $ "testDouble(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700148 return x
149
Jens Geyer8bcfdd92014-12-14 03:14:26 +0100150 testBinary _ x = do
151 System.IO.putStrLn $ "testBinary(" ++ show x ++ ")"
152 return x
153
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700154 testStruct _ struct@Xtruct{..} = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530155 System.IO.putStrLn $ "testStruct({" ++ show xtruct_string_thing
156 ++ ", " ++ show xtruct_byte_thing
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700157 ++ ", " ++ show xtruct_i32_thing
158 ++ ", " ++ show xtruct_i64_thing
159 ++ "})"
160 return struct
161
162 testNest _ nest@Xtruct2{..} = do
163 let Xtruct{..} = xtruct2_struct_thing
cdwijayarathnad9217912014-08-15 22:18:30 +0530164 System.IO.putStrLn $ "testNest({" ++ show xtruct2_byte_thing
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700165 ++ "{, " ++ show xtruct_string_thing
166 ++ ", " ++ show xtruct_byte_thing
167 ++ ", " ++ show xtruct_i32_thing
168 ++ ", " ++ show xtruct_i64_thing
169 ++ "}, " ++ show xtruct2_i32_thing
170 return nest
171
172 testMap _ m = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530173 System.IO.putStrLn $ "testMap({" ++ stringifyMap m ++ "})"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700174 return m
cdwijayarathnad9217912014-08-15 22:18:30 +0530175
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700176 testStringMap _ m = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530177 System.IO.putStrLn $ "testStringMap(" ++ stringifyMap m ++ "})"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700178 return m
179
180 testSet _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530181 System.IO.putStrLn $ "testSet({" ++ stringifySet x ++ "})"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700182 return x
183
184 testList _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530185 System.IO.putStrLn $ "testList(" ++ stringifyList x ++ "})"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700186 return x
187
188 testEnum _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530189 System.IO.putStrLn $ "testEnum(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700190 return x
191
192 testTypedef _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530193 System.IO.putStrLn $ "testTypedef(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700194 return x
195
196 testMapMap _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530197 System.IO.putStrLn $ "testMapMap(" ++ show x ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700198 return $ Map.fromList [ (-4, Map.fromList [ (-4, -4)
199 , (-3, -3)
200 , (-2, -2)
201 , (-1, -1)
202 ])
203 , (4, Map.fromList [ (1, 1)
204 , (2, 2)
205 , (3, 3)
206 , (4, 4)
207 ])
208 ]
209
210 testInsanity _ x = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530211 System.IO.putStrLn "testInsanity()"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700212 return $ Map.fromList [ (1, Map.fromList [ (TWO , x)
213 , (THREE, x)
214 ])
215 , (2, Map.fromList [ (SIX, default_Insanity)
216 ])
217 ]
218
219 testMulti _ byte i32 i64 _ _ _ = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530220 System.IO.putStrLn "testMulti()"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700221 return Xtruct{ xtruct_string_thing = Text.pack "Hello2"
222 , xtruct_byte_thing = byte
223 , xtruct_i32_thing = i32
224 , xtruct_i64_thing = i64
225 }
cdwijayarathnad9217912014-08-15 22:18:30 +0530226
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700227 testException _ s = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530228 System.IO.putStrLn $ "testException(" ++ show s ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700229 case s of
230 "Xception" -> throw $ Xception 1001 s
231 "TException" -> throw ThriftException
232 _ -> return ()
233
234 testMultiException _ s1 s2 = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530235 System.IO.putStrLn $ "testMultiException(" ++ show s1 ++ ", " ++ show s2 ++ ")"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700236 case s1 of
cdwijayarathnad9217912014-08-15 22:18:30 +0530237 "Xception" -> throw $ Xception 1001 "This is an Xception"
Nobuaki Sukegawa01ede042015-09-29 02:16:53 +0900238 "Xception2" -> throw $ Xception2 2002 $ Xtruct "This is an Xception2" 0 0 0
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700239 "TException" -> throw ThriftException
240 _ -> return default_Xtruct{ xtruct_string_thing = s2 }
241
242 testOneway _ i = do
cdwijayarathnad9217912014-08-15 22:18:30 +0530243 System.IO.putStrLn $ "testOneway(" ++ show i ++ "): Sleeping..."
Nobuaki Sukegawae8c71d82015-11-23 19:51:37 +0900244 threadDelay $ (fromIntegral i) * 1000000
cdwijayarathnad9217912014-08-15 22:18:30 +0530245 System.IO.putStrLn $ "testOneway(" ++ show i ++ "): done sleeping!"
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700246
247main :: IO ()
248main = do
249 options <- flip parseFlags defaultOptions <$> getArgs
250 case options of
251 Nothing -> showHelp
252 Just Options{..} -> do
Jens Geyerd629ea02015-09-23 21:16:50 +0200253 case Main.getTransport transport of
254 Buffered f -> runServer protocol f port
255 Framed f -> runServer protocol f port
256 NoTransport err -> putStrLn err
cdwijayarathnad9217912014-08-15 22:18:30 +0530257 System.IO.putStrLn $ "Starting \"" ++ show serverType ++ "\" server (" ++
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700258 show transport ++ ") listen on: " ++ domainSocket ++ show port
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700259 where
Jens Geyerd629ea02015-09-23 21:16:50 +0200260 acceptor p f socket = do
261 t <- f socket
262 return (p t, p t)
263
264 doRunServer p f = do
265 runThreadedServer (acceptor p f) TestHandler ThriftTest.process . PortNumber . fromIntegral
266
267 runServer p f port = case p of
268 Binary -> do doRunServer BinaryProtocol f port
269 Compact -> do doRunServer CompactProtocol f port
270 JSON -> do doRunServer JSONProtocol f port
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700271
272parseFlags :: [String] -> Options -> Maybe Options
cdwijayarathnad9217912014-08-15 22:18:30 +0530273parseFlags (flag : flags) opts = do
274 let pieces = splitOn "=" flag
275 case pieces of
276 "--port" : arg : _ -> parseFlags flags opts{ port = read arg }
277 "--domain-socket" : arg : _ -> parseFlags flags opts{ domainSocket = read arg }
278 "--server-type" : arg : _ -> parseFlags flags opts{ serverType = fromString arg }
279 "--transport" : arg : _ -> parseFlags flags opts{ transport = arg }
280 "--protocol" : arg : _ -> parseFlags flags opts{ protocol = getProtocol arg }
281 "--workers" : arg : _ -> parseFlags flags opts{ workers = read arg }
cdwijayarathna7191bc92014-08-16 23:36:07 +0530282 "-n" : arg : _ -> parseFlags flags opts{ workers = read arg }
cdwijayarathnad9217912014-08-15 22:18:30 +0530283 "--h" : _ -> Nothing
284 "--help" : _ -> Nothing
285 "--ssl" : _ -> parseFlags flags opts{ ssl = True }
286 "--processor-events" : _ -> parseFlags flags opts
cdwijayarathna7191bc92014-08-16 23:36:07 +0530287 _ -> Nothing
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700288parseFlags [] opts = Just opts
289
290showHelp :: IO ()
cdwijayarathnad9217912014-08-15 22:18:30 +0530291showHelp = System.IO.putStrLn
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700292 "Allowed options:\n\
293 \ -h [ --help ] produce help message\n\
294 \ --port arg (=9090) Port number to listen\n\
295 \ --domain-socket arg Unix Domain Socket (e.g. /tmp/ThriftTest.thrift)\n\
296 \ --server-type arg (=simple) type of server, \"simple\", \"thread-pool\",\n\
297 \ \"threaded\", or \"nonblocking\"\n\
Jens Geyerd629ea02015-09-23 21:16:50 +0200298 \ --transport arg (=buffered) transport: buffered, framed\n\
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700299 \ --protocol arg (=binary) protocol: binary, compact, json\n\
300 \ --ssl Encrypted Transport using SSL\n\
301 \ --processor-events processor-events\n\
cdwijayarathnad9217912014-08-15 22:18:30 +0530302 \ -n [ --workers ] arg (=4) Number of thread pools workers. Only valid for\n\
Jens Geyerd629ea02015-09-23 21:16:50 +0200303 \ thread-pool server type"