blob: cfe13441d4af6f783833f2f5e99ecc71b5a7d722 [file] [log] [blame]
David Reiss68f8c382010-01-11 19:13:18 +00001--
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
Roger Meier303eb1b2014-05-14 00:49:41 +020020{-# LANGUAGE OverloadedStrings #-}
21
David Reiss68f8c382010-01-11 19:13:18 +000022import qualified Calculator
23import Calculator_Iface
24import Tutorial_Types
25import SharedService_Iface
26import Shared_Types
27
28import Thrift
29import Thrift.Protocol.Binary
30import Thrift.Transport
31import Thrift.Server
32
Roger Meier303eb1b2014-05-14 00:49:41 +020033import Data.Int
34import Data.String
David Reiss68f8c382010-01-11 19:13:18 +000035import Data.Maybe
36import Text.Printf
37import Control.Exception (throw)
38import Control.Concurrent.MVar
39import qualified Data.Map as M
40import Data.Map ((!))
41import Data.Monoid
42
Roger Meier303eb1b2014-05-14 00:49:41 +020043data CalculatorHandler = CalculatorHandler {mathLog :: MVar (M.Map Int32 SharedStruct)}
David Reiss68f8c382010-01-11 19:13:18 +000044
45newCalculatorHandler = do
46 log <- newMVar mempty
47 return $ CalculatorHandler log
48
49instance SharedService_Iface CalculatorHandler where
50 getStruct self k = do
51 myLog <- readMVar (mathLog self)
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070052 return $ (myLog ! k)
David Reiss68f8c382010-01-11 19:13:18 +000053
54
55instance Calculator_Iface CalculatorHandler where
56 ping _ =
57 print "ping()"
58
59 add _ n1 n2 = do
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070060 printf "add(%d,%d)\n" n1 n2
61 return (n1 + n2)
David Reiss68f8c382010-01-11 19:13:18 +000062
63 calculate self mlogid mwork = do
64 printf "calculate(%d, %s)\n" logid (show work)
65
66 let val = case op work of
67 ADD ->
68 num1 work + num2 work
69 SUBTRACT ->
70 num1 work - num2 work
71 MULTIPLY ->
72 num1 work * num2 work
73 DIVIDE ->
74 if num2 work == 0 then
75 throw $
76 InvalidOperation {
Konrad Grochowski3b115df2015-05-18 17:58:36 +020077 invalidOperation_whatOp = fromIntegral $ fromEnum $ op work,
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070078 invalidOperation_why = "Cannot divide by 0"
David Reiss68f8c382010-01-11 19:13:18 +000079 }
80 else
81 num1 work `div` num2 work
82
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070083 let logEntry = SharedStruct logid (fromString $ show $ val)
David Reiss68f8c382010-01-11 19:13:18 +000084 modifyMVar_ (mathLog self) $ return .(M.insert logid logEntry)
85
Roger Meier303eb1b2014-05-14 00:49:41 +020086 return $! val
David Reiss68f8c382010-01-11 19:13:18 +000087
88 where
89 -- stupid dynamic languages f'ing it up
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070090 num1 = work_num1
91 num2 = work_num2
92 op = work_op
93 logid = mlogid
94 work = mwork
David Reiss68f8c382010-01-11 19:13:18 +000095
96 zip _ =
97 print "zip()"
98
99main = do
100 handler <- newCalculatorHandler
101 print "Starting the server..."
102 runBasicServer handler Calculator.process 9090
103 print "done."