{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-unticked-promoted-constructors #-}
module Simplex.Messaging.Protocol
(
Command (..),
Party (..),
Cmd (..),
SParty (..),
ErrorType (..),
CommandError (..),
Transmission,
SignedTransmission,
SignedTransmissionOrError,
RawTransmission,
SignedRawTransmission,
CorrId (..),
QueueId,
RecipientId,
SenderId,
RecipientPrivateKey,
RecipientPublicKey,
SenderPrivateKey,
SenderPublicKey,
Encoded,
MsgId,
MsgBody,
serializeTransmission,
serializeCommand,
serializeErrorType,
transmissionP,
commandP,
errorTypeP,
tPut,
tGet,
fromClient,
fromServer,
)
where
import Control.Applicative ((<|>))
import Control.Monad
import Control.Monad.Except
import Data.Attoparsec.ByteString.Char8 (Parser)
import qualified Data.Attoparsec.ByteString.Char8 as A
import Data.ByteString.Base64
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as B
import Data.Functor (($>))
import Data.Kind
import Data.String
import Data.Time.Clock
import Data.Time.ISO8601
import GHC.Generics (Generic)
import Generic.Random (genericArbitraryU)
import qualified Simplex.Messaging.Crypto as C
import Simplex.Messaging.Parsers
import Simplex.Messaging.Transport (THandle, TransportError (..), tGetEncrypted, tPutEncrypted)
import Simplex.Messaging.Util
import Test.QuickCheck (Arbitrary (..))
data Party = Broker | Recipient | Sender
deriving (Int -> Party -> ShowS
[Party] -> ShowS
Party -> String
(Int -> Party -> ShowS)
-> (Party -> String) -> ([Party] -> ShowS) -> Show Party
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Party] -> ShowS
$cshowList :: [Party] -> ShowS
show :: Party -> String
$cshow :: Party -> String
showsPrec :: Int -> Party -> ShowS
$cshowsPrec :: Int -> Party -> ShowS
Show)
data SParty :: Party -> Type where
SBroker :: SParty Broker
SRecipient :: SParty Recipient
SSender :: SParty Sender
deriving instance Show (SParty a)
data Cmd = forall a. Cmd (SParty a) (Command a)
deriving instance Show Cmd
type Transmission = (CorrId, QueueId, Cmd)
type SignedTransmission = (C.Signature, Transmission)
type TransmissionOrError = (CorrId, QueueId, Either ErrorType Cmd)
type SignedTransmissionOrError = (C.Signature, TransmissionOrError)
type RawTransmission = (ByteString, ByteString, ByteString, ByteString)
type SignedRawTransmission = (C.Signature, ByteString)
type RecipientId = QueueId
type SenderId = QueueId
type QueueId = Encoded
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
deriving instance Show (Command a)
deriving instance Eq (Command a)
type Encoded = ByteString
newtype CorrId = CorrId {CorrId -> ByteString
bs :: ByteString} deriving (CorrId -> CorrId -> Bool
(CorrId -> CorrId -> Bool)
-> (CorrId -> CorrId -> Bool) -> Eq CorrId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CorrId -> CorrId -> Bool
$c/= :: CorrId -> CorrId -> Bool
== :: CorrId -> CorrId -> Bool
$c== :: CorrId -> CorrId -> Bool
Eq, Eq CorrId
Eq CorrId =>
(CorrId -> CorrId -> Ordering)
-> (CorrId -> CorrId -> Bool)
-> (CorrId -> CorrId -> Bool)
-> (CorrId -> CorrId -> Bool)
-> (CorrId -> CorrId -> Bool)
-> (CorrId -> CorrId -> CorrId)
-> (CorrId -> CorrId -> CorrId)
-> Ord CorrId
CorrId -> CorrId -> Bool
CorrId -> CorrId -> Ordering
CorrId -> CorrId -> CorrId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CorrId -> CorrId -> CorrId
$cmin :: CorrId -> CorrId -> CorrId
max :: CorrId -> CorrId -> CorrId
$cmax :: CorrId -> CorrId -> CorrId
>= :: CorrId -> CorrId -> Bool
$c>= :: CorrId -> CorrId -> Bool
> :: CorrId -> CorrId -> Bool
$c> :: CorrId -> CorrId -> Bool
<= :: CorrId -> CorrId -> Bool
$c<= :: CorrId -> CorrId -> Bool
< :: CorrId -> CorrId -> Bool
$c< :: CorrId -> CorrId -> Bool
compare :: CorrId -> CorrId -> Ordering
$ccompare :: CorrId -> CorrId -> Ordering
$cp1Ord :: Eq CorrId
Ord, Int -> CorrId -> ShowS
[CorrId] -> ShowS
CorrId -> String
(Int -> CorrId -> ShowS)
-> (CorrId -> String) -> ([CorrId] -> ShowS) -> Show CorrId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CorrId] -> ShowS
$cshowList :: [CorrId] -> ShowS
show :: CorrId -> String
$cshow :: CorrId -> String
showsPrec :: Int -> CorrId -> ShowS
$cshowsPrec :: Int -> CorrId -> ShowS
Show)
instance IsString CorrId where
fromString :: String -> CorrId
fromString = ByteString -> CorrId
CorrId (ByteString -> CorrId)
-> (String -> ByteString) -> String -> CorrId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
forall a. IsString a => String -> a
fromString
type RecipientPrivateKey = C.SafePrivateKey
type RecipientPublicKey = C.PublicKey
type SenderPrivateKey = C.SafePrivateKey
type SenderPublicKey = C.PublicKey
type MsgId = Encoded
type MsgBody = ByteString
data ErrorType
=
BLOCK
|
CMD CommandError
|
AUTH
|
NO_MSG
|
INTERNAL
|
DUPLICATE_
deriving (ErrorType -> ErrorType -> Bool
(ErrorType -> ErrorType -> Bool)
-> (ErrorType -> ErrorType -> Bool) -> Eq ErrorType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ErrorType -> ErrorType -> Bool
$c/= :: ErrorType -> ErrorType -> Bool
== :: ErrorType -> ErrorType -> Bool
$c== :: ErrorType -> ErrorType -> Bool
Eq, (forall x. ErrorType -> Rep ErrorType x)
-> (forall x. Rep ErrorType x -> ErrorType) -> Generic ErrorType
forall x. Rep ErrorType x -> ErrorType
forall x. ErrorType -> Rep ErrorType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ErrorType x -> ErrorType
$cfrom :: forall x. ErrorType -> Rep ErrorType x
Generic, ReadPrec [ErrorType]
ReadPrec ErrorType
Int -> ReadS ErrorType
ReadS [ErrorType]
(Int -> ReadS ErrorType)
-> ReadS [ErrorType]
-> ReadPrec ErrorType
-> ReadPrec [ErrorType]
-> Read ErrorType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ErrorType]
$creadListPrec :: ReadPrec [ErrorType]
readPrec :: ReadPrec ErrorType
$creadPrec :: ReadPrec ErrorType
readList :: ReadS [ErrorType]
$creadList :: ReadS [ErrorType]
readsPrec :: Int -> ReadS ErrorType
$creadsPrec :: Int -> ReadS ErrorType
Read, Int -> ErrorType -> ShowS
[ErrorType] -> ShowS
ErrorType -> String
(Int -> ErrorType -> ShowS)
-> (ErrorType -> String)
-> ([ErrorType] -> ShowS)
-> Show ErrorType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ErrorType] -> ShowS
$cshowList :: [ErrorType] -> ShowS
show :: ErrorType -> String
$cshow :: ErrorType -> String
showsPrec :: Int -> ErrorType -> ShowS
$cshowsPrec :: Int -> ErrorType -> ShowS
Show)
data CommandError
=
PROHIBITED
|
KEY_SIZE
|
SYNTAX
|
NO_AUTH
|
HAS_AUTH
|
NO_QUEUE
deriving (CommandError -> CommandError -> Bool
(CommandError -> CommandError -> Bool)
-> (CommandError -> CommandError -> Bool) -> Eq CommandError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandError -> CommandError -> Bool
$c/= :: CommandError -> CommandError -> Bool
== :: CommandError -> CommandError -> Bool
$c== :: CommandError -> CommandError -> Bool
Eq, (forall x. CommandError -> Rep CommandError x)
-> (forall x. Rep CommandError x -> CommandError)
-> Generic CommandError
forall x. Rep CommandError x -> CommandError
forall x. CommandError -> Rep CommandError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CommandError x -> CommandError
$cfrom :: forall x. CommandError -> Rep CommandError x
Generic, ReadPrec [CommandError]
ReadPrec CommandError
Int -> ReadS CommandError
ReadS [CommandError]
(Int -> ReadS CommandError)
-> ReadS [CommandError]
-> ReadPrec CommandError
-> ReadPrec [CommandError]
-> Read CommandError
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CommandError]
$creadListPrec :: ReadPrec [CommandError]
readPrec :: ReadPrec CommandError
$creadPrec :: ReadPrec CommandError
readList :: ReadS [CommandError]
$creadList :: ReadS [CommandError]
readsPrec :: Int -> ReadS CommandError
$creadsPrec :: Int -> ReadS CommandError
Read, Int -> CommandError -> ShowS
[CommandError] -> ShowS
CommandError -> String
(Int -> CommandError -> ShowS)
-> (CommandError -> String)
-> ([CommandError] -> ShowS)
-> Show CommandError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandError] -> ShowS
$cshowList :: [CommandError] -> ShowS
show :: CommandError -> String
$cshow :: CommandError -> String
showsPrec :: Int -> CommandError -> ShowS
$cshowsPrec :: Int -> CommandError -> ShowS
Show)
instance Arbitrary ErrorType where arbitrary :: Gen ErrorType
arbitrary = Gen ErrorType
forall a. (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
genericArbitraryU
instance Arbitrary CommandError where arbitrary :: Gen CommandError
arbitrary = Gen CommandError
forall a. (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
genericArbitraryU
transmissionP :: Parser RawTransmission
transmissionP :: Parser RawTransmission
transmissionP = do
ByteString
signature <- Parser ByteString ByteString
segment
ByteString
corrId <- Parser ByteString ByteString
segment
ByteString
queueId <- Parser ByteString ByteString
segment
ByteString
command <- Parser ByteString ByteString
A.takeByteString
RawTransmission -> Parser RawTransmission
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
signature, ByteString
corrId, ByteString
queueId, ByteString
command)
where
segment :: Parser ByteString ByteString
segment = (Char -> Bool) -> Parser ByteString ByteString
A.takeTill (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== ' ') Parser ByteString ByteString
-> Parser ByteString ByteString -> Parser ByteString ByteString
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* " "
commandP :: Parser Cmd
commandP :: Parser Cmd
commandP =
"NEW " Parser ByteString ByteString -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Cmd
newCmd
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "IDS " Parser ByteString ByteString -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Cmd
idsResp
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "SUB" Parser ByteString ByteString -> Cmd -> Parser Cmd
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> SParty 'Recipient -> Command 'Recipient -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Recipient
SRecipient Command 'Recipient
SUB
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "KEY " Parser ByteString ByteString -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Cmd
keyCmd
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "ACK" Parser ByteString ByteString -> Cmd -> Parser Cmd
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> SParty 'Recipient -> Command 'Recipient -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Recipient
SRecipient Command 'Recipient
ACK
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "OFF" Parser ByteString ByteString -> Cmd -> Parser Cmd
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> SParty 'Recipient -> Command 'Recipient -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Recipient
SRecipient Command 'Recipient
OFF
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "DEL" Parser ByteString ByteString -> Cmd -> Parser Cmd
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> SParty 'Recipient -> Command 'Recipient -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Recipient
SRecipient Command 'Recipient
DEL
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "SEND " Parser ByteString ByteString -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Cmd
sendCmd
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "PING" Parser ByteString ByteString -> Cmd -> Parser Cmd
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> SParty 'Sender -> Command 'Sender -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Sender
SSender Command 'Sender
PING
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "MSG " Parser ByteString ByteString -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Cmd
message
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "END" Parser ByteString ByteString -> Cmd -> Parser Cmd
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> SParty 'Broker -> Command 'Broker -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Broker
SBroker Command 'Broker
END
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "OK" Parser ByteString ByteString -> Cmd -> Parser Cmd
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> SParty 'Broker -> Command 'Broker -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Broker
SBroker Command 'Broker
OK
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "ERR " Parser ByteString ByteString -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Cmd
serverError
Parser Cmd -> Parser Cmd -> Parser Cmd
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> "PONG" Parser ByteString ByteString -> Cmd -> Parser Cmd
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> SParty 'Broker -> Command 'Broker -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Broker
SBroker Command 'Broker
PONG
where
newCmd :: Parser Cmd
newCmd = SParty 'Recipient -> Command 'Recipient -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Recipient
SRecipient (Command 'Recipient -> Cmd)
-> (RecipientPublicKey -> Command 'Recipient)
-> RecipientPublicKey
-> Cmd
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RecipientPublicKey -> Command 'Recipient
NEW (RecipientPublicKey -> Cmd)
-> Parser ByteString RecipientPublicKey -> Parser Cmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString RecipientPublicKey
C.pubKeyP
idsResp :: Parser Cmd
idsResp = SParty 'Broker -> Command 'Broker -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Broker
SBroker (Command 'Broker -> Cmd)
-> Parser ByteString (Command 'Broker) -> Parser Cmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ByteString -> ByteString -> Command 'Broker
IDS (ByteString -> ByteString -> Command 'Broker)
-> Parser ByteString ByteString
-> Parser ByteString (ByteString -> Command 'Broker)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser ByteString ByteString
base64P Parser ByteString ByteString
-> Parser ByteString Char -> Parser ByteString ByteString
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ByteString Char
A.space) Parser ByteString (ByteString -> Command 'Broker)
-> Parser ByteString ByteString
-> Parser ByteString (Command 'Broker)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser ByteString ByteString
base64P)
keyCmd :: Parser Cmd
keyCmd = SParty 'Recipient -> Command 'Recipient -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Recipient
SRecipient (Command 'Recipient -> Cmd)
-> (RecipientPublicKey -> Command 'Recipient)
-> RecipientPublicKey
-> Cmd
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RecipientPublicKey -> Command 'Recipient
KEY (RecipientPublicKey -> Cmd)
-> Parser ByteString RecipientPublicKey -> Parser Cmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString RecipientPublicKey
C.pubKeyP
sendCmd :: Parser Cmd
sendCmd = do
Int
size <- Parser Int
forall a. Integral a => Parser a
A.decimal Parser Int -> Parser ByteString Char -> Parser Int
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ByteString Char
A.space
SParty 'Sender -> Command 'Sender -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Sender
SSender (Command 'Sender -> Cmd)
-> (ByteString -> Command 'Sender) -> ByteString -> Cmd
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Command 'Sender
SEND (ByteString -> Cmd) -> Parser ByteString ByteString -> Parser Cmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser ByteString ByteString
A.take Int
size Parser Cmd -> Parser ByteString Char -> Parser Cmd
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ByteString Char
A.space
message :: Parser Cmd
message = do
ByteString
msgId <- Parser ByteString ByteString
base64P Parser ByteString ByteString
-> Parser ByteString Char -> Parser ByteString ByteString
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ByteString Char
A.space
UTCTime
ts <- Parser UTCTime
tsISO8601P Parser UTCTime -> Parser ByteString Char -> Parser UTCTime
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ByteString Char
A.space
Int
size <- Parser Int
forall a. Integral a => Parser a
A.decimal Parser Int -> Parser ByteString Char -> Parser Int
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ByteString Char
A.space
SParty 'Broker -> Command 'Broker -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Broker
SBroker (Command 'Broker -> Cmd)
-> (ByteString -> Command 'Broker) -> ByteString -> Cmd
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> UTCTime -> ByteString -> Command 'Broker
MSG ByteString
msgId UTCTime
ts (ByteString -> Cmd) -> Parser ByteString ByteString -> Parser Cmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser ByteString ByteString
A.take Int
size Parser Cmd -> Parser ByteString Char -> Parser Cmd
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ByteString Char
A.space
serverError :: Parser Cmd
serverError = SParty 'Broker -> Command 'Broker -> Cmd
forall (a :: Party). SParty a -> Command a -> Cmd
Cmd SParty 'Broker
SBroker (Command 'Broker -> Cmd)
-> (ErrorType -> Command 'Broker) -> ErrorType -> Cmd
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorType -> Command 'Broker
ERR (ErrorType -> Cmd) -> Parser ByteString ErrorType -> Parser Cmd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString ErrorType
errorTypeP
parseCommand :: ByteString -> Either ErrorType Cmd
parseCommand :: ByteString -> Either ErrorType Cmd
parseCommand = Parser Cmd -> ErrorType -> ByteString -> Either ErrorType Cmd
forall a e. Parser a -> e -> ByteString -> Either e a
parse (Parser Cmd
commandP Parser Cmd -> Parser ByteString ByteString -> Parser Cmd
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* " " Parser Cmd -> Parser ByteString ByteString -> Parser Cmd
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ByteString ByteString
A.takeByteString) (ErrorType -> ByteString -> Either ErrorType Cmd)
-> ErrorType -> ByteString -> Either ErrorType Cmd
forall a b. (a -> b) -> a -> b
$ CommandError -> ErrorType
CMD CommandError
SYNTAX
serializeCommand :: Cmd -> ByteString
serializeCommand :: Cmd -> ByteString
serializeCommand = \case
Cmd SRecipient (NEW rKey :: RecipientPublicKey
rKey) -> "NEW " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> RecipientPublicKey -> ByteString
C.serializePubKey RecipientPublicKey
rKey
Cmd SRecipient (KEY sKey :: RecipientPublicKey
sKey) -> "KEY " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> RecipientPublicKey -> ByteString
C.serializePubKey RecipientPublicKey
sKey
Cmd SRecipient cmd :: Command a
cmd -> Command a -> ByteString
forall a. Show a => a -> ByteString
bshow Command a
cmd
Cmd SSender (SEND msgBody :: ByteString
msgBody) -> "SEND " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString -> ByteString
serializeMsg ByteString
msgBody
Cmd SSender PING -> "PING"
Cmd SBroker (MSG msgId :: ByteString
msgId ts :: UTCTime
ts msgBody :: ByteString
msgBody) ->
[ByteString] -> ByteString
B.unwords ["MSG", ByteString -> ByteString
encode ByteString
msgId, String -> ByteString
B.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ UTCTime -> String
formatISO8601Millis UTCTime
ts, ByteString -> ByteString
serializeMsg ByteString
msgBody]
Cmd SBroker (IDS rId :: ByteString
rId sId :: ByteString
sId) -> [ByteString] -> ByteString
B.unwords ["IDS", ByteString -> ByteString
encode ByteString
rId, ByteString -> ByteString
encode ByteString
sId]
Cmd SBroker (ERR err :: ErrorType
err) -> "ERR " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ErrorType -> ByteString
serializeErrorType ErrorType
err
Cmd SBroker resp :: Command a
resp -> Command a -> ByteString
forall a. Show a => a -> ByteString
bshow Command a
resp
where
serializeMsg :: ByteString -> ByteString
serializeMsg msgBody :: ByteString
msgBody = Int -> ByteString
forall a. Show a => a -> ByteString
bshow (ByteString -> Int
B.length ByteString
msgBody) ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> " " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
msgBody ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> " "
errorTypeP :: Parser ErrorType
errorTypeP :: Parser ByteString ErrorType
errorTypeP = "CMD " Parser ByteString ByteString
-> Parser ByteString ErrorType -> Parser ByteString ErrorType
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (CommandError -> ErrorType
CMD (CommandError -> ErrorType)
-> Parser ByteString CommandError -> Parser ByteString ErrorType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString CommandError
forall a. Read a => Parser a
parseRead1) Parser ByteString ErrorType
-> Parser ByteString ErrorType -> Parser ByteString ErrorType
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser ByteString ErrorType
forall a. Read a => Parser a
parseRead1
serializeErrorType :: ErrorType -> ByteString
serializeErrorType :: ErrorType -> ByteString
serializeErrorType = ErrorType -> ByteString
forall a. Show a => a -> ByteString
bshow
tPut :: THandle -> SignedRawTransmission -> IO (Either TransportError ())
tPut :: THandle -> SignedRawTransmission -> IO (Either TransportError ())
tPut th :: THandle
th (C.Signature sig :: ByteString
sig, t :: ByteString
t) =
THandle -> ByteString -> IO (Either TransportError ())
tPutEncrypted THandle
th (ByteString -> IO (Either TransportError ()))
-> ByteString -> IO (Either TransportError ())
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
encode ByteString
sig ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> " " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
t ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> " "
serializeTransmission :: Transmission -> ByteString
serializeTransmission :: Transmission -> ByteString
serializeTransmission (CorrId corrId :: ByteString
corrId, queueId :: ByteString
queueId, command :: Cmd
command) =
ByteString -> [ByteString] -> ByteString
B.intercalate " " [ByteString
corrId, ByteString -> ByteString
encode ByteString
queueId, Cmd -> ByteString
serializeCommand Cmd
command]
fromClient :: Cmd -> Either ErrorType Cmd
fromClient :: Cmd -> Either ErrorType Cmd
fromClient = \case
Cmd SBroker _ -> ErrorType -> Either ErrorType Cmd
forall a b. a -> Either a b
Left (ErrorType -> Either ErrorType Cmd)
-> ErrorType -> Either ErrorType Cmd
forall a b. (a -> b) -> a -> b
$ CommandError -> ErrorType
CMD CommandError
PROHIBITED
cmd :: Cmd
cmd -> Cmd -> Either ErrorType Cmd
forall a b. b -> Either a b
Right Cmd
cmd
fromServer :: Cmd -> Either ErrorType Cmd
fromServer :: Cmd -> Either ErrorType Cmd
fromServer = \case
cmd :: Cmd
cmd@(Cmd SBroker _) -> Cmd -> Either ErrorType Cmd
forall a b. b -> Either a b
Right Cmd
cmd
_ -> ErrorType -> Either ErrorType Cmd
forall a b. a -> Either a b
Left (ErrorType -> Either ErrorType Cmd)
-> ErrorType -> Either ErrorType Cmd
forall a b. (a -> b) -> a -> b
$ CommandError -> ErrorType
CMD CommandError
PROHIBITED
tGetParse :: THandle -> IO (Either TransportError RawTransmission)
tGetParse :: THandle -> IO (Either TransportError RawTransmission)
tGetParse th :: THandle
th = (Either TransportError ByteString
-> (ByteString -> Either TransportError RawTransmission)
-> Either TransportError RawTransmission
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Parser RawTransmission
-> TransportError
-> ByteString
-> Either TransportError RawTransmission
forall a e. Parser a -> e -> ByteString -> Either e a
parse Parser RawTransmission
transmissionP TransportError
TEBadBlock) (Either TransportError ByteString
-> Either TransportError RawTransmission)
-> IO (Either TransportError ByteString)
-> IO (Either TransportError RawTransmission)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> THandle -> IO (Either TransportError ByteString)
tGetEncrypted THandle
th
tGet :: forall m. MonadIO m => (Cmd -> Either ErrorType Cmd) -> THandle -> m SignedTransmissionOrError
tGet :: (Cmd -> Either ErrorType Cmd)
-> THandle -> m SignedTransmissionOrError
tGet fromParty :: Cmd -> Either ErrorType Cmd
fromParty th :: THandle
th = IO (Either TransportError RawTransmission)
-> m (Either TransportError RawTransmission)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (THandle -> IO (Either TransportError RawTransmission)
tGetParse THandle
th) m (Either TransportError RawTransmission)
-> (Either TransportError RawTransmission
-> m SignedTransmissionOrError)
-> m SignedTransmissionOrError
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Either TransportError RawTransmission
-> m SignedTransmissionOrError
decodeParseValidate
where
decodeParseValidate :: Either TransportError RawTransmission -> m SignedTransmissionOrError
decodeParseValidate :: Either TransportError RawTransmission
-> m SignedTransmissionOrError
decodeParseValidate = \case
Right (signature :: ByteString
signature, corrId :: ByteString
corrId, queueId :: ByteString
queueId, command :: ByteString
command) ->
let decodedTransmission :: Either String RawTransmission
decodedTransmission = (ByteString -> ByteString -> RawTransmission)
-> Either String ByteString
-> Either String ByteString
-> Either String RawTransmission
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (,ByteString
corrId,,ByteString
command) (ByteString -> Either String ByteString
validSig (ByteString -> Either String ByteString)
-> Either String ByteString -> Either String ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ByteString -> Either String ByteString
decode ByteString
signature) (ByteString -> Either String ByteString
decode ByteString
queueId)
in (String -> m SignedTransmissionOrError)
-> (RawTransmission -> m SignedTransmissionOrError)
-> Either String RawTransmission
-> m SignedTransmissionOrError
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (m SignedTransmissionOrError
-> String -> m SignedTransmissionOrError
forall a b. a -> b -> a
const (m SignedTransmissionOrError
-> String -> m SignedTransmissionOrError)
-> m SignedTransmissionOrError
-> String
-> m SignedTransmissionOrError
forall a b. (a -> b) -> a -> b
$ ByteString -> m SignedTransmissionOrError
tError ByteString
corrId) RawTransmission -> m SignedTransmissionOrError
tParseValidate Either String RawTransmission
decodedTransmission
Left _ -> ByteString -> m SignedTransmissionOrError
tError ""
validSig :: ByteString -> Either String ByteString
validSig :: ByteString -> Either String ByteString
validSig sig :: ByteString
sig
| ByteString -> Bool
B.null ByteString
sig Bool -> Bool -> Bool
|| Int -> Bool
C.validKeySize (ByteString -> Int
B.length ByteString
sig) = ByteString -> Either String ByteString
forall a b. b -> Either a b
Right ByteString
sig
| Bool
otherwise = String -> Either String ByteString
forall a b. a -> Either a b
Left "invalid signature size"
tError :: ByteString -> m SignedTransmissionOrError
tError :: ByteString -> m SignedTransmissionOrError
tError corrId :: ByteString
corrId = SignedTransmissionOrError -> m SignedTransmissionOrError
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> Signature
C.Signature "", (ByteString -> CorrId
CorrId ByteString
corrId, "", ErrorType -> Either ErrorType Cmd
forall a b. a -> Either a b
Left ErrorType
BLOCK))
tParseValidate :: RawTransmission -> m SignedTransmissionOrError
tParseValidate :: RawTransmission -> m SignedTransmissionOrError
tParseValidate t :: RawTransmission
t@(sig :: ByteString
sig, corrId :: ByteString
corrId, queueId :: ByteString
queueId, command :: ByteString
command) = do
let cmd :: Either ErrorType Cmd
cmd = ByteString -> Either ErrorType Cmd
parseCommand ByteString
command Either ErrorType Cmd
-> (Cmd -> Either ErrorType Cmd) -> Either ErrorType Cmd
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Cmd -> Either ErrorType Cmd
fromParty Either ErrorType Cmd
-> (Cmd -> Either ErrorType Cmd) -> Either ErrorType Cmd
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= RawTransmission -> Cmd -> Either ErrorType Cmd
tCredentials RawTransmission
t
SignedTransmissionOrError -> m SignedTransmissionOrError
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> Signature
C.Signature ByteString
sig, (ByteString -> CorrId
CorrId ByteString
corrId, ByteString
queueId, Either ErrorType Cmd
cmd))
tCredentials :: RawTransmission -> Cmd -> Either ErrorType Cmd
tCredentials :: RawTransmission -> Cmd -> Either ErrorType Cmd
tCredentials (signature :: ByteString
signature, _, queueId :: ByteString
queueId, _) cmd :: Cmd
cmd = case Cmd
cmd of
Cmd SBroker (IDS _ _) -> Cmd -> Either ErrorType Cmd
forall a b. b -> Either a b
Right Cmd
cmd
Cmd SBroker (ERR _) -> Cmd -> Either ErrorType Cmd
forall a b. b -> Either a b
Right Cmd
cmd
Cmd SBroker PONG
| ByteString -> Bool
B.null ByteString
queueId -> Cmd -> Either ErrorType Cmd
forall a b. b -> Either a b
Right Cmd
cmd
| Bool
otherwise -> ErrorType -> Either ErrorType Cmd
forall a b. a -> Either a b
Left (ErrorType -> Either ErrorType Cmd)
-> ErrorType -> Either ErrorType Cmd
forall a b. (a -> b) -> a -> b
$ CommandError -> ErrorType
CMD CommandError
HAS_AUTH
Cmd SBroker _
| ByteString -> Bool
B.null ByteString
queueId -> ErrorType -> Either ErrorType Cmd
forall a b. a -> Either a b
Left (ErrorType -> Either ErrorType Cmd)
-> ErrorType -> Either ErrorType Cmd
forall a b. (a -> b) -> a -> b
$ CommandError -> ErrorType
CMD CommandError
NO_QUEUE
| Bool
otherwise -> Cmd -> Either ErrorType Cmd
forall a b. b -> Either a b
Right Cmd
cmd
Cmd SRecipient (NEW _)
| ByteString -> Bool
B.null ByteString
signature -> ErrorType -> Either ErrorType Cmd
forall a b. a -> Either a b
Left (ErrorType -> Either ErrorType Cmd)
-> ErrorType -> Either ErrorType Cmd
forall a b. (a -> b) -> a -> b
$ CommandError -> ErrorType
CMD CommandError
NO_AUTH
| Bool -> Bool
not (ByteString -> Bool
B.null ByteString
queueId) -> ErrorType -> Either ErrorType Cmd
forall a b. a -> Either a b
Left (ErrorType -> Either ErrorType Cmd)
-> ErrorType -> Either ErrorType Cmd
forall a b. (a -> b) -> a -> b
$ CommandError -> ErrorType
CMD CommandError
HAS_AUTH
| Bool
otherwise -> Cmd -> Either ErrorType Cmd
forall a b. b -> Either a b
Right Cmd
cmd
Cmd SSender (SEND _)
| ByteString -> Bool
B.null ByteString
queueId -> ErrorType -> Either ErrorType Cmd
forall a b. a -> Either a b
Left (ErrorType -> Either ErrorType Cmd)
-> ErrorType -> Either ErrorType Cmd
forall a b. (a -> b) -> a -> b
$ CommandError -> ErrorType
CMD CommandError
NO_QUEUE
| Bool
otherwise -> Cmd -> Either ErrorType Cmd
forall a b. b -> Either a b
Right Cmd
cmd
Cmd SSender PING
| ByteString -> Bool
B.null ByteString
queueId Bool -> Bool -> Bool
&& ByteString -> Bool
B.null ByteString
signature -> Cmd -> Either ErrorType Cmd
forall a b. b -> Either a b
Right Cmd
cmd
| Bool
otherwise -> ErrorType -> Either ErrorType Cmd
forall a b. a -> Either a b
Left (ErrorType -> Either ErrorType Cmd)
-> ErrorType -> Either ErrorType Cmd
forall a b. (a -> b) -> a -> b
$ CommandError -> ErrorType
CMD CommandError
HAS_AUTH
Cmd SRecipient _
| ByteString -> Bool
B.null ByteString
signature Bool -> Bool -> Bool
|| ByteString -> Bool
B.null ByteString
queueId -> ErrorType -> Either ErrorType Cmd
forall a b. a -> Either a b
Left (ErrorType -> Either ErrorType Cmd)
-> ErrorType -> Either ErrorType Cmd
forall a b. (a -> b) -> a -> b
$ CommandError -> ErrorType
CMD CommandError
NO_AUTH
| Bool
otherwise -> Cmd -> Either ErrorType Cmd
forall a b. b -> Either a b
Right Cmd
cmd