show error message when database is not running (#1218)

Co-authored-by: Martin Šošić <Martinsos@users.noreply.github.com>
Co-authored-by: Mihovil Ilakovac <mihovil@ilakovac.com>
This commit is contained in:
Craig McIlwrath 2023-06-20 14:34:14 -04:00 committed by GitHub
parent e43b8f986c
commit 802e0c5e5d
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
26 changed files with 251 additions and 348 deletions

View File

@ -1,24 +1,35 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Wasp.Cli.Command module Wasp.Cli.Command
( Command, ( Command,
runCommand, runCommand,
CommandError (..), CommandError (..),
-- * Requirements
-- See "Wasp.Cli.Command.Requires" for documentation.
require,
Requirable (checkRequirement),
) )
where where
import Control.Monad.Except (ExceptT, MonadError, runExceptT) import Control.Monad.Error.Class (MonadError)
import Control.Monad.Except (ExceptT, runExceptT)
import Control.Monad.IO.Class (MonadIO) import Control.Monad.IO.Class (MonadIO)
import Control.Monad.State.Strict (StateT, evalStateT, gets, modify)
import Data.Data (Typeable, cast)
import Data.Maybe (mapMaybe)
import System.Exit (exitFailure) import System.Exit (exitFailure)
import Wasp.Cli.Message (cliSendMessage) import Wasp.Cli.Message (cliSendMessage)
import qualified Wasp.Message as Msg import qualified Wasp.Message as Msg
newtype Command a = Command {_runCommand :: ExceptT CommandError IO a} newtype Command a = Command {_runCommand :: StateT [Requirement] (ExceptT CommandError IO) a}
deriving (Functor, Applicative, Monad, MonadIO, MonadError CommandError) deriving (Functor, Applicative, Monad, MonadIO, MonadError CommandError)
runCommand :: Command a -> IO () runCommand :: Command a -> IO ()
runCommand cmd = do runCommand cmd = do
runExceptT (_runCommand cmd) >>= \case runExceptT (flip evalStateT [] $ _runCommand cmd) >>= \case
Left cmdError -> do Left cmdError -> do
cliSendMessage $ Msg.Failure (_errorTitle cmdError) (_errorMsg cmdError) cliSendMessage $ Msg.Failure (_errorTitle cmdError) (_errorMsg cmdError)
exitFailure exitFailure
@ -27,3 +38,33 @@ runCommand cmd = do
-- TODO: What if we want to recognize errors in order to handle them? -- TODO: What if we want to recognize errors in order to handle them?
-- Should we add _commandErrorType? Should CommandError be parametrized by it, is that even possible? -- Should we add _commandErrorType? Should CommandError be parametrized by it, is that even possible?
data CommandError = CommandError {_errorTitle :: !String, _errorMsg :: !String} data CommandError = CommandError {_errorTitle :: !String, _errorMsg :: !String}
data Requirement where
Requirement :: Requirable r => r -> Requirement
class Typeable r => Requirable r where
-- | Check if the requirement is met and return a value representing that
-- requirement.
--
-- This function must always return a value: if the requirement is not met,
-- throw a 'CommandError'.
checkRequirement :: Command r
-- | Assert that a requirement is met and receive information about that
-- requirement, if any is offered.
--
-- To use, pattern match on the result, e.g.
--
-- @
-- do
-- HasDbConnection <- require
-- @
require :: Requirable r => Command r
require =
Command (gets (mapMaybe cast)) >>= \case
(req : _) -> return req
[] -> do
-- Requirement hasn't been met, so run the check
req <- checkRequirement
Command $ modify (Requirement req :)
return req

View File

@ -13,11 +13,9 @@ import System.Directory
removeDirectoryRecursive, removeDirectoryRecursive,
) )
import Wasp.Cli.Command (Command, CommandError (..)) import Wasp.Cli.Command (Command, CommandError (..))
import Wasp.Cli.Command.Common
( findWaspProjectRootDirFromCwd,
)
import Wasp.Cli.Command.Compile (compileIOWithOptions, printCompilationResult) import Wasp.Cli.Command.Compile (compileIOWithOptions, printCompilationResult)
import Wasp.Cli.Command.Message (cliSendMessageC) import Wasp.Cli.Command.Message (cliSendMessageC)
import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import qualified Wasp.Cli.Common as Common import qualified Wasp.Cli.Common as Common
import Wasp.Cli.Message (cliSendMessage) import Wasp.Cli.Message (cliSendMessage)
import Wasp.CompileOptions (CompileOptions (..)) import Wasp.CompileOptions (CompileOptions (..))
@ -35,7 +33,7 @@ import Wasp.Project (CompileError, CompileWarning)
-- Very similar to 'compile'. -- Very similar to 'compile'.
build :: Command () build :: Command ()
build = do build = do
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
let buildDir = let buildDir =
waspProjectDir </> Common.dotWaspDirInWaspProjectDir waspProjectDir </> Common.dotWaspDirInWaspProjectDir
</> Common.buildDirInDotWaspDir </> Common.buildDirInDotWaspDir

View File

@ -10,14 +10,14 @@ import System.Directory
removeDirectoryRecursive, removeDirectoryRecursive,
) )
import Wasp.Cli.Command (Command) import Wasp.Cli.Command (Command)
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd)
import Wasp.Cli.Command.Message (cliSendMessageC) import Wasp.Cli.Command.Message (cliSendMessageC)
import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import qualified Wasp.Cli.Common as Common import qualified Wasp.Cli.Common as Common
import qualified Wasp.Message as Msg import qualified Wasp.Message as Msg
clean :: Command () clean :: Command ()
clean = do clean = do
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
let dotWaspDirFp = SP.toFilePath $ waspProjectDir SP.</> Common.dotWaspDirInWaspProjectDir let dotWaspDirFp = SP.toFilePath $ waspProjectDir SP.</> Common.dotWaspDirInWaspProjectDir
cliSendMessageC $ Msg.Start "Deleting .wasp/ directory..." cliSendMessageC $ Msg.Start "Deleting .wasp/ directory..."
doesDotWaspDirExist <- liftIO $ doesDirectoryExist dotWaspDirFp doesDotWaspDirExist <- liftIO $ doesDirectoryExist dotWaspDirFp

View File

