Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 1 | {-# LANGUAGE CPP #-} |
Bryan Duxbury | e59a80f | 2010-09-20 15:21:37 +0000 | [diff] [blame] | 2 | {-# LANGUAGE DeriveDataTypeable #-} |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 3 | {-# LANGUAGE OverloadedStrings #-} |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 4 | -- |
| 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 | |
| 23 | module Thrift.Protocol |
| 24 | ( Protocol(..) |
Nobuaki Sukegawa | 3c42007 | 2016-01-24 04:01:27 +0900 | [diff] [blame] | 25 | , StatelessProtocol(..) |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 26 | , ProtocolExn(..) |
| 27 | , ProtocolExnType(..) |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 28 | , getTypeOf |
| 29 | , runParser |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 30 | , bsToDouble |
Nobuaki Sukegawa | 7c7d679 | 2015-12-09 03:22:35 +0900 | [diff] [blame] | 31 | , bsToDoubleLE |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 32 | ) where |
| 33 | |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 34 | import Control.Exception |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 35 | import Data.Attoparsec.ByteString |
| 36 | import Data.Bits |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 37 | import Data.ByteString.Unsafe |
| 38 | import Data.Functor ((<$>)) |
Roger Meier | 6849f20 | 2012-05-18 07:35:19 +0000 | [diff] [blame] | 39 | import Data.Int |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 40 | import Data.Monoid (mempty) |
| 41 | import Data.Text.Lazy (Text) |
| 42 | import Data.Typeable (Typeable) |
| 43 | import Data.Word |
| 44 | import Foreign.Ptr (castPtr) |
Nobuaki Sukegawa | 3c42007 | 2016-01-24 04:01:27 +0900 | [diff] [blame] | 45 | import Foreign.Storable (peek, poke) |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 46 | import System.IO.Unsafe |
| 47 | import qualified Data.ByteString as BS |
| 48 | import qualified Data.HashMap.Strict as Map |
Nobuaki Sukegawa | 3c42007 | 2016-01-24 04:01:27 +0900 | [diff] [blame] | 49 | import qualified Data.ByteString.Lazy as LBS |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 50 | |
| 51 | import Thrift.Transport |
Nobuaki Sukegawa | 3c42007 | 2016-01-24 04:01:27 +0900 | [diff] [blame] | 52 | import Thrift.Types |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 53 | |
| 54 | class Protocol a where |
Nobuaki Sukegawa | 3c42007 | 2016-01-24 04:01:27 +0900 | [diff] [blame] | 55 | readByte :: a -> IO LBS.ByteString |
| 56 | readVal :: a -> ThriftType -> IO ThriftVal |
| 57 | readMessage :: a -> ((Text, MessageType, Int32) -> IO b) -> IO b |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 58 | |
Nobuaki Sukegawa | 3c42007 | 2016-01-24 04:01:27 +0900 | [diff] [blame] | 59 | writeVal :: a -> ThriftVal -> IO () |
| 60 | writeMessage :: a -> (Text, MessageType, Int32) -> IO () -> IO () |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 61 | |
Nobuaki Sukegawa | 3c42007 | 2016-01-24 04:01:27 +0900 | [diff] [blame] | 62 | class Protocol a => StatelessProtocol a where |
| 63 | serializeVal :: a -> ThriftVal -> LBS.ByteString |
| 64 | deserializeVal :: a -> ThriftType -> LBS.ByteString -> ThriftVal |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 65 | |
| 66 | data ProtocolExnType |
| 67 | = PE_UNKNOWN |
| 68 | | PE_INVALID_DATA |
| 69 | | PE_NEGATIVE_SIZE |
| 70 | | PE_SIZE_LIMIT |
| 71 | | PE_BAD_VERSION |
Jens Geyer | 6d1a83a | 2014-05-03 00:49:05 +0200 | [diff] [blame] | 72 | | PE_NOT_IMPLEMENTED |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 73 | | PE_MISSING_REQUIRED_FIELD |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 74 | deriving ( Eq, Show, Typeable ) |
| 75 | |
| 76 | data ProtocolExn = ProtocolExn ProtocolExnType String |
| 77 | deriving ( Show, Typeable ) |
| 78 | instance Exception ProtocolExn |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 79 | |
| 80 | getTypeOf :: ThriftVal -> ThriftType |
| 81 | getTypeOf 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 Sukegawa | e68ccc2 | 2015-12-13 21:45:39 +0900 | [diff] [blame] | 92 | TBinary{} -> T_BINARY |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 93 | TDouble{} -> T_DOUBLE |
| 94 | |
Nobuaki Sukegawa | 3c42007 | 2016-01-24 04:01:27 +0900 | [diff] [blame] | 95 | runParser :: (Protocol p, Show a) => p -> Parser a -> IO a |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 96 | runParser prot p = refill >>= getResult . parse p |
| 97 | where |
Nobuaki Sukegawa | 3c42007 | 2016-01-24 04:01:27 +0900 | [diff] [blame] | 98 | refill = handle handleEOF $ LBS.toStrict <$> readByte prot |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 99 | getResult (Done _ a) = return a |
| 100 | getResult (Partial k) = refill >>= getResult . k |
| 101 | getResult f = throw $ ProtocolExn PE_INVALID_DATA (show f) |
| 102 | |
| 103 | handleEOF :: SomeException -> IO BS.ByteString |
| 104 | handleEOF = 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. |
| 110 | bsToDouble :: BS.ByteString -> Double |
Nobuaki Sukegawa | 7c7d679 | 2015-12-09 03:22:35 +0900 | [diff] [blame] | 111 | bsToDoubleLE :: BS.ByteString -> Double |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 112 | #if __BYTE_ORDER == __LITTLE_ENDIAN |
Nobuaki Sukegawa | 7c7d679 | 2015-12-09 03:22:35 +0900 | [diff] [blame] | 113 | bsToDouble bs = unsafeDupablePerformIO $ unsafeUseAsCString bs castBsSwapped |
| 114 | bsToDoubleLE bs = unsafeDupablePerformIO $ unsafeUseAsCString bs castBs |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 115 | #else |
Nobuaki Sukegawa | 7c7d679 | 2015-12-09 03:22:35 +0900 | [diff] [blame] | 116 | bsToDouble bs = unsafeDupablePerformIO $ unsafeUseAsCString bs castBs |
| 117 | bsToDoubleLE bs = unsafeDupablePerformIO $ unsafeUseAsCString bs castBsSwapped |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 118 | #endif |
| 119 | |
Nobuaki Sukegawa | 7c7d679 | 2015-12-09 03:22:35 +0900 | [diff] [blame] | 120 | |
| 121 | castBsSwapped chrPtr = do |
| 122 | w <- peek (castPtr chrPtr) |
| 123 | poke (castPtr chrPtr) (byteSwap w) |
| 124 | peek (castPtr chrPtr) |
| 125 | castBs = peek . castPtr |
| 126 | |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 127 | -- | Swap endianness of a 64-bit word |
| 128 | byteSwap :: Word64 -> Word64 |
| 129 | byteSwap 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) |