blob: 1bc9add4279a3bea722e1e1e516f89e6facbeb4f [file] [log] [blame]
Bryan Duxburye59a80f2010-09-20 15:21:37 +00001{-# LANGUAGE ExistentialQuantification #-}
2{-# LANGUAGE MagicHash #-}
Roger Meier6849f202012-05-18 07:35:19 +00003{-# LANGUAGE OverloadedStrings #-}
Bryan Duxbury0781f2b2009-04-07 23:29:42 +00004--
5-- Licensed to the Apache Software Foundation (ASF) under one
6-- or more contributor license agreements. See the NOTICE file
7-- distributed with this work for additional information
8-- regarding copyright ownership. The ASF licenses this file
9-- to you under the Apache License, Version 2.0 (the
10-- "License"); you may not use this file except in compliance
11-- with the License. You may obtain a copy of the License at
12--
13-- http://www.apache.org/licenses/LICENSE-2.0
14--
15-- Unless required by applicable law or agreed to in writing,
16-- software distributed under the License is distributed on an
17-- "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
18-- KIND, either express or implied. See the License for the
19-- specific language governing permissions and limitations
20-- under the License.
21--
22
23module Thrift.Protocol.Binary
24 ( module Thrift.Protocol
25 , BinaryProtocol(..)
26 ) where
27
28import Control.Exception ( throw )
David Reiss752529e2010-01-11 19:12:56 +000029import Control.Monad ( liftM )
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000030
Christian Lavoieae7f7fa2010-11-02 21:42:53 +000031import qualified Data.Binary
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000032import Data.Bits
33import Data.Int
Roger Meier6849f202012-05-18 07:35:19 +000034import Data.Text.Lazy.Encoding ( decodeUtf8, encodeUtf8 )
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000035
36import GHC.Exts
37import GHC.Word
38
39import Thrift.Protocol
40import Thrift.Transport
41
Bryan Duxbury75a33e82010-09-22 00:48:56 +000042import 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
Christian Lavoieae7f7fa2010-11-02 21:42:53 +000074 writeBool p b = tWrite (getTransport p) $ LBS.singleton $ toEnum $ if b then 1 else 0
75 writeByte p b = tWrite (getTransport p) $ Data.Binary.encode b
76 writeI16 p b = tWrite (getTransport p) $ Data.Binary.encode b
77 writeI32 p b = tWrite (getTransport p) $ Data.Binary.encode b
78 writeI64 p b = tWrite (getTransport p) $ Data.Binary.encode b
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000079 writeDouble p d = writeI64 p (fromIntegral $ floatBits d)
Roger Meier6849f202012-05-18 07:35:19 +000080 writeString p s = writeI32 p (fromIntegral $ LBS.length s') >> tWrite (getTransport p) s'
81 where
82 s' = encodeUtf8 s
Bryan Duxbury75a33e82010-09-22 00:48:56 +000083 writeBinary p s = writeI32 p (fromIntegral $ LBS.length s) >> tWrite (getTransport p) s
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000084
85 readMessageBegin p = do
86 ver <- readI32 p
87 if (ver .&. version_mask /= version_1)
88 then throw $ ProtocolExn PE_BAD_VERSION "Missing version identifier"
89 else do
90 s <- readString p
91 sz <- readI32 p
Bryan Duxbury75a33e82010-09-22 00:48:56 +000092 return (s, toEnum $ fromIntegral $ ver .&. 0xFF, sz)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000093 readMessageEnd _ = return ()
94 readStructBegin _ = return ""
95 readStructEnd _ = return ()
96 readFieldBegin p = do
97 t <- readType p
98 n <- if t /= T_STOP then readI16 p else return 0
99 return ("", t, n)
100 readFieldEnd _ = return ()
101 readMapBegin p = do
102 kt <- readType p
103 vt <- readType p
104 n <- readI32 p
105 return (kt, vt, n)
106 readMapEnd _ = return ()
107 readListBegin p = do
108 t <- readType p
109 n <- readI32 p
110 return (t, n)
111 readListEnd _ = return ()
112 readSetBegin p = do
113 t <- readType p
114 n <- readI32 p
115 return (t, n)
116 readSetEnd _ = return ()
117
118 readBool p = (== 1) `fmap` readByte p
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000119
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000120 readByte p = do
121 bs <- tReadAll (getTransport p) 1
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000122 return $ Data.Binary.decode bs
123
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000124 readI16 p = do
125 bs <- tReadAll (getTransport p) 2
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000126 return $ Data.Binary.decode bs
127
128 readI32 p = do
129 bs <- tReadAll (getTransport p) 4
130 return $ Data.Binary.decode bs
131
132 readI64 p = do
133 bs <- tReadAll (getTransport p) 8
134 return $ Data.Binary.decode bs
135
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000136 readDouble p = do
137 bs <- readI64 p
138 return $ floatOfBits $ fromIntegral bs
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000139
David Reiss752529e2010-01-11 19:12:56 +0000140 readString p = do
141 i <- readI32 p
Roger Meier6849f202012-05-18 07:35:19 +0000142 decodeUtf8 `liftM` tReadAll (getTransport p) (fromIntegral i)
Christian Lavoieae7f7fa2010-11-02 21:42:53 +0000143
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000144 readBinary p = do
145 i <- readI32 p
146 tReadAll (getTransport p) (fromIntegral i)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000147
148
149-- | Write a type as a byte
150writeType :: (Protocol p, Transport t) => p t -> ThriftType -> IO ()
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000151writeType p t = writeByte p (fromIntegral $ fromEnum t)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000152
153-- | Read a byte as though it were a ThriftType
154readType :: (Protocol p, Transport t) => p t -> IO ThriftType
Bryan Duxbury75a33e82010-09-22 00:48:56 +0000155readType p = do
156 b <- readByte p
157 return $ toEnum $ fromIntegral b
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000158
Bryan Duxbury0781f2b2009-04-07 23:29:42 +0000159floatBits :: Double -> Word64
160floatBits (D# d#) = W64# (unsafeCoerce# d#)
161
162floatOfBits :: Word64 -> Double
163floatOfBits (W64# b#) = D# (unsafeCoerce# b#)
164