blob: c55ea5a21b1083605dd426e8276ab34dcd5faeaa [file] [log] [blame]
Bryan Duxburye59a80f2010-09-20 15:21:37 +00001{-# LANGUAGE ExistentialQuantification #-}
2{-# LANGUAGE MagicHash #-}
Bryan Duxbury0781f2b2009-04-07 23:29:42 +00003--
4-- Licensed to the Apache Software Foundation (ASF) under one
5-- or more contributor license agreements. See the NOTICE file
6-- distributed with this work for additional information
7-- regarding copyright ownership. The ASF licenses this file
8-- to you under the Apache License, Version 2.0 (the
9-- "License"); you may not use this file except in compliance
10-- with the License. You may obtain a copy of the License at
11--
12-- http://www.apache.org/licenses/LICENSE-2.0
13--
14-- Unless required by applicable law or agreed to in writing,
15-- software distributed under the License is distributed on an
16-- "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
17-- KIND, either express or implied. See the License for the
18-- specific language governing permissions and limitations
19-- under the License.
20--
21
22module Thrift.Protocol.Binary
23 ( module Thrift.Protocol
24 , BinaryProtocol(..)
25 ) where
26
27import Control.Exception ( throw )
David Reiss752529e2010-01-11 19:12:56 +000028import Control.Monad ( liftM )
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000029
Christian Lavoieae7f7fa2010-11-02 21:42:53 +000030import qualified Data.Binary
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000031import Data.Bits
32import Data.Int
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000033
34import GHC.Exts
35import GHC.Word
36
37import Thrift.Protocol
38import Thrift.Transport
39
Bryan Duxbury75a33e82010-09-22 00:48:56 +000040import qualified Data.ByteString.Lazy as LBS
Christian Lavoieae7f7fa2010-11-02 21:42:53 +000041import qualified Data.ByteString.Lazy.Char8 as LBSChar8
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000042
Bryan Duxbury75a33e82010-09-22 00:48:56 +000043version_mask :: Int32
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000044version_mask = 0xffff0000
Bryan Duxburye59a80f2010-09-20 15:21:37 +000045
Bryan Duxbury75a33e82010-09-22 00:48:56 +000046version_1 :: Int32
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000047version_1 = 0x80010000
48
49data BinaryProtocol a = Transport a => BinaryProtocol a
50
51
52instance Protocol BinaryProtocol where
53 getTransport (BinaryProtocol t) = t
54
55 writeMessageBegin p (n, t, s) = do
Bryan Duxbury75a33e82010-09-22 00:48:56 +000056 writeI32 p (version_1 .|. (fromIntegral $ fromEnum t))
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000057 writeString p n
58 writeI32 p s
59 writeMessageEnd _ = return ()
60
61 writeStructBegin _ _ = return ()
62 writeStructEnd _ = return ()
63 writeFieldBegin p (_, t, i) = writeType p t >> writeI16 p i
64 writeFieldEnd _ = return ()
65 writeFieldStop p = writeType p T_STOP
66 writeMapBegin p (k, v, n) = writeType p k >> writeType p v >> writeI32 p n
Bryan Duxburye59a80f2010-09-20 15:21:37 +000067 writeMapEnd _ = return ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000068 writeListBegin p (t, n) = writeType p t >> writeI32 p n
69 writeListEnd _ = return ()
70 writeSetBegin p (t, n) = writeType p t >> writeI32 p n
71 writeSetEnd _ = return ()
72
Christian Lavoieae7f7fa2010-11-02 21:42:53 +000073 writeBool p b = tWrite (getTransport p) $ LBS.singleton $ toEnum $ if b then 1 else 0
74 writeByte p b = tWrite (getTransport p) $ Data.Binary.encode b
75 writeI16 p b = tWrite (getTransport p) $ Data.Binary.encode b
76 writeI32 p b = tWrite (getTransport p) $ Data.Binary.encode b
77 writeI64 p b = tWrite (getTransport p) $ Data.Binary.encode b
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000078 writeDouble p d = writeI64 p (fromIntegral $ floatBits d)
Bryan Duxbury75a33e82010-09-22 00:48:56 +000079 writeString p s = writeI32 p (fromIntegral $ length s) >> tWrite (getTransport p) (LBSChar8.pack s)
80 writeBinary p s = writeI32 p (fromIntegral $ LBS.length s) >> tWrite (getTransport p) s
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000081
82 readMessageBegin p = do
83 ver <- readI32 p
84 if (ver .&. version_mask /= version_1)
85 then throw $ ProtocolExn PE_BAD_VERSION "Missing version identifier"
86 else do
87 s <- readString p
88 sz <- readI32 p
Bryan Duxbury75a33e82010-09-22 00:48:56 +000089 return (s, toEnum $ fromIntegral $ ver .&. 0xFF, sz)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000090 readMessageEnd _ = return ()
91 readStructBegin _ = return ""
92 readStructEnd _ = return ()
93 readFieldBegin p = do
94 t <- readType p
95 n <- if t /= T_STOP then readI16 p else return 0
96 return ("", t, n)
97 readFieldEnd _ = return ()
98 readMapBegin p = do
99 kt <- readType p
100 vt <- readType p
101 n <- readI32 p
102 return (kt, vt, n)
103 readMapEnd _ = return ()
104 readListBegin p = do
105 t <- readType p
106 n <- readI32 p
107 return (t, n)
108 readListEnd _ = return ()
109 readSetBegin p = do
110 t <- readType p
111 n <- readI32 p
112 return (t, n)
113 readSetEnd _ = return ()
114
115 readBool p = (== 1) `fmap` readByte p
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000116
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000117 readByte p = do
118 bs <- tReadAll (getTransport p) 1
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000119 return $ Data.Binary.decode bs
120
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000121 readI16 p = do
122 bs <- tReadAll (getTransport p) 2
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000123 return $ Data.Binary.decode bs
124
125 readI32 p = do
126 bs <- tReadAll (getTransport p) 4
127 return $ Data.Binary.decode bs
128
129 readI64 p = do
130 bs <- tReadAll (getTransport p) 8
131 return $ Data.Binary.decode bs
132
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000133 readDouble p = do
134 bs <- readI64 p
135 return $ floatOfBits $ fromIntegral bs
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000136
David Reiss752529e2010-01-11 19:12:56 +0000137 readString p = do
138 i <- readI32 p
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000139 LBSChar8.unpack `liftM` tReadAll (getTransport p) (fromIntegral i)
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000140
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000141 readBinary p = do
142 i <- readI32 p
143 tReadAll (getTransport p) (fromIntegral i)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000144
145
146-- | Write a type as a byte
147writeType :: (Protocol p, Transport t) => p t -> ThriftType -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000148writeType p t = writeByte p (fromIntegral $ fromEnum t)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000149
150-- | Read a byte as though it were a ThriftType
151readType :: (Protocol p, Transport t) => p t -> IO ThriftType
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000152readType p = do
153 b <- readByte p
154 return $ toEnum $ fromIntegral b
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000155
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000156floatBits :: Double -> Word64
157floatBits (D# d#) = W64# (unsafeCoerce# d#)
158
159floatOfBits :: Word64 -> Double
160floatOfBits (W64# b#) = D# (unsafeCoerce# b#)
161