simplexmq-0.5.2: SimpleXMQ message broker
Safe HaskellNone
LanguageHaskell2010

Simplex.Messaging.Agent.Store

Synopsis

Store management

class Monad m => MonadAgentStore s m where Source #

Store class type. Defines store access methods for implementations.

Methods

createRcvConn :: s -> TVar ChaChaDRG -> ConnData -> RcvQueue -> SConnectionMode c -> m ConnId Source #

createSndConn :: s -> TVar ChaChaDRG -> ConnData -> SndQueue -> m ConnId Source #

getConn :: s -> ConnId -> m SomeConn Source #

getAllConnIds :: s -> m [ConnId] Source #

getRcvConn :: s -> SMPServer -> RecipientId -> m SomeConn Source #

deleteConn :: s -> ConnId -> m () Source #

upgradeRcvConnToDuplex :: s -> ConnId -> SndQueue -> m () Source #

upgradeSndConnToDuplex :: s -> ConnId -> RcvQueue -> m () Source #

setRcvQueueStatus :: s -> RcvQueue -> QueueStatus -> m () Source #

setRcvQueueActive :: s -> RcvQueue -> VerificationKey -> m () Source #

setSndQueueStatus :: s -> SndQueue -> QueueStatus -> m () Source #

updateSignKey :: s -> SndQueue -> SignatureKey -> m () Source #

createConfirmation :: s -> TVar ChaChaDRG -> NewConfirmation -> m ConfirmationId Source #

acceptConfirmation :: s -> ConfirmationId -> ConnInfo -> m AcceptedConfirmation Source #

getAcceptedConfirmation :: s -> ConnId -> m AcceptedConfirmation Source #

removeConfirmations :: s -> ConnId -> m () Source #

createInvitation :: s -> TVar ChaChaDRG -> NewInvitation -> m InvitationId Source #

getInvitation :: s -> InvitationId -> m Invitation Source #

acceptInvitation :: s -> InvitationId -> ConnInfo -> m () Source #

deleteInvitation :: s -> ConnId -> InvitationId -> m () Source #

updateRcvIds :: s -> ConnId -> m (InternalId, InternalRcvId, PrevExternalSndId, PrevRcvMsgHash) Source #

createRcvMsg :: s -> ConnId -> RcvMsgData -> m () Source #

updateSndIds :: s -> ConnId -> m (InternalId, InternalSndId, PrevSndMsgHash) Source #

createSndMsg :: s -> ConnId -> SndMsgData -> m () Source #

updateSndMsgStatus :: s -> ConnId -> InternalId -> SndMsgStatus -> m () Source #

getPendingMsgData :: s -> ConnId -> InternalId -> m MsgBody Source #

getPendingMsgs :: s -> ConnId -> m [InternalId] Source #

getMsg :: s -> ConnId -> InternalId -> m Msg Source #

checkRcvMsg :: s -> ConnId -> InternalId -> m () Source #

updateRcvMsgAck :: s -> ConnId -> InternalId -> m () Source #

Instances

Instances details
(MonadUnliftIO m, MonadError StoreError m) => MonadAgentStore SQLiteStore m Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store.SQLite

Methods

createRcvConn :: forall (c :: ConnectionMode). SQLiteStore -> TVar ChaChaDRG -> ConnData -> RcvQueue -> SConnectionMode c -> m ConnId Source #

createSndConn :: SQLiteStore -> TVar ChaChaDRG -> ConnData -> SndQueue -> m ConnId Source #

getConn :: SQLiteStore -> ConnId -> m SomeConn Source #

getAllConnIds :: SQLiteStore -> m [ConnId] Source #

getRcvConn :: SQLiteStore -> SMPServer -> RecipientId -> m SomeConn Source #

deleteConn :: SQLiteStore -> ConnId -> m () Source #

upgradeRcvConnToDuplex :: SQLiteStore -> ConnId -> SndQueue -> m () Source #

upgradeSndConnToDuplex :: SQLiteStore -> ConnId -> RcvQueue -> m () Source #