@ -1,52 +1,20 @@
module Wasp.Cli.Command.Common module Wasp.Cli.Command.Common
( findWaspProjectRootDirFromCwd, ( readWaspCompileInfo,
findWaspProjectRoot,
readWaspCompileInfo,
throwIfExeIsNotAvailable, throwIfExeIsNotAvailable,
) )
where where
import Control.Monad.Except import Control.Monad.Except
import qualified Control.Monad.Except as E import qualified Control.Monad.Except as E
import Data.Maybe (fromJust)
import StrongPath (Abs, Dir, Path') import StrongPath (Abs, Dir, Path')
import qualified StrongPath as SP
import StrongPath.Operations import StrongPath.Operations
import System.Directory (doesFileExist, doesPathExist, findExecutable, getCurrentDirectory) import System.Directory (findExecutable)
import qualified System.FilePath as FP
import Wasp.Cli.Command (Command, CommandError (..)) import Wasp.Cli.Command (Command, CommandError (..))
import Wasp.Cli.Common (dotWaspRootFileInWaspProjectDir)
import qualified Wasp.Cli.Common as Cli.Common import qualified Wasp.Cli.Common as Cli.Common
import Wasp.Project (WaspProjectDir) import Wasp.Project (WaspProjectDir)
import Wasp.Util (ifM) import Wasp.Util (ifM)
import qualified Wasp.Util.IO as IOUtil import qualified Wasp.Util.IO as IOUtil
findWaspProjectRoot :: Path' Abs (Dir ()) -> Command (Path' Abs (Dir WaspProjectDir))
findWaspProjectRoot currentDir = do
let absCurrentDirFp = SP.fromAbsDir currentDir
doesCurrentDirExist <- liftIO $ doesPathExist absCurrentDirFp
unless doesCurrentDirExist (throwError notFoundError)
let dotWaspRootFilePath = absCurrentDirFp FP.</> SP.fromRelFile dotWaspRootFileInWaspProjectDir
isCurrentDirRoot <- liftIO $ doesFileExist dotWaspRootFilePath
if isCurrentDirRoot
then return $ SP.castDir currentDir
else do
let parentDir = SP.parent currentDir
when (parentDir == currentDir) (throwError notFoundError)
findWaspProjectRoot parentDir
where
notFoundError =
CommandError
"Wasp command failed"
( "Couldn't find wasp project root - make sure"
++ " you are running this command from a Wasp project."
)
findWaspProjectRootDirFromCwd :: Command (Path' Abs (Dir WaspProjectDir))
findWaspProjectRootDirFromCwd = do
absCurrentDir <- liftIO getCurrentDirectory
findWaspProjectRoot (fromJust $ SP.parseAbsDir absCurrentDir)
readWaspCompileInfo :: Path' Abs (Dir WaspProjectDir) -> IO String readWaspCompileInfo :: Path' Abs (Dir WaspProjectDir) -> IO String
readWaspCompileInfo waspDir = readWaspCompileInfo waspDir =
ifM ifM

View File

@ -18,10 +18,8 @@ import Data.List (intercalate)
import StrongPath (Abs, Dir, Path', (</>)) import StrongPath (Abs, Dir, Path', (</>))
import qualified Wasp.AppSpec as AS import qualified Wasp.AppSpec as AS
import Wasp.Cli.Command (Command, CommandError (..)) import Wasp.Cli.Command (Command, CommandError (..))
import Wasp.Cli.Command.Common
( findWaspProjectRootDirFromCwd,
)
import Wasp.Cli.Command.Message (cliSendMessageC) import Wasp.Cli.Command.Message (cliSendMessageC)
import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import qualified Wasp.Cli.Common as Common import qualified Wasp.Cli.Common as Common
import Wasp.Cli.Message (cliSendMessage) import Wasp.Cli.Message (cliSendMessage)
import Wasp.CompileOptions (CompileOptions (..)) import Wasp.CompileOptions (CompileOptions (..))
@ -36,7 +34,7 @@ compile = do
-- TODO: Consider a way to remove the redundancy of finding the project root -- 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 -- 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. -- add make externalCodeDirPath a helper function, along with any others we typically need.
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
compileWithOptions $ defaultCompileOptions waspProjectDir compileWithOptions $ defaultCompileOptions waspProjectDir
-- | Compiles Wasp project that the current working directory is part of. -- | Compiles Wasp project that the current working directory is part of.
@ -47,7 +45,7 @@ compile = do
-- Finally, throws if there was a compile error, otherwise returns any compile warnings. -- Finally, throws if there was a compile error, otherwise returns any compile warnings.
compileWithOptions :: CompileOptions -> Command [CompileWarning] compileWithOptions :: CompileOptions -> Command [CompileWarning]
compileWithOptions options = do compileWithOptions options = do
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
let outDir = let outDir =
waspProjectDir </> Common.dotWaspDirInWaspProjectDir waspProjectDir </> Common.dotWaspDirInWaspProjectDir
</> Common.generatedCodeDirInDotWaspDir </> Common.generatedCodeDirInDotWaspDir

View File

@ -4,8 +4,8 @@ module Wasp.Cli.Command.Db
where where
import Wasp.Cli.Command (Command, runCommand) import Wasp.Cli.Command (Command, runCommand)
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd)
import Wasp.Cli.Command.Compile (compileWithOptions, defaultCompileOptions) import Wasp.Cli.Command.Compile (compileWithOptions, defaultCompileOptions)
import Wasp.Cli.Command.Require (DbConnectionEstablished (DbConnectionEstablished), InWaspProject (InWaspProject), require)
import Wasp.CompileOptions (CompileOptions (generatorWarningsFilter)) import Wasp.CompileOptions (CompileOptions (generatorWarningsFilter))
import Wasp.Generator.Monad (GeneratorWarning (GeneratorNeedsMigrationWarning)) import Wasp.Generator.Monad (GeneratorWarning (GeneratorNeedsMigrationWarning))
@ -19,8 +19,9 @@ runDbCommand = runCommand . makeDbCommand
makeDbCommand :: Command a -> Command a makeDbCommand :: Command a -> Command a
makeDbCommand cmd = do makeDbCommand cmd = do
-- Ensure code is generated and npm dependencies are installed. -- Ensure code is generated and npm dependencies are installed.
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
_ <- compileWithOptions $ compileOptions waspProjectDir _ <- compileWithOptions $ compileOptions waspProjectDir
DbConnectionEstablished <- require
cmd cmd
where where
compileOptions waspProjectDir = compileOptions waspProjectDir =

View File

