Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Channel = Channel {}
- createChannel :: Connection c => c -> (c -> IO Transport) -> Protocol -> IO Channel
- createChannel1 :: (Transport, Protocol) -> (Transport, Protocol) -> Channel
- readMessage :: Channel -> IO (ReadResult Message)
- writeMessage :: Channel -> Message -> IO ()
- data ReadResult a
- newtype ServiceName = ServiceName Text
- class (Pinchable a, Tag a ~ TStruct) => ThriftResult a where
- type ResultType a
- unwrap :: a -> IO (ResultType a)
- wrap :: IO (ResultType a) -> IO a
- data Unit = Unit
Documentation
A bi-directional channel to read/write Thrift messages.
Channel | |
|
createChannel :: Connection c => c -> (c -> IO Transport) -> Protocol -> IO Channel Source #
Creates a channel using the same transport/protocol for both directions.
createChannel1 :: (Transport, Protocol) -> (Transport, Protocol) -> Channel Source #
Creates a channel.
readMessage :: Channel -> IO (ReadResult Message) Source #
data ReadResult a Source #
Instances
Show a => Show (ReadResult a) Source # | |
Defined in Pinch.Transport showsPrec :: Int -> ReadResult a -> ShowS # show :: ReadResult a -> String # showList :: [ReadResult a] -> ShowS # | |
Eq a => Eq (ReadResult a) Source # | |
Defined in Pinch.Transport (==) :: ReadResult a -> ReadResult a -> Bool # (/=) :: ReadResult a -> ReadResult a -> Bool # |
newtype ServiceName Source #
Instances
IsString ServiceName Source # | |
Defined in Pinch.Internal.RPC fromString :: String -> ServiceName # | |
Eq ServiceName Source # | |
Defined in Pinch.Internal.RPC (==) :: ServiceName -> ServiceName -> Bool # (/=) :: ServiceName -> ServiceName -> Bool # | |
Hashable ServiceName Source # | |
Defined in Pinch.Internal.RPC hashWithSalt :: Int -> ServiceName -> Int # hash :: ServiceName -> Int # | |
ContextItem ServiceName Source # | |
Defined in Pinch.Server |
class (Pinchable a, Tag a ~ TStruct) => ThriftResult a where Source #
The Result datatype for a Thrift Service Method.
type ResultType a Source #
The Haskell type returned when the Thrift call succeeds.
unwrap :: a -> IO (ResultType a) Source #
Tries to extract the result from a Thrift call. If the call threw any
of the Thrift exceptions declared for this Thrift service method,
the corresponding Haskell excpetions is thrown using throwIO
.
wrap :: IO (ResultType a) -> IO a Source #
Runs the given computation. If it throws any of the exceptions declared in the Thrift service definition, it is caught and converted to the corresponding Haskell result datatype constructor.
Instances
ThriftResult Unit Source # | |
Defined in Pinch.Internal.RPC type ResultType Unit Source # |
Result datatype for void methods not throwing any exceptions.
Instances
Pinchable Unit Source # | |
ThriftResult Unit Source # | |
Defined in Pinch.Internal.RPC type ResultType Unit Source # | |
type Tag Unit Source # | |
Defined in Pinch.Internal.RPC | |
type ResultType Unit Source # | |
Defined in Pinch.Internal.RPC |