tests for JSON message encoding/decoding (#190)
* tests for JSON message encoding/decoding * fix XContact parsing to allow absent field "content" * update XContact JSON encoding
This commit is contained in:
parent
be537f3a24
commit
cc4fff0ae5
@ -14,7 +14,7 @@
|
||||
module Simplex.Chat.Protocol where
|
||||
|
||||
import Control.Monad ((<=<))
|
||||
import Data.Aeson (FromJSON, ToJSON, (.:), (.=))
|
||||
import Data.Aeson (FromJSON, ToJSON, (.:), (.:?), (.=))
|
||||
import qualified Data.Aeson as J
|
||||
import qualified Data.Aeson.Types as JT
|
||||
import qualified Data.Attoparsec.ByteString.Char8 as A
|
||||
@ -56,7 +56,7 @@ data AppMessage = AppMessage
|
||||
}
|
||||
deriving (Generic, FromJSON)
|
||||
|
||||
instance ToJSON AppMessage where toEncoding = J.genericToEncoding J.defaultOptions
|
||||
instance ToJSON AppMessage where toEncoding = J.genericToEncoding J.defaultOptions {J.omitNothingFields = True}
|
||||
|
||||
newtype ChatMessage = ChatMessage {chatMsgEvent :: ChatMsgEvent}
|
||||
deriving (Eq, Show)
|
||||
@ -250,7 +250,7 @@ appToChatMessage AppMessage {event, params} = do
|
||||
XFile_ -> XFile <$> p "file"
|
||||
XFileAcpt_ -> XFileAcpt <$> p "fileName"
|
||||
XInfo_ -> XInfo <$> p "profile"
|
||||
XContact_ -> XContact <$> p "profile" <*> p "content"
|
||||
XContact_ -> XContact <$> p "profile" <*> JT.parseEither (.:? "content") params
|
||||
XGrpInv_ -> XGrpInv <$> p "groupInvitation"
|
||||
XGrpAcpt_ -> XGrpAcpt <$> p "memberId"
|
||||
XGrpMemNew_ -> XGrpMemNew <$> p "memberInfo"
|
||||
@ -279,7 +279,7 @@ chatToAppMessage ChatMessage {chatMsgEvent} = AppMessage {event, params}
|
||||
XFile fileInv -> o ["file" .= fileInv]
|
||||
XFileAcpt fileName -> o ["fileName" .= fileName]
|
||||
XInfo profile -> o ["profile" .= profile]
|
||||
XContact profile content -> o ["profile" .= profile, "content" .= content]
|
||||
XContact profile content -> o $ maybe id ((:) . ("content" .=)) content ["profile" .= profile]
|
||||
XGrpInv groupInv -> o ["groupInvitation" .= groupInv]
|
||||
XGrpAcpt memId -> o ["memberId" .= memId]
|
||||
XGrpMemNew memInfo -> o ["memberInfo" .= memInfo]
|
||||
|
@ -1,44 +1,121 @@
|
||||
-- {-# LANGUAGE OverloadedLists #-}
|
||||
-- {-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
{-# LANGUAGE OverloadedLists #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module ProtocolTests where
|
||||
|
||||
-- import Data.ByteString.Char8 (ByteString)
|
||||
-- import Simplex.Chat.Protocol.Legacy
|
||||
-- import Simplex.Messaging.Parsers (parseAll)
|
||||
-- import Test.Hspec
|
||||
import Data.ByteString.Char8 (ByteString)
|
||||
import Simplex.Chat.Protocol
|
||||
import Simplex.Chat.Types
|
||||
import Simplex.Messaging.Agent.Protocol
|
||||
import qualified Simplex.Messaging.Crypto as C
|
||||
import Simplex.Messaging.Crypto.Ratchet
|
||||
import Simplex.Messaging.Encoding.String
|
||||
import Simplex.Messaging.Parsers (parseAll)
|
||||
import Simplex.Messaging.Protocol (smpClientVRange)
|
||||
import Test.Hspec
|
||||
|
||||
-- protocolTests :: Spec
|
||||
-- protocolTests = do
|
||||
-- parseChatMessageTest
|
||||
protocolTests :: Spec
|
||||
protocolTests = decodeChatMessageTest
|
||||
|
||||
-- (#==) :: ByteString -> RawChatMessage -> Expectation
|
||||
-- s #== msg = parseAll rawChatMessageP s `shouldBe` Right msg
|
||||
srv :: SMPServer
|
||||
srv =
|
||||
SMPServer
|
||||
{ host = "smp.simplex.im",
|
||||
port = Just "5223",
|
||||
keyHash = C.KeyHash "\215m\248\251"
|
||||
}
|
||||
|
||||
-- parseChatMessageTest :: Spec
|
||||
-- parseChatMessageTest = describe "Raw chat message format" $ do
|
||||
-- it "no parameters and content" $
|
||||
-- "5 x.grp.mem.leave " #== RawChatMessage "x.grp.mem.leave" [] []
|
||||
-- it "one parameter, no content" $
|
||||
-- "6 x.msg.del 3 " #== RawChatMessage "x.msg.del" ["3"] []
|
||||
-- it "with content that fits the message" $
|
||||
-- "7 x.msg.new c.text x.text:11 hello there "
|
||||
-- #== RawChatMessage
|
||||
-- "x.msg.new"
|
||||
-- ["c.text"]
|
||||
-- [RawMsgBodyContent (RawContentType "x" "text") "hello there"]
|
||||
-- it "with DAG reference and partial content" $
|
||||
-- "8 x.msg.new c.image x.dag:16,x.text:7,m.image/jpg:6 0123456789012345 picture abcdef "
|
||||
-- #== RawChatMessage
|
||||
-- "x.msg.new"
|
||||
-- ["c.image"]
|
||||
-- [ RawMsgBodyContent (RawContentType "x" "dag") "0123456789012345",
|
||||
-- RawMsgBodyContent (RawContentType "x" "text") "picture",
|
||||
-- RawMsgBodyContent (RawContentType "m" "image/jpg") "abcdef"
|
||||
-- ]
|
||||
-- it "without message id" $
|
||||
-- " x.grp.mem.inv 23456,123 x.json:46 {\"contactRef\":\"john\",\"displayName\":\"John Doe\"} "
|
||||
-- #== RawChatMessage
|
||||
-- "x.grp.mem.inv"
|
||||
-- ["23456", "123"]
|
||||
-- [RawMsgBodyContent (RawContentType "x" "json") "{\"contactRef\":\"john\",\"displayName\":\"John Doe\"}"]
|
||||
queue :: SMPQueueUri
|
||||
queue =
|
||||
SMPQueueUri
|
||||
{ smpServer = srv,
|
||||
senderId = "\223\142z\251",
|
||||
clientVRange = smpClientVRange,
|
||||
dhPublicKey = "MCowBQYDK2VuAyEAjiswwI3O/NlS8Fk3HJUW870EY2bAwmttMBsvRB9eV3o="
|
||||
}
|
||||
|
||||
connReqData :: ConnReqUriData
|
||||
connReqData =
|
||||
ConnReqUriData
|
||||
{ crScheme = simplexChat,
|
||||
crAgentVRange = smpAgentVRange,
|
||||
crSmpQueues = [queue]
|
||||
}
|
||||
|
||||
testDhPubKey :: C.PublicKeyX448
|
||||
testDhPubKey = "MEIwBQYDK2VvAzkAmKuSYeQ/m0SixPDS8Wq8VBaTS1cW+Lp0n0h4Diu+kUpR+qXx4SDJ32YGEFoGFGSbGPry5Ychr6U="
|
||||
|
||||
testE2ERatchetParams :: E2ERatchetParamsUri 'C.X448
|
||||
testE2ERatchetParams = E2ERatchetParamsUri e2eEncryptVRange testDhPubKey testDhPubKey
|
||||
|
||||
testConnReq :: ConnectionRequestUri 'CMInvitation
|
||||
testConnReq = CRInvitationUri connReqData testE2ERatchetParams
|
||||
|
||||
(==#) :: ByteString -> ChatMsgEvent -> Expectation
|
||||
s ==# msg = do
|
||||
strDecode s `shouldBe` Right (ChatMessage msg)
|
||||
parseAll strP s `shouldBe` Right (ChatMessage msg)
|
||||
|
||||
(#==) :: ByteString -> ChatMsgEvent -> Expectation
|
||||
s #== msg = strEncode (ChatMessage msg) `shouldBe` s
|
||||
|
||||
(#==#) :: ByteString -> ChatMsgEvent -> Expectation
|
||||
s #==# msg = do
|
||||
s #== msg
|
||||
s ==# msg
|
||||
|
||||
testProfile :: Profile
|
||||
testProfile = Profile {displayName = "alice", fullName = "Alice"}
|
||||
|
||||
testGroupProfile :: GroupProfile
|
||||
testGroupProfile = GroupProfile {displayName = "team", fullName = "Team"}
|
||||
|
||||
decodeChatMessageTest :: Spec
|
||||
decodeChatMessageTest = describe "Chat message encoding/decoding" $ do
|
||||
it "x.msg.new" $ "{\"event\":\"x.msg.new\",\"params\":{\"content\":{\"text\":\"hello\",\"type\":\"text\"}}}" #==# XMsgNew (MCText "hello")
|
||||
it "x.file" $
|
||||
"{\"event\":\"x.file\",\"params\":{\"file\":{\"fileConnReq\":\"https://simplex.chat/invitation#/?v=1&smp=smp%3A%2F%2F1234-w%3D%3D%40smp.simplex.im%3A5223%2F3456-w%3D%3D%23MCowBQYDK2VuAyEAjiswwI3O_NlS8Fk3HJUW870EY2bAwmttMBsvRB9eV3o%3D&e2e=v%3D1%26x3dh%3DMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D%2CMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D\",\"fileSize\":12345,\"fileName\":\"photo.jpg\"}}}"
|
||||
#==# XFile FileInvitation {fileName = "photo.jpg", fileSize = 12345, fileConnReq = testConnReq}
|
||||
it "x.file.acpt" $ "{\"event\":\"x.file.acpt\",\"params\":{\"fileName\":\"photo.jpg\"}}" #==# XFileAcpt "photo.jpg"
|
||||
it "x.info" $ "{\"event\":\"x.info\",\"params\":{\"profile\":{\"fullName\":\"Alice\",\"displayName\":\"alice\"}}}" #==# XInfo testProfile
|
||||
it "x.info" $ "{\"event\":\"x.info\",\"params\":{\"profile\":{\"fullName\":\"\",\"displayName\":\"alice\"}}}" #==# XInfo Profile {displayName = "alice", fullName = ""}
|
||||
it "x.contact without content field" $
|
||||
"{\"event\":\"x.contact\",\"params\":{\"profile\":{\"fullName\":\"Alice\",\"displayName\":\"alice\"}}}"
|
||||
#==# XContact testProfile Nothing
|
||||
it "x.contact with content null" $
|
||||
"{\"event\":\"x.contact\",\"params\":{\"content\":null,\"profile\":{\"fullName\":\"Alice\",\"displayName\":\"alice\"}}}"
|
||||
==# XContact testProfile Nothing
|
||||
it "x.contact with content" $
|
||||
"{\"event\":\"x.contact\",\"params\":{\"content\":{\"text\":\"hello\",\"type\":\"text\"},\"profile\":{\"fullName\":\"Alice\",\"displayName\":\"alice\"}}}"
|
||||
#==# XContact testProfile (Just $ MCText "hello")
|
||||
it "x.grp.inv" $
|
||||
"{\"event\":\"x.grp.inv\",\"params\":{\"groupInvitation\":{\"connRequest\":\"https://simplex.chat/invitation#/?v=1&smp=smp%3A%2F%2F1234-w%3D%3D%40smp.simplex.im%3A5223%2F3456-w%3D%3D%23MCowBQYDK2VuAyEAjiswwI3O_NlS8Fk3HJUW870EY2bAwmttMBsvRB9eV3o%3D&e2e=v%3D1%26x3dh%3DMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D%2CMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D\",\"invitedMember\":{\"memberRole\":\"member\",\"memberId\":\"BQYHCA==\"},\"groupProfile\":{\"fullName\":\"Team\",\"displayName\":\"team\"},\"fromMember\":{\"memberRole\":\"admin\",\"memberId\":\"AQIDBA==\"}}}}"
|
||||
#==# XGrpInv GroupInvitation {fromMember = MemberIdRole (MemberId "\1\2\3\4") GRAdmin, invitedMember = MemberIdRole (MemberId "\5\6\7\8") GRMember, connRequest = testConnReq, groupProfile = testGroupProfile}
|
||||
it "x.grp.acpt" $ "{\"event\":\"x.grp.acpt\",\"params\":{\"memberId\":\"AQIDBA==\"}}" #==# XGrpAcpt (MemberId "\1\2\3\4")
|
||||
it "x.grp.acpt" $ "{\"event\":\"x.grp.acpt\",\"params\":{\"memberId\":\"AQIDBA==\"}}" #==# XGrpAcpt (MemberId "\1\2\3\4")
|
||||
it "x.grp.mem.new" $
|
||||
"{\"event\":\"x.grp.mem.new\",\"params\":{\"memberInfo\":{\"memberRole\":\"admin\",\"memberId\":\"AQIDBA==\",\"profile\":{\"fullName\":\"Alice\",\"displayName\":\"alice\"}}}}"
|
||||
#==# XGrpMemNew MemberInfo {memberId = MemberId "\1\2\3\4", memberRole = GRAdmin, profile = testProfile}
|
||||
it "x.grp.mem.intro" $
|
||||
"{\"event\":\"x.grp.mem.intro\",\"params\":{\"memberInfo\":{\"memberRole\":\"admin\",\"memberId\":\"AQIDBA==\",\"profile\":{\"fullName\":\"Alice\",\"displayName\":\"alice\"}}}}"
|
||||
#==# XGrpMemIntro MemberInfo {memberId = MemberId "\1\2\3\4", memberRole = GRAdmin, profile = testProfile}
|
||||
it "x.grp.mem.inv" $
|
||||
"{\"event\":\"x.grp.mem.inv\",\"params\":{\"memberId\":\"AQIDBA==\",\"memberIntro\":{\"directConnReq\":\"https://simplex.chat/invitation#/?v=1&smp=smp%3A%2F%2F1234-w%3D%3D%40smp.simplex.im%3A5223%2F3456-w%3D%3D%23MCowBQYDK2VuAyEAjiswwI3O_NlS8Fk3HJUW870EY2bAwmttMBsvRB9eV3o%3D&e2e=v%3D1%26x3dh%3DMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D%2CMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D\",\"groupConnReq\":\"https://simplex.chat/invitation#/?v=1&smp=smp%3A%2F%2F1234-w%3D%3D%40smp.simplex.im%3A5223%2F3456-w%3D%3D%23MCowBQYDK2VuAyEAjiswwI3O_NlS8Fk3HJUW870EY2bAwmttMBsvRB9eV3o%3D&e2e=v%3D1%26x3dh%3DMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D%2CMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D\"}}}"
|
||||
#==# XGrpMemInv (MemberId "\1\2\3\4") IntroInvitation {groupConnReq = testConnReq, directConnReq = testConnReq}
|
||||
it "x.grp.mem.fwd" $
|
||||
"{\"event\":\"x.grp.mem.fwd\",\"params\":{\"memberIntro\":{\"directConnReq\":\"https://simplex.chat/invitation#/?v=1&smp=smp%3A%2F%2F1234-w%3D%3D%40smp.simplex.im%3A5223%2F3456-w%3D%3D%23MCowBQYDK2VuAyEAjiswwI3O_NlS8Fk3HJUW870EY2bAwmttMBsvRB9eV3o%3D&e2e=v%3D1%26x3dh%3DMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D%2CMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D\",\"groupConnReq\":\"https://simplex.chat/invitation#/?v=1&smp=smp%3A%2F%2F1234-w%3D%3D%40smp.simplex.im%3A5223%2F3456-w%3D%3D%23MCowBQYDK2VuAyEAjiswwI3O_NlS8Fk3HJUW870EY2bAwmttMBsvRB9eV3o%3D&e2e=v%3D1%26x3dh%3DMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D%2CMEIwBQYDK2VvAzkAmKuSYeQ_m0SixPDS8Wq8VBaTS1cW-Lp0n0h4Diu-kUpR-qXx4SDJ32YGEFoGFGSbGPry5Ychr6U%3D\"},\"memberInfo\":{\"memberRole\":\"admin\",\"memberId\":\"AQIDBA==\",\"profile\":{\"fullName\":\"Alice\",\"displayName\":\"alice\"}}}}"
|
||||
#==# XGrpMemFwd MemberInfo {memberId = MemberId "\1\2\3\4", memberRole = GRAdmin, profile = testProfile} IntroInvitation {groupConnReq = testConnReq, directConnReq = testConnReq}
|
||||
it "x.grp.mem.info" $
|
||||
"{\"event\":\"x.grp.mem.info\",\"params\":{\"memberId\":\"AQIDBA==\",\"profile\":{\"fullName\":\"Alice\",\"displayName\":\"alice\"}}}"
|
||||
#== XGrpMemInfo (MemberId "\1\2\3\4") testProfile
|
||||
it "x.grp.mem.con" $ "{\"event\":\"x.grp.mem.con\",\"params\":{\"memberId\":\"AQIDBA==\"}}" #==# XGrpMemCon (MemberId "\1\2\3\4")
|
||||
it "x.grp.mem.con.all" $ "{\"event\":\"x.grp.mem.con.all\",\"params\":{\"memberId\":\"AQIDBA==\"}}" #==# XGrpMemConAll (MemberId "\1\2\3\4")
|
||||
it "x.grp.mem.del" $ "{\"event\":\"x.grp.mem.del\",\"params\":{\"memberId\":\"AQIDBA==\"}}" #==# XGrpMemDel (MemberId "\1\2\3\4")
|
||||
it "x.grp.leave" $ "{\"event\":\"x.grp.leave\",\"params\":{}}" ==# XGrpLeave
|
||||
it "x.grp.del" $ "{\"event\":\"x.grp.del\",\"params\":{}}" ==# XGrpDel
|
||||
it "x.info.probe" $ "{\"event\":\"x.info.probe\",\"params\":{\"probe\":\"AQIDBA==\"}}" #==# XInfoProbe (Probe "\1\2\3\4")
|
||||
it "x.info.probe.check" $ "{\"event\":\"x.info.probe.check\",\"params\":{\"probeHash\":\"AQIDBA==\"}}" #==# XInfoProbeCheck (ProbeHash "\1\2\3\4")
|
||||
it "x.info.probe.ok" $ "{\"event\":\"x.info.probe.ok\",\"params\":{\"probe\":\"AQIDBA==\"}}" #==# XInfoProbeOk (Probe "\1\2\3\4")
|
||||
it "x.ok" $ "{\"event\":\"x.ok\",\"params\":{}}" ==# XOk
|
||||
|
@ -1,11 +1,11 @@
|
||||
import ChatClient
|
||||
import ChatTests
|
||||
import MarkdownTests
|
||||
-- import ProtocolTests
|
||||
import ProtocolTests
|
||||
import Test.Hspec
|
||||
|
||||
main :: IO ()
|
||||
main = withSmpServer . hspec $ do
|
||||
describe "SimpleX chat markdown" markdownTests
|
||||
-- describe "SimpleX chat protocol" protocolTests
|
||||
describe "SimpleX chat protocol" protocolTests
|
||||
describe "SimpleX chat client" chatTests
|
||||
|
Loading…
Reference in New Issue
Block a user