blob: 658020991bc22b89dbd7b5d4371b01057f53d177 [file] [log] [blame]
Bryan Duxburye59a80f2010-09-20 15:21:37 +00001{-# LANGUAGE DeriveDataTypeable #-}
Roger Meier6849f202012-05-18 07:35:19 +00002{-# LANGUAGE OverloadedStrings #-}
Bryan Duxburye59a80f2010-09-20 15:21:37 +00003{-# LANGUAGE RankNTypes #-}
David Reissea2cba82009-03-30 21:35:00 +00004--
5-- Licensed to the Apache Software Foundation (ASF) under one
6-- or more contributor license agreements. See the NOTICE file
7-- distributed with this work for additional information
8-- regarding copyright ownership. The ASF licenses this file
9-- to you under the Apache License, Version 2.0 (the
10-- "License"); you may not use this file except in compliance
11-- with the License. You may obtain a copy of the License at
12--
13-- http://www.apache.org/licenses/LICENSE-2.0
14--
15-- Unless required by applicable law or agreed to in writing,
16-- software distributed under the License is distributed on an
17-- "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
18-- KIND, either express or implied. See the License for the
19-- specific language governing permissions and limitations
20-- under the License.
21--
22
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000023module Thrift
24 ( module Thrift.Transport
25 , module Thrift.Protocol
26 , AppExnType(..)
27 , AppExn(..)
28 , readAppExn
29 , writeAppExn
30 , ThriftException(..)
31 ) where
iproctorff8eb922007-07-25 19:06:13 +000032
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000033import Control.Exception
iproctorff8eb922007-07-25 19:06:13 +000034
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070035import Data.Int
36import Data.Text.Lazy ( Text, pack, unpack )
37import Data.Text.Lazy.Encoding
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000038import Data.Typeable ( Typeable )
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070039import qualified Data.HashMap.Strict as Map
iproctorff8eb922007-07-25 19:06:13 +000040
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000041import Thrift.Protocol
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070042import Thrift.Transport
43import Thrift.Types
David Reiss0c90f6f2008-02-06 22:18:40 +000044
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000045data ThriftException = ThriftException
46 deriving ( Show, Typeable )
47instance Exception ThriftException
David Reiss0c90f6f2008-02-06 22:18:40 +000048
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000049data AppExnType
50 = AE_UNKNOWN
51 | AE_UNKNOWN_METHOD
52 | AE_INVALID_MESSAGE_TYPE
53 | AE_WRONG_METHOD_NAME
54 | AE_BAD_SEQUENCE_ID
55 | AE_MISSING_RESULT
Roger Meier345ecc72011-08-03 09:49:27 +000056 | AE_INTERNAL_ERROR
57 | AE_PROTOCOL_ERROR
Roger Meier01931492012-12-22 21:31:03 +010058 | AE_INVALID_TRANSFORM
59 | AE_INVALID_PROTOCOL
60 | AE_UNSUPPORTED_CLIENT_TYPE
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000061 deriving ( Eq, Show, Typeable )
David Reiss0c90f6f2008-02-06 22:18:40 +000062
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000063instance Enum AppExnType where
64 toEnum 0 = AE_UNKNOWN
65 toEnum 1 = AE_UNKNOWN_METHOD
66 toEnum 2 = AE_INVALID_MESSAGE_TYPE
67 toEnum 3 = AE_WRONG_METHOD_NAME
68 toEnum 4 = AE_BAD_SEQUENCE_ID
69 toEnum 5 = AE_MISSING_RESULT
Roger Meier345ecc72011-08-03 09:49:27 +000070 toEnum 6 = AE_INTERNAL_ERROR
71 toEnum 7 = AE_PROTOCOL_ERROR
Roger Meier01931492012-12-22 21:31:03 +010072 toEnum 8 = AE_INVALID_TRANSFORM
73 toEnum 9 = AE_INVALID_PROTOCOL
74 toEnum 10 = AE_UNSUPPORTED_CLIENT_TYPE
Bryan Duxburye59a80f2010-09-20 15:21:37 +000075 toEnum t = error $ "Invalid AppExnType " ++ show t
David Reiss0c90f6f2008-02-06 22:18:40 +000076
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000077 fromEnum AE_UNKNOWN = 0
78 fromEnum AE_UNKNOWN_METHOD = 1
79 fromEnum AE_INVALID_MESSAGE_TYPE = 2
80 fromEnum AE_WRONG_METHOD_NAME = 3
81 fromEnum AE_BAD_SEQUENCE_ID = 4
82 fromEnum AE_MISSING_RESULT = 5
Roger Meier345ecc72011-08-03 09:49:27 +000083 fromEnum AE_INTERNAL_ERROR = 6
84 fromEnum AE_PROTOCOL_ERROR = 7
Roger Meier01931492012-12-22 21:31:03 +010085 fromEnum AE_INVALID_TRANSFORM = 8
86 fromEnum AE_INVALID_PROTOCOL = 9
87 fromEnum AE_UNSUPPORTED_CLIENT_TYPE = 10
David Reiss0c90f6f2008-02-06 22:18:40 +000088
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000089data AppExn = AppExn { ae_type :: AppExnType, ae_message :: String }
90 deriving ( Show, Typeable )
91instance Exception AppExn
David Reiss0c90f6f2008-02-06 22:18:40 +000092
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090093writeAppExn :: Protocol p => p -> AppExn -> IO ()
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070094writeAppExn pt ae = writeVal pt $ TStruct $ Map.fromList
95 [ (1, ("message", TString $ encodeUtf8 $ pack $ ae_message ae))
96 , (2, ("type", TI32 $ fromIntegral $ fromEnum (ae_type ae)))
97 ]
David Reiss0c90f6f2008-02-06 22:18:40 +000098
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090099readAppExn :: Protocol p => p -> IO AppExn
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000100readAppExn pt = do
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700101 let typemap = Map.fromList [(1,("message",T_STRING)),(2,("type",T_I32))]
102 TStruct fields <- readVal pt $ T_STRUCT typemap
103 return $ readAppExnFields fields
David Reiss0c90f6f2008-02-06 22:18:40 +0000104
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700105readAppExnFields :: Map.HashMap Int16 (Text, ThriftVal) -> AppExn
106readAppExnFields fields = AppExn{
107 ae_message = maybe undefined unwrapMessage $ Map.lookup 1 fields,
108 ae_type = maybe undefined unwrapType $ Map.lookup 2 fields
109 }
110 where
111 unwrapMessage (_, TString s) = unpack $ decodeUtf8 s
112 unwrapMessage _ = undefined
113 unwrapType (_, TI32 i) = toEnum $ fromIntegral i
114 unwrapType _ = undefined