pinch-0.3.4.0: An alternative implementation of Thrift for Haskell.

Copyright(c) Abhinav Gupta 2015
LicenseBSD3
MaintainerAbhinav Gupta <mail@abhinavg.net>
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Pinch.Internal.Message

Description

Message wrapper for Thrift payloads. Normal Thrift requests sent over the wire are wrapped inside a message envelope that contains information about the method being called, the type of message, etc. This information is essential for the RPC system to function.

Synopsis

Documentation

data Message Source #

Message envelope for Thrift payloads.

Constructors

Message 

Fields

  • messageName :: !Text

    Name of the method to which this message is targeted.

  • messageType :: !MessageType

    Type of the message.

  • messageId :: !Int32

    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.

  • messagePayload :: !(Value TStruct)

    Contents of the message.

Instances
Eq Message Source # 
Instance details

Defined in Pinch.Internal.Message

Methods

(==) :: Message -> Message -> Bool #

(/=) :: Message -> Message -> Bool #

Show Message Source # 
Instance details

Defined in Pinch.Internal.Message

Generic Message Source # 
Instance details

Defined in Pinch.Internal.Message

Associated Types

type Rep Message :: Type -> Type #

Methods

from :: Message -> Rep Message x #

to :: Rep Message x -> Message #

NFData Message Source # 
Instance details

Defined in Pinch.Internal.Message

Methods

rnf :: Message -> () #

type Rep Message Source # 
Instance details

Defined in Pinch.Internal.Message

type Rep Message = D1 (MetaData "Message" "Pinch.Internal.Message" "pinch-0.3.4.0-GalnCJLNzvkYRSpnIPXol" 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)))))

data MessageType Source #

Type of message being sent.

Constructors

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 throws clause of a method. Those exceptions are part of the response union of the method and are received in a Reply. This message type is used for Thrift-level failures.

Oneway

One-way call that expects no response.

Instances
Eq MessageType Source # 
Instance details

Defined in Pinch.Internal.Message

Data MessageType Source # 
Instance details

Defined in Pinch.Internal.Message

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageType -> c MessageType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageType #

toConstr :: MessageType -> Constr #

dataTypeOf :: MessageType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MessageType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageType) #

gmapT :: (forall b. Data b => b -> b) -> MessageType -> MessageType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageType -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageType -> m MessageType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageType -> m MessageType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageType -> m MessageType #

Show MessageType Source # 
Instance details

Defined in Pinch.Internal.Message

Generic MessageType Source # 
Instance details

Defined in Pinch.Internal.Message

Associated Types

type Rep MessageType :: Type -> Type #

NFData MessageType Source # 
Instance details

Defined in Pinch.Internal.Message

Methods

rnf :: MessageType -> () #

type Rep MessageType Source # 
Instance details

Defined in Pinch.Internal.Message

type Rep MessageType = D1 (MetaData "MessageType" "Pinch.Internal.Message" "pinch-0.3.4.0-GalnCJLNzvkYRSpnIPXol" False) ((C1 (MetaCons "Call" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Reply" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Exception" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Oneway" PrefixI False) (U1 :: Type -> Type)))