simplexmq-0.5.2: SimpleXMQ message broker
Copyright(c) simplex.chat
LicenseAGPL-3
Maintainerchat@simplex.chat
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Simplex.Messaging.Agent.Protocol

Description

Types, parsers, serializers and functions to send and receive SMP agent protocol commands and responses.

See https://github.com/simplex-chat/simplexmq/blob/master/protocol/agent-protocol.md

Synopsis

SMP agent protocol types

data AParty Source #

SMP agent protocol participants.

Constructors

Agent 
Client 

Instances

Instances details
Eq AParty Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Methods

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

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

Show AParty Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

TestEquality SAParty Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Methods

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

data SAParty :: AParty -> Type where Source #

Singleton types for SMP agent protocol participants.

Constructors

SAgent :: SAParty Agent 
SClient :: SAParty Client 

Instances

Instances details
TestEquality SAParty Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Methods

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

Eq (SAParty p) Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Methods

(==) :: SAParty p -> SAParty p -> Bool #

(/=) :: SAParty p -> SAParty p -> Bool #

Show (SAParty p) Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Methods

showsPrec :: Int -> SAParty p -> ShowS #

show :: SAParty p -> String #

showList :: [SAParty p] -> ShowS #

data MsgMeta Source #

Agent message metadata sent to the client

Instances

Instances details
Eq MsgMeta Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Methods

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

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

Show MsgMeta Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

data SMPMessage Source #

SMP message formats.

Constructors

SMPConfirmation

SMP confirmation (see SMP protocol)

Fields

  • senderKey :: SenderPublicKey

    sender's public key to use for authentication of sender's commands at the recepient's server

  • connInfo :: ConnInfo

    sender's information to be associated with the connection, e.g. sender's profile information

SMPMessage

Agent message header and envelope for client messages (see SMP agent protocol)

Fields

Instances

Instances details
Show SMPMessage Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

data AMessage where Source #

Constructors

HELLO :: VerificationKey -> AckMode -> AMessage

the first message in the queue to validate it is secured

REPLY :: ConnectionRequest CMInvitation -> AMessage

reply queue information

A_MSG :: MsgBody -> AMessage

agent envelope for the client message

A_INV :: ConnectionRequest CMInvitation -> ConnInfo -> AMessage

connection request with the invitation to connect

Instances

Instances details
Show AMessage Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

data SMPServer Source #

SMP server location and transport key digest (hash).

Constructors

SMPServer 

data AgentErrorType Source #

Error type used in errors sent to agent clients.

Constructors

CMD CommandErrorType

command or response error

CONN ConnectionErrorType

connection errors

SMP ErrorType

SMP protocol errors forwarded to agent clients

BROKER BrokerErrorType

SMP server errors

AGENT SMPAgentError

errors of other agents

INTERNAL String

agent implementation or dependency errors

Instances

Instances details
Eq AgentErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Read AgentErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Show AgentErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Generic AgentErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Associated Types

type Rep AgentErrorType :: Type -> Type #

Arbitrary AgentErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Exception AgentErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

type Rep AgentErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

data CommandErrorType Source #

SMP agent protocol command or response error.

Constructors

PROHIBITED

command is prohibited in this context

SYNTAX

command syntax is invalid

NO_CONN

entity ID is required with this command

SIZE

message size is not correct (no terminating space)

LARGE

message does not fit in SMP block

Instances

Instances details
Eq CommandErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Read CommandErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Show CommandErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Generic CommandErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Associated Types

type Rep CommandErrorType :: Type -> Type #

Arbitrary CommandErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Exception CommandErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

type Rep CommandErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

