Skip to content

Commit

Permalink
fix parsing, test
Browse files Browse the repository at this point in the history
  • Loading branch information
epoberezkin committed Nov 14, 2024
1 parent 777ee7e commit 706b14d
Show file tree
Hide file tree
Showing 5 changed files with 131 additions and 17 deletions.
1 change: 1 addition & 0 deletions simplex-chat.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -618,6 +618,7 @@ test-suite simplex-chat-test
MarkdownTests
MessageBatching
MobileTests
OperatorTests
ProtocolTests
RandomServers
RemoteTests
Expand Down
49 changes: 33 additions & 16 deletions src/Simplex/Chat/Operators.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ import Simplex.Chat.Types.Util (textParseJSON)
import Simplex.Messaging.Agent.Env.SQLite (ServerCfg (..), ServerRoles (..), allRoles)
import Simplex.Messaging.Encoding.String
import Simplex.Messaging.Parsers (defaultJSON, dropPrefix, fromTextField_, sumTypeJSON)
import Simplex.Messaging.Protocol (AProtoServerWithAuth (..), AProtocolType (..), ProtoServerWithAuth (..), ProtocolServer (..), ProtocolType (..), ProtocolTypeI, SProtocolType (..), UserProtocol)
import Simplex.Messaging.Protocol (AProtocolType (..), ProtoServerWithAuth (..), ProtocolServer (..), ProtocolType (..), ProtocolTypeI, SProtocolType (..), UserProtocol)
import Simplex.Messaging.Transport.Client (TransportHost (..))
import Simplex.Messaging.Util (atomicModifyIORef'_, safeDecodeUtf8)

Expand Down Expand Up @@ -203,12 +203,18 @@ data UpdatedUserOperatorServers = UpdatedUserOperatorServers

data ValidatedUserOperatorServers = ValidatedUserOperatorServers
{ operator :: Maybe ServerOperator,
smpServers :: [ValidatedServer 'PSMP],
xftpServers :: [ValidatedServer 'PXFTP]
smpServers :: [AValidatedServer 'PSMP],
xftpServers :: [AValidatedServer 'PXFTP]
}
deriving (Show)

data ValidatedServer p = ValidatedServer (Either Text (AUserServer p))
data AValidatedServer p = forall s. AVS (SDBStored s) (ValidatedServer s p)

deriving instance Show (AValidatedServer p)

type ValidatedServer s p = UserServer_ s ValidatedProtoServer p

data ValidatedProtoServer p = ValidatedProtoServer {unVPS :: Either Text (ProtoServerWithAuth p)}
deriving (Show)

class UserServersClass u where
Expand All @@ -218,7 +224,7 @@ class UserServersClass u where
servers' :: UserProtocol p => u -> SProtocolType p -> [AServer u p]

instance UserServersClass UserOperatorServers where
type AServer UserOperatorServers = UserServer' 'DBStored
type AServer UserOperatorServers = UserServer_ 'DBStored ProtoServerWithAuth
operator' UserOperatorServers {operator} = operator
partitionValid ss = ([], map (AUS SDBStored) ss)
servers' UserOperatorServers {smpServers, xftpServers} = \case
Expand All @@ -234,13 +240,18 @@ instance UserServersClass UpdatedUserOperatorServers where
SPXFTP -> xftpServers

instance UserServersClass ValidatedUserOperatorServers where
type AServer ValidatedUserOperatorServers = ValidatedServer
type AServer ValidatedUserOperatorServers = AValidatedServer
operator' ValidatedUserOperatorServers {operator} = operator
partitionValid = partitionEithers . map (\(ValidatedServer s) -> s)
partitionValid = partitionEithers . map serverOrErr
where
serverOrErr :: AValidatedServer p -> Either Text (AUserServer p)
serverOrErr (AVS s srv@UserServer {server = server'}) = (\server -> AUS s srv {server}) <$> unVPS server'
servers' ValidatedUserOperatorServers {smpServers, xftpServers} = \case
SPSMP -> smpServers
SPXFTP -> xftpServers

type UserServer' s p = UserServer_ s ProtoServerWithAuth p

type UserServer p = UserServer' 'DBStored p

type NewUserServer p = UserServer' 'DBNew p
Expand All @@ -249,9 +260,9 @@ data AUserServer p = forall s. AUS (SDBStored s) (UserServer' s p)

deriving instance Show (AUserServer p)

data UserServer' s p = UserServer
data UserServer_ s (srv :: ProtocolType -> Type) (p :: ProtocolType) = UserServer
{ serverId :: DBEntityId' s,
server :: ProtoServerWithAuth p,
server :: srv p,
preset :: Bool,
tested :: Maybe Bool,
enabled :: Bool,
Expand Down Expand Up @@ -396,7 +407,7 @@ data UserServersError
| USEStorageMissing {protocol :: AProtocolType, user :: Maybe User}
| USEProxyMissing {protocol :: AProtocolType, user :: Maybe User}
| USEInvalidServer {protocol :: AProtocolType, invalidServer :: Text}
| USEDuplicateServer {protocol :: AProtocolType, duplicateServer :: AProtoServerWithAuth, duplicateHost :: TransportHost}
| USEDuplicateServer {protocol :: AProtocolType, duplicateServer :: Text, duplicateHost :: TransportHost}
deriving (Show)

validateUserServers :: UserServersClass u' => [u'] -> [(User, [UserOperatorServers])] -> [UserServersError]
Expand All @@ -421,7 +432,7 @@ validateUserServers curr others = currUserErrs <> concatMap otherUserErrs others
(invalidSrvs, userSrvs) = partitionValid $ concatMap (`servers'` p) uss
srvs = filter (\(AUS _ UserServer {deleted}) -> not deleted) userSrvs
duplicateErr_ (AUS _ srv@UserServer {server}) =
USEDuplicateServer p' (AProtoServerWithAuth p server)
USEDuplicateServer p' (safeDecodeUtf8 $ strEncode server)
<$> find (`S.member` duplicateHosts) (srvHost srv)
duplicateHosts = snd $ foldl' addHost (S.empty, S.empty) allHosts
allHosts = concatMap (\(AUS _ srv) -> L.toList $ srvHost srv) srvs
Expand Down Expand Up @@ -462,17 +473,23 @@ instance DBStoredI s => FromJSON (ServerOperator' s) where
$(JQ.deriveJSON (sumTypeJSON $ dropPrefix "UCA") ''UsageConditionsAction)

instance ProtocolTypeI p => ToJSON (UserServer' s p) where
toEncoding = $(JQ.mkToEncoding defaultJSON ''UserServer')
toJSON = $(JQ.mkToJSON defaultJSON ''UserServer')
toEncoding = $(JQ.mkToEncoding defaultJSON ''UserServer_)
toJSON = $(JQ.mkToJSON defaultJSON ''UserServer_)

instance (DBStoredI s, ProtocolTypeI p) => FromJSON (UserServer' s p) where
parseJSON = $(JQ.mkParseJSON defaultJSON ''UserServer')
parseJSON = $(JQ.mkParseJSON defaultJSON ''UserServer_)

instance ProtocolTypeI p => FromJSON (AUserServer p) where
parseJSON v = (AUS SDBStored <$> parseJSON v) <|> (AUS SDBNew <$> parseJSON v)

instance ProtocolTypeI p => FromJSON (ValidatedServer p) where
parseJSON v = ValidatedServer <$> ((Right <$> parseJSON v) <|> (Left <$> parseJSON v))
instance ProtocolTypeI p => FromJSON (ValidatedProtoServer p) where
parseJSON v = ValidatedProtoServer <$> ((Right <$> parseJSON v) <|> (Left <$> parseJSON v))

instance (DBStoredI s, ProtocolTypeI p) => FromJSON (ValidatedServer s p) where
parseJSON = $(JQ.mkParseJSON defaultJSON ''UserServer_)

instance ProtocolTypeI p => FromJSON (AValidatedServer p) where
parseJSON v = (AVS SDBStored <$> parseJSON v) <|> (AVS SDBNew <$> parseJSON v)

$(JQ.deriveJSON defaultJSON ''UserOperatorServers)

Expand Down
92 changes: 92 additions & 0 deletions tests/OperatorTests.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,92 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_GHC -fno-warn-ambiguous-fields #-}

module OperatorTests (operatorTests) where

import qualified Data.List.NonEmpty as L
import Simplex.Chat
import Simplex.Chat.Operators
import Simplex.Chat.Types
import Simplex.FileTransfer.Client.Presets (defaultXFTPServers)
import Simplex.Messaging.Agent.Env.SQLite (ServerRoles (..), allRoles)
import Simplex.Messaging.Protocol
import Test.Hspec

operatorTests :: Spec
operatorTests = describe "managing server operators" $ do
validateServers

validateServers :: Spec
validateServers = describe "validate user servers" $ do
it "should pass valid user servers" $ validateUserServers [valid] [] `shouldBe` []
it "should fail without servers" $ do
validateUserServers [invalidNoServers] [] `shouldBe` [USENoServers aSMP Nothing]
validateUserServers [invalidDisabled] [] `shouldBe` [USENoServers aSMP Nothing]
validateUserServers [invalidDisabledOp] [] `shouldBe` [USENoServers aSMP Nothing, USENoServers aXFTP Nothing]
it "should fail without servers with storage role" $ do
validateUserServers [invalidNoStorage] [] `shouldBe` [USEStorageMissing aSMP Nothing, USEStorageMissing aXFTP Nothing]
it "should fail with duplicate host" $ do
validateUserServers [invalidDuplicate] [] `shouldBe`
[ USEDuplicateServer aSMP "smp://[email protected],beccx4yfxxbvyhqypaavemqurytl6hozr47wfc7uuecacjqdvwpw2xid.onion" "smp8.simplex.im",
USEDuplicateServer aSMP "smp://[email protected]" "smp8.simplex.im"
]
it "should fail with invalid host" $ do
validateUserServers [invalidHost] [] `shouldBe` [USENoServers aXFTP Nothing, USEInvalidServer aSMP "smp:[email protected]"]
where
aSMP = AProtocolType SPSMP
aXFTP = AProtocolType SPXFTP

deriving instance Eq User

deriving instance Eq UserServersError

valid :: UpdatedUserOperatorServers
valid =
UpdatedUserOperatorServers
{ operator = Just operatorSimpleXChat {operatorId = DBEntityId 1},
smpServers = map (AUS SDBNew) simplexChatSMPServers,
xftpServers = map (AUS SDBNew . presetServer True) $ L.toList defaultXFTPServers
}

invalidNoServers :: UpdatedUserOperatorServers
invalidNoServers = (valid :: UpdatedUserOperatorServers) {smpServers = []}

invalidDisabled :: UpdatedUserOperatorServers
invalidDisabled =
(valid :: UpdatedUserOperatorServers)
{ smpServers = map (AUS SDBNew . (\srv -> (srv :: NewUserServer 'PSMP) {enabled = False})) simplexChatSMPServers
}

invalidDisabledOp :: UpdatedUserOperatorServers
invalidDisabledOp =
(valid :: UpdatedUserOperatorServers)
{ operator = Just operatorSimpleXChat {operatorId = DBEntityId 1, enabled = False}
}

invalidNoStorage :: UpdatedUserOperatorServers
invalidNoStorage =
(valid :: UpdatedUserOperatorServers)
{ operator = Just operatorSimpleXChat {operatorId = DBEntityId 1, roles = allRoles {storage = False}}
}

invalidDuplicate :: UpdatedUserOperatorServers
invalidDuplicate =
(valid :: UpdatedUserOperatorServers)
{ smpServers = map (AUS SDBNew) $ simplexChatSMPServers <> [presetServer True "smp://[email protected]"]
}

invalidHost :: ValidatedUserOperatorServers
invalidHost =
ValidatedUserOperatorServers
{ operator = Just operatorSimpleXChat {operatorId = DBEntityId 1},
smpServers = [validatedServer (Left "smp:[email protected]"), validatedServer (Right "smp://[email protected]")],
xftpServers = []
}
where
validatedServer srv =
AVS SDBNew (presetServer @'PSMP True "smp://[email protected]") {server = ValidatedProtoServer srv}
4 changes: 3 additions & 1 deletion tests/RandomServers.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,10 @@
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_GHC -fno-warn-ambiguous-fields #-}

Expand All @@ -16,7 +18,7 @@ import qualified Data.List.NonEmpty as L
import Data.Monoid (Sum (..))
import Simplex.Chat (defaultChatConfig, randomPresetServers)
import Simplex.Chat.Controller (ChatConfig (..), PresetServers (..))
import Simplex.Chat.Operators (DBEntityId' (..), NewUserServer, UserServer' (..), operatorServers, operatorServersToUse)
import Simplex.Chat.Operators
import Simplex.Messaging.Agent.Env.SQLite (ServerRoles (..))
import Simplex.Messaging.Protocol (ProtoServerWithAuth (..), SProtocolType (..), UserProtocol)
import Test.Hspec
Expand Down
2 changes: 2 additions & 0 deletions tests/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ import MarkdownTests
import MessageBatching
import MobileTests
import ProtocolTests
import OperatorTests
import RandomServers
import RemoteTests
import SchemaDump
Expand All @@ -31,6 +32,7 @@ main = do
around tmpBracket $ describe "WebRTC encryption" webRTCTests
describe "Valid names" validNameTests
describe "Message batching" batchingTests
describe "Operators" operatorTests
describe "Random servers" randomServersTests
around testBracket $ do
describe "Mobile API Tests" mobileTests
Expand Down

0 comments on commit 706b14d

Please sign in to comment.