Copyright | (c) Abhinav Gupta 2015 |
---|---|
License | BSD3 |
Maintainer | Abhinav Gupta <mail@abhinavg.net> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Pinch defines machinery to specify how types can be encoded into or decoded from Thrift payloads.
Synopsis
- encode :: Pinchable a => Protocol -> a -> ByteString
- decode :: Pinchable a => Protocol -> ByteString -> Either String a
- decodeWithLeftovers :: Pinchable a => Protocol -> ByteString -> Either String (ByteString, a)
- encodeMessage :: Protocol -> Message -> ByteString
- decodeMessage :: Protocol -> ByteString -> Either String Message
- class IsTType (Tag a) => Pinchable a where
- data Parser a
- runParser :: Parser a -> Either String a
- newtype Field (n :: Nat) a = Field a
- getField :: Field n a -> a
- putField :: a -> Field n a
- field :: Functor f => (a -> f b) -> Field n a -> f (Field n b)
- data Void = Void
- data Enumeration (n :: Nat) = Enumeration
- enum :: Enumeration n
- (.=) :: Pinchable a => Int16 -> a -> FieldPair
- (?=) :: Pinchable a => Int16 -> Maybe a -> FieldPair
- struct :: [FieldPair] -> Value TStruct
- union :: Pinchable a => Int16 -> a -> Value TUnion
- type FieldPair = (Int16, Maybe SomeValue)
- (.:) :: forall a. Pinchable a => Value TStruct -> Int16 -> Parser a
- (.:?) :: forall a. Pinchable a => Value TStruct -> Int16 -> Parser (Maybe a)
- data Value a
- data SomeValue where
- data Message
- mkMessage :: (Pinchable a, Tag a ~ TStruct) => Text -> MessageType -> Int32 -> a -> Message
- messageName :: Message -> Text
- messageType :: Message -> MessageType
- messageId :: Message -> Int32
- getMessageBody :: (Pinchable a, Tag a ~ TStruct) => Message -> Either String a
- data MessageType
- data Protocol
- binaryProtocol :: Protocol
- compactProtocol :: Protocol
- data TType a
- class Typeable a => IsTType a where
- data TBool
- data TByte
- data TDouble
- type TEnum = TInt32
- data TInt16
- data TInt32
- data TInt64
- data TBinary
- data TStruct
- type TUnion = TStruct
- type TException = TStruct
- data TMap
- data TSet
- data TList
Serializing and deserializing
Types that can be serialized and deserialized into/from Thrift values
implement the Pinchable
typeclass. Instances may be derived automatically
using generics, or written out by hand.
The Pinchable
typeclass converts objects into and from Value
objects,
which act as a direct mapping to the Thrift wire representation. A
Protocol
is responsible for converting Value
objects to and from
bytestrings.
The encode
and decode
methods may be used on objects that implement the
Pinchable
typeclass to get the wire representation directly.
+------------+ Pinchable Protocol +------------+ | | +------------+ | | | +----pinch------> +---serialize---> | | Your Type | | Value a | | ByteString | | <---unpinch-----+ <--deserialize--+ | | | +------------+ | | | | | | | +-------------------encode-------------------> | | | | | | <-------------------decode-------------------+ | +------------+ +------------+
decodeWithLeftovers :: Pinchable a => Protocol -> ByteString -> Either String (ByteString, a) Source #
RPC
Thrift requests implicitly form a struct and responses implicitly form a
union. To send/receive the request/response, it must be wrapped inside a
Message
. The Message
contains information like the method name, the
message ID (to match out of order responses with requests), and whether
it contains a request or a response.
Requests and responses may be wrapped into Message
objects using the
mkMessage
function. The message body can be retrieved back using the
getMessageBody
function. The encodeMessage
and decodeMessage
functions may be used to encode and decode messages into/from bytestrings.
Consider the service method,
User getUser(1: string userName, 2: list<Attribute> attributes) throws (1: UserDoesNotExist doesNotExist, 2: InternalError internalError)
The request and response for this method implictly take the form:
struct getUserRequest { 1: string userName 2: list<Attribute> attributes }
union getUserResponse { 0: User success 1: UserDoesNotExist doesNotExist 2: InternalError InternalError }
(Note that the field ID 0 is reserved for the return value of the method.)
Given corresponding data types GetUserRequest
and GetUserResponse
, the
client can do something similar to,
let req = GetUserRequest "jsmith" [] msg =mkMessage
"getUser"Call
0 req response <- sendToServer (encodeMessage
msg) casedecodeMessage
response of Left err -> handleError err Right msg -> casegetMessageBody
msg of Left err -> handleError err Right (res :: GetUserResponse) -> handleResponse res
Similarly, on the server side,
case decodeMessage request of Left err -> handleError err Right msg -> casemessageName
msg of "getUser" -> case getMessageBody msg of Left err -> handleError err Right (req :: GetUserRequest) -> do let mid =messageId
msg res <- handleGetUser req return (mkMessage "getUser"Reply
mid res) -- Note that the response MUST contain the same -- message ID as its request. _ -> handleUnknownMethod
encodeMessage :: Protocol -> Message -> ByteString Source #
decodeMessage :: Protocol -> ByteString -> Either String Message Source #
Pinchable
class IsTType (Tag a) => Pinchable a where Source #
The Pinchable type class is implemented by types that can be sent or received over the wire as Thrift payloads.
Nothing
TType
tag for this type.
For most custom types, this will be TStruct
, TUnion
, or
TException
. For enums, it will be TEnum
. If the instance
automatically derived with use of Generic
, this is not required
because it is automatically determined by use of Field
or
Enumeration
.
pinch :: a -> Value (Tag a) Source #
Convert an a
into a Value
.
For structs, struct
, .=
, and ?=
may be used to construct
Value
objects tagged with TStruct
.
Instances
A simple continuation-based parser.
This is just Either e a
in continuation-passing style.
runParser :: Parser a -> Either String a Source #
Run a Parser
and return the result inside an Either
.
Automatically deriving instances
Pinch supports deriving instances of Pinchable
automatically for
types that implement the Generic
typeclass provided that they follow
the outlined patterns in their constructors.
Structs and exceptions
Given the struct,
struct User { 1: required string name 2: optional string emailAddress }
A Pinchable
instance for it can be automatically derived by wrapping
fields of the data type with the Field
type and specifying the field
identifier as a type-level numeral. Fields which hold a Maybe
value are
considered optional.
data User = User
{ userName :: Field
1 Text
, userEmailAddress :: Field 2 (Maybe Text)
}
deriving (Generic)
instance Pinchable User
The DeriveGeneric
extension is required to automatically derive instances
of the Generic
typeclass and the DataKinds
extension is required to use
type-level numerals.
Unions
As with structs and exceptions, fields of the data type representing a
union must be tagged with Field
, but to satisfy the property of a union
that only one value is set at a time, they must be on separate
constructors.
For example, given the union,
union Item { 1: binary bin 2: string str 3: i32 int }
A Pinchable
instance can be derived like so,
data Item = ItemBin (Field 1 ByteString) | ItemStr (Field 2 Text) | ItemInt (Field 3 Int32) deriving (Generic) instance Pinchable Item
The DeriveGeneric
extension is required to automatically derive instances
of the Generic
typeclass and the DataKinds
extension is required to use
type-level numerals.
If the union represents the response of a service method which returns a
void
result, the type Void
may be used.
data GetFooResponse
= GetFooDoesNotExist (Field 1 FooDoesNotExist)
| GetFooInternalError (Field 2 InternalError)
| GetFooSuccess Void
newtype Field (n :: Nat) a Source #
Fields of data types that represent structs, unions, and exceptions
should be wrapped inside Field
and tagged with the field identifier.
data Foo = Foo (Field 1 Text) (Field 2 (Maybe Int32)) deriving Generic instance Pinchable Foo
data A = A (Field 1 Int32) | B (Field 2 Text) deriving Generic instance Pinchable Foo
Fields which hold Maybe
values are treated as optional. All fields values
must be Pinchable
to automatically derive a Pinchable
instance for the
new data type.
Field a |
Instances
Foldable (Field n) Source # | |
Defined in Pinch.Internal.Generic fold :: Monoid m => Field n m -> m # foldMap :: Monoid m => (a -> m) -> Field n a -> m # foldMap' :: Monoid m => (a -> m) -> Field n a -> m # foldr :: (a -> b -> b) -> b -> Field n a -> b # foldr' :: (a -> b -> b) -> b -> Field n a -> b # foldl :: (b -> a -> b) -> b -> Field n a -> b # foldl' :: (b -> a -> b) -> b -> Field n a -> b # foldr1 :: (a -> a -> a) -> Field n a -> a # foldl1 :: (a -> a -> a) -> Field n a -> a # elem :: Eq a => a -> Field n a -> Bool # maximum :: Ord a => Field n a -> a # minimum :: Ord a => Field n a -> a # | |
Traversable (Field n) Source # | |
Functor (Field n) Source # | |
Monoid a => Monoid (Field n a) Source # | |
Semigroup a => Semigroup (Field n a) Source # | |
Bounded a => Bounded (Field n a) Source # | |
Enum a => Enum (Field n a) Source # | |
Defined in Pinch.Internal.Generic succ :: Field n a -> Field n a # pred :: Field n a -> Field n a # fromEnum :: Field n a -> Int # enumFrom :: Field n a -> [Field n a] # enumFromThen :: Field n a -> Field n a -> [Field n a] # enumFromTo :: Field n a -> Field n a -> [Field n a] # enumFromThenTo :: Field n a -> Field n a -> Field n a -> [Field n a] # | |
Generic (Field n a) Source # | |
Show a => Show (Field n a) Source # | |
NFData a => NFData (Field n a) Source # | |
Defined in Pinch.Internal.Generic | |
Eq a => Eq (Field n a) Source # | |
Ord a => Ord (Field n a) Source # | |
Defined in Pinch.Internal.Generic | |
(Pinchable a, KnownNat n) => GPinchable (K1 i (Field n (Maybe a)) :: Type -> Type) Source # | |
(Pinchable a, KnownNat n) => GPinchable (K1 i (Field n a) :: Type -> Type) Source # | |
type Rep (Field n a) Source # | |
Defined in Pinch.Internal.Generic | |
type GTag (K1 i (Field n (Maybe a)) :: Type -> Type) Source # | |
type GTag (K1 i (Field n a) :: Type -> Type) Source # | |
getField :: Field n a -> a Source #
Gets the current value of a field.
let Foo a' _ = {- ... -} a = getField a'
putField :: a -> Field n a Source #
Puts a value inside a field.
Foo (putField "Hello") (putField (Just 42))
field :: Functor f => (a -> f b) -> Field n a -> f (Field n b) Source #
A lens on Field
wrappers for use with the lens library.
person & name . field .~ "new value"
Represents a void
result for methods.
This should be used as an element in a response union along with Field
tags.
For a method,
void setValue(..) throws (1: ValueAlreadyExists alreadyExists, 2: InternalError internalError)
Something similar to the following can be used.
data SetValueResponse = SetValueAlreadyExists (Field 1 ValueAlreadyExists) | SetValueInternalError (Field 2 InternalError) | SetValueSuccess Void deriving (Generic) instance Pinchable SetValueResponse
Enums
Given the enum,
enum Op { Add, Sub, Mul, Div }
A Pinchable
instance can be derived for it by creating one constructor
for each of the enum values and providing it a single Enumeration
argument tagged with the enum value.
data Op
= OpAdd (Enumeration
0)
| OpSub (Enumeration 1)
| OpMul (Enumeration 2)
| OpDiv (Enumeration 3)
deriving (Generic)
instance Pinchable Op
Note that you need to know the values assigned to the enums. If not specified, Thrift automatically assigns incrementing values to the items in the order they appear starting at 0.
The DeriveGeneric
extension is required to automatically derive instances
of the Generic
typeclass and the DataKinds
extension is required to use
type-level numerals.
data Enumeration (n :: Nat) Source #
Data types that represent Thrift enums must have one constructor for each
enum item accepting an Enumeration
object tagged with the corresponding
enum value.
data Role = RoleUser (Enumeration 1) | RoleAdmin (Enumeration 2) deriving Generic instance Pinchable Role
Instances
enum :: Enumeration n Source #
Convenience function to construct Enumeration
objects.
let role = RoleUser enum
Manually writing instances
Instances of Pinchable
can be constructed by composing together
existing instances and using the .=
, .:
, etc. helpers.
Structs and exceptions
Given a Thrift struct,
struct Post { 1: optional string subject 2: required string body }
The Pinchable
instance for it will be,
data Post = Post { postSubject :: Maybe Text , postBody :: Text } instancePinchable
Post where typeTag
Post =TStruct
pinch (Post subject body) =struct
[ 1?=
subject , 2.=
body ] unpinch value = Post <$> value.:?
1 <*> value.:
2
Unions
Given a Thrift union,
union PostBody { 1: string markdown 2: binary rtf }
The Pinchable
instance for it will be,
data PostBody = PostBodyMarkdown Text | PostBodyRtf ByteString instance Pinchable PostBody where type Tag PostBody =TUnion
pinch (PostBodyMarkdown markdownBody) =union
1 markdownBody pinch (PostBodyRtf rtfBody) = union 2 rtfBody unpinch v = PostBodyMarkdown <$> v .: 1 <|> PostBodyRtf <$> v .: 2
Enums
Given an enum,
enum Role { DISABLED = 0, USER, ADMIN, }
The Pinchable
instance for it will be,
data Role = RoleDisabled | RoleUser | RoleAdmin instance Pinchable Role where type Tag Role = TEnum pinch RoleDisabled = pinch (0 :: Int32) pinch RoleUser = pinch (1 :: Int32) pinch RoleAdmin = pinch (2 :: Int32) unpinch v = do value <- unpinch v case (value :: Int32) of 0 -> Right RoleDisabled 1 -> Right RoleUser 2 -> Right RoleAdmin _ -> Left $ "Unknown role: " ++ show value
Helpers
pinch
type FieldPair = (Int16, Maybe SomeValue) Source #
A pair of field identifier and maybe a value stored in the field. If the value is absent, the field will be ignored.
unpinch
(.:) :: forall a. Pinchable a => Value TStruct -> Int16 -> Parser a Source #
Given a field ID and a Value TStruct
, get the value stored in the
struct under that field ID. The lookup fails if the field is absent or if
it's not the same type as expected by this call's context.
(.:?) :: forall a. Pinchable a => Value TStruct -> Int16 -> Parser (Maybe a) Source #
Given a field ID and a Value TStruct
, get the optional value stored in
the struct under the given field ID. The value returned is Nothing
if it
was absent or the wrong type. The lookup fails only if the value retrieved
fails to unpinch
.
Value
Value
is an intermediate representation of Thrift payloads tagged
with TType tags. Types that want to be serialized into/deserialized
from Thrift payloads need only define a way to convert themselves to
and from Value
objects via Pinchable
.
Value
maps directly to serialized representation of Thrift types. It
contains about as much information as what gets sent over the wire.
Value
objects are tagged with different TType
values to indicate the
type of the value.
Typical usage will not involve accessing the constructors for this type.
Pinchable
must be used to construct Value
objects or
convert them back to original types.
SomeValue
holds any value, regardless of type. This may be used when
the type of the value is not necessarily known at compile time. Typically,
this will be pattern matched on and code that depends on the value's
TType
will go inside the scope of the match.
Messages
Message envelope for Thrift payloads.
Instances
Generic Message Source # | |
Show Message Source # | |
NFData Message Source # | |
Defined in Pinch.Internal.Message | |
Eq Message Source # | |
type Rep Message Source # | |
Defined in Pinch.Internal.Message type Rep Message = D1 ('MetaData "Message" "Pinch.Internal.Message" "pinch-0.4.3.0-IP3NIMX7ovVBCBsW5ZUwO6" 'False) (C1 ('MetaCons "Message" 'PrefixI 'True) ((S1 ('MetaSel ('Just "messageName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "messageType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MessageType)) :*: (S1 ('MetaSel ('Just "messageId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int32) :*: S1 ('MetaSel ('Just "messagePayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Value TStruct))))) |
:: (Pinchable a, Tag a ~ TStruct) | |
=> Text | Name of the target method. |
-> MessageType | Type of the message. |
-> Int32 | Message ID. |
-> a | Message payload. This must be an object which serializes into a struct. |
-> Message |
Build a Message
.
messageName :: Message -> Text Source #
Name of the method to which this message is targeted.
messageType :: Message -> MessageType Source #
Type of the message.
messageId :: Message -> Int32 Source #
Sequence ID of the message.
If the clients expect to receive out-of-order responses, they may use the message ID to map responses back to their corresponding requests. If the client does not expect out-of-order responses, they are free to use the same message ID for all messages.
The server's contract regarding message IDs is that all responses must have the same message ID as their corresponding requests.
getMessageBody :: (Pinchable a, Tag a ~ TStruct) => Message -> Either String a Source #
Read the message contents.
This returns a Left
result if the message contents do not match the
requested type.
data MessageType Source #
Type of message being sent.
Call | A call to a specific method. The message body is the request arguments struct. |
Reply | Response to a call. The message body is the response union. |
Exception | Failure to make a call. Note: This message type is not used for exceptions that are defined
under the |
Oneway | One-way call that expects no response. |
Instances
Protocols
binaryProtocol :: Protocol Source #
Provides an implementation of the Thrift Binary Protocol.
compactProtocol :: Protocol Source #
Provides an implementation of the Thrift Compact Protocol.
TType
TType is used to refer to the Thrift protocol-level type of a value.
Represents the type of a Thrift value.
Objects of this type are tagged with one of the TType tags, so this type also acts as a singleton on the TTypes. It allows writing code that can enforce properties about the TType of values at compile time.
class Typeable a => IsTType a where Source #
Typeclass used to map type-leve TTypes into TType
objects. All TType
tags are instances of this class.
Based on the context in which this is used, it will automatically
return the corresponding TType
object.
Tags
TType tags allow writing code that depends on knowing the TType
of
values, or asserting conditions on it, at compile time.
For example, values in a map, list, or set must all have the same TType.
This is enforced at the type level by parameterizing Value
over these
tags.
bool
byte
double
i16
i32
i64
binary
struct
type TException = TStruct Source #
exception
map<k, v>
set<x>