type Rep CommandErrorType = D1 ('MetaData "CommandErrorType" "Simplex.Messaging.Agent.Protocol" "simplexmq-0.5.2-7Hr1oNZfhPnIOy42ZNhVg7" 'False) ((C1 ('MetaCons "PROHIBITED" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SYNTAX" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NO_CONN" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SIZE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LARGE" 'PrefixI 'False) (U1 :: Type -> Type))))

data ConnectionErrorType Source #

Connection error.

Constructors

NOT_FOUND

connection alias is not in the database

DUPLICATE

connection alias already exists

SIMPLEX

connection is simplex, but operation requires another queue

Instances

Instances details
Eq ConnectionErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Read ConnectionErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Show ConnectionErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Generic ConnectionErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Associated Types

type Rep ConnectionErrorType :: Type -> Type #

Arbitrary ConnectionErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Exception ConnectionErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

type Rep ConnectionErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

type Rep ConnectionErrorType = D1 ('MetaData "ConnectionErrorType" "Simplex.Messaging.Agent.Protocol" "simplexmq-0.5.2-7Hr1oNZfhPnIOy42ZNhVg7" 'False) (C1 ('MetaCons "NOT_FOUND" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DUPLICATE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SIMPLEX" 'PrefixI 'False) (U1 :: Type -> Type)))

data BrokerErrorType Source #

SMP server errors.

Constructors

RESPONSE ErrorType

invalid server response (failed to parse)

UNEXPECTED

unexpected response

NETWORK

network error

TRANSPORT TransportError

handshake or other transport error

TIMEOUT

command response timeout

Instances

Instances details
Eq BrokerErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Read BrokerErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Show BrokerErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Generic BrokerErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Associated Types

type Rep BrokerErrorType :: Type -> Type #

Arbitrary BrokerErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Exception BrokerErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

type Rep BrokerErrorType Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

type Rep BrokerErrorType = D1 ('MetaData "BrokerErrorType" "Simplex.Messaging.Agent.Protocol" "simplexmq-0.5.2-7Hr1oNZfhPnIOy42ZNhVg7" 'False) ((C1 ('MetaCons "RESPONSE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ErrorType)) :+: C1 ('MetaCons "UNEXPECTED" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NETWORK" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TRANSPORT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TransportError)) :+: C1 ('MetaCons "TIMEOUT" 'PrefixI 'False) (U1 :: Type -> Type))))

data SMPAgentError Source #

Errors of another SMP agent.

Constructors

A_MESSAGE

possibly should include bytestring that failed to parse

A_PROHIBITED

possibly should include the prohibited SMP/agent message

A_ENCRYPTION

cannot RSA/AES-decrypt or parse decrypted header

A_SIGNATURE

invalid RSA signature

Instances

Instances details
Eq SMPAgentError Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Read SMPAgentError Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Show SMPAgentError Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Generic SMPAgentError Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Associated Types

type Rep SMPAgentError :: Type -> Type #

Arbitrary SMPAgentError Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Exception SMPAgentError Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

type Rep SMPAgentError Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

type Rep SMPAgentError = D1 ('MetaData "SMPAgentError" "Simplex.Messaging.Agent.Protocol" "simplexmq-0.5.2-7Hr1oNZfhPnIOy42ZNhVg7" 'False) ((C1 ('MetaCons "A_MESSAGE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "A_PROHIBITED" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "A_ENCRYPTION" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "A_SIGNATURE" 'PrefixI 'False) (U1 :: Type -> Type)))

type ATransmission p = (ACorrId, ConnId, ACommand p) Source #

Parsed SMP agent protocol transmission.

type ATransmissionOrError p = (ACorrId, ConnId, Either AgentErrorType (ACommand p)) Source #

SMP agent protocol transmission or transmission error.

type ARawTransmission = (ByteString, ByteString, ByteString) Source #

Raw (unparsed) SMP agent protocol transmission.

type ConnId = ByteString Source #

SMP agent connection alias.

newtype AckMode Source #

Message acknowledgement mode of the connection.

Constructors

AckMode OnOff 

Instances

Instances details
Eq AckMode Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Methods

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

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

Show AckMode Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

data OnOff Source #

Connection modes.

Constructors

On 
Off 

Instances

Instances details
Eq OnOff Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Methods

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

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

Read OnOff Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Show OnOff Source # 
Instance details

Defined in Simplex.Messaging.Agent.Protocol

Methods

showsPrec :: Int -> OnOff -> ShowS #

show :: OnOff -> String #

showList :: [OnOff] -> ShowS #

data MsgIntegrity Source #

Result of received message integrity validation.

Constructors

MsgOk 
MsgError MsgErrorType 

data MsgErrorType Source #

Error of message integrity validation.

data QueueStatus Source #

SMP queue status.

Constructors

New

queue is created

Confirmed

queue is confirmed by the sender

Secured

queue is secured with sender key (only used by the queue recipient)

Active

queue is active

Disabled

queue is disabled (only used by the queue recipient)

type SignatureKey = APrivateKey Source #

Private key used to sign SMP commands

type VerificationKey = PublicKey Source #

Public key used by SMP server to authorize (verify) SMP commands.

type EncryptionKey = PublicKey Source #

Public key used to E2E encrypt SMP messages.

type DecryptionKey = SafePrivateKey Source #

Private key used to E2E decrypt SMP messages.

Parse and serialize

serializeCommand :: ACommand p -> ByteString Source #

Serialize SMP agent command.

serializeSMPMessage :: SMPMessage -> ByteString Source #

Serialize SMP message.

serializeMsgIntegrity :: MsgIntegrity -> ByteString Source #

Serialize message integrity validation result.

serializeServer :: SMPServer -> ByteString Source #

Serialize SMP server location.

serializeSMPQueueUri :: SMPQueueUri -> ByteString Source #

Serialize SMP queue information that is sent out-of-band.

serializeAgentError :: AgentErrorType -> ByteString Source #

Serialize SMP agent protocol error.

commandP :: Parser ACmd Source #

SMP agent command and response parser

smpServerP :: Parser SMPServer Source #

SMP server location parser.

smpQueueUriP :: Parser SMPQueueUri Source #

SMP queue information parser.

msgIntegrityP :: Parser MsgIntegrity Source #

Message integrity validation result parser.

agentErrorTypeP :: Parser AgentErrorType Source #

SMP agent protocol error parser.

TCP transport functions

tPut :: (Transport c, MonadIO m) => c -> ATransmission p -> m () Source #

Send SMP agent protocol command (or response) to TCP connection.

tGet :: forall c m p. (Transport c, MonadIO m) => SAParty p -> c -> m (ATransmissionOrError p) Source #

Receive client and agent transmissions from TCP connection.

tPutRaw :: Transport c => c -> ARawTransmission -> IO () Source #

Send raw (unparsed) SMP agent protocol transmission to TCP connection.

tGetRaw :: Transport c => c -> IO ARawTransmission Source #

Receive raw (unparsed) SMP agent protocol transmission from TCP connection.