@ -8,10 +8,8 @@ import Control.Monad.Except (ExceptT (ExceptT), liftEither, runExceptT, throwErr
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import StrongPath (Abs, Dir, Path', (</>)) import StrongPath (Abs, Dir, Path', (</>))
import Wasp.Cli.Command (Command, CommandError (..)) import Wasp.Cli.Command (Command, CommandError (..))
import Wasp.Cli.Command.Common
( findWaspProjectRootDirFromCwd,
)
import Wasp.Cli.Command.Message (cliSendMessageC) import Wasp.Cli.Command.Message (cliSendMessageC)
import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import qualified Wasp.Cli.Common as Cli.Common import qualified Wasp.Cli.Common as Cli.Common
import Wasp.Generator.Common (ProjectRootDir) import Wasp.Generator.Common (ProjectRootDir)
import Wasp.Generator.DbGenerator.Common (MigrateArgs (..), defaultMigrateArgs) import Wasp.Generator.DbGenerator.Common (MigrateArgs (..), defaultMigrateArgs)
@ -24,7 +22,7 @@ import Wasp.Project.Db.Migrations (DbMigrationsDir, dbMigrationsDirInWaspProject
-- The migrate function takes care of copying migrations from the generated project back to the source code. -- The migrate function takes care of copying migrations from the generated project back to the source code.
migrateDev :: [String] -> Command () migrateDev :: [String] -> Command ()
migrateDev optionalMigrateArgs = do migrateDev optionalMigrateArgs = do
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
let waspDbMigrationsDir = waspProjectDir </> dbMigrationsDirInWaspProjectDir let waspDbMigrationsDir = waspProjectDir </> dbMigrationsDirInWaspProjectDir
let projectRootDir = let projectRootDir =
waspProjectDir waspProjectDir

View File

@ -6,15 +6,15 @@ where
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import StrongPath ((</>)) import StrongPath ((</>))
import Wasp.Cli.Command (Command) import Wasp.Cli.Command (Command)
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd)
import Wasp.Cli.Command.Message (cliSendMessageC) import Wasp.Cli.Command.Message (cliSendMessageC)
import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import qualified Wasp.Cli.Common as Common import qualified Wasp.Cli.Common as Common
import Wasp.Generator.DbGenerator.Operations (dbReset) import Wasp.Generator.DbGenerator.Operations (dbReset)
import qualified Wasp.Message as Msg import qualified Wasp.Message as Msg
reset :: Command () reset :: Command ()
reset = do reset = do
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
let genProjectDir = let genProjectDir =
waspProjectDir </> Common.dotWaspDirInWaspProjectDir </> Common.generatedCodeDirInDotWaspDir waspProjectDir </> Common.dotWaspDirInWaspProjectDir </> Common.generatedCodeDirInDotWaspDir

View File

@ -16,16 +16,16 @@ import qualified Wasp.AppSpec.App.Db as AS.Db
import qualified Wasp.AppSpec.ExtImport as AS.ExtImport import qualified Wasp.AppSpec.ExtImport as AS.ExtImport
import qualified Wasp.AppSpec.Valid as ASV import qualified Wasp.AppSpec.Valid as ASV
import Wasp.Cli.Command (Command, CommandError (CommandError)) import Wasp.Cli.Command (Command, CommandError (CommandError))
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd)
import Wasp.Cli.Command.Compile (analyze) import Wasp.Cli.Command.Compile (analyze)
import Wasp.Cli.Command.Message (cliSendMessageC) import Wasp.Cli.Command.Message (cliSendMessageC)
import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import qualified Wasp.Cli.Common as Common import qualified Wasp.Cli.Common as Common
import Wasp.Generator.DbGenerator.Operations (dbSeed) import Wasp.Generator.DbGenerator.Operations (dbSeed)
import qualified Wasp.Message as Msg import qualified Wasp.Message as Msg
seed :: Maybe String -> Command () seed :: Maybe String -> Command ()
seed maybeUserProvidedSeedName = do seed maybeUserProvidedSeedName = do
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
let genProjectDir = let genProjectDir =
waspProjectDir </> Common.dotWaspDirInWaspProjectDir </> Common.generatedCodeDirInDotWaspDir waspProjectDir </> Common.dotWaspDirInWaspProjectDir </> Common.generatedCodeDirInDotWaspDir

View File

@ -8,8 +8,8 @@ import Control.Concurrent.Async (concurrently)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import StrongPath ((</>)) import StrongPath ((</>))
import Wasp.Cli.Command (Command) import Wasp.Cli.Command (Command)
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd)
import Wasp.Cli.Command.Message (cliSendMessageC) import Wasp.Cli.Command.Message (cliSendMessageC)
import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import qualified Wasp.Cli.Common as Common import qualified Wasp.Cli.Common as Common
import Wasp.Generator.DbGenerator.Jobs (runStudio) import Wasp.Generator.DbGenerator.Jobs (runStudio)
import Wasp.Generator.Job.IO (readJobMessagesAndPrintThemPrefixed) import Wasp.Generator.Job.IO (readJobMessagesAndPrintThemPrefixed)
@ -17,7 +17,7 @@ import qualified Wasp.Message as Msg
studio :: Command () studio :: Command ()
studio = do studio = do
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
let genProjectDir = let genProjectDir =
waspProjectDir </> Common.dotWaspDirInWaspProjectDir </> Common.generatedCodeDirInDotWaspDir waspProjectDir </> Common.dotWaspDirInWaspProjectDir </> Common.generatedCodeDirInDotWaspDir

View File

@ -7,12 +7,12 @@ import Control.Monad.Except (throwError)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import System.Environment (getExecutablePath) import System.Environment (getExecutablePath)
import Wasp.Cli.Command (Command, CommandError (CommandError)) import Wasp.Cli.Command (Command, CommandError (CommandError))
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd) import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import qualified Wasp.Project.Deployment import qualified Wasp.Project.Deployment
deploy :: [String] -> Command () deploy :: [String] -> Command ()
deploy cmdArgs = do deploy cmdArgs = do
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
deployResult <- liftIO $ do deployResult <- liftIO $ do
-- `getExecutablePath` has some caveats: -- `getExecutablePath` has some caveats:
-- https://frasertweedale.github.io/blog-fp/posts/2022-05-10-improved-executable-path-queries.html -- https://frasertweedale.github.io/blog-fp/posts/2022-05-10-improved-executable-path-queries.html

View File

@ -8,8 +8,8 @@ import Control.Monad.IO.Class (liftIO)
import Wasp.AppSpec (AppSpec) import Wasp.AppSpec (AppSpec)
import qualified Wasp.AppSpec.App.Dependency as AS.Dependency import qualified Wasp.AppSpec.App.Dependency as AS.Dependency
import Wasp.Cli.Command (Command, CommandError (..)) import Wasp.Cli.Command (Command, CommandError (..))
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd)
import Wasp.Cli.Command.Compile (defaultCompileOptions) import Wasp.Cli.Command.Compile (defaultCompileOptions)
import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import Wasp.Cli.Terminal (title) import Wasp.Cli.Terminal (title)
import qualified Wasp.Generator.NpmDependencies as N import qualified Wasp.Generator.NpmDependencies as N
import qualified Wasp.Generator.ServerGenerator as ServerGenerator import qualified Wasp.Generator.ServerGenerator as ServerGenerator
@ -19,7 +19,7 @@ import qualified Wasp.Util.Terminal as Term
deps :: Command () deps :: Command ()
deps = do deps = do
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
appSpecOrAnalyzerErrors <- liftIO $ analyzeWaspProject waspProjectDir (defaultCompileOptions waspProjectDir) appSpecOrAnalyzerErrors <- liftIO $ analyzeWaspProject waspProjectDir (defaultCompileOptions waspProjectDir)
appSpec <- appSpec <-
either either

View File

@ -7,13 +7,13 @@ import Control.Monad.Except (throwError)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import qualified Data.Text.IO as T.IO import qualified Data.Text.IO as T.IO
import Wasp.Cli.Command (Command, CommandError (..)) import Wasp.Cli.Command (Command, CommandError (..))
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd)
import Wasp.Cli.Command.Compile (defaultCompileOptions) import Wasp.Cli.Command.Compile (defaultCompileOptions)
import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import Wasp.Project (compileAndRenderDockerfile) import Wasp.Project (compileAndRenderDockerfile)
printDockerfile :: Command () printDockerfile :: Command ()
printDockerfile = do printDockerfile = do
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
dockerfileContentOrCompileErrors <- liftIO $ compileAndRenderDockerfile waspProjectDir (defaultCompileOptions waspProjectDir) dockerfileContentOrCompileErrors <- liftIO $ compileAndRenderDockerfile waspProjectDir (defaultCompileOptions waspProjectDir)
either either
(throwError . CommandError "Displaying Dockerfile failed due to a compilation error in your Wasp project" . unwords) (throwError . CommandError "Displaying Dockerfile failed due to a compilation error in your Wasp project" . unwords)

View File

