mirror of
https://github.com/wasp-lang/wasp.git
synced 2024-12-24 17:44:21 +03:00
Make warnings filterable to avoid redundant messages (#610)
This commit is contained in:
parent
1721371fc7
commit
a264d2ee29
@ -1,3 +1,5 @@
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
|
||||
module Wasp.Cli.Command.Build
|
||||
( build,
|
||||
)
|
||||
@ -22,6 +24,7 @@ import Wasp.Cli.Command.Message (cliSendMessageC)
|
||||
import qualified Wasp.Cli.Common as Common
|
||||
import Wasp.Cli.Message (cliSendMessage)
|
||||
import Wasp.CompileOptions (CompileOptions (..))
|
||||
import Wasp.Generator.Monad (GeneratorWarning (GeneratorNeedsMigrationWarning))
|
||||
import qualified Wasp.Lib
|
||||
import qualified Wasp.Message as Msg
|
||||
|
||||
@ -56,5 +59,12 @@ buildIO waspProjectDir buildDir = compileIOWithOptions options waspProjectDir bu
|
||||
CompileOptions
|
||||
{ externalCodeDirPath = waspProjectDir </> Common.extCodeDirInWaspProjectDir,
|
||||
isBuild = True,
|
||||
sendMessage = cliSendMessage
|
||||
sendMessage = cliSendMessage,
|
||||
-- Ignore "DB needs migration warnings" during build, as that is not a required step.
|
||||
generatorWarningsFilter =
|
||||
filter
|
||||
( \case
|
||||
GeneratorNeedsMigrationWarning _ -> False
|
||||
_ -> True
|
||||
)
|
||||
}
|
||||
|
@ -1,6 +1,7 @@
|
||||
module Wasp.Cli.Command.Compile
|
||||
( compileIO,
|
||||
compile,
|
||||
compileWithOptions,
|
||||
compileIOWithOptions,
|
||||
defaultCompileOptions,
|
||||
)
|
||||
@ -24,13 +25,21 @@ import qualified Wasp.Message as Msg
|
||||
|
||||
compile :: Command ()
|
||||
compile = do
|
||||
-- TODO: Consider a way to remove the redundancy of finding the project root
|
||||
-- here and in compileWithOptions. One option could be to add this to defaultCompileOptions
|
||||
-- add make externalCodeDirPath a helper function, along with any others we typically need.
|
||||
waspProjectDir <- findWaspProjectRootDirFromCwd
|
||||
compileWithOptions $ defaultCompileOptions waspProjectDir
|
||||
|
||||
compileWithOptions :: CompileOptions -> Command ()
|
||||
compileWithOptions options = do
|
||||
waspProjectDir <- findWaspProjectRootDirFromCwd
|
||||
let outDir =
|
||||
waspProjectDir </> Common.dotWaspDirInWaspProjectDir
|
||||
</> Common.generatedCodeDirInDotWaspDir
|
||||
|
||||
cliSendMessageC $ Msg.Start "Compiling wasp code..."
|
||||
compilationResult <- liftIO $ compileIO waspProjectDir outDir
|
||||
compilationResult <- liftIO $ compileIOWithOptions options waspProjectDir outDir
|
||||
case compilationResult of
|
||||
Left compileError -> throwError $ CommandError "Compilation failed" compileError
|
||||
Right () -> cliSendMessageC $ Msg.Success "Code has been successfully compiled, project has been generated."
|
||||
@ -66,5 +75,6 @@ defaultCompileOptions waspProjectDir =
|
||||
CompileOptions
|
||||
{ externalCodeDirPath = waspProjectDir </> Common.extCodeDirInWaspProjectDir,
|
||||
isBuild = False,
|
||||
sendMessage = cliSendMessage
|
||||
sendMessage = cliSendMessage,
|
||||
generatorWarningsFilter = id
|
||||
}
|
||||
|
@ -1,3 +1,5 @@
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
|
||||
module Wasp.Cli.Command.Db
|
||||
( runDbCommand,
|
||||
studio,
|
||||
@ -10,11 +12,13 @@ import Control.Monad.IO.Class (liftIO)
|
||||
import StrongPath ((</>))
|
||||
import Wasp.Cli.Command (Command, runCommand)
|
||||
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd)
|
||||
import Wasp.Cli.Command.Compile (compile)
|
||||
import Wasp.Cli.Command.Compile (compileWithOptions, defaultCompileOptions)
|
||||
import Wasp.Cli.Command.Message (cliSendMessageC)
|
||||
import qualified Wasp.Cli.Common as Common
|
||||
import Wasp.CompileOptions (CompileOptions (generatorWarningsFilter))
|
||||
import Wasp.Generator.DbGenerator.Jobs (runStudio)
|
||||
import Wasp.Generator.Job.IO (readJobMessagesAndPrintThemPrefixed)
|
||||
import Wasp.Generator.Monad (GeneratorWarning (GeneratorNeedsMigrationWarning))
|
||||
import qualified Wasp.Message as Msg
|
||||
|
||||
runDbCommand :: Command a -> IO ()
|
||||
@ -27,8 +31,21 @@ runDbCommand = runCommand . makeDbCommand
|
||||
makeDbCommand :: Command a -> Command a
|
||||
makeDbCommand cmd = do
|
||||
-- Ensure code is generated and npm dependencies are installed.
|
||||
compile
|
||||
waspProjectDir <- findWaspProjectRootDirFromCwd
|
||||
compileWithOptions $ compileOptions waspProjectDir
|
||||
cmd
|
||||
where
|
||||
compileOptions waspProjectDir =
|
||||
(defaultCompileOptions waspProjectDir)
|
||||
{ -- Ignore "DB needs migration warnings" during database commands, as that is redundant
|
||||
-- for `db migrate-dev` and not helpful for `db studio`.
|
||||
generatorWarningsFilter =
|
||||
filter
|
||||
( \case
|
||||
GeneratorNeedsMigrationWarning _ -> False
|
||||
_ -> True
|
||||
)
|
||||
}
|
||||
|
||||
-- TODO(matija): should we extract this into a separate file, like we did for migrate?
|
||||
studio :: Command ()
|
||||
|
@ -5,6 +5,7 @@ where
|
||||
|
||||
import StrongPath (Abs, Dir, Path')
|
||||
import Wasp.AppSpec.ExternalCode (SourceExternalCodeDir)
|
||||
import Wasp.Generator.Monad (GeneratorWarning)
|
||||
import Wasp.Message (SendMessage)
|
||||
|
||||
-- TODO(martin): Should these be merged with Wasp data? Is it really a separate thing or not?
|
||||
@ -16,5 +17,10 @@ data CompileOptions = CompileOptions
|
||||
-- We give the compiler the ability to send messages. The code that
|
||||
-- invokes the compiler (such as the CLI) can then implement a way
|
||||
-- to display these messages.
|
||||
sendMessage :: SendMessage
|
||||
sendMessage :: SendMessage,
|
||||
-- The generator returns a list of warnings and errors that happen during compilation.
|
||||
-- CLI commands will almost always compile before they execute to ensure the project is up to date.
|
||||
-- This filter function allows callers to ignore certain warnings where they do not make sense.
|
||||
-- For example, showing a compilation warning to run `db migrate-dev` when you are running that command.
|
||||
generatorWarningsFilter :: [GeneratorWarning] -> [GeneratorWarning]
|
||||
}
|
||||
|
@ -31,7 +31,12 @@ import Wasp.Generator.DbGenerator.Common
|
||||
)
|
||||
import qualified Wasp.Generator.DbGenerator.Operations as DbOps
|
||||
import Wasp.Generator.FileDraft (FileDraft, createCopyDirFileDraft, createTemplateFileDraft)
|
||||
import Wasp.Generator.Monad (Generator, GeneratorError (..), GeneratorWarning (GenericGeneratorWarning), logAndThrowGeneratorError)
|
||||
import Wasp.Generator.Monad
|
||||
( Generator,
|
||||
GeneratorError (..),
|
||||
GeneratorWarning (GeneratorNeedsMigrationWarning),
|
||||
logAndThrowGeneratorError,
|
||||
)
|
||||
import qualified Wasp.Psl.Ast.Model as Psl.Ast.Model
|
||||
import qualified Wasp.Psl.Generator.Model as Psl.Generator.Model
|
||||
import Wasp.Util (checksumFromFilePath, hexToString, ifM, (<:>))
|
||||
@ -113,7 +118,7 @@ warnIfDbSchemaChangedSinceLastMigration spec projectRootDir = do
|
||||
entitiesExist = not . null $ getEntities spec
|
||||
|
||||
warnIf :: Bool -> String -> Maybe GeneratorWarning
|
||||
warnIf b msg = if b then Just $ GenericGeneratorWarning msg else Nothing
|
||||
warnIf b msg = if b then Just $ GeneratorNeedsMigrationWarning msg else Nothing
|
||||
|
||||
genPrismaClient :: AppSpec -> Path' Abs (Dir ProjectRootDir) -> IO (Maybe GeneratorError)
|
||||
genPrismaClient spec projectRootDir = do
|
||||
|
@ -45,10 +45,13 @@ data GeneratorError = GenericGeneratorError String
|
||||
instance Show GeneratorError where
|
||||
show (GenericGeneratorError e) = e
|
||||
|
||||
data GeneratorWarning = GenericGeneratorWarning String
|
||||
data GeneratorWarning
|
||||
= GenericGeneratorWarning String
|
||||
| GeneratorNeedsMigrationWarning String
|
||||
|
||||
instance Show GeneratorWarning where
|
||||
show (GenericGeneratorWarning e) = e
|
||||
show (GeneratorNeedsMigrationWarning e) = e
|
||||
|
||||
-- Runs the generator and either returns a result, or a list of 1 or more errors.
|
||||
-- Results in error if any error was ever logged and thrown (even if caught).
|
||||
|
@ -16,7 +16,7 @@ import Wasp.Analyzer.AnalyzeError (getErrorMessageAndCtx)
|
||||
import qualified Wasp.AppSpec as AS
|
||||
import qualified Wasp.AppSpec.Valid as ASV
|
||||
import Wasp.Common (DbMigrationsDir, WaspProjectDir, dbMigrationsDirInWaspProjectDir)
|
||||
import Wasp.CompileOptions (CompileOptions, sendMessage)
|
||||
import Wasp.CompileOptions (CompileOptions (generatorWarningsFilter), sendMessage)
|
||||
import qualified Wasp.CompileOptions as CompileOptions
|
||||
import Wasp.Error (showCompilerErrorForTerminal)
|
||||
import qualified Wasp.ExternalCode as ExternalCode
|
||||
@ -41,7 +41,7 @@ compile waspDir outDir options = do
|
||||
case ASV.validateAppSpec appSpec of
|
||||
[] -> do
|
||||
(generatorWarnings, generatorErrors) <- Generator.writeWebAppCode appSpec outDir (sendMessage options)
|
||||
return (map show generatorWarnings, map show generatorErrors)
|
||||
return (map show $ generatorWarningsFilter options generatorWarnings, map show generatorErrors)
|
||||
validationErrors -> do
|
||||
return ([], map show validationErrors)
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user