blob: b34e80660081aa67af5903410948d3ad5e9654f3 [file] [log] [blame]
Bryan Duxburye59a80f2010-09-20 15:21:37 +00001{-# LANGUAGE DeriveDataTypeable #-}
Bryan Duxbury0781f2b2009-04-07 23:29:42 +00002--
3-- Licensed to the Apache Software Foundation (ASF) under one
4-- or more contributor license agreements. See the NOTICE file
5-- distributed with this work for additional information
6-- regarding copyright ownership. The ASF licenses this file
7-- to you under the Apache License, Version 2.0 (the
8-- "License"); you may not use this file except in compliance
9-- with the License. You may obtain a copy of the License at
10--
11-- http://www.apache.org/licenses/LICENSE-2.0
12--
13-- Unless required by applicable law or agreed to in writing,
14-- software distributed under the License is distributed on an
15-- "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
16-- KIND, either express or implied. See the License for the
17-- specific language governing permissions and limitations
18-- under the License.
19--
20
21module Thrift.Protocol
22 ( Protocol(..)
23 , skip
24 , MessageType(..)
25 , ThriftType(..)
26 , ProtocolExn(..)
27 , ProtocolExnType(..)
28 ) where
29
30import Control.Monad ( replicateM_, unless )
31import Control.Exception
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000032import Data.Int
Bryan Duxbury75a33e82010-09-22 00:48:56 +000033import Data.Typeable ( Typeable )
34import Data.Word
35import Data.ByteString.Lazy
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000036
37import Thrift.Transport
38
39
40data ThriftType
41 = T_STOP
42 | T_VOID
43 | T_BOOL
44 | T_BYTE
45 | T_DOUBLE
46 | T_I16
47 | T_I32
48 | T_I64
49 | T_STRING
50 | T_STRUCT
51 | T_MAP
52 | T_SET
53 | T_LIST
54 deriving ( Eq )
55
56instance Enum ThriftType where
57 fromEnum T_STOP = 0
58 fromEnum T_VOID = 1
59 fromEnum T_BOOL = 2
60 fromEnum T_BYTE = 3
61 fromEnum T_DOUBLE = 4
62 fromEnum T_I16 = 6
63 fromEnum T_I32 = 8
64 fromEnum T_I64 = 10
65 fromEnum T_STRING = 11
66 fromEnum T_STRUCT = 12
67 fromEnum T_MAP = 13
68 fromEnum T_SET = 14
69 fromEnum T_LIST = 15
70
71 toEnum 0 = T_STOP
72 toEnum 1 = T_VOID
73 toEnum 2 = T_BOOL
74 toEnum 3 = T_BYTE
75 toEnum 4 = T_DOUBLE
76 toEnum 6 = T_I16
77 toEnum 8 = T_I32
78 toEnum 10 = T_I64
79 toEnum 11 = T_STRING
80 toEnum 12 = T_STRUCT
81 toEnum 13 = T_MAP
82 toEnum 14 = T_SET
83 toEnum 15 = T_LIST
Bryan Duxburye59a80f2010-09-20 15:21:37 +000084 toEnum t = error $ "Invalid ThriftType " ++ show t
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000085
86data MessageType
87 = M_CALL
88 | M_REPLY
89 | M_EXCEPTION
90 deriving ( Eq )
91
92instance Enum MessageType where
93 fromEnum M_CALL = 1
94 fromEnum M_REPLY = 2
95 fromEnum M_EXCEPTION = 3
96
97 toEnum 1 = M_CALL
98 toEnum 2 = M_REPLY
99 toEnum 3 = M_EXCEPTION
Bryan Duxburye59a80f2010-09-20 15:21:37 +0000100 toEnum t = error $ "Invalid MessageType " ++ show t
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000101
102
103class Protocol a where
104 getTransport :: Transport t => a t -> t
105
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000106 writeMessageBegin :: Transport t => a t -> (String, MessageType, Int32) -> IO ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000107 writeMessageEnd :: Transport t => a t -> IO ()
108
109 writeStructBegin :: Transport t => a t -> String -> IO ()
110 writeStructEnd :: Transport t => a t -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000111 writeFieldBegin :: Transport t => a t -> (String, ThriftType, Int16) -> IO ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000112 writeFieldEnd :: Transport t => a t -> IO ()
113 writeFieldStop :: Transport t => a t -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000114 writeMapBegin :: Transport t => a t -> (ThriftType, ThriftType, Int32) -> IO ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000115 writeMapEnd :: Transport t => a t -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000116 writeListBegin :: Transport t => a t -> (ThriftType, Int32) -> IO ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000117 writeListEnd :: Transport t => a t -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000118 writeSetBegin :: Transport t => a t -> (ThriftType, Int32) -> IO ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000119 writeSetEnd :: Transport t => a t -> IO ()
120
121 writeBool :: Transport t => a t -> Bool -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000122 writeByte :: Transport t => a t -> Word8 -> IO ()
123 writeI16 :: Transport t => a t -> Int16 -> IO ()
124 writeI32 :: Transport t => a t -> Int32 -> IO ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000125 writeI64 :: Transport t => a t -> Int64 -> IO ()
126 writeDouble :: Transport t => a t -> Double -> IO ()
127 writeString :: Transport t => a t -> String -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000128 writeBinary :: Transport t => a t -> ByteString -> IO ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000129
130
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000131 readMessageBegin :: Transport t => a t -> IO (String, MessageType, Int32)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000132 readMessageEnd :: Transport t => a t -> IO ()
133
134 readStructBegin :: Transport t => a t -> IO String
135 readStructEnd :: Transport t => a t -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000136 readFieldBegin :: Transport t => a t -> IO (String, ThriftType, Int16)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000137 readFieldEnd :: Transport t => a t -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000138 readMapBegin :: Transport t => a t -> IO (ThriftType, ThriftType, Int32)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000139 readMapEnd :: Transport t => a t -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000140 readListBegin :: Transport t => a t -> IO (ThriftType, Int32)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000141 readListEnd :: Transport t => a t -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000142 readSetBegin :: Transport t => a t -> IO (ThriftType, Int32)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000143 readSetEnd :: Transport t => a t -> IO ()
144
145 readBool :: Transport t => a t -> IO Bool
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000146 readByte :: Transport t => a t -> IO Word8
147 readI16 :: Transport t => a t -> IO Int16
148 readI32 :: Transport t => a t -> IO Int32
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000149 readI64 :: Transport t => a t -> IO Int64
150 readDouble :: Transport t => a t -> IO Double
151 readString :: Transport t => a t -> IO String
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000152 readBinary :: Transport t => a t -> IO ByteString
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000153
154
155skip :: (Protocol p, Transport t) => p t -> ThriftType -> IO ()
Bryan Duxburye59a80f2010-09-20 15:21:37 +0000156skip _ T_STOP = return ()
157skip _ T_VOID = return ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000158skip p T_BOOL = readBool p >> return ()
159skip p T_BYTE = readByte p >> return ()
160skip p T_I16 = readI16 p >> return ()
161skip p T_I32 = readI32 p >> return ()
162skip p T_I64 = readI64 p >> return ()
163skip p T_DOUBLE = readDouble p >> return ()
164skip p T_STRING = readString p >> return ()
Bryan Duxburye59a80f2010-09-20 15:21:37 +0000165skip p T_STRUCT = do _ <- readStructBegin p
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000166 skipFields p
167 readStructEnd p
168skip p T_MAP = do (k, v, s) <- readMapBegin p
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000169 replicateM_ (fromIntegral s) (skip p k >> skip p v)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000170 readMapEnd p
171skip p T_SET = do (t, n) <- readSetBegin p
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000172 replicateM_ (fromIntegral n) (skip p t)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000173 readSetEnd p
174skip p T_LIST = do (t, n) <- readListBegin p
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000175 replicateM_ (fromIntegral n) (skip p t)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000176 readListEnd p
177
178
179skipFields :: (Protocol p, Transport t) => p t -> IO ()
180skipFields p = do
181 (_, t, _) <- readFieldBegin p
182 unless (t == T_STOP) (skip p t >> readFieldEnd p >> skipFields p)
183
184
185data ProtocolExnType
186 = PE_UNKNOWN
187 | PE_INVALID_DATA
188 | PE_NEGATIVE_SIZE
189 | PE_SIZE_LIMIT
190 | PE_BAD_VERSION
191 deriving ( Eq, Show, Typeable )
192
193data ProtocolExn = ProtocolExn ProtocolExnType String
194 deriving ( Show, Typeable )
195instance Exception ProtocolExn