@ -1,5 +1,3 @@
{-# LANGUAGE TypeApplications #-}
module Wasp.Cli.Command.Info module Wasp.Cli.Command.Info
( info, ( info,
) )
@ -12,9 +10,10 @@ import StrongPath.Operations ()
import System.Directory (getFileSize) import System.Directory (getFileSize)
import qualified Wasp.AppSpec.Valid as ASV import qualified Wasp.AppSpec.Valid as ASV
import Wasp.Cli.Command (Command) import Wasp.Cli.Command (Command)
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd, readWaspCompileInfo) import Wasp.Cli.Command.Common (readWaspCompileInfo)
import Wasp.Cli.Command.Compile (analyze) import Wasp.Cli.Command.Compile (analyze)
import Wasp.Cli.Command.Message (cliSendMessageC) import Wasp.Cli.Command.Message (cliSendMessageC)
import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import Wasp.Cli.Command.Start.Db (getDbSystem) import Wasp.Cli.Command.Start.Db (getDbSystem)
import Wasp.Cli.Terminal (title) import Wasp.Cli.Terminal (title)
import qualified Wasp.Message as Msg import qualified Wasp.Message as Msg
@ -24,7 +23,7 @@ import qualified Wasp.Util.Terminal as Term
info :: Command () info :: Command ()
info = do info = do
waspDir <- findWaspProjectRootDirFromCwd InWaspProject waspDir <- require
compileInfo <- liftIO $ readWaspCompileInfo waspDir compileInfo <- liftIO $ readWaspCompileInfo waspDir
projectSize <- liftIO $ readDirectorySizeMB waspDir projectSize <- liftIO $ readDirectorySizeMB waspDir

View File

@ -0,0 +1,98 @@
module Wasp.Cli.Command.Require
( -- * Asserting Requirements
-- There are some requirements we want to assert in command code, such as
-- ensuring the command is being run inside a wasp project directory. We
-- might end up wanting to check each requirement multiple times, especially
-- if we want the value from it (like getting the wasp project directory),
-- but we also want to avoid duplicating work. Using 'require' results in
-- checked requirements being stored so they can be immediately retrieved
-- when checking the same requirements additional times.
--
-- For example, you can check if you are in a wasp project by doing
--
-- @
-- do
-- InWaspProject waspProjectDir <- require
-- @
--
-- See instances of 'Requirable' for what kinds of requirements are
-- supported. To implement a new requirable type, give your type an instance
-- of 'Requirable'.
require,
-- * Requirables
Requirable (checkRequirement),
DbConnectionEstablished (DbConnectionEstablished),
InWaspProject (InWaspProject),
)
where
import Control.Monad (unless, when)
import Control.Monad.Error.Class (throwError)
import Control.Monad.IO.Class (liftIO)
import Data.Data (Typeable)
import Data.Maybe (fromJust)
import qualified StrongPath as SP
import System.Directory (doesFileExist, doesPathExist, getCurrentDirectory)
import qualified System.FilePath as FP
import Wasp.Cli.Command (CommandError (CommandError), Requirable (checkRequirement), require)
import Wasp.Cli.Common (WaspProjectDir)
import qualified Wasp.Cli.Common as Cli.Common
import Wasp.Generator.DbGenerator.Operations (isDbRunning)
data DbConnectionEstablished = DbConnectionEstablished deriving (Typeable)
instance Requirable DbConnectionEstablished where
checkRequirement = do
-- NOTE: 'InWaspProject' does not depend on this requirement, so this
-- call to 'require' will not result in an infinite loop.
InWaspProject waspProjectDir <- require
let outDir = waspProjectDir SP.</> Cli.Common.dotWaspDirInWaspProjectDir SP.</> Cli.Common.generatedCodeDirInDotWaspDir
dbIsRunning <- liftIO $ isDbRunning outDir
if dbIsRunning
then return DbConnectionEstablished
else throwError noDbError
where
noDbError =
CommandError
"Can not connect to database"
( "The database needs to be running in order to execute this command."
++ " You can easily start a managed dev database with `wasp start db`."
)
-- | Require a Wasp project to exist near the current directory. Get the
-- project directory by pattern matching on the result of 'require':
--
-- @
-- do
-- InWaspProject waspProjectDir <- require
-- @
newtype InWaspProject = InWaspProject (SP.Path' SP.Abs (SP.Dir WaspProjectDir)) deriving (Typeable)
instance Requirable InWaspProject where
checkRequirement = do
-- Recursively searches up from CWD until @.wasproot@ file is found, or
-- throw an error if it is never found.
currentDir <- fromJust . SP.parseAbsDir <$> liftIO getCurrentDirectory
findWaspProjectRoot currentDir
where
findWaspProjectRoot currentDir = do
let absCurrentDirFp = SP.fromAbsDir currentDir
doesCurrentDirExist <- liftIO $ doesPathExist absCurrentDirFp
unless doesCurrentDirExist (throwError notFoundError)
let dotWaspRootFilePath = absCurrentDirFp FP.</> SP.fromRelFile Cli.Common.dotWaspRootFileInWaspProjectDir
isCurrentDirRoot <- liftIO $ doesFileExist dotWaspRootFilePath
if isCurrentDirRoot
then return $ InWaspProject $ SP.castDir currentDir
else do
let parentDir = SP.parent currentDir
when (parentDir == currentDir) (throwError notFoundError)
findWaspProjectRoot parentDir
notFoundError =
CommandError
"Wasp command failed"
( "Couldn't find wasp project root - make sure"
++ " you are running this command from a Wasp project."
)

View File

@ -10,9 +10,9 @@ import Control.Monad.Except (throwError)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import StrongPath ((</>)) import StrongPath ((</>))
import Wasp.Cli.Command (Command, CommandError (..)) import Wasp.Cli.Command (Command, CommandError (..))
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd)
import Wasp.Cli.Command.Compile (compile, printWarningsAndErrorsIfAny) import Wasp.Cli.Command.Compile (compile, printWarningsAndErrorsIfAny)
import Wasp.Cli.Command.Message (cliSendMessageC) import Wasp.Cli.Command.Message (cliSendMessageC)
import Wasp.Cli.Command.Require (DbConnectionEstablished (DbConnectionEstablished), InWaspProject (InWaspProject), require)
import Wasp.Cli.Command.Watch (watch) import Wasp.Cli.Command.Watch (watch)
import qualified Wasp.Cli.Common as Common import qualified Wasp.Cli.Common as Common
import qualified Wasp.Generator import qualified Wasp.Generator
@ -23,13 +23,15 @@ import Wasp.Project (CompileError, CompileWarning)
-- It also listens for any file changes and recompiles and restarts generated project accordingly. -- It also listens for any file changes and recompiles and restarts generated project accordingly.
start :: Command () start :: Command ()
start = do start = do
waspRoot <- findWaspProjectRootDirFromCwd InWaspProject waspRoot <- require
let outDir = waspRoot </> Common.dotWaspDirInWaspProjectDir </> Common.generatedCodeDirInDotWaspDir let outDir = waspRoot </> Common.dotWaspDirInWaspProjectDir </> Common.generatedCodeDirInDotWaspDir
cliSendMessageC $ Msg.Start "Starting compilation and setup phase. Hold tight..." cliSendMessageC $ Msg.Start "Starting compilation and setup phase. Hold tight..."
warnings <- compile warnings <- compile
DbConnectionEstablished <- require
cliSendMessageC $ Msg.Start "Listening for file changes..." cliSendMessageC $ Msg.Start "Listening for file changes..."
cliSendMessageC $ Msg.Start "Starting up generated project..." cliSendMessageC $ Msg.Start "Starting up generated project..."

