44{-# LANGUAGE FlexibleContexts #-}
55{-# LANGUAGE GADTs #-}
66{-# LANGUAGE LambdaCase #-}
7+ {-# LANGUAGE MultiWayIf #-}
78{-# LANGUAGE NamedFieldPuns #-}
89{-# LANGUAGE TupleSections #-}
910{-# LANGUAGE TypeFamilyDependencies #-}
11+ {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
12+
13+ {-# HLINT ignore "Redundant multi-way if" #-}
1014
1115module Simplex.Messaging.Server.MsgStore.Types where
1216
@@ -21,6 +25,7 @@ import Simplex.Messaging.Protocol
2125import Simplex.Messaging.Server.QueueStore
2226import Simplex.Messaging.Server.StoreLog.Types
2327import Simplex.Messaging.TMap (TMap )
28+ import Simplex.Messaging.Util ((<$$>) )
2429import System.IO (IOMode (.. ))
2530
2631class MsgStoreClass s => STMQueueStore s where
@@ -44,8 +49,9 @@ class Monad (StoreMonad s) => MsgStoreClass s where
4449 logQueueStates :: s -> IO ()
4550 logQueueState :: StoreQueue s -> StoreMonad s ()
4651 queueRec' :: StoreQueue s -> TVar (Maybe QueueRec )
47- getNonEmptyMsgQueue :: s -> RecipientId -> StoreQueue s -> StoreMonad s (Maybe (MsgQueue s ))
52+ getPeekMsgQueue :: s -> RecipientId -> StoreQueue s -> StoreMonad s (Maybe (MsgQueue s , Message ))
4853 getMsgQueue :: s -> RecipientId -> StoreQueue s -> StoreMonad s (MsgQueue s )
54+
4955 -- the journal queue will be closed after action if it was initially closed or idle longer than interval in config
5056 withIdleMsgQueue :: Int64 -> s -> RecipientId -> StoreQueue s -> (MsgQueue s -> StoreMonad s a ) -> StoreMonad s (Maybe a , Int )
5157 deleteQueue :: s -> RecipientId -> StoreQueue s -> IO (Either ErrorType QueueRec )
@@ -74,39 +80,39 @@ withActiveMsgQueues st f = readTVarIO (activeMsgQueues st) >>= foldM run mempty
7480 pure $! acc <> r
7581
7682getQueueMessages :: MsgStoreClass s => Bool -> s -> RecipientId -> StoreQueue s -> ExceptT ErrorType IO [Message ]
77- getQueueMessages drainMsgs st rId q = withMsgQueue st rId q " getQueueSize" $ maybe (pure [] ) $ getQueueMessages_ drainMsgs
83+ getQueueMessages drainMsgs st rId q = withPeekMsgQueue st rId q " getQueueSize" $ maybe (pure [] ) ( getQueueMessages_ drainMsgs . fst )
7884{-# INLINE getQueueMessages #-}
7985
8086getQueueSize :: MsgStoreClass s => s -> RecipientId -> StoreQueue s -> ExceptT ErrorType IO Int
81- getQueueSize st rId q = withMsgQueue st rId q " getQueueSize" $ maybe (pure 0 ) getQueueSize_
87+ getQueueSize st rId q = withPeekMsgQueue st rId q " getQueueSize" $ maybe (pure 0 ) ( getQueueSize_ . fst )
8288{-# INLINE getQueueSize #-}
8389
8490tryPeekMsg :: MsgStoreClass s => s -> RecipientId -> StoreQueue s -> ExceptT ErrorType IO (Maybe Message )
85- tryPeekMsg st rId q = withMsgQueue st rId q " tryPeekMsg" $ maybe ( pure Nothing ) (tryPeekMsg_ q)
91+ tryPeekMsg st rId q = snd <$$> withPeekMsgQueue st rId q " tryPeekMsg" pure
8692{-# INLINE tryPeekMsg #-}
8793
8894tryDelMsg :: MsgStoreClass s => s -> RecipientId -> StoreQueue s -> MsgId -> ExceptT ErrorType IO (Maybe Message )
89- tryDelMsg st rId q msgId' = withMsgQueue st rId q " tryDelMsg" $ maybe (pure Nothing ) $ \ mq ->
90- tryPeekMsg_ q mq >>= \ case
91- msg_@ (Just msg)
95+ tryDelMsg st rId q msgId' =
96+ withPeekMsgQueue st rId q " tryDelMsg" $
97+ maybe (pure Nothing ) $ \ (mq, msg) ->
98+ if
9299 | messageId msg == msgId' ->
93- tryDeleteMsg_ q mq True >> pure msg_
94- _ -> pure Nothing
100+ tryDeleteMsg_ q mq True >> pure ( Just msg)
101+ | otherwise -> pure Nothing
95102
96103-- atomic delete (== read) last and peek next message if available
97104tryDelPeekMsg :: MsgStoreClass s => s -> RecipientId -> StoreQueue s -> MsgId -> ExceptT ErrorType IO (Maybe Message , Maybe Message )
98105tryDelPeekMsg st rId q msgId' =
99- withMsgQueue st rId q " tryDelPeekMsg" $ maybe (pure (Nothing , Nothing )) $ \ mq ->
100- tryPeekMsg_ q mq >>= \ case
101- msg_@ (Just msg)
102- | messageId msg == msgId' -> (msg_,) <$> (tryDeleteMsg_ q mq True >> tryPeekMsg_ q mq)
103- | otherwise -> pure (Nothing , msg_)
104- _ -> pure (Nothing , Nothing )
106+ withPeekMsgQueue st rId q " tryDelPeekMsg" $
107+ maybe (pure (Nothing , Nothing )) $ \ (mq, msg) ->
108+ if
109+ | messageId msg == msgId' -> (Just msg,) <$> (tryDeleteMsg_ q mq True >> tryPeekMsg_ q mq)
110+ | otherwise -> pure (Nothing , Just msg)
105111
106112-- The action is called with Nothing when it is known that the queue is empty
107- withMsgQueue :: MsgStoreClass s => s -> RecipientId -> StoreQueue s -> String -> (Maybe (MsgQueue s ) -> StoreMonad s a ) -> ExceptT ErrorType IO a
108- withMsgQueue st rId q op a = isolateQueue rId q op $ getNonEmptyMsgQueue st rId q >>= a
109- {-# INLINE withMsgQueue #-}
113+ withPeekMsgQueue :: MsgStoreClass s => s -> RecipientId -> StoreQueue s -> String -> (Maybe (MsgQueue s , Message ) -> StoreMonad s a ) -> ExceptT ErrorType IO a
114+ withPeekMsgQueue st rId q op a = isolateQueue rId q op $ getPeekMsgQueue st rId q >>= a
115+ {-# INLINE withPeekMsgQueue #-}
110116
111117deleteExpiredMsgs :: MsgStoreClass s => s -> RecipientId -> StoreQueue s -> Int64 -> ExceptT ErrorType IO Int
112118deleteExpiredMsgs st rId q old =
0 commit comments