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(..) |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 25 | , ProtocolExn(..) |
| 26 | , ProtocolExnType(..) |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 27 | , getTypeOf |
| 28 | , runParser |
| 29 | , versionMask |
| 30 | , version1 |
| 31 | , bsToDouble |
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 |
| 37 | import Data.ByteString.Lazy (ByteString, toStrict) |
| 38 | import Data.ByteString.Unsafe |
| 39 | import Data.Functor ((<$>)) |
Roger Meier | 6849f20 | 2012-05-18 07:35:19 +0000 | [diff] [blame] | 40 | import Data.Int |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 41 | import Data.Monoid (mempty) |
| 42 | import Data.Text.Lazy (Text) |
| 43 | import Data.Typeable (Typeable) |
| 44 | import Data.Word |
| 45 | import Foreign.Ptr (castPtr) |
| 46 | import Foreign.Storable (Storable, peek, poke) |
| 47 | import System.IO.Unsafe |
| 48 | import qualified Data.ByteString as BS |
| 49 | import qualified Data.HashMap.Strict as Map |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 50 | |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 51 | import Thrift.Types |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 52 | import Thrift.Transport |
| 53 | |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 54 | versionMask :: Int32 |
| 55 | versionMask = fromIntegral (0xffff0000 :: Word32) |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 56 | |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 57 | version1 :: Int32 |
| 58 | version1 = fromIntegral (0x80010000 :: Word32) |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 59 | |
| 60 | class Protocol a where |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 61 | getTransport :: Transport t => a t -> t |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 62 | |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 63 | 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 Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 70 | |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 71 | serializeVal :: Transport t => a t -> ThriftVal -> ByteString |
| 72 | deserializeVal :: Transport t => a t -> ThriftType -> ByteString -> ThriftVal |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 73 | |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 74 | 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 Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 77 | |
| 78 | data ProtocolExnType |
| 79 | = PE_UNKNOWN |
| 80 | | PE_INVALID_DATA |
| 81 | | PE_NEGATIVE_SIZE |
| 82 | | PE_SIZE_LIMIT |
| 83 | | PE_BAD_VERSION |
Jens Geyer | 6d1a83a | 2014-05-03 00:49:05 +0200 | [diff] [blame] | 84 | | PE_NOT_IMPLEMENTED |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 85 | | PE_MISSING_REQUIRED_FIELD |
Bryan Duxbury | 0781f2b | 2009-04-07 23:29:42 +0000 | [diff] [blame] | 86 | deriving ( Eq, Show, Typeable ) |
| 87 | |
| 88 | data ProtocolExn = ProtocolExn ProtocolExnType String |
| 89 | deriving ( Show, Typeable ) |
| 90 | instance Exception ProtocolExn |
Noam Zilberstein | af5d64a | 2014-07-31 15:44:13 -0700 | [diff] [blame] | 91 | |
| 92 | getTypeOf :: ThriftVal -> ThriftType |
| 93 | getTypeOf 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 | |
| 106 | runParser :: (Protocol p, Transport t, Show a) => p t -> Parser a -> IO a |
| 107 | runParser 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 | |
| 114 | handleEOF :: SomeException -> IO BS.ByteString |
| 115 | handleEOF = 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. |
| 121 | bsToDouble :: BS.ByteString -> Double |
| 122 | bsToDouble 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 |
| 135 | byteSwap :: Word64 -> Word64 |
| 136 | byteSwap 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 |