View File

@ -18,9 +18,10 @@ import qualified Wasp.AppSpec.App as AS.App
import qualified Wasp.AppSpec.App.Db as AS.App.Db import qualified Wasp.AppSpec.App.Db as AS.App.Db
import qualified Wasp.AppSpec.Valid as ASV import qualified Wasp.AppSpec.Valid as ASV
import Wasp.Cli.Command (Command, CommandError (CommandError)) import Wasp.Cli.Command (Command, CommandError (CommandError))
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd, throwIfExeIsNotAvailable) import Wasp.Cli.Command.Common (throwIfExeIsNotAvailable)
import Wasp.Cli.Command.Compile (analyze) import Wasp.Cli.Command.Compile (analyze)
import Wasp.Cli.Command.Message (cliSendMessageC) import Wasp.Cli.Command.Message (cliSendMessageC)
import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import Wasp.Cli.Common (WaspProjectDir) import Wasp.Cli.Common (WaspProjectDir)
import qualified Wasp.Message as Msg import qualified Wasp.Message as Msg
import Wasp.Project.Db (databaseUrlEnvVarName) import Wasp.Project.Db (databaseUrlEnvVarName)
@ -36,7 +37,7 @@ import qualified Wasp.Util.Network.Socket as Socket
-- in Wasp configuration and spins up a database of appropriate type. -- in Wasp configuration and spins up a database of appropriate type.
start :: Command () start :: Command ()
start = do start = do
waspProjectDir <- findWaspProjectRootDirFromCwd InWaspProject waspProjectDir <- require
appSpec <- analyze waspProjectDir appSpec <- analyze waspProjectDir
throwIfCustomDbAlreadyInUse appSpec throwIfCustomDbAlreadyInUse appSpec

View File

@ -31,7 +31,7 @@ import qualified System.Environment as ENV
import qualified System.Info import qualified System.Info
import Wasp.Cli.Command (Command) import Wasp.Cli.Command (Command)
import qualified Wasp.Cli.Command.Call as Command.Call import qualified Wasp.Cli.Command.Call as Command.Call
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd) import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import Wasp.Cli.Command.Telemetry.Common (TelemetryCacheDir) import Wasp.Cli.Command.Telemetry.Common (TelemetryCacheDir)
import Wasp.Cli.Command.Telemetry.User (UserSignature (..)) import Wasp.Cli.Command.Telemetry.User (UserSignature (..))
import Wasp.Util (ifM) import Wasp.Util (ifM)
@ -100,7 +100,9 @@ checkIfEnvValueIsTruthy (Just v)
newtype ProjectHash = ProjectHash {_projectHashValue :: String} deriving (Show) newtype ProjectHash = ProjectHash {_projectHashValue :: String} deriving (Show)
getWaspProjectPathHash :: Command ProjectHash getWaspProjectPathHash :: Command ProjectHash
getWaspProjectPathHash = ProjectHash . take 16 . sha256 . SP.toFilePath <$> findWaspProjectRootDirFromCwd getWaspProjectPathHash = do
InWaspProject waspRoot <- require
return . ProjectHash . take 16 . sha256 . SP.toFilePath $ waspRoot
where where
sha256 :: String -> String sha256 :: String -> String
sha256 = show . hashWith SHA256 . ByteStringUTF8.fromString sha256 = show . hashWith SHA256 . ByteStringUTF8.fromString

View File

@ -10,9 +10,9 @@ import Control.Monad.IO.Class (liftIO)
import StrongPath (Abs, Dir, (</>)) import StrongPath (Abs, Dir, (</>))
import StrongPath.Types (Path') import StrongPath.Types (Path')
import Wasp.Cli.Command (Command, CommandError (..)) import Wasp.Cli.Command (Command, CommandError (..))
import Wasp.Cli.Command.Common (findWaspProjectRootDirFromCwd)
import Wasp.Cli.Command.Compile (compile) import Wasp.Cli.Command.Compile (compile)
import Wasp.Cli.Command.Message (cliSendMessageC) import Wasp.Cli.Command.Message (cliSendMessageC)
import Wasp.Cli.Command.Require (InWaspProject (InWaspProject), require)
import Wasp.Cli.Command.Watch (watch) import Wasp.Cli.Command.Watch (watch)
import qualified Wasp.Cli.Common as Common import qualified Wasp.Cli.Common as Common
import qualified Wasp.Generator import qualified Wasp.Generator
@ -27,7 +27,7 @@ test _ = throwError $ CommandError "Invalid arguments" "Expected: wasp test clie
watchAndTest :: (Path' Abs (Dir ProjectRootDir) -> IO (Either String ())) -> Command () watchAndTest :: (Path' Abs (Dir ProjectRootDir) -> IO (Either String ())) -> Command ()
watchAndTest testRunner = do watchAndTest testRunner = do
waspRoot <- findWaspProjectRootDirFromCwd InWaspProject waspRoot <- require
let outDir = waspRoot </> Common.dotWaspDirInWaspProjectDir </> Common.generatedCodeDirInDotWaspDir let outDir = waspRoot </> Common.dotWaspDirInWaspProjectDir </> Common.generatedCodeDirInDotWaspDir
cliSendMessageC $ Msg.Start "Starting compilation and setup phase. Hold tight..." cliSendMessageC $ Msg.Start "Starting compilation and setup phase. Hold tight..."

View File

@ -23,4 +23,4 @@ npm run example-app:start
### How to run in CI ### How to run in CI
We set up a GitHub Action to run the test in CI. See `.github/workflows/ci.yml` for details. We set up a GitHub Action to run the test in CI. See `.github/workflows/ci.yml` for details.

View File