setRcvQueueStatus :: SQLiteStore -> RcvQueue -> QueueStatus -> m () Source #

setRcvQueueActive :: SQLiteStore -> RcvQueue -> VerificationKey -> m () Source #

setSndQueueStatus :: SQLiteStore -> SndQueue -> QueueStatus -> m () Source #

updateSignKey :: SQLiteStore -> SndQueue -> SignatureKey -> m () Source #

createConfirmation :: SQLiteStore -> TVar ChaChaDRG -> NewConfirmation -> m ConfirmationId Source #

acceptConfirmation :: SQLiteStore -> ConfirmationId -> ConnInfo -> m AcceptedConfirmation Source #

getAcceptedConfirmation :: SQLiteStore -> ConnId -> m AcceptedConfirmation Source #

removeConfirmations :: SQLiteStore -> ConnId -> m () Source #

createInvitation :: SQLiteStore -> TVar ChaChaDRG -> NewInvitation -> m InvitationId Source #

getInvitation :: SQLiteStore -> InvitationId -> m Invitation Source #

acceptInvitation :: SQLiteStore -> InvitationId -> ConnInfo -> m () Source #

deleteInvitation :: SQLiteStore -> ConnId -> InvitationId -> m () Source #

updateRcvIds :: SQLiteStore -> ConnId -> m (InternalId, InternalRcvId, PrevExternalSndId, PrevRcvMsgHash) Source #

createRcvMsg :: SQLiteStore -> ConnId -> RcvMsgData -> m () Source #

updateSndIds :: SQLiteStore -> ConnId -> m (InternalId, InternalSndId, PrevSndMsgHash) Source #

createSndMsg :: SQLiteStore -> ConnId -> SndMsgData -> m () Source #

updateSndMsgStatus :: SQLiteStore -> ConnId -> InternalId -> SndMsgStatus -> m () Source #

getPendingMsgData :: SQLiteStore -> ConnId -> InternalId -> m MsgBody Source #

getPendingMsgs :: SQLiteStore -> ConnId -> m [InternalId] Source #

getMsg :: SQLiteStore -> ConnId -> InternalId -> m Msg Source #

checkRcvMsg :: SQLiteStore -> ConnId -> InternalId -> m () Source #

updateRcvMsgAck :: SQLiteStore -> ConnId -> InternalId -> m () Source #

Queue types

data RcvQueue Source #

A receive queue. SMP queue through which the agent receives messages from a sender.

Instances

Instances details
Eq RcvQueue Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Show RcvQueue Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

data SndQueue Source #

A send queue. SMP queue through which the agent sends messages to a recipient.

Instances

Instances details
Eq SndQueue Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Show SndQueue Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Connection types

data ConnType Source #

Type of a connection.

Constructors

CRcv 
CSnd 
CDuplex 
CContact 

Instances

Instances details
Eq ConnType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Show ConnType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

TestEquality SConnType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Methods

testEquality :: forall (a :: k) (b :: k). SConnType a -> SConnType b -> Maybe (a :~: b) #

data Connection (d :: ConnType) where Source #

Connection of a specific type.

  • RcvConnection is a connection that only has a receive queue set up, typically created by a recipient initiating a duplex connection.
  • SndConnection is a connection that only has a send queue set up, typically created by a sender joining a duplex connection through a recipient's invitation.
  • DuplexConnection is a connection that has both receive and send queues set up, typically created by upgrading a receive or a send connection with a missing queue.

Instances

Instances details
Eq (Connection d) Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Methods

(==) :: Connection d -> Connection d -> Bool #

(/=) :: Connection d -> Connection d -> Bool #

Show (Connection d) Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

data SConnType :: ConnType -> Type where Source #

Instances

Instances details
TestEquality SConnType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Methods

testEquality :: forall (a :: k) (b :: k). SConnType a -> SConnType b -> Maybe (a :~: b) #

Eq (SConnType d) Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Methods

(==) :: SConnType d -> SConnType d -> Bool #

