blob: fa9a20799b39d4c4ecc7333ceb65961a4ef4b651 [file] [log] [blame]
Bryan Duxbury0781f2b2009-04-07 23:29:42 +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
20module Thrift.Protocol.Binary
21 ( module Thrift.Protocol
22 , BinaryProtocol(..)
23 ) where
24
25import Control.Exception ( throw )
David Reiss752529e2010-01-11 19:12:56 +000026import Control.Monad ( liftM )
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000027
28import Data.Bits
29import Data.Int
30import Data.List ( foldl' )
31
32import GHC.Exts
33import GHC.Word
34
35import Thrift.Protocol
36import Thrift.Transport
37
David Reiss752529e2010-01-11 19:12:56 +000038import qualified Data.ByteString.Lazy.Char8 as LBS
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000039
40version_mask = 0xffff0000
41version_1 = 0x80010000
42
43data BinaryProtocol a = Transport a => BinaryProtocol a
44
45
46instance Protocol BinaryProtocol where
47 getTransport (BinaryProtocol t) = t
48
49 writeMessageBegin p (n, t, s) = do
50 writeI32 p (version_1 .|. (fromEnum t))
51 writeString p n
52 writeI32 p s
53 writeMessageEnd _ = return ()
54
55 writeStructBegin _ _ = return ()
56 writeStructEnd _ = return ()
57 writeFieldBegin p (_, t, i) = writeType p t >> writeI16 p i
58 writeFieldEnd _ = return ()
59 writeFieldStop p = writeType p T_STOP
60 writeMapBegin p (k, v, n) = writeType p k >> writeType p v >> writeI32 p n
61 writeMapEnd p = return ()
62 writeListBegin p (t, n) = writeType p t >> writeI32 p n
63 writeListEnd _ = return ()
64 writeSetBegin p (t, n) = writeType p t >> writeI32 p n
65 writeSetEnd _ = return ()
66
David Reiss752529e2010-01-11 19:12:56 +000067 writeBool p b = tWrite (getTransport p) $ LBS.singleton $ toEnum $ if b then 1 else 0
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000068 writeByte p b = tWrite (getTransport p) (getBytes b 1)
69 writeI16 p b = tWrite (getTransport p) (getBytes b 2)
70 writeI32 p b = tWrite (getTransport p) (getBytes b 4)
71 writeI64 p b = tWrite (getTransport p) (getBytes b 8)
72 writeDouble p d = writeI64 p (fromIntegral $ floatBits d)
David Reiss752529e2010-01-11 19:12:56 +000073 writeString p s = writeI32 p (length s) >> tWrite (getTransport p) (LBS.pack s)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000074 writeBinary = writeString
75
76 readMessageBegin p = do
77 ver <- readI32 p
78 if (ver .&. version_mask /= version_1)
79 then throw $ ProtocolExn PE_BAD_VERSION "Missing version identifier"
80 else do
81 s <- readString p
82 sz <- readI32 p
83 return (s, toEnum $ ver .&. 0xFF, sz)
84 readMessageEnd _ = return ()
85 readStructBegin _ = return ""
86 readStructEnd _ = return ()
87 readFieldBegin p = do
88 t <- readType p
89 n <- if t /= T_STOP then readI16 p else return 0
90 return ("", t, n)
91 readFieldEnd _ = return ()
92 readMapBegin p = do
93 kt <- readType p
94 vt <- readType p
95 n <- readI32 p
96 return (kt, vt, n)
97 readMapEnd _ = return ()
98 readListBegin p = do
99 t <- readType p
100 n <- readI32 p
101 return (t, n)
102 readListEnd _ = return ()
103 readSetBegin p = do
104 t <- readType p
105 n <- readI32 p
106 return (t, n)
107 readSetEnd _ = return ()
108
109 readBool p = (== 1) `fmap` readByte p
110 readByte p = do
111 bs <- tReadAll (getTransport p) 1
112 return $ fromIntegral (composeBytes bs :: Int8)
113 readI16 p = do
114 bs <- tReadAll (getTransport p) 2
115 return $ fromIntegral (composeBytes bs :: Int16)
116 readI32 p = composeBytes `fmap` tReadAll (getTransport p) 4
117 readI64 p = composeBytes `fmap` tReadAll (getTransport p) 8
118 readDouble p = do
119 bs <- readI64 p
120 return $ floatOfBits $ fromIntegral bs
David Reiss752529e2010-01-11 19:12:56 +0000121 readString p = do
122 i <- readI32 p
123 LBS.unpack `liftM` tReadAll (getTransport p) i
124
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000125 readBinary = readString
126
127
128-- | Write a type as a byte
129writeType :: (Protocol p, Transport t) => p t -> ThriftType -> IO ()
130writeType p t = writeByte p (fromEnum t)
131
132-- | Read a byte as though it were a ThriftType
133readType :: (Protocol p, Transport t) => p t -> IO ThriftType
134readType p = toEnum `fmap` readByte p
135
David Reiss752529e2010-01-11 19:12:56 +0000136composeBytes :: (Bits b) => LBS.ByteString -> b
137composeBytes = (foldl' fn 0) . (map (fromIntegral . fromEnum)) . LBS.unpack
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000138 where fn acc b = (acc `shiftL` 8) .|. b
139
140getByte :: Bits a => a -> Int -> a
141getByte i n = 255 .&. (i `shiftR` (8 * n))
142
David Reiss752529e2010-01-11 19:12:56 +0000143getBytes :: (Bits a, Integral a) => a -> Int -> LBS.ByteString
144getBytes i 0 = LBS.empty
145getBytes i n = (toEnum $ fromIntegral $ getByte i (n-1)) `LBS.cons` (getBytes i (n-1))
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000146
147floatBits :: Double -> Word64
148floatBits (D# d#) = W64# (unsafeCoerce# d#)
149
150floatOfBits :: Word64 -> Double
151floatOfBits (W64# b#) = D# (unsafeCoerce# b#)
152