@@ -21,6 +21,7 @@ import Control.Concurrent.Async
21
21
import Control.Concurrent.STM (atomically )
22
22
import Control.Concurrent.STM.TMChan
23
23
import Control.Concurrent.STM.TMVar
24
+ import Control.Exception (throwIO )
24
25
import Control.Monad.IO.Class
25
26
import Data.Avro
26
27
import qualified Data.ByteString.Char8 as BS
@@ -38,7 +39,7 @@ import Network.GRPC.Client.Helpers
38
39
import Network.GRPC.HTTP2.Encoding (GRPCInput , GRPCOutput )
39
40
import Network.HTTP2 (ErrorCode )
40
41
import Network.HTTP2.Client (ClientError , ClientIO , TooMuchConcurrency ,
41
- runExceptT )
42
+ runExceptT , ExceptT )
42
43
43
44
import Mu.Adapter.ProtoBuf.Via
44
45
import Mu.GRpc.Avro
@@ -304,47 +305,50 @@ conduitFromChannel chan promise = go
304
305
305
306
instance ( KnownName name
306
307
, GRpcInputWrapper p vref v , GRpcOutputWrapper p rref r
307
- , handler ~ (CompressMode -> IO (ConduitT v ( GRpcReply r ) IO () )) )
308
+ , handler ~ (CompressMode -> IO (ConduitT v Void IO () , ConduitT () r IO (GRpcReply ( ) ))) )
308
309
=> GRpcMethodCall p ('Method name '[ 'ArgStream aname vref ]
309
310
('RetStream rref )) handler where
310
311
gRpcMethodCall rpc _ client compress
311
- = do -- Create a new TMChan
312
- inchan <- newTMChanIO :: IO (TMChan (GRpcReply r ))
313
- outchan <- newTMChanIO :: IO (TMChan v )
314
- var <- newEmptyTMVarIO -- if full, this means an error
312
+ = do serverChan <- newTMChanIO :: IO (TMChan r )
313
+ clientChan <- newTMChanIO :: IO (TMChan v )
314
+ finalReply <- newEmptyTMVarIO :: IO (TMVar (GRpcReply () ))
315
315
-- Start executing the client in another thread
316
+ -- TODO: Is there anything that makes sure that this thread doesn't keep running forever?
316
317
_ <- async $ do
317
318
v <- simplifyResponse $
318
319
buildGRpcReply3 <$>
319
320
rawGeneralStream
320
321
@ _ @ (GRpcIWTy p vref v ) @ (GRpcOWTy p rref r )
321
322
rpc client
322
- () (\ _ ievent -> do -- on the first iteration, say that everything is OK
323
- _ <- liftIO $ atomically $ tryPutTMVar var (GRpcOk () )
324
- case ievent of
325
- RecvMessage o -> liftIO $ atomically $ writeTMChan inchan (GRpcOk $ unGRpcOWTy(Proxy @ p ) (Proxy @ rref ) o)
326
- Invalid e -> liftIO $ atomically $ writeTMChan inchan (GRpcErrorString (show e))
327
- _ -> pure () )
328
- () (\ _ -> do
329
- nextVal <- liftIO $ atomically $ readTMChan outchan
330
- case nextVal of
331
- Nothing -> pure (() , Finalize )
332
- Just v -> pure (() , SendMessage compress (buildGRpcIWTy (Proxy @ p ) (Proxy @ vref ) v)))
333
- case v of
334
- GRpcOk () -> liftIO $ atomically $ closeTMChan inchan
335
- _ -> liftIO $ atomically $ putTMVar var v
336
- -- This conduit feeds information to the other thread
337
- let go = do err <- liftIO $ atomically $ takeTMVar var
338
- case err of
339
- GRpcOk _ -> go2
340
- e -> yield $ (\ _ -> error " this should never happen" ) <$> e
341
- go2 = do nextOut <- await
342
- case nextOut of
343
- Just v -> do liftIO $ atomically $ writeTMChan outchan v
344
- go2
345
- Nothing -> do r <- liftIO $ atomically $ tryReadTMChan inchan
346
- case r of
347
- Nothing -> pure () -- both are empty, end
348
- Just Nothing -> go2
349
- Just (Just nextIn) -> yield nextIn >> go2
350
- pure go
323
+ () (incomingEventConsumer serverChan)
324
+ () (outgoingEventProducer clientChan)
325
+ liftIO $ atomically $ putTMVar finalReply v
326
+ let clientConduit = do
327
+ sinkTMChan clientChan
328
+ liftIO . atomically . closeTMChan $ clientChan
329
+ serverConduit = do
330
+ sourceTMChan serverChan
331
+ liftIO . atomically . readTMVar $ finalReply
332
+ pure (clientConduit, serverConduit)
333
+ where
334
+ incomingEventConsumer :: TMChan r -> () -> IncomingEvent (GRpcOWTy p rref r ) () -> ExceptT ClientError IO ()
335
+ incomingEventConsumer serverChan _ ievent =
336
+ case ievent of
337
+ RecvMessage o -> do
338
+ liftIO $ atomically $ writeTMChan serverChan (unGRpcOWTy (Proxy @ p ) (Proxy @ rref ) o)
339
+ Invalid e -> liftIO $ do
340
+ atomically $ closeTMChan serverChan
341
+ throwIO e
342
+ Trailers _ ->
343
+ -- TODO: Read the trailers and use them to make the 'finalReply'
344
+ liftIO $ atomically $ closeTMChan serverChan
345
+ Headers _ ->
346
+ -- TODO: Read the headers and use them to make the 'finalReply'
347
+ pure ()
348
+
349
+ outgoingEventProducer :: TMChan v -> () -> ExceptT ClientError IO (() , OutgoingEvent (GRpcIWTy p vref v ) () )
350
+ outgoingEventProducer clientChan _ = do
351
+ nextVal <- liftIO $ atomically $ readTMChan clientChan
352
+ case nextVal of
353
+ Nothing -> pure (() , Finalize )
354
+ Just v -> pure (() , SendMessage compress (buildGRpcIWTy (Proxy @ p ) (Proxy @ vref ) v))
0 commit comments