(/=) :: SConnType d -> SConnType d -> Bool #

Show (SConnType d) Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

data SomeConn Source #

Connection of an unknown type. Used to refer to an arbitrary connection when retrieving from store.

Constructors

forall d. SomeConn (SConnType d) (Connection d) 

Instances

Instances details
Eq SomeConn Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Show SomeConn Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

newtype ConnData Source #

Constructors

ConnData 

Fields

Instances

Instances details
Eq ConnData Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Show ConnData Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Confirmation types

Invitations

Message integrity validation types

type PrevExternalSndId = Int64 Source #

Corresponds to last_external_snd_msg_id in connections table

type PrevRcvMsgHash = MsgHash Source #

Corresponds to last_rcv_msg_hash in connections table

type PrevSndMsgHash = MsgHash Source #

Corresponds to last_snd_msg_hash in connections table

Message data containers - used on Msg creation to reduce number of parameters

data PendingMsg Source #

Constructors

PendingMsg 

Fields

Instances

Instances details
Show PendingMsg Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Broadcast types

Message types

data Msg Source #

A message in either direction that is stored by the agent.

Constructors

MRcv RcvMsg 
MSnd SndMsg 

Instances

Instances details
Eq Msg Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Methods

(==) :: Msg -> Msg -> Bool #

(/=) :: Msg -> Msg -> Bool #

Show Msg Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Methods

showsPrec :: Int -> Msg -> ShowS #

show :: Msg -> String #

showList :: [Msg] -> ShowS #

data RcvMsg Source #

A message received by the agent from a sender.

Constructors

RcvMsg 

Fields

Instances

Instances details
Eq RcvMsg Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Methods

(==) :: RcvMsg -> RcvMsg -> Bool #

(/=) :: RcvMsg -> RcvMsg -> Bool #

Show RcvMsg Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

data SndMsg Source #

A message sent by the agent to a recipient.

Constructors

SndMsg 

Fields

Instances

Instances details
Eq SndMsg Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Methods

(==) :: SndMsg -> SndMsg -> Bool #

(/=) :: SndMsg -> SndMsg -> Bool #

Show SndMsg Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

data MsgBase Source #

Base message data independent of direction.

Constructors

MsgBase 

Fields

  • connAlias :: ConnId
     
  • internalId :: InternalId

    Monotonically increasing id of a message per connection, internal to the agent. Internal Id preserves ordering between both received and sent messages, and is needed to track the order of the conversation (which can be different for the sender / receiver) and address messages in commands. External [sender] Id cannot be used for this purpose due to a possibility of implementation errors in different agents.

  • internalTs :: InternalTs
     
  • msgBody :: MsgBody
     
  • internalHash :: MsgHash

    Hash of the message as computed by agent.

Instances

Instances details
Eq MsgBase Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

Methods

(==) :: MsgBase -> MsgBase -> Bool #

(/=) :: MsgBase -> MsgBase -> Bool #

Show MsgBase Source # 
Instance details

Defined in Simplex.Messaging.Agent.Store

newtype InternalId Source #

Constructors

InternalId 

Fields

Store errors

data StoreError Source #

Agent store error.

Constructors

SEInternal ByteString

IO exceptions in store actions.

SEUniqueID

failed to generate unique random ID

SEConnNotFound

Connection alias not found (or both queues absent).

SEConnDuplicate

Connection alias already used.

SEBadConnType ConnType

Wrong connection type, e.g. "send" connection when "receive" or "duplex" is expected, or vice versa. upgradeRcvConnToDuplex and upgradeSndConnToDuplex do not allow duplex connections - they would also return this error.

SEConfirmationNotFound

Confirmation not found.

SEInvitationNotFound

Invitation not found

SEMsgNotFound

Message not found

SEBadQueueStatus

Currently not used. The intention was to pass current expected queue status in methods, as we always know what it should be at any stage of the protocol, and in case it does not match use this error.

SENotImplemented

Used in getMsg that is not implemented/used. TODO remove.