{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Temporal.Core.Client (
Client,
clientConfig,
connectClient,
defaultClientConfig,
closeClient,
clientRuntime,
touchClient,
CoreClient,
ClientConfig (..),
ClientTlsConfig (..),
ByteVector (..),
ClientRetryConfig (..),
call,
RpcCall (..),
RpcError (..),
ClientError (..),
CRpcCall,
TokioCall,
TokioResult,
PrimRpcCall,
withClient,
) where
import Control.Concurrent
import Control.Exception
import Control.Monad
import Data.Aeson
import Data.Aeson.TH
import Data.ByteString (ByteString)
import qualified Data.ByteString as BL
import qualified Data.ByteString as BS
import qualified Data.ByteString.Internal as BS
import Data.HashMap.Strict (HashMap)
import Data.ProtoLens.Encoding
import Data.ProtoLens.Service.Types
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Vector.Storable as V
import Data.Word
import Foreign.C.String
import Foreign.ForeignPtr
import Foreign.Marshal
import Foreign.Ptr
import Foreign.Storable
import Network.BSD
import System.Posix.Process
import Temporal.Core.CTypes
import Temporal.Internal.FFI
import Temporal.Runtime
foreign import ccall "hs_temporal_connect_client" raw_connectClient :: Ptr Runtime -> CString -> TokioCall (CArray Word8) CoreClient
foreign import ccall "&hs_temporal_drop_client" raw_freeClient :: FinalizerPtr CoreClient
data ClientConfig = ClientConfig
{ ClientConfig -> Text
targetUrl :: Text
, ClientConfig -> Text
clientName :: Text
, ClientConfig -> Text
clientVersion :: Text
, ClientConfig -> HashMap Text Text
metadata :: HashMap Text Text
, ClientConfig -> Text
identity :: Text
, ClientConfig -> Maybe ClientTlsConfig
tlsConfig :: Maybe ClientTlsConfig
, ClientConfig -> Maybe ClientRetryConfig
retryConfig :: Maybe ClientRetryConfig
}
data ClientTlsConfig = ClientTlsConfig
{ ClientTlsConfig -> Maybe ByteVector
serverRootCaCert :: Maybe ByteVector
, ClientTlsConfig -> Maybe Text
domain :: Maybe Text
, ClientTlsConfig -> Maybe ByteVector
clientCert :: Maybe ByteVector
, ClientTlsConfig -> Maybe ByteVector
clientPrivateKey :: Maybe ByteVector
}
data ClientRetryConfig = ClientRetryConfig
{ ClientRetryConfig -> Word64
initialIntervalMillis :: Word64
, ClientRetryConfig -> Double
randomizationFactor :: Double
, ClientRetryConfig -> Double
multiplier :: Double
, ClientRetryConfig -> Word64
maxIntervalMillis :: Word64
, ClientRetryConfig -> Maybe Word64
maxElapsedTimeMillis :: Maybe Word64
, ClientRetryConfig -> Word64
maxRetries :: Word64
}
data Client = Client
{ Client -> MVar CoreClient
client :: MVar CoreClient
, Client -> Runtime
runtime :: Runtime
, Client -> ClientConfig
config :: ClientConfig
}
clientConfig :: Client -> ClientConfig
clientConfig :: Client -> ClientConfig
clientConfig = Client -> ClientConfig
config
clientRuntime :: Client -> Runtime
clientRuntime :: Client -> Runtime
clientRuntime = Client -> Runtime
runtime
withClient :: Client -> (Ptr CoreClient -> IO a) -> IO a
withClient :: forall a. Client -> (Ptr CoreClient -> IO a) -> IO a
withClient (Client MVar CoreClient
cc Runtime
r ClientConfig
_) Ptr CoreClient -> IO a
f =
MVar CoreClient -> (CoreClient -> IO a) -> IO a
forall a b. MVar a -> (a -> IO b) -> IO b
withMVar MVar CoreClient
cc ((CoreClient -> IO a) -> IO a) -> (CoreClient -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \(CoreClient ForeignPtr CoreClient
c) ->
Runtime -> (Ptr Runtime -> IO a) -> IO a
forall a. Runtime -> (Ptr Runtime -> IO a) -> IO a
withRuntime Runtime
r ((Ptr Runtime -> IO a) -> IO a) -> (Ptr Runtime -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr Runtime
_ ->
ForeignPtr CoreClient -> (Ptr CoreClient -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr CoreClient
c Ptr CoreClient -> IO a
f
touchClient :: Client -> IO ()
touchClient :: Client -> IO ()
touchClient (Client MVar CoreClient
cc Runtime
_ ClientConfig
_) = do
mcc <- MVar CoreClient -> IO (Maybe CoreClient)
forall a. MVar a -> IO (Maybe a)
tryReadMVar MVar CoreClient
cc
case mcc of
Maybe CoreClient
Nothing -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just (CoreClient ForeignPtr CoreClient
c) -> ForeignPtr CoreClient -> IO ()
forall a. ForeignPtr a -> IO ()
touchForeignPtr ForeignPtr CoreClient
c
newtype ByteVector = ByteVector {ByteVector -> ByteString
byteVector :: ByteString}
byteStringToVector :: BS.ByteString -> V.Vector Word8
byteStringToVector :: ByteString -> Vector Word8
byteStringToVector ByteString
bs = Vector Word8
vec
where
vec :: Vector Word8
vec = ForeignPtr Word8 -> Int -> Int -> Vector Word8
forall a. Storable a => ForeignPtr a -> Int -> Int -> Vector a
V.unsafeFromForeignPtr (ForeignPtr Word8 -> ForeignPtr Word8
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr ForeignPtr Word8
fptr) Int
off Int
len
(ForeignPtr Word8
fptr, Int
off, Int
len) = ByteString -> (ForeignPtr Word8, Int, Int)
BS.toForeignPtr ByteString
bs
vectorToByteString :: V.Vector Word8 -> BS.ByteString
vectorToByteString :: Vector Word8 -> ByteString
vectorToByteString Vector Word8
vec = ForeignPtr Word8 -> Int -> Int -> ByteString
BS.fromForeignPtr (ForeignPtr Word8 -> ForeignPtr Word8
forall a b. ForeignPtr a -> ForeignPtr b
castForeignPtr ForeignPtr Word8
fptr) Int
off Int
len
where
(ForeignPtr Word8
fptr, Int
off, Int
len) = Vector Word8 -> (ForeignPtr Word8, Int, Int)
forall a. Vector a -> (ForeignPtr a, Int, Int)
V.unsafeToForeignPtr Vector Word8
vec
instance ToJSON ByteVector where
toJSON :: ByteVector -> Value
toJSON = Vector Word8 -> Value
forall a. ToJSON a => a -> Value
toJSON (Vector Word8 -> Value)
-> (ByteVector -> Vector Word8) -> ByteVector -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Vector Word8
byteStringToVector (ByteString -> Vector Word8)
-> (ByteVector -> ByteString) -> ByteVector -> Vector Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteVector -> ByteString
byteVector
instance FromJSON ByteVector where
parseJSON :: Value -> Parser ByteVector
parseJSON = (Vector Word8 -> ByteVector)
-> Parser (Vector Word8) -> Parser ByteVector
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ByteString -> ByteVector
ByteVector (ByteString -> ByteVector)
-> (Vector Word8 -> ByteString) -> Vector Word8 -> ByteVector
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Word8 -> ByteString
vectorToByteString) (Parser (Vector Word8) -> Parser ByteVector)
-> (Value -> Parser (Vector Word8)) -> Value -> Parser ByteVector
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser (Vector Word8)
forall a. FromJSON a => Value -> Parser a
parseJSON
deriveJSON (defaultOptions {fieldLabelModifier = camelTo2 '_'}) ''ClientTlsConfig
deriveJSON (defaultOptions {fieldLabelModifier = camelTo2 '_'}) ''ClientRetryConfig
deriveJSON (defaultOptions {fieldLabelModifier = camelTo2 '_'}) ''ClientConfig
data RpcCall a = RpcCall
{ forall a. RpcCall a -> a
req :: a
, forall a. RpcCall a -> Bool
retry :: Bool
, forall a. RpcCall a -> HashMap Text Text
metadata :: HashMap Text Text
, forall a. RpcCall a -> Maybe Word64
timeoutMillis :: Maybe Word64
}
data ClientError
= ClientConnectionError Text
| ClientClosedError
deriving (Int -> ClientError -> ShowS
[ClientError] -> ShowS
ClientError -> String
(Int -> ClientError -> ShowS)
-> (ClientError -> String)
-> ([ClientError] -> ShowS)
-> Show ClientError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClientError -> ShowS
showsPrec :: Int -> ClientError -> ShowS
$cshow :: ClientError -> String
show :: ClientError -> String
$cshowList :: [ClientError] -> ShowS
showList :: [ClientError] -> ShowS
Show)
instance Exception ClientError
defaultClientConfig :: ClientConfig
defaultClientConfig :: ClientConfig
defaultClientConfig =
ClientConfig
{ targetUrl :: Text
targetUrl = Text
"http://localhost:7233"
, clientName :: Text
clientName = Text
"temporal-haskell"
, clientVersion :: Text
clientVersion = Text
"0.0.1"
, metadata :: HashMap Text Text
metadata = HashMap Text Text
forall a. Monoid a => a
mempty
, identity :: Text
identity = Text
""
, tlsConfig :: Maybe ClientTlsConfig
tlsConfig = Maybe ClientTlsConfig
forall a. Maybe a
Nothing
, retryConfig :: Maybe ClientRetryConfig
retryConfig = Maybe ClientRetryConfig
forall a. Maybe a
Nothing
}
defaultClientIdentity :: IO Text
defaultClientIdentity :: IO Text
defaultClientIdentity = do
pid <- IO ProcessID
getProcessID
host <- getHostName
pure (T.pack $ show pid <> "@" <> host)
connectClient :: Runtime -> ClientConfig -> IO Client
connectClient :: Runtime -> ClientConfig -> IO Client
connectClient Runtime
rt ClientConfig
conf = do
conf' <-
if ClientConfig -> Text
identity ClientConfig
conf Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
""
then do
ident <- IO Text
defaultClientIdentity
pure $ conf {identity = ident}
else ClientConfig -> IO ClientConfig
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ClientConfig
conf
clientPtrSlot <- newEmptyMVar
_ <- forkIO $ do
withRuntime rt $ \Ptr Runtime
rtPtr -> ByteString -> (CString -> IO ()) -> IO ()
forall a. ByteString -> (CString -> IO a) -> IO a
BS.useAsCString (LazyByteString -> ByteString
BL.toStrict (LazyByteString -> ByteString) -> LazyByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ ClientConfig -> LazyByteString
forall a. ToJSON a => a -> LazyByteString
encode ClientConfig
conf') ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
confPtr -> do
let tryConnect :: IO (Either (ForeignPtr (CArray Word8)) (ForeignPtr CoreClient))
tryConnect =
TokioCall (CArray Word8) CoreClient
-> Maybe (FinalizerPtr (CArray Word8))
-> Maybe (FinalizerPtr CoreClient)
-> IO (Either (ForeignPtr (CArray Word8)) (ForeignPtr CoreClient))
forall err res.
TokioCall err res
-> Maybe (FinalizerPtr err)
-> Maybe (FinalizerPtr res)
-> IO (Either (ForeignPtr err) (ForeignPtr res))
makeTokioAsyncCall
(Ptr Runtime -> CString -> TokioCall (CArray Word8) CoreClient
raw_connectClient Ptr Runtime
rtPtr CString
confPtr)
(FinalizerPtr (CArray Word8) -> Maybe (FinalizerPtr (CArray Word8))
forall a. a -> Maybe a
Just FinalizerPtr (CArray Word8)
rust_dropByteArray)
(FinalizerPtr CoreClient -> Maybe (FinalizerPtr CoreClient)
forall a. a -> Maybe a
Just FinalizerPtr CoreClient
raw_freeClient)
go :: Word64 -> IO ()
go Word64
attempt = do
result <- IO (Either (ForeignPtr (CArray Word8)) (ForeignPtr CoreClient))
tryConnect
case result of
Left ForeignPtr (CArray Word8)
errFP -> do
err <- ForeignPtr (CArray Word8)
-> (Ptr (CArray Word8) -> IO Text) -> IO Text
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr (CArray Word8)
errFP ((Ptr (CArray Word8) -> IO Text) -> IO Text)
-> (Ptr (CArray Word8) -> IO Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ Ptr (CArray Word8) -> IO (CArray Word8)
forall a. Storable a => Ptr a -> IO a
peek (Ptr (CArray Word8) -> IO (CArray Word8))
-> (CArray Word8 -> IO Text) -> Ptr (CArray Word8) -> IO Text
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> CArray Word8 -> IO Text
cArrayToText
case retryConfig conf of
Maybe ClientRetryConfig
Nothing -> MVar CoreClient -> CoreClient -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar CoreClient
clientPtrSlot (ClientError -> CoreClient
forall a e. (?callStack::CallStack, Exception e) => e -> a
throw (ClientError -> CoreClient) -> ClientError -> CoreClient
forall a b. (a -> b) -> a -> b
$ Text -> ClientError
ClientConnectionError Text
err)
Just ClientRetryConfig
retryConf -> do
let delayMillis :: Double
delayMillis = Word64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ClientRetryConfig -> Word64
initialIntervalMillis ClientRetryConfig
retryConf) Double -> Double -> Double
forall a. Num a => a -> a -> a
* ClientRetryConfig -> Double
multiplier ClientRetryConfig
retryConf Double -> Word64 -> Double
forall a b. (Num a, Integral b) => a -> b -> a
^ Word64
attempt
delayMicros :: Double
delayMicros = Double
delayMillis Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
1000
if ((Word64 -> Double) -> Maybe Word64 -> Maybe Double
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ClientRetryConfig -> Maybe Word64
maxElapsedTimeMillis ClientRetryConfig
retryConf) Maybe Double -> Maybe Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double -> Maybe Double
forall a. a -> Maybe a
Just Double
delayMillis) Bool -> Bool -> Bool
|| (ClientRetryConfig -> Word64
maxRetries ClientRetryConfig
retryConf Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word64
attempt)
then MVar CoreClient -> CoreClient -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar CoreClient
clientPtrSlot (ClientError -> CoreClient
forall a e. (?callStack::CallStack, Exception e) => e -> a
throw (ClientError -> CoreClient) -> ClientError -> CoreClient
forall a b. (a -> b) -> a -> b
$ Text -> ClientError
ClientConnectionError Text
err)
else do
Int -> IO ()
threadDelay (Int -> IO ()) -> Int -> IO ()
forall a b. (a -> b) -> a -> b
$ Double -> Int
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
round Double
delayMicros
Word64 -> IO ()
go (Word64
attempt Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1)
Right ForeignPtr CoreClient
client_ -> MVar CoreClient -> CoreClient -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar CoreClient
clientPtrSlot (ForeignPtr CoreClient -> CoreClient
CoreClient ForeignPtr CoreClient
client_)
Word64 -> IO ()
go Word64
1
pure $ Client clientPtrSlot rt conf'
reconnectClient :: Client -> IO ()
reconnectClient :: Client -> IO ()
reconnectClient (Client MVar CoreClient
clientPtrSlot Runtime
rt ClientConfig
conf) = ((forall a. IO a -> IO a) -> IO ()) -> IO ()
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
mask (((forall a. IO a -> IO a) -> IO ()) -> IO ())
-> ((forall a. IO a -> IO a) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
restore -> do
(CoreClient clientPtr) <- MVar CoreClient -> IO CoreClient
forall a. MVar a -> IO a
takeMVar MVar CoreClient
clientPtrSlot
(Client newClientPtr _ _) <- restore (connectClient rt conf) `catch` (\ClientError
c -> MVar CoreClient -> CoreClient -> IO ()
forall a. MVar a -> a -> IO ()
putMVar MVar CoreClient
clientPtrSlot (ClientError -> CoreClient
forall a e. (?callStack::CallStack, Exception e) => e -> a
throw (ClientError
c :: ClientError)) IO () -> IO Client -> IO Client
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ClientError -> IO Client
forall e a. (?callStack::CallStack, Exception e) => e -> IO a
throwIO ClientError
c)
takeMVar newClientPtr >>= putMVar clientPtrSlot
closeClient :: Client -> IO ()
closeClient :: Client -> IO ()
closeClient (Client MVar CoreClient
clientPtrSlot Runtime
_ ClientConfig
_) = IO () -> IO ()
forall a. IO a -> IO a
mask_ (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
(CoreClient clientPtr) <- MVar CoreClient -> IO CoreClient
forall a. MVar a -> IO a
takeMVar MVar CoreClient
clientPtrSlot
finalizeForeignPtr clientPtr
putMVar clientPtrSlot (throw ClientClosedError)
type PrimRpcCall = Ptr CoreClient -> Ptr CRpcCall -> TokioCall CRPCError (CArray Word8)
call :: forall svc t. (HasMethodImpl svc t) => PrimRpcCall -> Client -> MethodInput svc t -> IO (Either RpcError (MethodOutput svc t))
call :: forall svc (t :: Symbol).
HasMethodImpl svc t =>
PrimRpcCall
-> Client
-> MethodInput svc t
-> IO (Either RpcError (MethodOutput svc t))
call PrimRpcCall
f Client
c MethodInput svc t
req_ = Client
-> (Ptr CoreClient -> IO (Either RpcError (MethodOutput svc t)))
-> IO (Either RpcError (MethodOutput svc t))
forall a. Client -> (Ptr CoreClient -> IO a) -> IO a
withClient Client
c ((Ptr CoreClient -> IO (Either RpcError (MethodOutput svc t)))
-> IO (Either RpcError (MethodOutput svc t)))
-> (Ptr CoreClient -> IO (Either RpcError (MethodOutput svc t)))
-> IO (Either RpcError (MethodOutput svc t))
forall a b. (a -> b) -> a -> b
$ \Ptr CoreClient
cPtr -> do
let msgBytes :: ByteString
msgBytes = MethodInput svc t -> ByteString
forall msg. Message msg => msg -> ByteString
encodeMessage MethodInput svc t
req_
ByteString
-> (CStringLen -> IO (Either RpcError (MethodOutput svc t)))
-> IO (Either RpcError (MethodOutput svc t))
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
msgBytes ((CStringLen -> IO (Either RpcError (MethodOutput svc t)))
-> IO (Either RpcError (MethodOutput svc t)))
-> (CStringLen -> IO (Either RpcError (MethodOutput svc t)))
-> IO (Either RpcError (MethodOutput svc t))
forall a b. (a -> b) -> a -> b
$ \(CString
msgPtr, Int
msgLen) -> do
(Ptr (CArray CChar) -> IO (Either RpcError (MethodOutput svc t)))
-> IO (Either RpcError (MethodOutput svc t))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr (CArray CChar) -> IO (Either RpcError (MethodOutput svc t)))
-> IO (Either RpcError (MethodOutput svc t)))
-> (Ptr (CArray CChar)
-> IO (Either RpcError (MethodOutput svc t)))
-> IO (Either RpcError (MethodOutput svc t))
forall a b. (a -> b) -> a -> b
$ \Ptr (CArray CChar)
cArrayPtr -> do
Ptr (CArray CChar) -> CArray CChar -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (CArray CChar)
cArrayPtr (CString -> Word64 -> CArray CChar
forall a. Ptr a -> Word64 -> CArray a
CArray CString
msgPtr (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
msgLen))
let rpcCall :: CRpcCall
rpcCall =
CRpcCall
{ rpcCallReq :: Ptr (CArray Word8)
rpcCallReq = Ptr (CArray CChar) -> Ptr (CArray Word8)
forall a b. Ptr a -> Ptr b
castPtr Ptr (CArray CChar)
cArrayPtr
, rpcCallRetry :: Word8
rpcCallRetry = if Bool
False then Word8
0 else Word8
1
, rpcCallMetadata :: Ptr HashMapEntries
rpcCallMetadata = Ptr HashMapEntries
forall a. Ptr a
nullPtr
, rpcCallTimeoutMillis :: Ptr Word64
rpcCallTimeoutMillis = Ptr Word64
forall a. Ptr a
nullPtr
}
(Ptr CRpcCall -> IO (Either RpcError (MethodOutput svc t)))
-> IO (Either RpcError (MethodOutput svc t))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CRpcCall -> IO (Either RpcError (MethodOutput svc t)))
-> IO (Either RpcError (MethodOutput svc t)))
-> (Ptr CRpcCall -> IO (Either RpcError (MethodOutput svc t)))
-> IO (Either RpcError (MethodOutput svc t))
forall a b. (a -> b) -> a -> b
$ \Ptr CRpcCall
rpcCallPtr -> do
Ptr CRpcCall -> CRpcCall -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CRpcCall
rpcCallPtr CRpcCall
rpcCall
result <-
TokioCall CRPCError (CArray Word8)
-> Maybe (FinalizerPtr CRPCError)
-> Maybe (FinalizerPtr (CArray Word8))
-> IO (Either (ForeignPtr CRPCError) (ForeignPtr (CArray Word8)))
forall err res.
TokioCall err res
-> Maybe (FinalizerPtr err)
-> Maybe (FinalizerPtr res)
-> IO (Either (ForeignPtr err) (ForeignPtr res))
makeTokioAsyncCall
(PrimRpcCall
f Ptr CoreClient
cPtr Ptr CRpcCall
rpcCallPtr)
(FinalizerPtr CRPCError -> Maybe (FinalizerPtr CRPCError)
forall a. a -> Maybe a
Just FinalizerPtr CRPCError
rust_drop_rpc_error)
(FinalizerPtr (CArray Word8) -> Maybe (FinalizerPtr (CArray Word8))
forall a. a -> Maybe a
Just FinalizerPtr (CArray Word8)
rust_dropByteArray)
case result of
Left ForeignPtr CRPCError
err -> RpcError -> Either RpcError (MethodOutput svc t)
forall a b. a -> Either a b
Left (RpcError -> Either RpcError (MethodOutput svc t))
-> IO RpcError -> IO (Either RpcError (MethodOutput svc t))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ForeignPtr CRPCError
-> (Ptr CRPCError -> IO RpcError) -> IO RpcError
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr CRPCError
err (Ptr CRPCError -> IO CRPCError
forall a. Storable a => Ptr a -> IO a
peek (Ptr CRPCError -> IO CRPCError)
-> (CRPCError -> IO RpcError) -> Ptr CRPCError -> IO RpcError
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> CRPCError -> IO RpcError
peekCRPCError)
Right ForeignPtr (CArray Word8)
r -> MethodOutput svc t -> Either RpcError (MethodOutput svc t)
forall a b. b -> Either a b
Right (MethodOutput svc t -> Either RpcError (MethodOutput svc t))
-> (ByteString -> MethodOutput svc t)
-> ByteString
-> Either RpcError (MethodOutput svc t)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> MethodOutput svc t
forall msg. Message msg => ByteString -> msg
decodeMessageOrDie (ByteString -> Either RpcError (MethodOutput svc t))
-> IO ByteString -> IO (Either RpcError (MethodOutput svc t))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ForeignPtr (CArray Word8)
-> (Ptr (CArray Word8) -> IO ByteString) -> IO ByteString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr (CArray Word8)
r (Ptr (CArray Word8) -> IO (CArray Word8)
forall a. Storable a => Ptr a -> IO a
peek (Ptr (CArray Word8) -> IO (CArray Word8))
-> (CArray Word8 -> IO ByteString)
-> Ptr (CArray Word8)
-> IO ByteString
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> CArray Word8 -> IO ByteString
cArrayToByteString)