blob: e57cff584303e35af4890dce40e0fc205e585ee0 [file] [log] [blame]
Bryan Duxburye59a80f2010-09-20 15:21:37 +00001{-# LANGUAGE DeriveDataTypeable #-}
2{-# LANGUAGE KindSignatures #-}
3{-# 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.Monad ( when )
34import Control.Exception
iproctorff8eb922007-07-25 19:06:13 +000035
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000036import Data.Typeable ( Typeable )
iproctorff8eb922007-07-25 19:06:13 +000037
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000038import Thrift.Transport
39import Thrift.Protocol
David Reiss0c90f6f2008-02-06 22:18:40 +000040
41
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000042data ThriftException = ThriftException
43 deriving ( Show, Typeable )
44instance Exception ThriftException
David Reiss0c90f6f2008-02-06 22:18:40 +000045
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000046data AppExnType
47 = AE_UNKNOWN
48 | AE_UNKNOWN_METHOD
49 | AE_INVALID_MESSAGE_TYPE
50 | AE_WRONG_METHOD_NAME
51 | AE_BAD_SEQUENCE_ID
52 | AE_MISSING_RESULT
Roger Meier345ecc72011-08-03 09:49:27 +000053 | AE_INTERNAL_ERROR
54 | AE_PROTOCOL_ERROR
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000055 deriving ( Eq, Show, Typeable )
David Reiss0c90f6f2008-02-06 22:18:40 +000056
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000057instance Enum AppExnType where
58 toEnum 0 = AE_UNKNOWN
59 toEnum 1 = AE_UNKNOWN_METHOD
60 toEnum 2 = AE_INVALID_MESSAGE_TYPE
61 toEnum 3 = AE_WRONG_METHOD_NAME
62 toEnum 4 = AE_BAD_SEQUENCE_ID
63 toEnum 5 = AE_MISSING_RESULT
Roger Meier345ecc72011-08-03 09:49:27 +000064 toEnum 6 = AE_INTERNAL_ERROR
65 toEnum 7 = AE_PROTOCOL_ERROR
Bryan Duxburye59a80f2010-09-20 15:21:37 +000066 toEnum t = error $ "Invalid AppExnType " ++ show t
David Reiss0c90f6f2008-02-06 22:18:40 +000067
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000068 fromEnum AE_UNKNOWN = 0
69 fromEnum AE_UNKNOWN_METHOD = 1
70 fromEnum AE_INVALID_MESSAGE_TYPE = 2
71 fromEnum AE_WRONG_METHOD_NAME = 3
72 fromEnum AE_BAD_SEQUENCE_ID = 4
73 fromEnum AE_MISSING_RESULT = 5
Roger Meier345ecc72011-08-03 09:49:27 +000074 fromEnum AE_INTERNAL_ERROR = 6
75 fromEnum AE_PROTOCOL_ERROR = 7
David Reiss0c90f6f2008-02-06 22:18:40 +000076
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000077data AppExn = AppExn { ae_type :: AppExnType, ae_message :: String }
78 deriving ( Show, Typeable )
79instance Exception AppExn
David Reiss0c90f6f2008-02-06 22:18:40 +000080
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000081writeAppExn :: (Protocol p, Transport t) => p t -> AppExn -> IO ()
82writeAppExn pt ae = do
83 writeStructBegin pt "TApplicationException"
David Reiss0c90f6f2008-02-06 22:18:40 +000084
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000085 when (ae_message ae /= "") $ do
86 writeFieldBegin pt ("message", T_STRING , 1)
87 writeString pt (ae_message ae)
88 writeFieldEnd pt
David Reiss0c90f6f2008-02-06 22:18:40 +000089
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000090 writeFieldBegin pt ("type", T_I32, 2);
Bryan Duxbury75a33e82010-09-22 00:48:56 +000091 writeI32 pt (fromIntegral $ fromEnum (ae_type ae))
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000092 writeFieldEnd pt
93 writeFieldStop pt
94 writeStructEnd pt
David Reiss0c90f6f2008-02-06 22:18:40 +000095
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000096readAppExn :: (Protocol p, Transport t) => p t -> IO AppExn
97readAppExn pt = do
Bryan Duxburye59a80f2010-09-20 15:21:37 +000098 _ <- readStructBegin pt
Anthony F. Molinarodaef1c82010-09-26 04:25:36 +000099 record <- readAppExnFields pt (AppExn {ae_type = undefined, ae_message = undefined})
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000100 readStructEnd pt
Anthony F. Molinarodaef1c82010-09-26 04:25:36 +0000101 return record
David Reiss0c90f6f2008-02-06 22:18:40 +0000102
Bryan Duxburye59a80f2010-09-20 15:21:37 +0000103readAppExnFields :: forall (a :: * -> *) t. (Protocol a, Transport t) => a t -> AppExn -> IO AppExn
Anthony F. Molinarodaef1c82010-09-26 04:25:36 +0000104readAppExnFields pt record = do
Bryan Duxburye59a80f2010-09-20 15:21:37 +0000105 (_, ft, tag) <- readFieldBegin pt
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000106 if ft == T_STOP
Anthony F. Molinarodaef1c82010-09-26 04:25:36 +0000107 then return record
Bryan Duxburye59a80f2010-09-20 15:21:37 +0000108 else case tag of
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000109 1 -> if ft == T_STRING then
110 do s <- readString pt
Anthony F. Molinarodaef1c82010-09-26 04:25:36 +0000111 readAppExnFields pt record{ae_message = s}
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000112 else do skip pt ft
Anthony F. Molinarodaef1c82010-09-26 04:25:36 +0000113 readAppExnFields pt record
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000114 2 -> if ft == T_I32 then
115 do i <- readI32 pt
Anthony F. Molinarodaef1c82010-09-26 04:25:36 +0000116 readAppExnFields pt record{ae_type = (toEnum $ fromIntegral i)}
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000117 else do skip pt ft
Anthony F. Molinarodaef1c82010-09-26 04:25:36 +0000118 readAppExnFields pt record
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000119 _ -> do skip pt ft
120 readFieldEnd pt
Anthony F. Molinarodaef1c82010-09-26 04:25:36 +0000121 readAppExnFields pt record
David Reiss0c90f6f2008-02-06 22:18:40 +0000122