@ -9,27 +9,15 @@
"version": "1.0.0", "version": "1.0.0",
"license": "ISC", "license": "ISC",
"dependencies": { "dependencies": {
"@prisma/client": "^4.12.0" "@prisma/client": "^4.12.0",
"linebyline": "^1.3.0"
}, },
"devDependencies": { "devDependencies": {
"@playwright/test": "^1.33.0", "@playwright/test": "^1.33.0",
"concurrently": "^8.0.1",
"prisma": "^4.12.0", "prisma": "^4.12.0",
"wait-port": "^1.0.4" "wait-port": "^1.0.4"
} }
}, },
"node_modules/@babel/runtime": {
"version": "7.21.5",
"resolved": "https://registry.npmjs.org/@babel/runtime/-/runtime-7.21.5.tgz",
"integrity": "sha512-8jI69toZqqcsnqGGqwGS4Qb1VwLOEp4hz+CXPywcvjs60u3B4Pom/U/7rm4W8tMOYEB+E9wgD0mW1l3r8qlI9Q==",
"dev": true,
"dependencies": {
"regenerator-runtime": "^0.13.11"
},
"engines": {
"node": ">=6.9.0"
}
},
"node_modules/@playwright/test": { "node_modules/@playwright/test": {
"version": "1.33.0", "version": "1.33.0",
"resolved": "https://registry.npmjs.org/@playwright/test/-/test-1.33.0.tgz", "resolved": "https://registry.npmjs.org/@playwright/test/-/test-1.33.0.tgz",
@ -87,15 +75,6 @@
"integrity": "sha512-OPs5WnnT1xkCBiuQrZA4+YAV4HEJejmHneyraIaxsbev5yCEr6KMwINNFP9wQeFIw8FWcoTqF3vQsa5CDaI+8Q==", "integrity": "sha512-OPs5WnnT1xkCBiuQrZA4+YAV4HEJejmHneyraIaxsbev5yCEr6KMwINNFP9wQeFIw8FWcoTqF3vQsa5CDaI+8Q==",
"dev": true "dev": true
}, },
"node_modules/ansi-regex": {
"version": "5.0.1",
"resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-5.0.1.tgz",
"integrity": "sha512-quJQXlTSUGL2LH9SUXo8VwsY4soanhgo6LNSm84E1LBcE8s3O0wpdiRzyR9z/ZZJMlMWv37qOOb9pdJlMUEKFQ==",
"dev": true,
"engines": {
"node": ">=8"
}
},
"node_modules/ansi-styles": { "node_modules/ansi-styles": {
"version": "4.3.0", "version": "4.3.0",
"resolved": "https://registry.npmjs.org/ansi-styles/-/ansi-styles-4.3.0.tgz", "resolved": "https://registry.npmjs.org/ansi-styles/-/ansi-styles-4.3.0.tgz",
@ -139,20 +118,6 @@
"node": ">=8" "node": ">=8"
} }
}, },
"node_modules/cliui": {
"version": "8.0.1",
"resolved": "https://registry.npmjs.org/cliui/-/cliui-8.0.1.tgz",
"integrity": "sha512-BSeNnyus75C4//NQ9gQt1/csTXyo/8Sb+afLAkzAptFuMsod9HFokGNudZpi/oQV73hnVK+sR+5PVRMd+Dr7YQ==",
"dev": true,
"dependencies": {
"string-width": "^4.2.0",
"strip-ansi": "^6.0.1",
"wrap-ansi": "^7.0.0"
},
"engines": {
"node": ">=12"
}
},
"node_modules/color-convert": { "node_modules/color-convert": {
"version": "2.0.1", "version": "2.0.1",
"resolved": "https://registry.npmjs.org/color-convert/-/color-convert-2.0.1.tgz", "resolved": "https://registry.npmjs.org/color-convert/-/color-convert-2.0.1.tgz",
@ -180,49 +145,6 @@
"node": "^12.20.0 || >=14" "node": "^12.20.0 || >=14"
} }
}, },
"node_modules/concurrently": {
"version": "8.0.1",
"resolved": "https://registry.npmjs.org/concurrently/-/concurrently-8.0.1.tgz",
"integrity": "sha512-Sh8bGQMEL0TAmAm2meAXMjcASHZa7V0xXQVDBLknCPa9TPtkY9yYs+0cnGGgfdkW0SV1Mlg+hVGfXcoI8d3MJA==",
"dev": true,
"dependencies": {
"chalk": "^4.1.2",
"date-fns": "^2.29.3",
"lodash": "^4.17.21",
"rxjs": "^7.8.0",
"shell-quote": "^1.8.0",
"spawn-command": "0.0.2-1",
"supports-color": "^8.1.1",
"tree-kill": "^1.2.2",
"yargs": "^17.7.1"
},
"bin": {
"conc": "dist/bin/concurrently.js",
"concurrently": "dist/bin/concurrently.js"
},
"engines": {
"node": "^14.13.0 || >=16.0.0"
},
"funding": {
"url": "https://github.com/open-cli-tools/concurrently?sponsor=1"
}
},
"node_modules/date-fns": {
"version": "2.30.0",
"resolved": "https://registry.npmjs.org/date-fns/-/date-fns-2.30.0.tgz",
"integrity": "sha512-fnULvOpxnC5/Vg3NCiWelDsLiUc9bRwAPs/+LfTLNvetFCtCTN+yQz15C/fs4AwX1R9K5GLtLfn8QW+dWisaAw==",
"dev": true,
"dependencies": {
"@babel/runtime": "^7.21.0"
},
"engines": {
"node": ">=0.11"
},
"funding": {
"type": "opencollective",
"url": "https://opencollective.com/date-fns"
}
},
"node_modules/debug": { "node_modules/debug": {
"version": "4.3.4", "version": "4.3.4",
"resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz",
@ -240,21 +162,6 @@
} }
} }
}, },
"node_modules/emoji-regex": {
"version": "8.0.0",
"resolved": "https://registry.npmjs.org/emoji-regex/-/emoji-regex-8.0.0.tgz",
"integrity": "sha512-MSjYzcWNOA0ewAHpz0MxpYFvwg6yjy1NG3xteoqz644VCo/RPgnr1/GGt+ic3iJTzQ8Eu3TdM14SawnVUmGE6A==",
"dev": true
},
"node_modules/escalade": {
"version": "3.1.1",
"resolved": "https://registry.npmjs.org/escalade/-/escalade-3.1.1.tgz",
"integrity": "sha512-k0er2gUkLf8O0zKJiAhmkTnJlTvINGv7ygDNPbeIsX/TJjGJZHuh9B2UxbsaEkmlEo9MfhrSzmhIlhRlI2GXnw==",
"dev": true,
"engines": {
"node": ">=6"
}
},
"node_modules/fsevents": { "node_modules/fsevents": {
"version": "2.3.2", "version": "2.3.2",
"resolved": "https://registry.npmjs.org/fsevents/-/fsevents-2.3.2.tgz", "resolved": "https://registry.npmjs.org/fsevents/-/fsevents-2.3.2.tgz",
@ -269,15 +176,6 @@
"node": "^8.16.0 || ^10.6.0 || >=11.0.0" "node": "^8.16.0 || ^10.6.0 || >=11.0.0"
} }
}, },
"node_modules/get-caller-file": {
"version": "2.0.5",
"resolved": "https://registry.npmjs.org/get-caller-file/-/get-caller-file-2.0.5.tgz",
"integrity": "sha512-DyFP3BM/3YHTQOCUL/w0OZHR0lpKeGrxotcHWcqNEdnltqFwXVfhEBQ94eIo34AfQpo0rGki4cyIiftY06h2Fg==",
"dev": true,
"engines": {
"node": "6.* || 8.* || >= 10.*"
}
},
"node_modules/has-flag": { "node_modules/has-flag": {
"version": "4.0.0", "version": "4.0.0",
"resolved": "https://registry.npmjs.org/has-flag/-/has-flag-4.0.0.tgz", "resolved": "https://registry.npmjs.org/has-flag/-/has-flag-4.0.0.tgz",
@ -287,20 +185,10 @@
"node": ">=8" "node": ">=8"
} }
}, },
"node_modules/is-fullwidth-code-point": { "node_modules/linebyline": {
"version": "3.0.0", "version": "1.3.0",
"resolved": "https://registry.npmjs.org/is-fullwidth-code-point/-/is-fullwidth-code-point-3.0.0.tgz", "resolved": "https://registry.npmjs.org/linebyline/-/linebyline-1.3.0.tgz",
"integrity": "sha512-zymm5+u+sCsSWyD9qNaejV3DFvhCKclKdizYaJUuHA83RLjb7nSuGnddCHGv0hk+KY7BMAlsWeK4Ueg6EV6XQg==", "integrity": "sha512-3fpIYMrSU77OCf89hjXKuCx6vGwgWEu4N5DDCGqgZ1BF0HYy9V8IbQb/3+VWIU17iBQ83qQoUokH0AhPMOTi7w=="
"dev": true,
"engines": {
"node": ">=8"
}
},
"node_modules/lodash": {
"version": "4.17.21",
"resolved": "https://registry.npmjs.org/lodash/-/lodash-4.17.21.tgz",
"integrity": "sha512-v2kDEe57lecTulaDIuNTPy3Ry4gLGJ6Z1O3vE1krgXZNrsQ+LFTGHVxVjcXPs17LhbZVGedAJv8XZ1tvj5FvSg==",
"dev": true
}, },
"node_modules/ms": { "node_modules/ms": {
"version": "2.1.2", "version": "2.1.2",
@ -337,101 +225,6 @@
"node": ">=14.17" "node": ">=14.17"
} }
}, },
"node_modules/regenerator-runtime": {
"version": "0.13.11",
"resolved": "https://registry.npmjs.org/regenerator-runtime/-/regenerator-runtime-0.13.11.tgz",
"integrity": "sha512-kY1AZVr2Ra+t+piVaJ4gxaFaReZVH40AKNo7UCX6W+dEwBo/2oZJzqfuN1qLq1oL45o56cPaTXELwrTh8Fpggg==",
"dev": true
},
"node_modules/require-directory": {
"version": "2.1.1",
"resolved": "https://registry.npmjs.org/require-directory/-/require-directory-2.1.1.tgz",
"integrity": "sha512-fGxEI7+wsG9xrvdjsrlmL22OMTTiHRwAMroiEeMgq8gzoLC/PQr7RsRDSTLUg/bZAZtF+TVIkHc6/4RIKrui+Q==",
"dev": true,
"engines": {
"node": ">=0.10.0"
}
},
"node_modules/rxjs": {
"version": "7.8.1",
"resolved": "https://registry.npmjs.org/rxjs/-/rxjs-7.8.1.tgz",
"integrity": "sha512-AA3TVj+0A2iuIoQkWEK/tqFjBq2j+6PO6Y0zJcvzLAFhEFIO3HL0vls9hWLncZbAAbK0mar7oZ4V079I/qPMxg==",
"dev": true,
"dependencies": {
"tslib": "^2.1.0"
}
},
"node_modules/shell-quote": {
"version": "1.8.1",
"resolved": "https://registry.npmjs.org/shell-quote/-/shell-quote-1.8.1.tgz",
"integrity": "sha512-6j1W9l1iAs/4xYBI1SYOVZyFcCis9b4KCLQ8fgAGG07QvzaRLVVRQvAy85yNmmZSjYjg4MWh4gNvlPujU/5LpA==",
"dev": true,
"funding": {
"url": "https://github.com/sponsors/ljharb"
}
},
"node_modules/spawn-command": {
"version": "0.0.2-1",
"resolved": "https://registry.npmjs.org/spawn-command/-/spawn-command-0.0.2-1.tgz",
"integrity": "sha512-n98l9E2RMSJ9ON1AKisHzz7V42VDiBQGY6PB1BwRglz99wpVsSuGzQ+jOi6lFXBGVTCrRpltvjm+/XA+tpeJrg==",
"dev": true
},
"node_modules/string-width": {
"version": "4.2.3",
"resolved": "https://registry.npmjs.org/string-width/-/string-width-4.2.3.tgz",
"integrity": "sha512-wKyQRQpjJ0sIp62ErSZdGsjMJWsap5oRNihHhu6G7JVO/9jIB6UyevL+tXuOqrng8j/cxKTWyWUwvSTriiZz/g==",
"dev": true,
"dependencies": {
"emoji-regex": "^8.0.0",
"is-fullwidth-code-point": "^3.0.0",
"strip-ansi": "^6.0.1"
},
"engines": {
"node": ">=8"
}
},
"node_modules/strip-ansi": {
"version": "6.0.1",
"resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-6.0.1.tgz",
"integrity": "sha512-Y38VPSHcqkFrCpFnQ9vuSXmquuv5oXOKpGeT6aGrr3o3Gc9AlVa6JBfUSOCnbxGGZF+/0ooI7KrPuUSztUdU5A==",
"dev": true,
"dependencies": {
"ansi-regex": "^5.0.1"
},
"engines": {
"node": ">=8"
}
},
"node_modules/supports-color": {
"version": "8.1.1",
"resolved": "https://registry.npmjs.org/supports-color/-/supports-color-8.1.1.tgz",
"integrity": "sha512-MpUEN2OodtUzxvKQl72cUF7RQ5EiHsGvSsVG0ia9c5RbWGL2CI4C7EpPS8UTBIplnlzZiNuV56w+FuNxy3ty2Q==",
"dev": true,
"dependencies": {
"has-flag": "^4.0.0"
},
"engines": {
"node": ">=10"
},
"funding": {
"url": "https://github.com/chalk/supports-color?sponsor=1"
}
},
"node_modules/tree-kill": {
"version": "1.2.2",
"resolved": "https://registry.npmjs.org/tree-kill/-/tree-kill-1.2.2.tgz",
"integrity": "sha512-L0Orpi8qGpRG//Nd+H90vFB+3iHnue1zSSGmNOOCh1GLJ7rUKVwV2HvijphGQS2UmhUZewS9VgvxYIdgr+fG1A==",
"dev": true,
"bin": {
"tree-kill": "cli.js"
}
},
"node_modules/tslib": {
"version": "2.5.0",
"resolved": "https://registry.npmjs.org/tslib/-/tslib-2.5.0.tgz",
"integrity": "sha512-336iVw3rtn2BUK7ORdIAHTyxHGRIHVReokCR3XjbckJMK7ms8FysBfhLR8IXnAgy7T0PTPNBWKiH514FOW/WSg==",
"dev": true
},
"node_modules/wait-port": { "node_modules/wait-port": {
"version": "1.0.4", "version": "1.0.4",
"resolved": "https://registry.npmjs.org/wait-port/-/wait-port-1.0.4.tgz", "resolved": "https://registry.npmjs.org/wait-port/-/wait-port-1.0.4.tgz",
@ -448,59 +241,6 @@
"engines": { "engines": {
"node": ">=10" "node": ">=10"
} }
},
"node_modules/wrap-ansi": {
"version": "7.0.0",
"resolved": "https://registry.npmjs.org/wrap-ansi/-/wrap-ansi-7.0.0.tgz",
"integrity": "sha512-YVGIj2kamLSTxw6NsZjoBxfSwsn0ycdesmc4p+Q21c5zPuZ1pl+NfxVdxPtdHvmNVOQ6XSYG4AUtyt/Fi7D16Q==",
"dev": true,
"dependencies": {
"ansi-styles": "^4.0.0",
"string-width": "^4.1.0",
"strip-ansi": "^6.0.0"
},
"engines": {
"node": ">=10"
},
"funding": {
"url": "https://github.com/chalk/wrap-ansi?sponsor=1"
}
},
"node_modules/y18n": {
"version": "5.0.8",
"resolved": "https://registry.npmjs.org/y18n/-/y18n-5.0.8.tgz",
"integrity": "sha512-0pfFzegeDWJHJIAmTLRP2DwHjdF5s7jo9tuztdQxAhINCdvS+3nGINqPd00AphqJR/0LhANUS6/+7SCb98YOfA==",
"dev": true,
"engines": {
"node": ">=10"
}
},
"node_modules/yargs": {
"version": "17.7.2",
"resolved": "https://registry.npmjs.org/yargs/-/yargs-17.7.2.tgz",
"integrity": "sha512-7dSzzRQ++CKnNI/krKnYRV7JKKPUXMEh61soaHKg9mrWEhzFWhFnxPxGl+69cD1Ou63C13NUPCnmIcrvqCuM6w==",
"dev": true,
"dependencies": {
"cliui": "^8.0.1",
"escalade": "^3.1.1",
"get-caller-file": "^2.0.5",
"require-directory": "^2.1.1",
"string-width": "^4.2.3",
"y18n": "^5.0.5",
"yargs-parser": "^21.1.1"
},
"engines": {
"node": ">=12"
}
},
"node_modules/yargs-parser": {
"version": "21.1.1",
"resolved": "https://registry.npmjs.org/yargs-parser/-/yargs-parser-21.1.1.tgz",
"integrity": "sha512-tVpsJW7DdjecAiFpbIB1e3qxIQsE6NoPc5/eTdrbbIC4h0LVsWhnoa3g+m2HclBIujHzsxZ4VJVA+GUuc2/LBw==",
"dev": true,
"engines": {
"node": ">=12"
}
} }
} }
} }

