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

Simplex.Messaging.Protocol

Description

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

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

Synopsis

SMP protocol types

data Command (a :: Party) where Source #

Parameterized type for SMP protocol commands from all participants.

Instances

Instances details
Eq (Command a) Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Methods

(==) :: Command a -> Command a -> Bool #

(/=) :: Command a -> Command a -> Bool #

Show (Command a) Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Methods

showsPrec :: Int -> Command a -> ShowS #

show :: Command a -> String #

showList :: [Command a] -> ShowS #

data Party Source #

SMP protocol participants.

Constructors

Broker 
Recipient 
Sender 

Instances

Instances details
Show Party Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Methods

showsPrec :: Int -> Party -> ShowS #

show :: Party -> String #

showList :: [Party] -> ShowS #

data Cmd Source #

Type for command or response of any participant.

Constructors

forall a. Cmd (SParty a) (Command a) 

Instances

Instances details
Show Cmd Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Methods

showsPrec :: Int -> Cmd -> ShowS #

show :: Cmd -> String #

showList :: [Cmd] -> ShowS #

data SParty :: Party -> Type where Source #

Singleton types for SMP protocol participants.

Instances

Instances details
Show (SParty a) Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Methods

showsPrec :: Int -> SParty a -> ShowS #

show :: SParty a -> String #

showList :: [SParty a] -> ShowS #

data ErrorType Source #

Type for protocol errors.

Constructors

BLOCK

incorrect block format, encoding or signature size

CMD CommandError

SMP command is unknown or has invalid syntax

AUTH

command authorization error - bad signature or non-existing SMP queue

QUOTA

SMP queue capacity is exceeded on the server

NO_MSG

ACK command is sent without message to be acknowledged

INTERNAL

internal server error

DUPLICATE_

used internally, never returned by the server (to be removed)

Instances

Instances details
Eq ErrorType Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Read ErrorType Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Show ErrorType Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Generic ErrorType Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Associated Types

type Rep ErrorType :: Type -> Type #

Arbitrary ErrorType Source # 
Instance details

Defined in Simplex.Messaging.Protocol

type Rep ErrorType Source # 
Instance details

Defined in Simplex.Messaging.Protocol

type Rep ErrorType = D1 ('MetaData "ErrorType" "Simplex.Messaging.Protocol" "simplexmq-0.5.2-7Hr1oNZfhPnIOy42ZNhVg7" 'False) ((C1 ('MetaCons "BLOCK" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CMD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommandError)) :+: C1 ('MetaCons "AUTH" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "QUOTA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NO_MSG" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "INTERNAL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DUPLICATE_" 'PrefixI 'False) (U1 :: Type -> Type))))

data CommandError Source #

SMP command error type.

Constructors

PROHIBITED

server response sent from client or vice versa

KEY_SIZE

bad RSA key size in NEW or KEY commands (only 1024, 2048 and 4096 bits keys are allowed)

SYNTAX

error parsing command

NO_AUTH

transmission has no required credentials (signature or queue ID)

HAS_AUTH

transmission has credentials that are not allowed for this command

NO_QUEUE

transmission has no required queue ID

Instances

Instances details
Eq CommandError Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Read CommandError Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Show CommandError Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Generic CommandError Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Associated Types

type Rep CommandError :: Type -> Type #

Arbitrary CommandError Source # 
Instance details

Defined in Simplex.Messaging.Protocol

type Rep CommandError Source # 
Instance details

Defined in Simplex.Messaging.Protocol

type Rep CommandError = D1 ('MetaData "CommandError" "Simplex.Messaging.Protocol" "simplexmq-0.5.2-7Hr1oNZfhPnIOy42ZNhVg7" 'False) ((C1 ('MetaCons "PROHIBITED" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KEY_SIZE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SYNTAX" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "NO_AUTH" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HAS_AUTH" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NO_QUEUE" 'PrefixI 'False) (U1 :: Type -> Type))))

type Transmission = (CorrId, QueueId, Cmd) Source #

SMP transmission without signature.

type SignedTransmission = (Signature, Transmission) Source #

SMP transmission with signature.

type SignedTransmissionOrError = (Signature, TransmissionOrError) Source #

signed parsed transmission, with parsing error.

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

unparsed SMP transmission with signature.

type SignedRawTransmission = (Signature, ByteString) Source #

unparsed SMP transmission with signature.

newtype CorrId Source #

Transmission correlation ID.

A newtype to avoid accidentally changing order of transmission parts.

Constructors

CorrId 

Fields

Instances

Instances details
Eq CorrId Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Methods

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

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

Ord CorrId Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Show CorrId Source # 
Instance details

Defined in Simplex.Messaging.Protocol

IsString CorrId Source # 
Instance details

Defined in Simplex.Messaging.Protocol

Methods

fromString :: String -> CorrId #

type QueueId = Encoded Source #

SMP queue ID on the server.

type RecipientId = QueueId Source #

SMP queue ID for the recipient.

type SenderId = QueueId Source #

SMP queue ID for the sender.

type RecipientPrivateKey = SafePrivateKey Source #

Recipient's private key used by the recipient to authorize (sign) SMP commands.

Only used by SMP agent, kept here so its definition is close to respective public key.

type RecipientPublicKey = PublicKey Source #

Recipient's public key used by SMP server to verify authorization of SMP commands.

type SenderPrivateKey = SafePrivateKey Source #

Sender's private key used by the recipient to authorize (sign) SMP commands.

Only used by SMP agent, kept here so its definition is close to respective public key.

type SenderPublicKey = PublicKey Source #

Sender's public key used by SMP server to verify authorization of SMP commands.

type Encoded = ByteString Source #

Base-64 encoded string.

type MsgId = Encoded Source #

SMP message server ID.

type MsgBody = ByteString Source #

SMP message body.

Parse and serialize

serializeTransmission :: Transmission -> ByteString Source #

Serialize SMP transmission.

serializeCommand :: Cmd -> ByteString Source #

Serialize SMP command.

serializeErrorType :: ErrorType -> ByteString Source #

Serialize SMP error.

transmissionP :: Parser RawTransmission Source #

SMP transmission parser.

commandP :: Parser Cmd Source #

SMP command parser.

errorTypeP :: Parser ErrorType Source #

SMP error parser.

TCP transport functions

tPut :: Transport c => THandle c -> SignedRawTransmission -> IO (Either TransportError ()) Source #

Send signed SMP transmission to TCP transport.

tGet :: forall c m. (Transport c, MonadIO m) => (Cmd -> Either ErrorType Cmd) -> THandle c -> m SignedTransmissionOrError Source #

Receive client and server transmissions.

The first argument is used to limit allowed senders. fromClient or fromServer should be used here.

fromClient :: Cmd -> Either ErrorType Cmd Source #

Validate that it is an SMP client command, used with tGet by Server.

fromServer :: Cmd -> Either ErrorType Cmd Source #

Validate that it is an SMP server command, used with tGet by Client.