Copyright | (c) simplex.chat |
---|---|
License | AGPL-3 |
Maintainer | chat@simplex.chat |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
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
- data Command (a :: Party) where
- NEW :: RecipientPublicKey -> Command Recipient
- SUB :: Command Recipient
- KEY :: SenderPublicKey -> Command Recipient
- ACK :: Command Recipient
- OFF :: Command Recipient
- DEL :: Command Recipient
- SEND :: MsgBody -> Command Sender
- PING :: Command Sender
- IDS :: RecipientId -> SenderId -> Command Broker
- MSG :: MsgId -> UTCTime -> MsgBody -> Command Broker
- END :: Command Broker
- OK :: Command Broker
- ERR :: ErrorType -> Command Broker
- PONG :: Command Broker
- data Party
- data Cmd = forall a. Cmd (SParty a) (Command a)
- data SParty :: Party -> Type where
- data ErrorType
- = BLOCK
- | CMD CommandError
- | AUTH
- | QUOTA
- | NO_MSG
- | INTERNAL
- | DUPLICATE_
- data CommandError
- type Transmission = (CorrId, QueueId, Cmd)
- type SignedTransmission = (Signature, Transmission)
- type SignedTransmissionOrError = (Signature, TransmissionOrError)
- type RawTransmission = (ByteString, ByteString, ByteString, ByteString)
- type SignedRawTransmission = (Signature, ByteString)
- newtype CorrId = CorrId {
- bs :: ByteString
- type QueueId = Encoded
- type RecipientId = QueueId
- type SenderId = QueueId
- type RecipientPrivateKey = SafePrivateKey
- type RecipientPublicKey = PublicKey
- type SenderPrivateKey = SafePrivateKey
- type SenderPublicKey = PublicKey
- type Encoded = ByteString
- type MsgId = Encoded
- type MsgBody = ByteString
- serializeTransmission :: Transmission -> ByteString
- serializeCommand :: Cmd -> ByteString
- serializeErrorType :: ErrorType -> ByteString
- transmissionP :: Parser RawTransmission
- commandP :: Parser Cmd
- errorTypeP :: Parser ErrorType
- tPut :: Transport c => THandle c -> SignedRawTransmission -> IO (Either TransportError ())
- tGet :: forall c m. (Transport c, MonadIO m) => (Cmd -> Either ErrorType Cmd) -> THandle c -> m SignedTransmissionOrError
- fromClient :: Cmd -> Either ErrorType Cmd
- fromServer :: Cmd -> Either ErrorType Cmd
SMP protocol types
data Command (a :: Party) where Source #
Parameterized type for SMP protocol commands from all participants.
NEW :: RecipientPublicKey -> Command Recipient | |
SUB :: Command Recipient | |
KEY :: SenderPublicKey -> Command Recipient | |
ACK :: Command Recipient | |
OFF :: Command Recipient | |
DEL :: Command Recipient | |
SEND :: MsgBody -> Command Sender | |
PING :: Command Sender | |
IDS :: RecipientId -> SenderId -> Command Broker | |
MSG :: MsgId -> UTCTime -> MsgBody -> Command Broker | |
END :: Command Broker | |
OK :: Command Broker | |
ERR :: ErrorType -> Command Broker | |
PONG :: Command Broker |
SMP protocol participants.
Type for command or response of any participant.
Type for protocol errors.
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
Eq ErrorType Source # | |
Read ErrorType Source # | |
Show ErrorType Source # | |
Generic ErrorType Source # | |
Arbitrary ErrorType Source # | |
type Rep ErrorType Source # | |
Defined in Simplex.Messaging.Protocol type Rep ErrorType = D1 ('MetaData "ErrorType" "Simplex.Messaging.Protocol" "simplexmq-0.5.1-CSQimoFGQNC4ZJ0aiTG9kT" '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.
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
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.
Transmission correlation ID.
A newtype to avoid accidentally changing order of transmission parts.
CorrId | |
|
type RecipientId = QueueId Source #
SMP queue ID for the recipient.
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 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.
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.