blob: 2903d014d8dfb3d70fe92d30df4df4252f6d2cae [file] [log] [blame]
iproctorff8eb922007-07-25 19:06:13 +00001module TBinaryProtocol (TBinaryProtocol(..)) where
2 import Thrift
3 import Data.Bits
4 import Data.Int
5 import GHC.Exts
6 import GHC.Prim
7 import GHC.Word
8 import Control.Exception
9
iproctor55aebc42008-02-11 22:59:01 +000010 data TBinaryProtocol a = TTransport a => TBinaryProtocol a
iproctorff8eb922007-07-25 19:06:13 +000011
12 version_mask = 0xffff0000
13 version_1 = 0x80010000;
David Reiss0c90f6f2008-02-06 22:18:40 +000014
iproctorff8eb922007-07-25 19:06:13 +000015 getByte i b= 255 .&. (shiftR i (8*b))
16 getBytes i 0 = []
17 getBytes i n = (toEnum (getByte i (n-1)) :: Char):(getBytes i (n-1))
David Reiss0c90f6f2008-02-06 22:18:40 +000018
iproctorff8eb922007-07-25 19:06:13 +000019 floatBits :: Double -> Word64
20 floatBits (D# d#) = W64# (unsafeCoerce# d#)
21
22 floatOfBits :: Word64 -> Double
23 floatOfBits (W64# b#) = D# (unsafeCoerce# b#)
24
25 composeBytesH :: [Char] -> Int -> Word32
26 composeBytesH [] n = 0
27 composeBytesH (h:t) n = (shiftL (fromIntegral (fromEnum h) :: Word32) (8*n)) .|. (composeBytesH t (n-1))
28 compBytes :: [Char] -> Word32
29 compBytes b = composeBytesH b ((length b)-1)
30
31 composeBytes64H :: [Char] -> Int -> Word64
32 composeBytes64H [] n = 0
33 composeBytes64H (h:t) n = (shiftL (fromIntegral (fromEnum h) :: Word64) (8*n)) .|. (composeBytes64H t (n-1))
34 compBytes64 :: [Char] -> Word64
35 compBytes64 b = composeBytes64H b ((length b)-1)
iproctor55aebc42008-02-11 22:59:01 +000036 instance Protocol TBinaryProtocol where
37 getTransport (TBinaryProtocol t) = t
38 writeBool (TBinaryProtocol tr) b = twrite tr (if b then [toEnum 1::Char] else [toEnum 0::Char])
39 writeByte (TBinaryProtocol tr) b = twrite tr (getBytes b 1)
40 writeI16 (TBinaryProtocol tr) b = twrite tr (getBytes b 2)
41 writeI32 (TBinaryProtocol tr) b = twrite tr (getBytes b 4)
42 writeI64 (TBinaryProtocol tr) b = twrite tr (getBytes b 8)
43 writeDouble (TBinaryProtocol tr) b = writeI64 (TBinaryProtocol tr) (fromIntegral (floatBits b) :: Int)
44 writeString (TBinaryProtocol tr) s = do twrite tr (getBytes (length s) 4)
45 twrite tr s
46 writeBinary = writeString
47 writeMessageBegin (TBinaryProtocol tr) (n,t,s) = do writeI32 (TBinaryProtocol tr) (version_1 .|. (fromEnum t))
48 writeString (TBinaryProtocol tr) n
49 writeI32 (TBinaryProtocol tr) s
50 writeMessageEnd (TBinaryProtocol tr) = return ()
51 writeStructBegin (TBinaryProtocol tr) s = return ()
52 writeStructEnd (TBinaryProtocol tr) = return ()
53 writeFieldBegin a (n,t,i) = do writeByte a (fromEnum t)
54 writeI16 a i
55 writeFieldEnd a = return ()
56 writeFieldStop a = writeByte a (fromEnum T_STOP)
57 writeMapBegin a (k,v,s) = do writeByte a (fromEnum k)
58 writeByte a (fromEnum v)
59 writeI32 a s
60 writeMapEnd a = return ()
61 writeListBegin a (t,s) = do writeByte a (fromEnum t)
62 writeI32 a s
63 writeListEnd a = return ()
64 writeSetBegin = writeListBegin
65 writeSetEnd a = return ()
66 readByte (TBinaryProtocol tr) = do b <- treadAll tr 1
67 return $ (fromIntegral (fromIntegral (compBytes b) :: Int8) :: Int)
68 readI16 (TBinaryProtocol tr) = do b <- treadAll tr 2
69 return $ (fromIntegral (fromIntegral (compBytes b) :: Int16) :: Int)
70 readI32 (TBinaryProtocol tr) = do b <- treadAll tr 4
71 return $ (fromIntegral (fromIntegral (compBytes b) :: Int32) :: Int)
72 readI64 (TBinaryProtocol tr) = do b <- treadAll tr 8
73 return $ (fromIntegral (fromIntegral (compBytes64 b) :: Int64) :: Int)
74 readDouble (TBinaryProtocol tr) = do b <- readI64 (TBinaryProtocol tr)
75 return $ floatOfBits (fromIntegral b :: Word64)
76 readBool (TBinaryProtocol tr) = do b <- readByte (TBinaryProtocol tr)
77 return $ b == 1
78 readString (TBinaryProtocol tr) = do l <- readI32 (TBinaryProtocol tr)
79 treadAll tr l
80 readBinary = readString
81 readMessageBegin (TBinaryProtocol tr) = do ver <- readI32 (TBinaryProtocol tr)
82 if (ver .&. version_mask /= version_1) then
83 throwDyn (ProtocolExn PE_BAD_VERSION "Missing version identifier")
84 else do
85 s <- readString (TBinaryProtocol tr)
86 sz <- readI32 (TBinaryProtocol tr)
87 return (s,toEnum (ver .&. 0xFF) :: Message_type,fromIntegral sz :: Int)
88 readMessageEnd (TBinaryProtocol tr) = return ()
89 readStructBegin (TBinaryProtocol tr) = return ""
90 readStructEnd (TBinaryProtocol tr) = return ()
91 readFieldBegin (TBinaryProtocol tr) = do t <- readByte (TBinaryProtocol tr)
92 if (toEnum t :: T_type) /= T_STOP then
93 do s <- readI16 (TBinaryProtocol tr)
94 return ("",toEnum t :: T_type,fromIntegral s :: Int)
95 else return ("",toEnum t :: T_type,0)
96 readFieldEnd (TBinaryProtocol tr) = return ()
97 readMapBegin a = do kt <- readByte a
98 vt <- readByte a
99 s <- readI32 a
100 return (toEnum kt :: T_type,toEnum vt :: T_type,fromIntegral s :: Int)
101 readMapEnd a = return ()
102 readListBegin a = do b <- readByte a
103 s <- readI32 a
104 return (toEnum b :: T_type,fromIntegral s :: Int)
105 readListEnd a = return ()
106 readSetBegin = readListBegin
107 readSetEnd = readListEnd
iproctorff8eb922007-07-25 19:06:13 +0000108
David Reiss0c90f6f2008-02-06 22:18:40 +0000109
iproctorff8eb922007-07-25 19:06:13 +0000110