blob: ea58642a3d6433fc389aa62393ea24ca8927bfdd [file] [log] [blame]
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -07001{-# LANGUAGE CPP #-}
Bryan Duxburye59a80f2010-09-20 15:21:37 +00002{-# LANGUAGE DeriveDataTypeable #-}
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -07003{-# 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
24 ( Protocol(..)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000025 , ProtocolExn(..)
26 , ProtocolExnType(..)
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070027 , getTypeOf
28 , runParser
29 , versionMask
30 , version1
31 , bsToDouble
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000032 ) where
33
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000034import Control.Exception
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070035import Data.Attoparsec.ByteString
36import Data.Bits
37import Data.ByteString.Lazy (ByteString, toStrict)
38import Data.ByteString.Unsafe
39import Data.Functor ((<$>))
Roger Meier6849f202012-05-18 07:35:19 +000040import Data.Int
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070041import Data.Monoid (mempty)
42import Data.Text.Lazy (Text)
43import Data.Typeable (Typeable)
44import Data.Word
45import Foreign.Ptr (castPtr)
46import Foreign.Storable (Storable, peek, poke)
47import System.IO.Unsafe
48import qualified Data.ByteString as BS
49import qualified Data.HashMap.Strict as Map
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000050
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070051import Thrift.Types
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000052import Thrift.Transport
53
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070054versionMask :: Int32
55versionMask = fromIntegral (0xffff0000 :: Word32)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000056
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070057version1 :: Int32
58version1 = fromIntegral (0x80010000 :: Word32)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000059
60class Protocol a where
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070061 getTransport :: Transport t => a t -> t
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000062
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070063 writeMessageBegin :: Transport t => a t -> (Text, MessageType, Int32) -> IO ()
64 writeMessageEnd :: Transport t => a t -> IO ()
65 writeMessageEnd _ = return ()
66
67 readMessageBegin :: Transport t => a t -> IO (Text, MessageType, Int32)
68 readMessageEnd :: Transport t => a t -> IO ()
69 readMessageEnd _ = return ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000070
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070071 serializeVal :: Transport t => a t -> ThriftVal -> ByteString
72 deserializeVal :: Transport t => a t -> ThriftType -> ByteString -> ThriftVal
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000073
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070074 writeVal :: Transport t => a t -> ThriftVal -> IO ()
75 writeVal p = tWrite (getTransport p) . serializeVal p
76 readVal :: Transport t => a t -> ThriftType -> IO ThriftVal
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000077
78data ProtocolExnType
79 = PE_UNKNOWN
80 | PE_INVALID_DATA
81 | PE_NEGATIVE_SIZE
82 | PE_SIZE_LIMIT
83 | PE_BAD_VERSION
Jens Geyer6d1a83a2014-05-03 00:49:05 +020084 | PE_NOT_IMPLEMENTED
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070085 | PE_MISSING_REQUIRED_FIELD
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000086 deriving ( Eq, Show, Typeable )
87
88data ProtocolExn = ProtocolExn ProtocolExnType String
89 deriving ( Show, Typeable )
90instance Exception ProtocolExn
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070091
92getTypeOf :: ThriftVal -> ThriftType
93getTypeOf v = case v of
94 TStruct{} -> T_STRUCT Map.empty
95 TMap{} -> T_MAP T_VOID T_VOID
96 TList{} -> T_LIST T_VOID
97 TSet{} -> T_SET T_VOID
98 TBool{} -> T_BOOL
99 TByte{} -> T_BYTE
100 TI16{} -> T_I16
101 TI32{} -> T_I32
102 TI64{} -> T_I64
103 TString{} -> T_STRING
104 TDouble{} -> T_DOUBLE
105
106runParser :: (Protocol p, Transport t, Show a) => p t -> Parser a -> IO a
107runParser prot p = refill >>= getResult . parse p
108 where
109 refill = handle handleEOF $ toStrict <$> tRead (getTransport prot) 1
110 getResult (Done _ a) = return a
111 getResult (Partial k) = refill >>= getResult . k
112 getResult f = throw $ ProtocolExn PE_INVALID_DATA (show f)
113
114handleEOF :: SomeException -> IO BS.ByteString
115handleEOF = const $ return mempty
116
117-- | Converts a ByteString to a Floating point number
118-- The ByteString is assumed to be encoded in network order (Big Endian)
119-- therefore the behavior of this function varies based on whether the local
120-- machine is big endian or little endian.
121bsToDouble :: BS.ByteString -> Double
122bsToDouble bs = unsafeDupablePerformIO $ unsafeUseAsCString bs castBs
123 where
124#if __BYTE_ORDER == __LITTLE_ENDIAN
125 castBs chrPtr = do
126 w <- peek (castPtr chrPtr)
127 poke (castPtr chrPtr) (byteSwap w)
128 peek (castPtr chrPtr)
129#else
130 castBs = peek . castPtr
131#endif
132
133#if __BYTE_ORDER == __LITTLE_ENDIAN
134-- | Swap endianness of a 64-bit word
135byteSwap :: Word64 -> Word64
136byteSwap w = (w `shiftL` 56 .&. 0xFF00000000000000) .|.
137 (w `shiftL` 40 .&. 0x00FF000000000000) .|.
138 (w `shiftL` 24 .&. 0x0000FF0000000000) .|.
139 (w `shiftL` 8 .&. 0x000000FF00000000) .|.
140 (w `shiftR` 8 .&. 0x00000000FF000000) .|.
141 (w `shiftR` 24 .&. 0x0000000000FF0000) .|.
142 (w `shiftR` 40 .&. 0x000000000000FF00) .|.
143 (w `shiftR` 56 .&. 0x00000000000000FF)
144#endif