blob: ed2151b240565f3b6a394c63e7882dfebf84a8ed [file] [log] [blame]
David Reissea2cba82009-03-30 21:35:00 +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
iproctorff8eb922007-07-25 19:06:13 +000020module TBinaryProtocol (TBinaryProtocol(..)) where
21 import Thrift
22 import Data.Bits
23 import Data.Int
24 import GHC.Exts
25 import GHC.Prim
26 import GHC.Word
27 import Control.Exception
28
iproctor55aebc42008-02-11 22:59:01 +000029 data TBinaryProtocol a = TTransport a => TBinaryProtocol a
iproctorff8eb922007-07-25 19:06:13 +000030
31 version_mask = 0xffff0000
32 version_1 = 0x80010000;
David Reiss0c90f6f2008-02-06 22:18:40 +000033
Bryan Duxburyf3c83cf2009-03-24 00:34:16 +000034 getByte :: Bits a => a -> Int -> a
35 getByte i b = 255 .&. (shiftR i (8*b))
36
37 getBytes :: (Bits a, Integral a) => a -> Int -> String
iproctorff8eb922007-07-25 19:06:13 +000038 getBytes i 0 = []
Bryan Duxburyf3c83cf2009-03-24 00:34:16 +000039 getBytes i n = (toEnum $ fromIntegral $ getByte i (n-1)):(getBytes i (n-1))
David Reiss0c90f6f2008-02-06 22:18:40 +000040
iproctorff8eb922007-07-25 19:06:13 +000041 floatBits :: Double -> Word64
42 floatBits (D# d#) = W64# (unsafeCoerce# d#)
43
44 floatOfBits :: Word64 -> Double
45 floatOfBits (W64# b#) = D# (unsafeCoerce# b#)
46
47 composeBytesH :: [Char] -> Int -> Word32
48 composeBytesH [] n = 0
49 composeBytesH (h:t) n = (shiftL (fromIntegral (fromEnum h) :: Word32) (8*n)) .|. (composeBytesH t (n-1))
50 compBytes :: [Char] -> Word32
51 compBytes b = composeBytesH b ((length b)-1)
52
53 composeBytes64H :: [Char] -> Int -> Word64
54 composeBytes64H [] n = 0
55 composeBytes64H (h:t) n = (shiftL (fromIntegral (fromEnum h) :: Word64) (8*n)) .|. (composeBytes64H t (n-1))
56 compBytes64 :: [Char] -> Word64
57 compBytes64 b = composeBytes64H b ((length b)-1)
iproctor55aebc42008-02-11 22:59:01 +000058 instance Protocol TBinaryProtocol where
59 getTransport (TBinaryProtocol t) = t
60 writeBool (TBinaryProtocol tr) b = twrite tr (if b then [toEnum 1::Char] else [toEnum 0::Char])
61 writeByte (TBinaryProtocol tr) b = twrite tr (getBytes b 1)
62 writeI16 (TBinaryProtocol tr) b = twrite tr (getBytes b 2)
63 writeI32 (TBinaryProtocol tr) b = twrite tr (getBytes b 4)
64 writeI64 (TBinaryProtocol tr) b = twrite tr (getBytes b 8)
Bryan Duxburyf3c83cf2009-03-24 00:34:16 +000065 writeDouble (TBinaryProtocol tr) b = writeI64 (TBinaryProtocol tr) (fromIntegral (floatBits b) :: Int64)
iproctor55aebc42008-02-11 22:59:01 +000066 writeString (TBinaryProtocol tr) s = do twrite tr (getBytes (length s) 4)
67 twrite tr s
68 writeBinary = writeString
69 writeMessageBegin (TBinaryProtocol tr) (n,t,s) = do writeI32 (TBinaryProtocol tr) (version_1 .|. (fromEnum t))
70 writeString (TBinaryProtocol tr) n
71 writeI32 (TBinaryProtocol tr) s
72 writeMessageEnd (TBinaryProtocol tr) = return ()
73 writeStructBegin (TBinaryProtocol tr) s = return ()
74 writeStructEnd (TBinaryProtocol tr) = return ()
75 writeFieldBegin a (n,t,i) = do writeByte a (fromEnum t)
76 writeI16 a i
77 writeFieldEnd a = return ()
78 writeFieldStop a = writeByte a (fromEnum T_STOP)
79 writeMapBegin a (k,v,s) = do writeByte a (fromEnum k)
80 writeByte a (fromEnum v)
81 writeI32 a s
82 writeMapEnd a = return ()
83 writeListBegin a (t,s) = do writeByte a (fromEnum t)
84 writeI32 a s
85 writeListEnd a = return ()
86 writeSetBegin = writeListBegin
87 writeSetEnd a = return ()
88 readByte (TBinaryProtocol tr) = do b <- treadAll tr 1
89 return $ (fromIntegral (fromIntegral (compBytes b) :: Int8) :: Int)
90 readI16 (TBinaryProtocol tr) = do b <- treadAll tr 2
91 return $ (fromIntegral (fromIntegral (compBytes b) :: Int16) :: Int)
92 readI32 (TBinaryProtocol tr) = do b <- treadAll tr 4
93 return $ (fromIntegral (fromIntegral (compBytes b) :: Int32) :: Int)
94 readI64 (TBinaryProtocol tr) = do b <- treadAll tr 8
Bryan Duxburyf3c83cf2009-03-24 00:34:16 +000095 return $ (fromIntegral (compBytes64 b) :: Int64)
iproctor55aebc42008-02-11 22:59:01 +000096 readDouble (TBinaryProtocol tr) = do b <- readI64 (TBinaryProtocol tr)
97 return $ floatOfBits (fromIntegral b :: Word64)
98 readBool (TBinaryProtocol tr) = do b <- readByte (TBinaryProtocol tr)
99 return $ b == 1
100 readString (TBinaryProtocol tr) = do l <- readI32 (TBinaryProtocol tr)
101 treadAll tr l
102 readBinary = readString
103 readMessageBegin (TBinaryProtocol tr) = do ver <- readI32 (TBinaryProtocol tr)
104 if (ver .&. version_mask /= version_1) then
105 throwDyn (ProtocolExn PE_BAD_VERSION "Missing version identifier")
106 else do
107 s <- readString (TBinaryProtocol tr)
108 sz <- readI32 (TBinaryProtocol tr)
109 return (s,toEnum (ver .&. 0xFF) :: Message_type,fromIntegral sz :: Int)
110 readMessageEnd (TBinaryProtocol tr) = return ()
111 readStructBegin (TBinaryProtocol tr) = return ""
112 readStructEnd (TBinaryProtocol tr) = return ()
113 readFieldBegin (TBinaryProtocol tr) = do t <- readByte (TBinaryProtocol tr)
114 if (toEnum t :: T_type) /= T_STOP then
115 do s <- readI16 (TBinaryProtocol tr)
116 return ("",toEnum t :: T_type,fromIntegral s :: Int)
117 else return ("",toEnum t :: T_type,0)
118 readFieldEnd (TBinaryProtocol tr) = return ()
119 readMapBegin a = do kt <- readByte a
120 vt <- readByte a
121 s <- readI32 a
122 return (toEnum kt :: T_type,toEnum vt :: T_type,fromIntegral s :: Int)
123 readMapEnd a = return ()
124 readListBegin a = do b <- readByte a
125 s <- readI32 a
126 return (toEnum b :: T_type,fromIntegral s :: Int)
127 readListEnd a = return ()
128 readSetBegin = readListBegin
129 readSetEnd = readListEnd
iproctorff8eb922007-07-25 19:06:13 +0000130
David Reiss0c90f6f2008-02-06 22:18:40 +0000131
iproctorff8eb922007-07-25 19:06:13 +0000132