{-# LANGUAGE ExistentialQuantification  #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies               #-}
module Pinch.Internal.RPC
  ( Channel(..)
  , createChannel
  , createChannel1
  , readMessage
  , writeMessage
  , ReadResult(..)
  , ServiceName(..)
  , ThriftResult(..)
  , Unit(..)
  ) where
import           Data.Hashable            (Hashable (..))
import           Data.String              (IsString (..))
import           Data.Typeable            (Typeable)
import qualified Data.HashMap.Strict      as HM
import qualified Data.Text                as T
import           Pinch.Internal.Message
import           Pinch.Internal.Pinchable (Pinchable (..), Tag)
import           Pinch.Internal.TType     (TStruct)
import           Pinch.Internal.Value     (Value (..))
import           Pinch.Protocol           (Protocol, deserializeMessage',
                                           serializeMessage)
import           Pinch.Transport          (Connection, ReadResult (..),
                                           Transport)
import qualified Pinch.Transport          as Transport
data Channel = Channel
  { Channel -> Transport
cTransportIn  :: !Transport
  , Channel -> Transport
cTransportOut :: !Transport
  , Channel -> Protocol
cProtocolIn   :: !Protocol
  , Channel -> Protocol
cProtocolOut  :: !Protocol
  }
createChannel :: Connection c => c -> (c -> IO Transport) -> Protocol -> IO Channel
createChannel :: forall c.
Connection c =>
c -> (c -> IO Transport) -> Protocol -> IO Channel
createChannel c
c c -> IO Transport
t Protocol
p = do
  Transport
t' <- c -> IO Transport
t c
c
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Transport -> Transport -> Protocol -> Protocol -> Channel
Channel Transport
t' Transport
t' Protocol
p Protocol
p
createChannel1 :: (Transport, Protocol) -> (Transport, Protocol) -> Channel
createChannel1 :: (Transport, Protocol) -> (Transport, Protocol) -> Channel
createChannel1 (Transport
tIn, Protocol
pIn) (Transport
tOut, Protocol
pOut) = Transport -> Transport -> Protocol -> Protocol -> Channel
Channel Transport
tIn Transport
tOut Protocol
pIn Protocol
pOut
readMessage :: Channel -> IO (ReadResult Message)
readMessage :: Channel -> IO (ReadResult Message)
readMessage Channel
chan = Transport -> forall a. Get a -> IO (ReadResult a)
Transport.readMessage (Channel -> Transport
cTransportIn Channel
chan) forall a b. (a -> b) -> a -> b
$ Protocol -> Get Message
deserializeMessage' (Channel -> Protocol
cProtocolIn Channel
chan)
writeMessage :: Channel -> Message -> IO ()
writeMessage :: Channel -> Message -> IO ()
writeMessage Channel
chan Message
msg = Transport -> Builder -> IO ()
Transport.writeMessage (Channel -> Transport
cTransportOut Channel
chan) forall a b. (a -> b) -> a -> b
$ Protocol -> Message -> Builder
serializeMessage (Channel -> Protocol
cProtocolOut Channel
chan) Message
msg
newtype ServiceName = ServiceName T.Text
  deriving (Typeable, ServiceName -> ServiceName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ServiceName -> ServiceName -> Bool
$c/= :: ServiceName -> ServiceName -> Bool
== :: ServiceName -> ServiceName -> Bool
$c== :: ServiceName -> ServiceName -> Bool
Eq, Eq ServiceName
Int -> ServiceName -> Int
ServiceName -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ServiceName -> Int
$chash :: ServiceName -> Int
hashWithSalt :: Int -> ServiceName -> Int
$chashWithSalt :: Int -> ServiceName -> Int
Hashable)
instance IsString ServiceName where
  fromString :: String -> ServiceName
fromString = Text -> ServiceName
ServiceName forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
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
instance Pinchable Unit where
  type Tag Unit = TStruct
  pinch :: Unit -> Value (Tag Unit)
pinch Unit
Unit = HashMap Int16 SomeValue -> Value TStruct
VStruct forall a. Monoid a => a
mempty
  unpinch :: Value (Tag Unit) -> Parser Unit
unpinch (VStruct HashMap Int16 SomeValue
xs) | forall k v. HashMap k v -> Bool
HM.null HashMap Int16 SomeValue
xs = forall (f :: * -> *) a. Applicative f => a -> f a
pure Unit
Unit
  unpinch Value (Tag Unit)
x            = forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Failed to read void success. Got " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Value (Tag Unit)
x
instance ThriftResult Unit where
  type ResultType Unit = ()
  wrap :: IO (ResultType Unit) -> IO Unit
wrap IO (ResultType Unit)
m = Unit
Unit forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ IO (ResultType Unit)
m
  unwrap :: Unit -> IO (ResultType Unit)
unwrap Unit
Unit = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()