blob: cd9596543e1bf0ccdce02bd466f60dd3e086fcd7 [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
30import Data.Bits
31import Data.Int
32import Data.List ( foldl' )
Bryan Duxbury75a33e82010-09-22 00:48:56 +000033import Data.Word
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000034
35import GHC.Exts
36import GHC.Word
37
38import Thrift.Protocol
39import Thrift.Transport
40
Bryan Duxbury75a33e82010-09-22 00:48:56 +000041import qualified Data.ByteString.Lazy.Char8 as LBSChar8
42import qualified Data.ByteString.Lazy as LBS
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000043
Bryan Duxbury75a33e82010-09-22 00:48:56 +000044version_mask :: Int32
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000045version_mask = 0xffff0000
Bryan Duxburye59a80f2010-09-20 15:21:37 +000046
Bryan Duxbury75a33e82010-09-22 00:48:56 +000047version_1 :: Int32
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000048version_1 = 0x80010000
49
50data BinaryProtocol a = Transport a => BinaryProtocol a
51
52
53instance Protocol BinaryProtocol where
54 getTransport (BinaryProtocol t) = t
55
56 writeMessageBegin p (n, t, s) = do
Bryan Duxbury75a33e82010-09-22 00:48:56 +000057 writeI32 p (version_1 .|. (fromIntegral $ fromEnum t))
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000058 writeString p n
59 writeI32 p s
60 writeMessageEnd _ = return ()
61
62 writeStructBegin _ _ = return ()
63 writeStructEnd _ = return ()
64 writeFieldBegin p (_, t, i) = writeType p t >> writeI16 p i
65 writeFieldEnd _ = return ()
66 writeFieldStop p = writeType p T_STOP
67 writeMapBegin p (k, v, n) = writeType p k >> writeType p v >> writeI32 p n
Bryan Duxburye59a80f2010-09-20 15:21:37 +000068 writeMapEnd _ = return ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000069 writeListBegin p (t, n) = writeType p t >> writeI32 p n
70 writeListEnd _ = return ()
71 writeSetBegin p (t, n) = writeType p t >> writeI32 p n
72 writeSetEnd _ = return ()
73
Bryan Duxbury75a33e82010-09-22 00:48:56 +000074 writeBool p b = tWrite (getTransport p) $ LBSChar8.singleton $ toEnum $ if b then 1 else 0
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000075 writeByte p b = tWrite (getTransport p) (getBytes b 1)
76 writeI16 p b = tWrite (getTransport p) (getBytes b 2)
77 writeI32 p b = tWrite (getTransport p) (getBytes b 4)
78 writeI64 p b = tWrite (getTransport p) (getBytes b 8)
79 writeDouble p d = writeI64 p (fromIntegral $ floatBits d)
Bryan Duxbury75a33e82010-09-22 00:48:56 +000080 writeString p s = writeI32 p (fromIntegral $ length s) >> tWrite (getTransport p) (LBSChar8.pack s)
81 writeBinary p s = writeI32 p (fromIntegral $ LBS.length s) >> tWrite (getTransport p) s
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000082
83 readMessageBegin p = do
84 ver <- readI32 p
85 if (ver .&. version_mask /= version_1)
86 then throw $ ProtocolExn PE_BAD_VERSION "Missing version identifier"
87 else do
88 s <- readString p
89 sz <- readI32 p
Bryan Duxbury75a33e82010-09-22 00:48:56 +000090 return (s, toEnum $ fromIntegral $ ver .&. 0xFF, sz)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000091 readMessageEnd _ = return ()
92 readStructBegin _ = return ""
93 readStructEnd _ = return ()
94 readFieldBegin p = do
95 t <- readType p
96 n <- if t /= T_STOP then readI16 p else return 0
97 return ("", t, n)
98 readFieldEnd _ = return ()
99 readMapBegin p = do
100 kt <- readType p
101 vt <- readType p
102 n <- readI32 p
103 return (kt, vt, n)
104 readMapEnd _ = return ()
105 readListBegin p = do
106 t <- readType p
107 n <- readI32 p
108 return (t, n)
109 readListEnd _ = return ()
110 readSetBegin p = do
111 t <- readType p
112 n <- readI32 p
113 return (t, n)
114 readSetEnd _ = return ()
115
116 readBool p = (== 1) `fmap` readByte p
117 readByte p = do
118 bs <- tReadAll (getTransport p) 1
119 return $ fromIntegral (composeBytes bs :: Int8)
120 readI16 p = do
121 bs <- tReadAll (getTransport p) 2
122 return $ fromIntegral (composeBytes bs :: Int16)
123 readI32 p = composeBytes `fmap` tReadAll (getTransport p) 4
124 readI64 p = composeBytes `fmap` tReadAll (getTransport p) 8
125 readDouble p = do
126 bs <- readI64 p
127 return $ floatOfBits $ fromIntegral bs
David Reiss752529e2010-01-11 19:12:56 +0000128 readString p = do
129 i <- readI32 p
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000130 LBSChar8.unpack `liftM` tReadAll (getTransport p) (fromIntegral i)
131 readBinary p = do
132 i <- readI32 p
133 tReadAll (getTransport p) (fromIntegral i)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000134
135
136-- | Write a type as a byte
137writeType :: (Protocol p, Transport t) => p t -> ThriftType -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000138writeType p t = writeByte p (fromIntegral $ fromEnum t)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000139
140-- | Read a byte as though it were a ThriftType
141readType :: (Protocol p, Transport t) => p t -> IO ThriftType
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000142readType p = do
143 b <- readByte p
144 return $ toEnum $ fromIntegral b
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000145
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000146composeBytes :: (Bits b) => LBSChar8.ByteString -> b
147composeBytes = (foldl' fn 0) . (map (fromIntegral . fromEnum)) . LBSChar8.unpack
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000148 where fn acc b = (acc `shiftL` 8) .|. b
149
150getByte :: Bits a => a -> Int -> a
151getByte i n = 255 .&. (i `shiftR` (8 * n))
152
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000153getBytes :: (Bits a, Integral a) => a -> Int -> LBSChar8.ByteString
154getBytes _ 0 = LBSChar8.empty
155getBytes i n = (toEnum $ fromIntegral $ getByte i (n-1)) `LBSChar8.cons` (getBytes i (n-1))
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000156
157floatBits :: Double -> Word64
158floatBits (D# d#) = W64# (unsafeCoerce# d#)
159
160floatOfBits :: Word64 -> Double
161floatOfBits (W64# b#) = D# (unsafeCoerce# b#)
162