mirror of
https://github.com/wasp-lang/wasp.git
synced 2024-12-23 17:13:40 +03:00
Add support for --create-only
migrations (#862)
This commit is contained in:
parent
a678c41d7e
commit
a16aa73753
@ -1,5 +1,10 @@
|
||||
# Changelog
|
||||
|
||||
## v0.7.3
|
||||
|
||||
### MINOR CLI BREAKING CHANGE
|
||||
- The CLI command for applying a migration with a name has changed from `wasp db migrate-dev foo` to `wasp db migrate-dev --name foo`. This allowed us to add more flags, like `--create-only`.
|
||||
|
||||
## v0.7.2
|
||||
|
||||
### Bug fixes
|
||||
|
@ -127,8 +127,7 @@ printVersion = do
|
||||
-- TODO(matija): maybe extract to a separate module, e.g. DbCli.hs?
|
||||
dbCli :: [String] -> IO ()
|
||||
dbCli args = case args of
|
||||
["migrate-dev", migrationName] -> runDbCommand $ Command.Db.Migrate.migrateDev (Just migrationName)
|
||||
["migrate-dev"] -> runDbCommand $ Command.Db.Migrate.migrateDev Nothing
|
||||
"migrate-dev" : optionalMigrateArgs -> runDbCommand $ Command.Db.Migrate.migrateDev optionalMigrateArgs
|
||||
["studio"] -> runDbCommand studio
|
||||
_ -> printDbUsage
|
||||
|
||||
@ -141,15 +140,19 @@ printDbUsage =
|
||||
"",
|
||||
title "COMMANDS",
|
||||
cmd
|
||||
( " migrate-dev [migration-name] Ensures dev database corresponds to the current state of schema(entities):\n"
|
||||
( " migrate-dev Ensures dev database corresponds to the current state of schema(entities):\n"
|
||||
<> " - Generates a new migration if there are changes in the schema.\n"
|
||||
<> " - Applies any pending migrations to the database either using the supplied migration name or asking for one.\n"
|
||||
<> "\nOPTIONS:\n"
|
||||
<> " --name [migration-name]\n"
|
||||
<> " --create-only\n"
|
||||
),
|
||||
cmd " studio GUI for inspecting your database.",
|
||||
"",
|
||||
title "EXAMPLES",
|
||||
" wasp db migrate-dev",
|
||||
" wasp db migrate-dev \"Added User entity\"",
|
||||
" wasp db migrate-dev --name \"Added User entity\"",
|
||||
" wasp db migrate-dev --create-only",
|
||||
" wasp db studio"
|
||||
]
|
||||
|
||||
|
@ -1,5 +1,6 @@
|
||||
module Wasp.Cli.Command.Db.Migrate
|
||||
( migrateDev,
|
||||
parseMigrateArgs,
|
||||
)
|
||||
where
|
||||
|
||||
@ -15,14 +16,15 @@ import Wasp.Cli.Command.Common
|
||||
import Wasp.Cli.Command.Message (cliSendMessageC)
|
||||
import qualified Wasp.Cli.Common as Cli.Common
|
||||
import qualified Wasp.Common
|
||||
import Wasp.Generator.DbGenerator.Common (MigrateArgs (..), defaultMigrateArgs)
|
||||
import qualified Wasp.Generator.DbGenerator.Operations as DbOps
|
||||
import qualified Wasp.Message as Msg
|
||||
|
||||
-- | NOTE(shayne): Performs database schema migration (based on current schema) in the generated project.
|
||||
-- This assumes the wasp project migrations dir was copied from wasp source project by a previous compile.
|
||||
-- The migrate function takes care of copying migrations from the generated project back to the source code.
|
||||
migrateDev :: Maybe String -> Command ()
|
||||
migrateDev maybeMigrationName = do
|
||||
migrateDev :: [String] -> Command ()
|
||||
migrateDev optionalMigrateArgs = do
|
||||
waspProjectDir <- findWaspProjectRootDirFromCwd
|
||||
let genProjectRootDir =
|
||||
waspProjectDir
|
||||
@ -33,9 +35,26 @@ migrateDev maybeMigrationName = do
|
||||
waspProjectDir
|
||||
</> Wasp.Common.dbMigrationsDirInWaspProjectDir
|
||||
|
||||
let parsedMigrateArgs = parseMigrateArgs optionalMigrateArgs
|
||||
case parsedMigrateArgs of
|
||||
Left parseError ->
|
||||
throwError $ CommandError "Migrate dev failed" parseError
|
||||
Right migrateArgs -> do
|
||||
cliSendMessageC $ Msg.Start "Performing migration..."
|
||||
migrateResult <- liftIO $ DbOps.migrateDevAndCopyToSource waspDbMigrationsDir genProjectRootDir maybeMigrationName
|
||||
migrateResult <- liftIO $ DbOps.migrateDevAndCopyToSource waspDbMigrationsDir genProjectRootDir migrateArgs
|
||||
case migrateResult of
|
||||
Left migrateError ->
|
||||
throwError $ CommandError "Migrate dev failed" migrateError
|
||||
Right () -> cliSendMessageC $ Msg.Success "Migration done."
|
||||
|
||||
-- | Basic parsing of db-migrate args. In the future, we could use a smarter parser
|
||||
-- for this (and all other CLI arg parsing).
|
||||
parseMigrateArgs :: [String] -> Either String MigrateArgs
|
||||
parseMigrateArgs migrateArgs = do
|
||||
go migrateArgs defaultMigrateArgs
|
||||
where
|
||||
go :: [String] -> MigrateArgs -> Either String MigrateArgs
|
||||
go [] mArgs = Right mArgs
|
||||
go ("--create-only" : rest) mArgs = go rest $ mArgs {_isCreateOnlyMigration = True}
|
||||
go ("--name" : name : rest) mArgs = go rest $ mArgs {_migrationName = Just name}
|
||||
go unknown _ = Left $ "Unknown migrate arg(s): " ++ unwords unknown
|
||||
|
22
waspc/cli/test/DbMigrateTest.hs
Normal file
22
waspc/cli/test/DbMigrateTest.hs
Normal file
@ -0,0 +1,22 @@
|
||||
module DbMigrateTest where
|
||||
|
||||
import Data.Either (isLeft)
|
||||
import Test.Tasty.Hspec
|
||||
import Wasp.Cli.Command.Db.Migrate (parseMigrateArgs)
|
||||
import Wasp.Generator.DbGenerator.Common (MigrateArgs (..), defaultMigrateArgs)
|
||||
|
||||
spec_parseMigrateArgs :: Spec
|
||||
spec_parseMigrateArgs =
|
||||
it "should parse input options strings correcly" $ do
|
||||
parseMigrateArgs [] `shouldBe` Right defaultMigrateArgs
|
||||
parseMigrateArgs ["--create-only"]
|
||||
`shouldBe` Right (MigrateArgs {_migrationName = Nothing, _isCreateOnlyMigration = True})
|
||||
parseMigrateArgs ["--name", "something"]
|
||||
`shouldBe` Right (MigrateArgs {_migrationName = Just "something", _isCreateOnlyMigration = False})
|
||||
parseMigrateArgs ["--name", "something else longer"]
|
||||
`shouldBe` Right (MigrateArgs {_migrationName = Just "something else longer", _isCreateOnlyMigration = False})
|
||||
parseMigrateArgs ["--name", "something", "--create-only"]
|
||||
`shouldBe` Right (MigrateArgs {_migrationName = Just "something", _isCreateOnlyMigration = True})
|
||||
parseMigrateArgs ["--create-only", "--name", "something"]
|
||||
`shouldBe` Right (MigrateArgs {_migrationName = Just "something", _isCreateOnlyMigration = True})
|
||||
isLeft (parseMigrateArgs ["--create-only", "--wtf"]) `shouldBe` True
|
@ -98,7 +98,7 @@ waspCliMigrate migrationName =
|
||||
in return $
|
||||
combineShellCommands
|
||||
[ -- Migrate using a migration name to avoid Prisma asking via CLI.
|
||||
"wasp-cli db migrate-dev " ++ migrationName,
|
||||
"wasp-cli db migrate-dev --name " ++ migrationName,
|
||||
-- Rename both migrations to remove the date-specific portion of the directory to something static.
|
||||
"mv " ++ (waspMigrationsDir </> ("*" ++ migrationName)) ++ " " ++ (waspMigrationsDir </> ("no-date-" ++ migrationName)),
|
||||
"mv " ++ (generatedMigrationsDir </> ("*" ++ migrationName)) ++ " " ++ (generatedMigrationsDir </> ("no-date-" ++ migrationName))
|
||||
|
@ -105,11 +105,7 @@ postWriteDbGeneratorActions spec dstDir = do
|
||||
-- In either of those scenarios, validate against DB itself to avoid redundant warnings.
|
||||
--
|
||||
-- NOTE: As one final optimization, if they do not have a schema.prisma.wasp-last-db-concurrence-checksum but the schema is
|
||||
-- in sync with the databse, we generate that file to avoid future checks.
|
||||
--
|
||||
-- NOTE: Because we currently only allow devs to migrate-dev, we only compare the schema to the DB since
|
||||
-- there are no likely scenarios where schema == db but schema != migrations dir. In the future, as we add more DB commands,
|
||||
-- we may wish to also compare the migrations dir to the DB as well.
|
||||
-- in sync with the database and all migrations are applied, we generate that file to avoid future checks.
|
||||
warnIfDbNeedsMigration :: AppSpec -> Path' Abs (Dir ProjectRootDir) -> IO (Maybe GeneratorWarning)
|
||||
warnIfDbNeedsMigration spec projectRootDir = do
|
||||
dbSchemaChecksumFileExists <- doesFileExist dbSchemaChecksumFp
|
||||
@ -117,7 +113,7 @@ warnIfDbNeedsMigration spec projectRootDir = do
|
||||
then warnIfSchemaDiffersFromChecksum dbSchemaFp dbSchemaChecksumFp
|
||||
else
|
||||
if entitiesExist
|
||||
then warnIfSchemaDiffersFromDb projectRootDir
|
||||
then warnProjectDiffersFromDb projectRootDir
|
||||
else return Nothing
|
||||
where
|
||||
dbSchemaFp = SP.fromAbsFile $ projectRootDir </> dbSchemaFileInProjectRootDir
|
||||
@ -132,16 +128,21 @@ warnIfSchemaDiffersFromChecksum dbSchemaFp dbSchemaChecksumFp = do
|
||||
then return . Just $ GeneratorNeedsMigrationWarning "Your Prisma schema has changed, please run `wasp db migrate-dev` when ready."
|
||||
else return Nothing
|
||||
|
||||
warnIfSchemaDiffersFromDb :: Path' Abs (Dir ProjectRootDir) -> IO (Maybe GeneratorWarning)
|
||||
warnIfSchemaDiffersFromDb projectRootDir = do
|
||||
-- NOTE: If we wanted to, we could also check that the migrations dir == db,
|
||||
-- but a schema check should handle all most likely cases.
|
||||
-- | Checks if the project's Prisma schema file and migrations dir matches the DB state.
|
||||
-- Issues a warning if it cannot connect, or if either check fails.
|
||||
warnProjectDiffersFromDb :: Path' Abs (Dir ProjectRootDir) -> IO (Maybe GeneratorWarning)
|
||||
warnProjectDiffersFromDb projectRootDir = do
|
||||
schemaMatchesDb <- DbOps.doesSchemaMatchDb projectRootDir
|
||||
case schemaMatchesDb of
|
||||
Just True -> do
|
||||
-- NOTE: Since we know schema == db, writing this file prevents future redundant Prisma checks.
|
||||
allMigrationsAppliedToDb <- DbOps.areAllMigrationsAppliedToDb projectRootDir
|
||||
if allMigrationsAppliedToDb == Just True
|
||||
then do
|
||||
-- NOTE: Since we know schema == db and all migrations are applied,
|
||||
-- we can write this file to prevent future redundant Prisma checks.
|
||||
DbOps.writeDbSchemaChecksumToFile projectRootDir (SP.castFile dbSchemaChecksumOnLastDbConcurrenceFileProjectRootDir)
|
||||
return Nothing
|
||||
else return . Just $ GeneratorNeedsMigrationWarning "You have unapplied migrations. Please run `wasp db migrate-dev` when ready."
|
||||
Just False -> return . Just $ GeneratorNeedsMigrationWarning "Your Prisma schema does not match your database, please run `wasp db migrate-dev`."
|
||||
-- NOTE: If there was an error, it could mean we could not connect to the SQLite db, since it does not exist.
|
||||
-- Or it could mean their DATABASE_URL is wrong, or database is down, or any other number of causes.
|
||||
|
@ -6,6 +6,10 @@ module Wasp.Generator.DbGenerator.Common
|
||||
dbSchemaFileInDbTemplatesDir,
|
||||
dbSchemaFileInProjectRootDir,
|
||||
dbTemplatesDirInTemplatesDir,
|
||||
defaultMigrateArgs,
|
||||
getOnLastDbConcurrenceChecksumFileRefreshAction,
|
||||
MigrateArgs (..),
|
||||
RefreshOnLastDbConcurrenceChecksumFile (..),
|
||||
)
|
||||
where
|
||||
|
||||
@ -60,3 +64,26 @@ dbSchemaChecksumOnLastGenerateFileInDbRootDir = [relfile|schema.prisma.wasp-gene
|
||||
|
||||
dbSchemaChecksumOnLastGenerateFileProjectRootDir :: Path' (Rel ProjectRootDir) (File DbSchemaChecksumOnLastGenerateFile)
|
||||
dbSchemaChecksumOnLastGenerateFileProjectRootDir = dbRootDirInProjectRootDir </> dbSchemaChecksumOnLastGenerateFileInDbRootDir
|
||||
|
||||
data MigrateArgs = MigrateArgs
|
||||
{ _migrationName :: Maybe String,
|
||||
_isCreateOnlyMigration :: Bool
|
||||
}
|
||||
deriving (Show, Eq)
|
||||
|
||||
defaultMigrateArgs :: MigrateArgs
|
||||
defaultMigrateArgs = MigrateArgs {_migrationName = Nothing, _isCreateOnlyMigration = False}
|
||||
|
||||
-- | This type tells us what we need to do with the DbSchemaChecksumOnLastDbConcurrenceFile.
|
||||
data RefreshOnLastDbConcurrenceChecksumFile
|
||||
= WriteOnLastDbConcurrenceChecksumFile
|
||||
| RemoveOnLastDbConcurrenceChecksumFile
|
||||
| IgnoreOnLastDbConcurrenceChecksumFile
|
||||
|
||||
getOnLastDbConcurrenceChecksumFileRefreshAction :: MigrateArgs -> RefreshOnLastDbConcurrenceChecksumFile
|
||||
getOnLastDbConcurrenceChecksumFileRefreshAction migrateArgs =
|
||||
-- Since a create-only migration allows users to write any SQL, we remove the file to force
|
||||
-- revalidation with the DB. If it is a regular migration, we write it since they will be in sync.
|
||||
if _isCreateOnlyMigration migrateArgs
|
||||
then RemoveOnLastDbConcurrenceChecksumFile
|
||||
else WriteOnLastDbConcurrenceChecksumFile
|
||||
|
@ -3,6 +3,8 @@ module Wasp.Generator.DbGenerator.Jobs
|
||||
migrateDiff,
|
||||
generatePrismaClient,
|
||||
runStudio,
|
||||
migrateStatus,
|
||||
asPrismaCliArgs,
|
||||
)
|
||||
where
|
||||
|
||||
@ -10,7 +12,7 @@ import StrongPath (Abs, Dir, File', Path', Rel, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import qualified System.Info
|
||||
import Wasp.Generator.Common (ProjectRootDir)
|
||||
import Wasp.Generator.DbGenerator.Common (dbSchemaFileInProjectRootDir)
|
||||
import Wasp.Generator.DbGenerator.Common (MigrateArgs (..), dbSchemaFileInProjectRootDir)
|
||||
import qualified Wasp.Generator.Job as J
|
||||
import Wasp.Generator.Job.Process (runNodeCommandAsJob)
|
||||
import Wasp.Generator.ServerGenerator.Common (serverRootDirInProjectRootDir)
|
||||
@ -24,13 +26,11 @@ prismaInServerNodeModules = serverRootDirInProjectRootDir </> [SP.relfile|./node
|
||||
absPrismaExecutableFp :: Path' Abs (Dir ProjectRootDir) -> FilePath
|
||||
absPrismaExecutableFp projectDir = SP.toFilePath $ projectDir </> prismaInServerNodeModules
|
||||
|
||||
migrateDev :: Path' Abs (Dir ProjectRootDir) -> Maybe String -> J.Job
|
||||
migrateDev projectDir maybeMigrationName = do
|
||||
migrateDev :: Path' Abs (Dir ProjectRootDir) -> MigrateArgs -> J.Job
|
||||
migrateDev projectDir migrateArgs = do
|
||||
let serverDir = projectDir </> serverRootDirInProjectRootDir
|
||||
let schemaFile = projectDir </> dbSchemaFileInProjectRootDir
|
||||
|
||||
let optionalMigrationArgs = maybe [] (\name -> ["--name", name]) maybeMigrationName
|
||||
|
||||
-- NOTE(matija): We are running this command from server's root dir since that is where
|
||||
-- Prisma packages (cli and client) are currently installed.
|
||||
-- NOTE(martin): `prisma migrate dev` refuses to execute when interactivity is needed if stdout is being piped,
|
||||
@ -40,7 +40,7 @@ migrateDev projectDir maybeMigrationName = do
|
||||
-- we are using `script` to trick Prisma into thinking it is running in TTY (interactively).
|
||||
|
||||
-- NOTE(martin): For this to work on Mac, filepath in the list below must be as it is now - not wrapped in any quotes.
|
||||
let prismaMigrateCmd = absPrismaExecutableFp projectDir : ["migrate", "dev", "--schema", SP.toFilePath schemaFile] ++ optionalMigrationArgs
|
||||
let prismaMigrateCmd = absPrismaExecutableFp projectDir : ["migrate", "dev", "--schema", SP.toFilePath schemaFile] ++ asPrismaCliArgs migrateArgs
|
||||
let scriptArgs =
|
||||
if System.Info.os == "darwin"
|
||||
then -- NOTE(martin): On MacOS, command that `script` should execute is treated as multiple arguments.
|
||||
@ -50,6 +50,13 @@ migrateDev projectDir maybeMigrationName = do
|
||||
|
||||
runNodeCommandAsJob serverDir "script" scriptArgs J.Db
|
||||
|
||||
asPrismaCliArgs :: MigrateArgs -> [String]
|
||||
asPrismaCliArgs migrateArgs = do
|
||||
concat . concat $
|
||||
[ [["--create-only"] | _isCreateOnlyMigration migrateArgs],
|
||||
[["--name", name] | Just name <- [_migrationName migrateArgs]]
|
||||
]
|
||||
|
||||
-- | Diffs the Prisma schema file against the db.
|
||||
-- Because of the --exit-code flag, it changes the exit code behavior
|
||||
-- to signal if the diff is empty or not (Empty: 0, Error: 1, Not empty: 2)
|
||||
@ -69,6 +76,24 @@ migrateDiff projectDir = do
|
||||
|
||||
runNodeCommandAsJob serverDir (absPrismaExecutableFp projectDir) prismaMigrateDiffCmdArgs J.Db
|
||||
|
||||
-- | Checks to see if all migrations are applied to the DB.
|
||||
-- An exit code of 0 means we successfully verified all migrations are applied.
|
||||
-- An exit code of 1 could mean either: (a) there was a DB connection error,
|
||||
-- or (b) there are pending migrations to apply.
|
||||
-- Therefore, this should be checked **after** a command that ensures connectivity.
|
||||
migrateStatus :: Path' Abs (Dir ProjectRootDir) -> J.Job
|
||||
migrateStatus projectDir = do
|
||||
let serverDir = projectDir </> serverRootDirInProjectRootDir
|
||||
let schemaFileFp = SP.toFilePath $ projectDir </> dbSchemaFileInProjectRootDir
|
||||
let prismaMigrateDiffCmdArgs =
|
||||
[ "migrate",
|
||||
"status",
|
||||
"--schema",
|
||||
schemaFileFp
|
||||
]
|
||||
|
||||
runNodeCommandAsJob serverDir (absPrismaExecutableFp projectDir) prismaMigrateDiffCmdArgs J.Db
|
||||
|
||||
-- | Runs `prisma studio` - Prisma's db inspector.
|
||||
runStudio :: Path' Abs (Dir ProjectRootDir) -> J.Job
|
||||
runStudio projectDir = do
|
||||
|
@ -3,6 +3,8 @@ module Wasp.Generator.DbGenerator.Operations
|
||||
generatePrismaClient,
|
||||
doesSchemaMatchDb,
|
||||
writeDbSchemaChecksumToFile,
|
||||
removeDbSchemaChecksumFile,
|
||||
areAllMigrationsAppliedToDb,
|
||||
)
|
||||
where
|
||||
|
||||
@ -13,16 +15,19 @@ import Control.Monad.Catch (catch)
|
||||
import qualified Path as P
|
||||
import StrongPath (Abs, Dir, File', Path', Rel)
|
||||
import qualified StrongPath as SP
|
||||
import System.Directory (doesFileExist)
|
||||
import System.Directory (doesFileExist, removeFile)
|
||||
import System.Exit (ExitCode (..))
|
||||
import Wasp.Common (DbMigrationsDir)
|
||||
import Wasp.Generator.Common (ProjectRootDir)
|
||||
import Wasp.Generator.DbGenerator.Common
|
||||
( dbMigrationsDirInDbRootDir,
|
||||
( MigrateArgs,
|
||||
RefreshOnLastDbConcurrenceChecksumFile (..),
|
||||
dbMigrationsDirInDbRootDir,
|
||||
dbRootDirInProjectRootDir,
|
||||
dbSchemaChecksumOnLastDbConcurrenceFileProjectRootDir,
|
||||
dbSchemaChecksumOnLastGenerateFileProjectRootDir,
|
||||
dbSchemaFileInProjectRootDir,
|
||||
getOnLastDbConcurrenceChecksumFileRefreshAction,
|
||||
)
|
||||
import qualified Wasp.Generator.DbGenerator.Jobs as DbJobs
|
||||
import Wasp.Generator.FileDraft.WriteableMonad
|
||||
@ -43,26 +48,33 @@ printJobMsgsUntilExitReceived chan = do
|
||||
|
||||
-- | Migrates in the generated project context and then copies the migrations dir back
|
||||
-- up to the wasp project dir to ensure they remain in sync.
|
||||
migrateDevAndCopyToSource :: Path' Abs (Dir DbMigrationsDir) -> Path' Abs (Dir ProjectRootDir) -> Maybe String -> IO (Either String ())
|
||||
migrateDevAndCopyToSource dbMigrationsDirInWaspProjectDirAbs genProjectRootDirAbs maybeMigrationName = do
|
||||
migrateDevAndCopyToSource :: Path' Abs (Dir DbMigrationsDir) -> Path' Abs (Dir ProjectRootDir) -> MigrateArgs -> IO (Either String ())
|
||||
migrateDevAndCopyToSource dbMigrationsDirInWaspProjectDirAbs genProjectRootDirAbs migrateArgs = do
|
||||
chan <- newChan
|
||||
(_, dbExitCode) <-
|
||||
concurrently
|
||||
(printJobMsgsUntilExitReceived chan)
|
||||
(DbJobs.migrateDev genProjectRootDirAbs maybeMigrationName chan)
|
||||
(DbJobs.migrateDev genProjectRootDirAbs migrateArgs chan)
|
||||
case dbExitCode of
|
||||
ExitSuccess -> finalizeMigration genProjectRootDirAbs dbMigrationsDirInWaspProjectDirAbs
|
||||
ExitSuccess -> finalizeMigration genProjectRootDirAbs dbMigrationsDirInWaspProjectDirAbs (getOnLastDbConcurrenceChecksumFileRefreshAction migrateArgs)
|
||||
ExitFailure code -> return $ Left $ "Migrate (dev) failed with exit code: " ++ show code
|
||||
|
||||
finalizeMigration :: Path' Abs (Dir ProjectRootDir) -> Path' Abs (Dir DbMigrationsDir) -> IO (Either String ())
|
||||
finalizeMigration genProjectRootDirAbs dbMigrationsDirInWaspProjectDirAbs = do
|
||||
finalizeMigration :: Path' Abs (Dir ProjectRootDir) -> Path' Abs (Dir DbMigrationsDir) -> RefreshOnLastDbConcurrenceChecksumFile -> IO (Either String ())
|
||||
finalizeMigration genProjectRootDirAbs dbMigrationsDirInWaspProjectDirAbs onLastDbConcurrenceChecksumFileRefreshAction = do
|
||||
-- NOTE: We are updating a managed CopyDirFileDraft outside the normal generation process, so we must invalidate the checksum entry for it.
|
||||
Generator.WriteFileDrafts.removeFromChecksumFile genProjectRootDirAbs [Right $ SP.castDir dbMigrationsDirInProjectRootDir]
|
||||
res <- copyMigrationsBackToSource genProjectRootDirAbs dbMigrationsDirInWaspProjectDirAbs
|
||||
writeDbSchemaChecksumToFile genProjectRootDirAbs (SP.castFile dbSchemaChecksumOnLastDbConcurrenceFileProjectRootDir)
|
||||
applyOnLastDbConcurrenceChecksumFileRefreshAction
|
||||
return res
|
||||
where
|
||||
dbMigrationsDirInProjectRootDir = dbRootDirInProjectRootDir SP.</> dbMigrationsDirInDbRootDir
|
||||
applyOnLastDbConcurrenceChecksumFileRefreshAction =
|
||||
case onLastDbConcurrenceChecksumFileRefreshAction of
|
||||
WriteOnLastDbConcurrenceChecksumFile ->
|
||||
writeDbSchemaChecksumToFile genProjectRootDirAbs (SP.castFile dbSchemaChecksumOnLastDbConcurrenceFileProjectRootDir)
|
||||
RemoveOnLastDbConcurrenceChecksumFile ->
|
||||
removeDbSchemaChecksumFile genProjectRootDirAbs (SP.castFile dbSchemaChecksumOnLastDbConcurrenceFileProjectRootDir)
|
||||
IgnoreOnLastDbConcurrenceChecksumFile -> return ()
|
||||
|
||||
-- | Copies the DB migrations from the generated project dir back up to theh wasp project dir
|
||||
copyMigrationsBackToSource :: Path' Abs (Dir ProjectRootDir) -> Path' Abs (Dir DbMigrationsDir) -> IO (Either String ())
|
||||
@ -86,6 +98,11 @@ writeDbSchemaChecksumToFile genProjectRootDirAbs dbSchemaChecksumInProjectRootDi
|
||||
dbSchemaFp = SP.fromAbsFile $ genProjectRootDirAbs SP.</> dbSchemaFileInProjectRootDir
|
||||
dbSchemaChecksumFp = SP.fromAbsFile $ genProjectRootDirAbs SP.</> dbSchemaChecksumInProjectRootDir
|
||||
|
||||
removeDbSchemaChecksumFile :: Path' Abs (Dir ProjectRootDir) -> Path' (Rel ProjectRootDir) File' -> IO ()
|
||||
removeDbSchemaChecksumFile genProjectRootDirAbs dbSchemaChecksumInProjectRootDir =
|
||||
let dbSchemaChecksumFp = SP.fromAbsFile $ genProjectRootDirAbs SP.</> dbSchemaChecksumInProjectRootDir
|
||||
in removeFile dbSchemaChecksumFp
|
||||
|
||||
generatePrismaClient :: Path' Abs (Dir ProjectRootDir) -> IO (Either String ())
|
||||
generatePrismaClient genProjectRootDirAbs = do
|
||||
chan <- newChan
|
||||
@ -116,3 +133,19 @@ doesSchemaMatchDb genProjectRootDirAbs = do
|
||||
ExitSuccess -> return $ Just True
|
||||
ExitFailure 2 -> return $ Just False
|
||||
ExitFailure _ -> return Nothing
|
||||
|
||||
-- | Checks `prisma migrate status` exit code to determine if migrations dir
|
||||
-- matches the DB. Returns Nothing on error as we do not know the current state.
|
||||
-- Returns Just True if all migrations are applied. Due to the fact the command
|
||||
-- returns an error on connection or unapplied migrations, Just False is never returned.
|
||||
-- It is recommended to call this after some check that confirms DB connectivity, like `doesSchemaMatchDb`.
|
||||
areAllMigrationsAppliedToDb :: Path' Abs (Dir ProjectRootDir) -> IO (Maybe Bool)
|
||||
areAllMigrationsAppliedToDb genProjectRootDirAbs = do
|
||||
chan <- newChan
|
||||
(_, dbExitCode) <-
|
||||
concurrently
|
||||
(readJobMessagesAndPrintThemPrefixed chan)
|
||||
(DbJobs.migrateStatus genProjectRootDirAbs chan)
|
||||
case dbExitCode of
|
||||
ExitSuccess -> return $ Just True
|
||||
ExitFailure _ -> return Nothing
|
||||
|
@ -15,7 +15,14 @@ import StrongPath
|
||||
import qualified StrongPath as SP
|
||||
import Wasp.Generator.Common (ProjectRootDir)
|
||||
import Wasp.Generator.FileDraft.Writeable
|
||||
import Wasp.Generator.FileDraft.WriteableMonad (WriteableMonad (copyDirectoryRecursive, createDirectoryIfMissing), doesDirectoryExist)
|
||||
import Wasp.Generator.FileDraft.WriteableMonad
|
||||
( WriteableMonad
|
||||
( copyDirectoryRecursive,
|
||||
createDirectoryIfMissing,
|
||||
removeDirectoryRecursive
|
||||
),
|
||||
doesDirectoryExist,
|
||||
)
|
||||
import Wasp.Util (checksumFromByteString, checksumFromChecksums)
|
||||
import Wasp.Util.IO (listDirectoryDeep)
|
||||
|
||||
@ -35,6 +42,8 @@ data CopyDirFileDraft = CopyDirFileDraft
|
||||
instance Writeable CopyDirFileDraft where
|
||||
write projectRootAbsPath draft = do
|
||||
srcDirExists <- doesDirectoryExist $ SP.fromAbsDir srcPathAbsDir
|
||||
dstDirExists <- doesDirectoryExist $ SP.fromAbsDir dstPathAbsDir
|
||||
when dstDirExists $ removeDirectoryRecursive dstPathAbsDir
|
||||
when srcDirExists $ do
|
||||
createDirectoryIfMissing True (SP.fromAbsDir dstPathAbsDir)
|
||||
copyDirectoryRecursive srcPathAbsDir dstPathAbsDir
|
||||
|
@ -44,6 +44,10 @@ class (MonadIO m) => WriteableMonad m where
|
||||
Path' Abs (Dir b) ->
|
||||
m ()
|
||||
|
||||
-- | Removes an existing directory dir together with its contents and sub-directories.
|
||||
-- Within this directory, symbolic links are removed without affecting their targets.
|
||||
removeDirectoryRecursive :: Path' Abs (Dir b) -> m ()
|
||||
|
||||
doesFileExist :: FilePath -> m Bool
|
||||
|
||||
doesDirectoryExist :: FilePath -> m Bool
|
||||
@ -85,6 +89,8 @@ instance WriteableMonad IO where
|
||||
copyDirectoryRecursive src dst = do
|
||||
PathIO.copyDirRecur (SP.Path.toPathAbsDir src) (SP.Path.toPathAbsDir dst)
|
||||
|
||||
removeDirectoryRecursive dir = PathIO.removeDirRecur (SP.Path.toPathAbsDir dir)
|
||||
|
||||
doesFileExist = System.Directory.doesFileExist
|
||||
doesDirectoryExist = System.Directory.doesDirectoryExist
|
||||
writeFileFromText = Data.Text.IO.writeFile
|
||||
|
21
waspc/test/Generator/DbGeneratorTest.hs
Normal file
21
waspc/test/Generator/DbGeneratorTest.hs
Normal file
@ -0,0 +1,21 @@
|
||||
module Generator.DbGeneratorTest where
|
||||
|
||||
import Test.Tasty.Hspec (Spec, it, shouldBe)
|
||||
import Wasp.Generator.DbGenerator.Common
|
||||
( MigrateArgs (..),
|
||||
defaultMigrateArgs,
|
||||
)
|
||||
import Wasp.Generator.DbGenerator.Jobs (asPrismaCliArgs)
|
||||
|
||||
spec_Jobs :: Spec
|
||||
spec_Jobs =
|
||||
it "should produce expected args" $ do
|
||||
asPrismaCliArgs defaultMigrateArgs `shouldBe` []
|
||||
asPrismaCliArgs (MigrateArgs {_migrationName = Nothing, _isCreateOnlyMigration = True})
|
||||
`shouldBe` ["--create-only"]
|
||||
asPrismaCliArgs (MigrateArgs {_migrationName = Just "something", _isCreateOnlyMigration = False})
|
||||
`shouldBe` ["--name", "something"]
|
||||
asPrismaCliArgs (MigrateArgs {_migrationName = Just "something else longer", _isCreateOnlyMigration = False})
|
||||
`shouldBe` ["--name", "something else longer"]
|
||||
asPrismaCliArgs (MigrateArgs {_migrationName = Just "something", _isCreateOnlyMigration = True})
|
||||
`shouldBe` ["--create-only", "--name", "something"]
|
@ -39,7 +39,7 @@ defaultMockConfig =
|
||||
getMockLogs :: MockWriteableMonad a -> MockWriteableMonadConfig -> MockWriteableMonadLogs
|
||||
getMockLogs mock config = fst $ execState (unMockWriteableMonad mock) (emptyLogs, config)
|
||||
where
|
||||
emptyLogs = MockWriteableMonadLogs [] [] [] [] [] [] []
|
||||
emptyLogs = MockWriteableMonadLogs [] [] [] [] [] [] [] []
|
||||
|
||||
instance WriteableMonad MockWriteableMonad where
|
||||
writeFileFromText dstPath text = MockWriteableMonad $ do
|
||||
@ -77,6 +77,9 @@ instance WriteableMonad MockWriteableMonad where
|
||||
copyDirectoryRecursive srcPath dstPath = MockWriteableMonad $ do
|
||||
modifyLogs (copyDirectoryRecursive_addCall (castDir srcPath) (castDir dstPath))
|
||||
|
||||
removeDirectoryRecursive dir = MockWriteableMonad $ do
|
||||
modifyLogs (removeDirectoryRecursive_addCall (castDir dir))
|
||||
|
||||
throwIO = throwIO
|
||||
|
||||
instance MonadIO MockWriteableMonad where
|
||||
@ -97,7 +100,8 @@ data MockWriteableMonadLogs = MockWriteableMonadLogs
|
||||
copyFile_calls :: [(FilePath, FilePath)],
|
||||
getTemplateFileAbsPath_calls :: [Path' (Rel TemplatesDir) File'],
|
||||
compileAndRenderTemplate_calls :: [(Path' (Rel TemplatesDir) File', Aeson.Value)],
|
||||
copyDirectoryRecursive_calls :: [(Path' Abs Dir', Path' Abs Dir')]
|
||||
copyDirectoryRecursive_calls :: [(Path' Abs Dir', Path' Abs Dir')],
|
||||
removeDirectoryRecursive_calls :: [Path' Abs Dir']
|
||||
}
|
||||
|
||||
data MockWriteableMonadConfig = MockWriteableMonadConfig
|
||||
@ -135,6 +139,10 @@ copyDirectoryRecursive_addCall :: Path' Abs Dir' -> Path' Abs Dir' -> MockWritea
|
||||
copyDirectoryRecursive_addCall srcPath dstPath logs =
|
||||
logs {copyDirectoryRecursive_calls = (srcPath, dstPath) : copyDirectoryRecursive_calls logs}
|
||||
|
||||
removeDirectoryRecursive_addCall :: Path' Abs Dir' -> MockWriteableMonadLogs -> MockWriteableMonadLogs
|
||||
removeDirectoryRecursive_addCall dir logs =
|
||||
logs {removeDirectoryRecursive_calls = dir : removeDirectoryRecursive_calls logs}
|
||||
|
||||
compileAndRenderTemplate_addCall ::
|
||||
Path' (Rel TemplatesDir) File' ->
|
||||
Aeson.Value ->
|
||||
|
@ -411,6 +411,7 @@ test-suite waspc-test
|
||||
ErrorTest
|
||||
FilePath.ExtraTest
|
||||
Fixtures
|
||||
Generator.DbGeneratorTest
|
||||
Generator.ExternalCodeGenerator.JsTest
|
||||
Generator.FileDraft.CopyFileDraftTest
|
||||
Generator.FileDraft.TemplateFileDraftTest
|
||||
@ -447,6 +448,7 @@ test-suite cli-test
|
||||
, tasty-hspec >= 1.1 && < 1.1.7
|
||||
, tasty-quickcheck ^>= 0.10
|
||||
other-modules:
|
||||
DbMigrateTest
|
||||
TerminalTest
|
||||
Paths_waspc
|
||||
|
||||
|
@ -16,6 +16,7 @@ COMMANDS
|
||||
GENERAL
|
||||
new <project-name> Creates new Wasp project.
|
||||
version Prints current version of CLI.
|
||||
waspls Run Wasp Language Server. Add --help to get more info.
|
||||
completion Prints help on bash completion.
|
||||
IN PROJECT
|
||||
start Runs Wasp app in development mode, watching for file changes.
|
||||
@ -24,6 +25,7 @@ COMMANDS
|
||||
build Generates full web app code, ready for deployment. Use when deploying or ejecting.
|
||||
telemetry Prints telemetry status.
|
||||
deps Prints the dependencies that Wasp uses in your project.
|
||||
dockerfile Prints the contents of the Wasp generated Dockerfile.
|
||||
info Prints basic information about current Wasp project.
|
||||
|
||||
EXAMPLES
|
||||
@ -33,7 +35,7 @@ EXAMPLES
|
||||
|
||||
Docs: https://wasp-lang.dev/docs
|
||||
Discord (chat): https://discord.gg/rzdnErX
|
||||
|
||||
Newsletter: https://wasp-lang.dev/#signup
|
||||
```
|
||||
|
||||
## Commands
|
||||
@ -88,5 +90,6 @@ To setup Bash completion, execute `wasp completion` and follow the instructions.
|
||||
Wasp has a set of commands for working with the database. They all start with `db` and mostly call prisma commands in the background.
|
||||
|
||||
- `wasp db migrate-dev` ensures dev database corresponds to the current state of schema (entities): it generates a new migration if there are changes in the schema and it applies any pending migration to the database.
|
||||
- Supports a `--name foo` option for providing a migration name, as well as `--create-only` for creating an empty migration but not applying it.
|
||||
|
||||
- `wasp db studio` opens the GUI for inspecting your database.
|
||||
|
Loading…
Reference in New Issue
Block a user