blob: 67a9175cb3310a8ce9672ad5f95d6652d2f994c1 [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(..)
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090025 , StatelessProtocol(..)
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000026 , ProtocolExn(..)
27 , ProtocolExnType(..)
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070028 , getTypeOf
29 , runParser
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070030 , bsToDouble
Nobuaki Sukegawa7c7d6792015-12-09 03:22:35 +090031 , bsToDoubleLE
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
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070037import Data.ByteString.Unsafe
38import Data.Functor ((<$>))
Roger Meier6849f202012-05-18 07:35:19 +000039import Data.Int
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070040import Data.Monoid (mempty)
41import Data.Text.Lazy (Text)
42import Data.Typeable (Typeable)
43import Data.Word
44import Foreign.Ptr (castPtr)
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090045import Foreign.Storable (peek, poke)
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070046import System.IO.Unsafe
47import qualified Data.ByteString as BS
48import qualified Data.HashMap.Strict as Map
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090049import qualified Data.ByteString.Lazy as LBS
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000050
51import Thrift.Transport
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090052import Thrift.Types
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000053
54class Protocol a where
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090055 readByte :: a -> IO LBS.ByteString
56 readVal :: a -> ThriftType -> IO ThriftVal
57 readMessage :: a -> ((Text, MessageType, Int32) -> IO b) -> IO b
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000058
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090059 writeVal :: a -> ThriftVal -> IO ()
60 writeMessage :: a -> (Text, MessageType, Int32) -> IO () -> IO ()
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000061
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090062class Protocol a => StatelessProtocol a where
63 serializeVal :: a -> ThriftVal -> LBS.ByteString
64 deserializeVal :: a -> ThriftType -> LBS.ByteString -> ThriftVal
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000065
66data ProtocolExnType
67 = PE_UNKNOWN
68 | PE_INVALID_DATA
69 | PE_NEGATIVE_SIZE
70 | PE_SIZE_LIMIT
71 | PE_BAD_VERSION
Jens Geyer6d1a83a2014-05-03 00:49:05 +020072 | PE_NOT_IMPLEMENTED
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070073 | PE_MISSING_REQUIRED_FIELD
Bryan Duxbury0781f2b2009-04-07 23:29:42 +000074 deriving ( Eq, Show, Typeable )
75
76data ProtocolExn = ProtocolExn ProtocolExnType String
77 deriving ( Show, Typeable )
78instance Exception ProtocolExn
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070079
80getTypeOf :: ThriftVal -> ThriftType
81getTypeOf v = case v of
82 TStruct{} -> T_STRUCT Map.empty
83 TMap{} -> T_MAP T_VOID T_VOID
84 TList{} -> T_LIST T_VOID
85 TSet{} -> T_SET T_VOID
86 TBool{} -> T_BOOL
87 TByte{} -> T_BYTE
88 TI16{} -> T_I16
89 TI32{} -> T_I32
90 TI64{} -> T_I64
91 TString{} -> T_STRING
Nobuaki Sukegawae68ccc22015-12-13 21:45:39 +090092 TBinary{} -> T_BINARY
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070093 TDouble{} -> T_DOUBLE
94
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090095runParser :: (Protocol p, Show a) => p -> Parser a -> IO a
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070096runParser prot p = refill >>= getResult . parse p
97 where
Nobuaki Sukegawa3c420072016-01-24 04:01:27 +090098 refill = handle handleEOF $ LBS.toStrict <$> readByte prot
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -070099 getResult (Done _ a) = return a
100 getResult (Partial k) = refill >>= getResult . k
101 getResult f = throw $ ProtocolExn PE_INVALID_DATA (show f)
102
103handleEOF :: SomeException -> IO BS.ByteString
104handleEOF = const $ return mempty
105
106-- | Converts a ByteString to a Floating point number
107-- The ByteString is assumed to be encoded in network order (Big Endian)
108-- therefore the behavior of this function varies based on whether the local
109-- machine is big endian or little endian.
110bsToDouble :: BS.ByteString -> Double
Nobuaki Sukegawa7c7d6792015-12-09 03:22:35 +0900111bsToDoubleLE :: BS.ByteString -> Double
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700112#if __BYTE_ORDER == __LITTLE_ENDIAN
Nobuaki Sukegawa7c7d6792015-12-09 03:22:35 +0900113bsToDouble bs = unsafeDupablePerformIO $ unsafeUseAsCString bs castBsSwapped
114bsToDoubleLE bs = unsafeDupablePerformIO $ unsafeUseAsCString bs castBs
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700115#else
Nobuaki Sukegawa7c7d6792015-12-09 03:22:35 +0900116bsToDouble bs = unsafeDupablePerformIO $ unsafeUseAsCString bs castBs
117bsToDoubleLE bs = unsafeDupablePerformIO $ unsafeUseAsCString bs castBsSwapped
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700118#endif
119
Nobuaki Sukegawa7c7d6792015-12-09 03:22:35 +0900120
121castBsSwapped chrPtr = do
122 w <- peek (castPtr chrPtr)
123 poke (castPtr chrPtr) (byteSwap w)
124 peek (castPtr chrPtr)
125castBs = peek . castPtr
126
Noam Zilbersteinaf5d64a2014-07-31 15:44:13 -0700127-- | Swap endianness of a 64-bit word
128byteSwap :: Word64 -> Word64
129byteSwap w = (w `shiftL` 56 .&. 0xFF00000000000000) .|.
130 (w `shiftL` 40 .&. 0x00FF000000000000) .|.
131 (w `shiftL` 24 .&. 0x0000FF0000000000) .|.
132 (w `shiftL` 8 .&. 0x000000FF00000000) .|.
133 (w `shiftR` 8 .&. 0x00000000FF000000) .|.
134 (w `shiftR` 24 .&. 0x0000000000FF0000) .|.
135 (w `shiftR` 40 .&. 0x000000000000FF00) .|.
136 (w `shiftR` 56 .&. 0x00000000000000FF)