SimpleX-Chat/tests/SchemaDump.hs

80 lines
3 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"
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
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 "" MCError
getSchema testDB appSchema `shouldReturn` savedSchema
removeFile testDB
testSchemaMigrations :: IO ()
testSchemaMigrations = withTmpFiles $ do
let noDownMigrations = dropWhileEnd (\Migration {down} -> isJust down) Store.migrations
Right st <- createSQLiteStore testDB "" 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"
]
getSchema :: FilePath -> FilePath -> IO String
getSchema dpPath schemaPath = do
void $ readCreateProcess (shell $ "sqlite3 " <> dpPath <> " '.schema --indent' > " <> schemaPath) ""
sch <- readFile schemaPath
sch `deepseq` pure sch