SimpleX-Chat/tests/SchemaDump.hs

123 lines
4.9 KiB
Haskell
Raw Normal View History

{-# LANGUAGE NamedFieldPuns #-}
2022-04-05 12:44:22 +04:00
{-# LANGUAGE OverloadedStrings #-}
module SchemaDump where
import ChatClient (withTmpFiles)
import Control.DeepSeq
import Control.Monad (unless, void)
import Data.List (dropWhileEnd)
import Data.Maybe (fromJust, isJust)
import Simplex.Chat.Store (createChatStore)
import qualified Simplex.Chat.Store as Store
import Simplex.Messaging.Agent.Store.SQLite (MigrationConfirmation (..), closeSQLiteStore, createSQLiteStore)
import Simplex.Messaging.Agent.Store.SQLite.Migrations (Migration (..), MigrationsToRun (..), toDownMigration)
import qualified Simplex.Messaging.Agent.Store.SQLite.Migrations as Migrations
2023-03-27 19:39:22 +01:00
import Simplex.Messaging.Util (ifM, whenM)
import System.Directory (doesFileExist, removeFile)
2022-04-05 12:44:22 +04:00
import System.Process (readCreateProcess, shell)
import Test.Hspec
testDB :: FilePath
testDB = "tests/tmp/test_chat.db"
appSchema :: FilePath
appSchema = "src/Simplex/Chat/Migrations/chat_schema.sql"
2024-10-09 15:15:58 +04:00
-- Some indexes found by `.lint fkey-indexes` are not added to schema, explanation:
--
-- - CREATE INDEX 'chat_items_group_id' ON 'chat_items'('group_id'); --> groups(group_id)
--
-- Covering index is used instead. See for example:
-- EXPLAIN QUERY PLAN DELETE FROM groups;
-- (uses idx_chat_items_groups_item_status)
--
-- - CREATE INDEX 'connections_group_member_id' ON 'connections'('group_member_id'); --> group_members(group_member_id)
--
-- Covering index is used instead. See for example:
-- EXPLAIN QUERY PLAN DELETE FROM group_members;
-- (uses idx_connections_group_member)
appLint :: FilePath
appLint = "src/Simplex/Chat/Migrations/chat_lint.sql"
testSchema :: FilePath
testSchema = "tests/tmp/test_agent_schema.sql"
2022-04-05 12:44:22 +04:00
schemaDumpTest :: Spec
schemaDumpTest = do
2022-04-05 12:44:22 +04:00
it "verify and overwrite schema dump" testVerifySchemaDump
2024-10-09 15:15:58 +04:00
it "verify .lint fkey-indexes" testVerifyLintFKeyIndexes
it "verify schema down migrations" testSchemaMigrations
2022-04-05 12:44:22 +04:00
testVerifySchemaDump :: IO ()
testVerifySchemaDump = withTmpFiles $ do
savedSchema <- ifM (doesFileExist appSchema) (readFile appSchema) (pure "")
savedSchema `deepseq` pure ()
void $ createChatStore testDB "" False MCError
getSchema testDB appSchema `shouldReturn` savedSchema
removeFile testDB
2024-10-09 15:15:58 +04:00
testVerifyLintFKeyIndexes :: IO ()
testVerifyLintFKeyIndexes = withTmpFiles $ do
savedLint <- ifM (doesFileExist appLint) (readFile appLint) (pure "")
savedLint `deepseq` pure ()
void $ createChatStore testDB "" False MCError
getLintFKeyIndexes testDB "tests/tmp/chat_lint.sql" `shouldReturn` savedLint
removeFile testDB
testSchemaMigrations :: IO ()
testSchemaMigrations = withTmpFiles $ do
let noDownMigrations = dropWhileEnd (\Migration {down} -> isJust down) Store.migrations
Right st <- createSQLiteStore testDB "" False noDownMigrations MCError
mapM_ (testDownMigration st) $ drop (length noDownMigrations) Store.migrations
closeSQLiteStore st
removeFile testDB
2023-03-27 19:39:22 +01:00
whenM (doesFileExist testSchema) $ removeFile testSchema
where
testDownMigration st m = do
putStrLn $ "down migration " <> name m
let downMigr = fromJust $ toDownMigration m
schema <- getSchema testDB testSchema
Migrations.run st $ MTRUp [m]
schema' <- getSchema testDB testSchema
schema' `shouldNotBe` schema
Migrations.run st $ MTRDown [downMigr]
unless (name m `elem` skipComparisonForDownMigrations) $ do
schema'' <- getSchema testDB testSchema
schema'' `shouldBe` schema
Migrations.run st $ MTRUp [m]
schema''' <- getSchema testDB testSchema
schema''' `shouldBe` schema'
skipComparisonForDownMigrations :: [String]
skipComparisonForDownMigrations =
[ -- on down migration msg_delivery_events table moves down to the end of the file
"20230504_recreate_msg_delivery_events_cleanup_messages",
-- on down migration idx_chat_items_timed_delete_at index moves down to the end of the file
"20230529_indexes",
-- table and index definitions move down the file, so fields are re-created as not unique
"20230914_member_probes",
-- on down migration idx_connections_via_contact_uri_hash index moves down to the end of the file
core: support batch sending in groups, batch introductions; send recent message history to new members (#3519) * core: batch send stubs, comments * multiple events in ChatMessage and supporting types * Revert "multiple events in ChatMessage and supporting types" This reverts commit 9b239b26ba5c8fdec41c6689a6421baf7ffcc27d. * schema, refactor group processing for batched messages * encoding, refactor processing * refactor code to work with updated schema * encoding, remove instances * wip * implement batching * batch introductions * wip * collect and send message history * missing new line * rename * test * rework to build history via chat items * refactor, tests * correctly set member version range, dont include deleted items * tests * fix disappearing messages * check number of errors * comment * check size in encodeChatMessage * fix - don't check msg size for binary * use builder * rename * rename * rework batching * lazy msg body * use withStoreBatch * refactor * reverse batches * comment * possibly fix builder for single msg * refactor batcher * refactor * dont repopulate msg_deliveries on down migration * EncodedChatMessage type * remove type * batcher tests * add tests * group history preference * test group link * fix tests * fix for random update * add test testImageFitsSingleBatch * refactor * rename function * refactor * mconcat * rename feature * catch error on each batch * refactor file inv retrieval * refactor gathering item forward events * refactor message batching * unite migrations * move files * refactor * Revert "unite migrations" This reverts commit 0be7a3117a2b4eb7f13f1ff639188bb3ff826af8. * refactor splitFileDescr * improve tests * Revert "dont repopulate msg_deliveries on down migration" This reverts commit 2944c1cc28acf85282a85d8458c67cefb7787ac7. * fix down migration --------- Co-authored-by: Evgeny Poberezkin <2769109+epoberezkin@users.noreply.github.com>
2023-12-23 17:07:23 +04:00
"20231019_indexes",
-- table and indexes move down to the end of the file
"20231215_recreate_msg_deliveries",
-- on down migration idx_msg_deliveries_agent_ack_cmd_id index moves down to the end of the file
core: pagination API to load items around defined or the earliest unread item (#5100) * core: auto increment chat item ids (#5088) * core: auto increment chat item ids * file name * down name * update schema * ignore down migration on schema dump test * fix testDirectMessageDelete test * fix testNotes test * core: initial api support for items around a given item (#5092) * core: initial api support for items around a given item * implementation and tests for local messages * pass entities down * unused * getAllChatItems implementation and tests * pagination for getting chat and tests * remove unused import * group implementation and tests * refactor * order by created at for local and direct chats * core: initial landing api for chat and gaps (#5104) * initial work on initial param for loading chat * support for initial * controller parse * fixed sqls * refactor names * fix ChatLandingSection serialized type * total accuracy on landing section * descriptive view message * foldr * refactor to make landingSection reusable * refactor: use foldr everywhere * propagate search * Revert "propagate search" This reverts commit 01611fd7197c135639db2a869d96d7621ba093ee. * throw when search is sent for initial * gap size wip (needs testing) * final * remove order by * remove index --------- Co-authored-by: spaced4ndy <8711996+spaced4ndy@users.noreply.github.com> * core: fix initial api latest chat items ordering (#5151) * core: fix one item missing from latest in initial and wrong check (#5153) * core: fix one item missing from latest in initial and wrong check * final fixes and tests * clearer tests * core: remove gaps and make sure page size is always the same (#5163) * remove gaps * consistent pagination size * proper fix and around fix too * optimize * refactor * core: simplify pagination * core: first unread queries (#5174) * core: pagination nav info (#5175) * core: pagination nav info * wip * rework * rework * group, local * fix * rename * fix tests * just --------- Co-authored-by: spaced4ndy <8711996+spaced4ndy@users.noreply.github.com> Co-authored-by: Evgeny Poberezkin <evgeny@poberezkin.com>
2024-11-14 08:34:25 +00:00
"20240313_drop_agent_ack_cmd_id",
2024-11-25 18:51:49 +04:00
-- sequence table moves down to the end of the file
"20241023_chat_item_autoincrement_id",
-- indexes move down to the end of the file
"20241125_indexes"
]
getSchema :: FilePath -> FilePath -> IO String
2024-10-09 15:15:58 +04:00
getSchema dbPath schemaPath = do
void $ readCreateProcess (shell $ "sqlite3 " <> dbPath <> " '.schema --indent' > " <> schemaPath) ""
sch <- readFile schemaPath
sch `deepseq` pure sch
2024-10-09 15:15:58 +04:00
getLintFKeyIndexes :: FilePath -> FilePath -> IO String
getLintFKeyIndexes dbPath lintPath = do
void $ readCreateProcess (shell $ "sqlite3 " <> dbPath <> " '.lint fkey-indexes' > " <> lintPath) ""
lint <- readFile lintPath
lint `deepseq` pure lint