View File

@ -4,7 +4,7 @@
"description": "", "description": "",
"main": "index.js", "main": "index.js",
"scripts": { "scripts": {
"example-app:start": "concurrently \"npm:example-app:start-db\" \"npm:example-app:start-app\" --kill-others-on-fail", "example-app:start": "node start.js",
"example-app:start-db": "npm run example-app:cleanup-db && cd ./examples/todoApp && cabal run wasp-cli start db", "example-app:start-db": "npm run example-app:cleanup-db && cd ./examples/todoApp && cabal run wasp-cli start db",
"example-app:start-app": "npm run example-app:wait-for-db && cd ./examples/todoApp && cabal run wasp-cli db migrate-dev && cabal run wasp-cli start", "example-app:start-app": "npm run example-app:wait-for-db && cd ./examples/todoApp && cabal run wasp-cli db migrate-dev && cabal run wasp-cli start",
"example-app:wait-for-db": "sleep 5 && ./node_modules/.bin/wait-port 5432", "example-app:wait-for-db": "sleep 5 && ./node_modules/.bin/wait-port 5432",
@ -15,9 +15,9 @@
"license": "ISC", "license": "ISC",
"devDependencies": { "devDependencies": {
"@playwright/test": "^1.33.0", "@playwright/test": "^1.33.0",
"concurrently": "^8.0.1",
"prisma": "^4.12.0", "prisma": "^4.12.0",
"wait-port": "^1.0.4" "wait-port": "^1.0.4",
"linebyline": "^1.3.0"
}, },
"dependencies": { "dependencies": {
"@prisma/client": "^4.12.0" "@prisma/client": "^4.12.0"

View File

@ -0,0 +1,31 @@
const cp = require('child_process');
const readline = require('linebyline');
function spawn(name, cmd, args, done) {
const spawnOptions = {
detached: true,
};
const proc = cp.spawn(cmd, args, spawnOptions);
// We close stdin stream on the new process because otherwise the start-app
// process hangs.
// See https://github.com/wasp-lang/wasp/pull/1218#issuecomment-1599098272.
proc.stdin.destroy();
readline(proc.stdout).on('line', data => {
console.log(`\x1b[0m\x1b[33m[${name}][out]\x1b[0m ${data}`);
});
readline(proc.stderr).on('line', data => {
console.log(`\x1b[0m\x1b[33m[${name}][err]\x1b[0m ${data}`);
});
proc.on('exit', done);
}
// Exit if either child fails
const cb = (code) => {
if (code !== 0) {
process.exit(code);
}
}
spawn('app', 'npm', ['run', 'example-app:start-app'], cb);
spawn('db', 'npm', ['run', 'example-app:start-db'], cb)

View File

@ -7,6 +7,7 @@ module Wasp.Generator.DbGenerator.Jobs
runStudio, runStudio,
reset, reset,
seed, seed,
dbExecuteTest,
migrateStatus, migrateStatus,
asPrismaCliArgs, asPrismaCliArgs,
) )
@ -113,6 +114,19 @@ seed projectDir seedName =
projectDir projectDir
(const ["db", "seed"]) (const ["db", "seed"])
-- | Checks if the DB is running and connectable by running
-- `prisma db execute --stdin --schema <path to db schema>`.
-- Runs the command in the generated server code directory so it has access to the database URL.
--
-- Since nothing is passed to stdin, `prisma db execute` just runs an empty
-- SQL command, which works perfectly for checking if the database is running.
dbExecuteTest :: Path' Abs (Dir ProjectRootDir) -> J.Job
dbExecuteTest projectDir =
let absSchemaPath = projectDir </> dbSchemaFileInProjectRootDir
in runPrismaCommandAsDbJob
projectDir
(const ["db", "execute", "--stdin", "--schema", SP.fromAbsFile absSchemaPath])
-- | Runs `prisma studio` - Prisma's db inspector. -- | Runs `prisma studio` - Prisma's db inspector.
runStudio :: Path' Abs (Dir ProjectRootDir) -> J.Job runStudio :: Path' Abs (Dir ProjectRootDir) -> J.Job
runStudio projectDir = runPrismaCommandAsDbJob projectDir $ \schema -> runStudio projectDir = runPrismaCommandAsDbJob projectDir $ \schema ->

View File

@ -6,6 +6,7 @@ module Wasp.Generator.DbGenerator.Operations
areAllMigrationsAppliedToDb, areAllMigrationsAppliedToDb,
dbReset, dbReset,
dbSeed, dbSeed,
isDbRunning,
) )
where where
@ -134,6 +135,16 @@ dbSeed genProjectDir seedName = do
ExitSuccess -> Right () ExitSuccess -> Right ()
ExitFailure c -> Left $ "Failed with exit code " <> show c ExitFailure c -> Left $ "Failed with exit code " <> show c
isDbRunning ::
Path' Abs (Dir ProjectRootDir) ->
IO Bool
isDbRunning genProjectDir = do
chan <- newChan
exitCode <- DbJobs.dbExecuteTest genProjectDir chan
-- NOTE: We only care if the command succeeds or fails, so we don't look at
-- the exit code or stdout/stderr for the process.
return $ exitCode == ExitSuccess
generatePrismaClients :: Path' Abs (Dir ProjectRootDir) -> IO (Either String ()) generatePrismaClients :: Path' Abs (Dir ProjectRootDir) -> IO (Either String ())
generatePrismaClients projectRootDir = do generatePrismaClients projectRootDir = do
generateResult <- liftA2 (>>) generatePrismaClientForServer generatePrismaClientForWebApp projectRootDir generateResult <- liftA2 (>>) generatePrismaClientForServer generatePrismaClientForWebApp projectRootDir

View File

@ -426,6 +426,7 @@ library cli-lib
Wasp.Cli.Command.Deploy Wasp.Cli.Command.Deploy
Wasp.Cli.Command.Dockerfile Wasp.Cli.Command.Dockerfile
Wasp.Cli.Command.Info Wasp.Cli.Command.Info
Wasp.Cli.Command.Require
Wasp.Cli.Command.Start Wasp.Cli.Command.Start
Wasp.Cli.Command.Start.Db Wasp.Cli.Command.Start.Db
Wasp.Cli.Command.Telemetry Wasp.Cli.Command.Telemetry