blob: 3f798ceea606802eda7da98725e6e5ec40f0721b [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 )
26
27import Data.Bits
28import Data.Int
29import Data.List ( foldl' )
30
31import GHC.Exts
32import GHC.Word
33
34import Thrift.Protocol
35import Thrift.Transport
36
37
38version_mask = 0xffff0000
39version_1 = 0x80010000
40
41data BinaryProtocol a = Transport a => BinaryProtocol a
42
43
44instance Protocol BinaryProtocol where
45 getTransport (BinaryProtocol t) = t
46
47 writeMessageBegin p (n, t, s) = do
48 writeI32 p (version_1 .|. (fromEnum t))
49 writeString p n
50 writeI32 p s
51 writeMessageEnd _ = return ()
52
53 writeStructBegin _ _ = return ()
54 writeStructEnd _ = return ()
55 writeFieldBegin p (_, t, i) = writeType p t >> writeI16 p i
56 writeFieldEnd _ = return ()
57 writeFieldStop p = writeType p T_STOP
58 writeMapBegin p (k, v, n) = writeType p k >> writeType p v >> writeI32 p n
59 writeMapEnd p = return ()
60 writeListBegin p (t, n) = writeType p t >> writeI32 p n
61 writeListEnd _ = return ()
62 writeSetBegin p (t, n) = writeType p t >> writeI32 p n
63 writeSetEnd _ = return ()
64
65 writeBool p b = tWrite (getTransport p) [toEnum $ if b then 1 else 0]
66 writeByte p b = tWrite (getTransport p) (getBytes b 1)
67 writeI16 p b = tWrite (getTransport p) (getBytes b 2)
68 writeI32 p b = tWrite (getTransport p) (getBytes b 4)
69 writeI64 p b = tWrite (getTransport p) (getBytes b 8)
70 writeDouble p d = writeI64 p (fromIntegral $ floatBits d)
71 writeString p s = writeI32 p (length s) >> tWrite (getTransport p) s
72 writeBinary = writeString
73
74 readMessageBegin p = do
75 ver <- readI32 p
76 if (ver .&. version_mask /= version_1)
77 then throw $ ProtocolExn PE_BAD_VERSION "Missing version identifier"
78 else do
79 s <- readString p
80 sz <- readI32 p
81 return (s, toEnum $ ver .&. 0xFF, sz)
82 readMessageEnd _ = return ()
83 readStructBegin _ = return ""
84 readStructEnd _ = return ()
85 readFieldBegin p = do
86 t <- readType p
87 n <- if t /= T_STOP then readI16 p else return 0
88 return ("", t, n)
89 readFieldEnd _ = return ()
90 readMapBegin p = do
91 kt <- readType p
92 vt <- readType p
93 n <- readI32 p
94 return (kt, vt, n)
95 readMapEnd _ = return ()
96 readListBegin p = do
97 t <- readType p
98 n <- readI32 p
99 return (t, n)
100 readListEnd _ = return ()
101 readSetBegin p = do
102 t <- readType p
103 n <- readI32 p
104 return (t, n)
105 readSetEnd _ = return ()
106
107 readBool p = (== 1) `fmap` readByte p
108 readByte p = do
109 bs <- tReadAll (getTransport p) 1
110 return $ fromIntegral (composeBytes bs :: Int8)
111 readI16 p = do
112 bs <- tReadAll (getTransport p) 2
113 return $ fromIntegral (composeBytes bs :: Int16)
114 readI32 p = composeBytes `fmap` tReadAll (getTransport p) 4
115 readI64 p = composeBytes `fmap` tReadAll (getTransport p) 8
116 readDouble p = do
117 bs <- readI64 p
118 return $ floatOfBits $ fromIntegral bs
119 readString p = readI32 p >>= tReadAll (getTransport p)
120 readBinary = readString
121
122
123-- | Write a type as a byte
124writeType :: (Protocol p, Transport t) => p t -> ThriftType -> IO ()
125writeType p t = writeByte p (fromEnum t)
126
127-- | Read a byte as though it were a ThriftType
128readType :: (Protocol p, Transport t) => p t -> IO ThriftType
129readType p = toEnum `fmap` readByte p
130
131composeBytes :: (Bits b, Enum t) => [t] -> b
132composeBytes = (foldl' fn 0) . (map $ fromIntegral . fromEnum)
133 where fn acc b = (acc `shiftL` 8) .|. b
134
135getByte :: Bits a => a -> Int -> a
136getByte i n = 255 .&. (i `shiftR` (8 * n))
137
138getBytes :: (Bits a, Integral a) => a -> Int -> String
139getBytes i 0 = []
140getBytes i n = (toEnum $ fromIntegral $ getByte i (n-1)):(getBytes i (n-1))
141
142floatBits :: Double -> Word64
143floatBits (D# d#) = W64# (unsafeCoerce# d#)
144
145floatOfBits :: Word64 -> Double
146floatOfBits (W64# b#) = D# (unsafeCoerce# b#)
147