mirror of
https://github.com/wasp-lang/wasp.git
synced 2024-12-25 01:52:00 +03:00
Move Wasp file logic into a separate module
This commit is contained in:
parent
e8badd27b3
commit
6d03463a5d
@ -10,9 +10,10 @@ import StrongPath (Abs, Dir, File, Path')
|
||||
import Wasp.Cli.Command.CreateNewProject.Common (defaultWaspVersionBounds)
|
||||
import Wasp.Cli.Command.CreateNewProject.ProjectDescription (NewProjectAppName, NewProjectName)
|
||||
import Wasp.NodePackageFFI (InstallablePackage (WaspConfigPackage), getPackageInstallationPath)
|
||||
import Wasp.Project.Analyze (WaspFilePath (..), findWaspFile)
|
||||
import Wasp.Project.Analyze (WaspFilePath (..))
|
||||
import Wasp.Project.Common (WaspProjectDir)
|
||||
import Wasp.Project.ExternalConfig.PackageJson (findPackageJsonFile)
|
||||
import Wasp.Project.WaspFile (findWaspFile)
|
||||
import qualified Wasp.Util.IO as IOUtil
|
||||
|
||||
replaceTemplatePlaceholdersInTemplateFiles :: NewProjectAppName -> NewProjectName -> Path' Abs (Dir WaspProjectDir) -> IO ()
|
||||
|
@ -24,7 +24,7 @@ import qualified Wasp.AI.GenerateNewProject.Common.Prompts as Prompts
|
||||
import Wasp.AI.GenerateNewProject.Plan (Plan)
|
||||
import Wasp.AI.OpenAI.ChatGPT (ChatMessage (..), ChatRole (..))
|
||||
import Wasp.Analyzer.Parser.Ctx (Ctx (..))
|
||||
import Wasp.Project.Analyze (analyzeWaspFileContent)
|
||||
import Wasp.Project.WaspFile (analyzeWaspFileContent)
|
||||
import qualified Wasp.Psl.Ast.Schema as Psl.Schema
|
||||
import qualified Wasp.Util.Aeson as Utils.Aeson
|
||||
|
||||
|
@ -154,7 +154,6 @@ tuple4 eval1 eval2 eval3 eval4 = evaluation $ \(typeDefs, bindings) -> withCtx $
|
||||
extImport :: TypedExprEvaluation AppSpec.ExtImport.ExtImport
|
||||
extImport = evaluation' . withCtx $ \ctx -> \case
|
||||
TypedAST.ExtImport name extImportPath ->
|
||||
-- NOTE(martin): This parsing here could instead be done in Parser.
|
||||
-- NOTE(martin): This parsing here could instead be done in Parser.
|
||||
-- I don't have a very good reason for doing it here instead of Parser, except
|
||||
-- for being somewhat simpler to implement.
|
||||
|
@ -1,57 +1,30 @@
|
||||
module Wasp.Project.Analyze
|
||||
( analyzeWaspProject,
|
||||
analyzeWaspFileContent,
|
||||
findWaspFile,
|
||||
analyzePrismaSchema,
|
||||
WaspFilePath (..),
|
||||
)
|
||||
where
|
||||
|
||||
import Control.Arrow (ArrowChoice (left))
|
||||
import Control.Concurrent (newChan)
|
||||
import Control.Concurrent.Async (concurrently)
|
||||
import Control.Monad.Except (ExceptT (..), liftEither, runExceptT)
|
||||
import qualified Data.Aeson as Aeson
|
||||
import Data.List (find, isSuffixOf)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import StrongPath
|
||||
( Abs,
|
||||
Dir,
|
||||
File,
|
||||
File',
|
||||
Path',
|
||||
Rel,
|
||||
basename,
|
||||
castFile,
|
||||
fromAbsDir,
|
||||
fromAbsFile,
|
||||
fromRelFile,
|
||||
relfile,
|
||||
(</>),
|
||||
)
|
||||
import System.Exit (ExitCode (..))
|
||||
import qualified Wasp.Analyzer as Analyzer
|
||||
import Wasp.Analyzer.AnalyzeError (getErrorMessageAndCtx)
|
||||
import Wasp.Analyzer.Parser.Ctx (Ctx)
|
||||
import qualified Wasp.AppSpec as AS
|
||||
import Wasp.AppSpec.Core.Decl.JSON ()
|
||||
import qualified Wasp.AppSpec.Valid as ASV
|
||||
import Wasp.CompileOptions (CompileOptions)
|
||||
import qualified Wasp.CompileOptions as CompileOptions
|
||||
import qualified Wasp.ConfigFile as CF
|
||||
import Wasp.Error (showCompilerErrorForTerminal)
|
||||
import qualified Wasp.Generator.ConfigFile as G.CF
|
||||
import qualified Wasp.Generator.Job as J
|
||||
import Wasp.Generator.Job.IO (readJobMessagesAndPrintThemPrefixed)
|
||||
import Wasp.Generator.Job.Process (runNodeCommandAsJob)
|
||||
import Wasp.Project.Common
|
||||
( CompileError,
|
||||
CompileWarning,
|
||||
WaspFilePath (..),
|
||||
WaspLangFile,
|
||||
WaspProjectDir,
|
||||
WaspTsFile,
|
||||
dotWaspDirInWaspProjectDir,
|
||||
findFileInWaspProjectDir,
|
||||
getSrcTsConfigInWaspProjectDir,
|
||||
prismaSchemaFileInWaspProjectDir,
|
||||
@ -63,13 +36,12 @@ import Wasp.Project.Env (readDotEnvClient, readDotEnvServer)
|
||||
import qualified Wasp.Project.ExternalConfig as EC
|
||||
import qualified Wasp.Project.ExternalFiles as ExternalFiles
|
||||
import Wasp.Project.Vite (findCustomViteConfigPath)
|
||||
import Wasp.Project.WaspFile (analyzeWaspFile, findWaspFile)
|
||||
import qualified Wasp.Psl.Ast.Schema as Psl.Schema
|
||||
import qualified Wasp.Psl.Parser.Schema as Psl.Parser
|
||||
import Wasp.Psl.Valid (getValidDbSystemFromPrismaSchema)
|
||||
import qualified Wasp.Psl.Valid as PslV
|
||||
import Wasp.Util.Aeson (encodeToString)
|
||||
import qualified Wasp.Util.IO as IOUtil
|
||||
import Wasp.Util.StrongPath (replaceRelExtension)
|
||||
import Wasp.Valid (ValidationError)
|
||||
import qualified Wasp.Valid as Valid
|
||||
|
||||
@ -79,7 +51,6 @@ analyzeWaspProject ::
|
||||
IO (Either [CompileError] AS.AppSpec, [CompileWarning])
|
||||
analyzeWaspProject waspDir options = do
|
||||
waspFilePathOrError <- left (: []) <$> findWaspFile waspDir
|
||||
|
||||
case waspFilePathOrError of
|
||||
Left err -> return (Left err, [])
|
||||
Right waspFilePath ->
|
||||
@ -94,118 +65,6 @@ analyzeWaspProject waspDir options = do
|
||||
Left errors -> return (Left errors, [])
|
||||
Right externalConfigs -> constructAppSpec waspDir options externalConfigs prismaSchemaAst declarations
|
||||
|
||||
data CompiledWaspJsFile
|
||||
|
||||
data AppSpecDeclsJsonFile
|
||||
|
||||
analyzeWaspFile :: Path' Abs (Dir WaspProjectDir) -> Psl.Schema.Schema -> WaspFilePath -> IO (Either [CompileError] [AS.Decl])
|
||||
analyzeWaspFile waspDir prismaSchemaAst = \case
|
||||
WaspLang waspFilePath -> analyzeWaspLangFile prismaSchemaAst waspFilePath
|
||||
WaspTs waspFilePath -> analyzeWaspTsFile waspDir prismaSchemaAst waspFilePath
|
||||
|
||||
analyzeWaspTsFile :: Path' Abs (Dir WaspProjectDir) -> Psl.Schema.Schema -> Path' Abs (File WaspTsFile) -> IO (Either [CompileError] [AS.Decl])
|
||||
analyzeWaspTsFile waspProjectDir prismaSchemaAst waspFilePath = runExceptT $ do
|
||||
-- TODO: I'm not yet sure where tsconfig.node.json location should come from
|
||||
-- because we also need that knowledge when generating a TS SDK project.
|
||||
compiledWaspJsFile <- ExceptT $ compileWaspTsFile waspProjectDir [relfile|tsconfig.wasp.json|] waspFilePath
|
||||
declsJsonFile <- ExceptT $ executeMainWaspJsFileAndGetDeclsFile waspProjectDir prismaSchemaAst compiledWaspJsFile
|
||||
ExceptT $ readDecls prismaSchemaAst declsJsonFile
|
||||
|
||||
compileWaspTsFile ::
|
||||
Path' Abs (Dir WaspProjectDir) ->
|
||||
Path' (Rel WaspProjectDir) File' ->
|
||||
Path' Abs (File WaspTsFile) ->
|
||||
IO (Either [CompileError] (Path' Abs (File CompiledWaspJsFile)))
|
||||
compileWaspTsFile waspProjectDir tsconfigNodeFileInWaspProjectDir waspFilePath = do
|
||||
chan <- newChan
|
||||
(_, tscExitCode) <-
|
||||
concurrently
|
||||
(readJobMessagesAndPrintThemPrefixed chan)
|
||||
( runNodeCommandAsJob
|
||||
waspProjectDir
|
||||
"npx"
|
||||
[ "tsc",
|
||||
"-p",
|
||||
fromAbsFile (waspProjectDir </> tsconfigNodeFileInWaspProjectDir),
|
||||
"--noEmit",
|
||||
"false",
|
||||
"--outDir",
|
||||
fromAbsDir outDir
|
||||
]
|
||||
J.Wasp
|
||||
chan
|
||||
)
|
||||
return $ case tscExitCode of
|
||||
ExitFailure _status -> Left ["Got TypeScript compiler errors for " ++ fromAbsFile waspFilePath ++ "."]
|
||||
ExitSuccess -> Right absCompiledWaspJsFile
|
||||
where
|
||||
outDir = waspProjectDir </> dotWaspDirInWaspProjectDir
|
||||
absCompiledWaspJsFile = outDir </> compiledWaspJsFileInDotWaspDir
|
||||
compiledWaspJsFileInDotWaspDir =
|
||||
castFile $
|
||||
fromMaybe
|
||||
(error $ "Couldn't calculate the compiled JS file path for " ++ fromAbsFile waspFilePath ++ ".")
|
||||
(replaceRelExtension (basename waspFilePath) ".js")
|
||||
|
||||
executeMainWaspJsFileAndGetDeclsFile ::
|
||||
Path' Abs (Dir WaspProjectDir) ->
|
||||
Psl.Schema.Schema ->
|
||||
Path' Abs (File CompiledWaspJsFile) ->
|
||||
IO (Either [CompileError] (Path' Abs (File AppSpecDeclsJsonFile)))
|
||||
executeMainWaspJsFileAndGetDeclsFile waspProjectDir prismaSchemaAst absCompiledMainWaspJsFile = do
|
||||
chan <- newChan
|
||||
(_, runExitCode) <- do
|
||||
concurrently
|
||||
(readJobMessagesAndPrintThemPrefixed chan)
|
||||
( runNodeCommandAsJob
|
||||
waspProjectDir
|
||||
"npx"
|
||||
-- TODO: Figure out how to keep running instructions in a single
|
||||
-- place (e.g., this is string the same as the package name, but it's
|
||||
-- repeated in two places).
|
||||
-- Before this, I had the entrypoint file hardcoded, which was bad
|
||||
-- too: waspProjectDir </> [relfile|node_modules/wasp-config/dist/run.js|]
|
||||
[ "wasp-config",
|
||||
fromAbsFile absCompiledMainWaspJsFile,
|
||||
fromAbsFile absDeclsOutputFile,
|
||||
encodeToString allowedEntityNames
|
||||
]
|
||||
J.Wasp
|
||||
chan
|
||||
)
|
||||
case runExitCode of
|
||||
ExitFailure _status -> return $ Left ["Error while running the compiled *.wasp.ts file."]
|
||||
ExitSuccess -> return $ Right absDeclsOutputFile
|
||||
where
|
||||
absDeclsOutputFile = waspProjectDir </> dotWaspDirInWaspProjectDir </> [relfile|decls.json|]
|
||||
allowedEntityNames = Psl.Schema.getModelNames prismaSchemaAst
|
||||
|
||||
readDecls :: Psl.Schema.Schema -> Path' Abs (File AppSpecDeclsJsonFile) -> IO (Either [CompileError] [AS.Decl])
|
||||
readDecls prismaSchemaAst declsJsonFile = runExceptT $ do
|
||||
entityDecls <- liftEither entityDeclsOrErrors
|
||||
remainingDecls <- ExceptT $ left (: []) <$> declsFromJsonOrError
|
||||
return $ entityDecls ++ remainingDecls
|
||||
where
|
||||
entityDeclsOrErrors =
|
||||
left (map fst) $
|
||||
left (map getErrorMessageAndCtx) $
|
||||
Analyzer.getEntityDecls prismaSchemaAst
|
||||
|
||||
declsFromJsonOrError = do
|
||||
declsBytestring <- IOUtil.readFileBytes declsJsonFile
|
||||
return $
|
||||
left ("Error while reading the declarations from JSON: " ++) $
|
||||
Aeson.eitherDecode declsBytestring
|
||||
|
||||
analyzeWaspLangFile :: Psl.Schema.Schema -> Path' Abs (File WaspLangFile) -> IO (Either [CompileError] [AS.Decl])
|
||||
analyzeWaspLangFile prismaSchemaAst waspFilePath = do
|
||||
waspFileContent <- IOUtil.readFile waspFilePath
|
||||
left (map $ showCompilerErrorForTerminal (waspFilePath, waspFileContent))
|
||||
<$> analyzeWaspFileContent prismaSchemaAst waspFileContent
|
||||
|
||||
analyzeWaspFileContent :: Psl.Schema.Schema -> String -> IO (Either [(String, Ctx)] [AS.Decl])
|
||||
analyzeWaspFileContent prismaSchemaAst = return . left (map getErrorMessageAndCtx) . Analyzer.analyze prismaSchemaAst
|
||||
|
||||
constructAppSpec ::
|
||||
Path' Abs (Dir WaspProjectDir) ->
|
||||
CompileOptions ->
|
||||
@ -248,24 +107,6 @@ constructAppSpec waspDir options externalConfigs parsedPrismaSchema decls = do
|
||||
|
||||
return $ runValidation ASV.validateAppSpec appSpec
|
||||
|
||||
findWaspFile :: Path' Abs (Dir WaspProjectDir) -> IO (Either String WaspFilePath)
|
||||
findWaspFile waspDir = do
|
||||
files <- fst <$> IOUtil.listDirectory waspDir
|
||||
return $ case (findWaspTsFile files, findWaspLangFile files) of
|
||||
(Just _, Just _) -> Left bothFilesFoundMessage
|
||||
(Nothing, Nothing) -> Left fileNotFoundMessage
|
||||
(Just waspTsFile, Nothing) -> Right waspTsFile
|
||||
(Nothing, Just waspLangFile) -> Right waspLangFile
|
||||
where
|
||||
findWaspTsFile files = WaspTs <$> findFileThatEndsWith ".wasp.ts" files
|
||||
findWaspLangFile files = WaspLang <$> findFileThatEndsWith ".wasp" files
|
||||
findFileThatEndsWith suffix files = castFile . (waspDir </>) <$> find ((suffix `isSuffixOf`) . fromRelFile) files
|
||||
|
||||
fileNotFoundMessage = "Couldn't find the *.wasp or a *.wasp.ts file in the " ++ fromAbsDir waspDir ++ " directory"
|
||||
bothFilesFoundMessage =
|
||||
"Found both *.wasp and *.wasp.ts files in the project directory. "
|
||||
++ "You must choose how you want to define your app (using Wasp or TypeScript) and only keep one of them."
|
||||
|
||||
analyzePrismaSchema :: Path' Abs (Dir WaspProjectDir) -> IO (Either [CompileError] Psl.Schema.Schema, [CompileWarning])
|
||||
analyzePrismaSchema waspProjectDir = do
|
||||
findPrismaSchemaFile waspProjectDir >>= \case
|
||||
|
@ -88,7 +88,6 @@ dotWaspInfoFileInGeneratedCodeDir = [relfile|.waspinfo|]
|
||||
packageJsonInWaspProjectDir :: Path' (Rel WaspProjectDir) (File PackageJsonFile)
|
||||
packageJsonInWaspProjectDir = [relfile|package.json|]
|
||||
|
||||
-- TODO: The entire tsconfig story is very fragile
|
||||
getSrcTsConfigInWaspProjectDir :: WaspFilePath -> Path' (Rel WaspProjectDir) (File SrcTsConfigFile)
|
||||
getSrcTsConfigInWaspProjectDir = \case
|
||||
WaspTs _ -> srcTsConfigInWaspTsProject
|
||||
|
190
waspc/src/Wasp/Project/WaspFile.hs
Normal file
190
waspc/src/Wasp/Project/WaspFile.hs
Normal file
@ -0,0 +1,190 @@
|
||||
module Wasp.Project.WaspFile
|
||||
( findWaspFile,
|
||||
analyzeWaspFile,
|
||||
analyzeWaspFileContent,
|
||||
)
|
||||
where
|
||||
|
||||
import Control.Arrow (left)
|
||||
import Control.Concurrent (newChan)
|
||||
import Control.Concurrent.Async (concurrently)
|
||||
import Control.Monad.Except (ExceptT (ExceptT), liftEither, runExceptT)
|
||||
import qualified Data.Aeson as Aeson
|
||||
import Data.List (find, isSuffixOf)
|
||||
import StrongPath
|
||||
( Abs,
|
||||
Dir,
|
||||
File,
|
||||
File',
|
||||
Path',
|
||||
Rel,
|
||||
basename,
|
||||
castFile,
|
||||
fromAbsDir,
|
||||
fromAbsFile,
|
||||
fromRelFile,
|
||||
relfile,
|
||||
(</>),
|
||||
)
|
||||
import System.Exit (ExitCode (..))
|
||||
import qualified Wasp.Analyzer as Analyzer
|
||||
import Wasp.Analyzer.Parser.Ctx (Ctx)
|
||||
import qualified Wasp.AppSpec as AS
|
||||
import Wasp.AppSpec.Core.Decl.JSON ()
|
||||
import Wasp.Error (showCompilerErrorForTerminal)
|
||||
import qualified Wasp.Generator.Job as J
|
||||
import Wasp.Generator.Job.IO (readJobMessagesAndPrintThemPrefixed)
|
||||
import Wasp.Generator.Job.Process (runNodeCommandAsJob)
|
||||
import Wasp.Project.Common
|
||||
( CompileError,
|
||||
WaspFilePath (..),
|
||||
WaspLangFile,
|
||||
WaspProjectDir,
|
||||
WaspTsFile,
|
||||
dotWaspDirInWaspProjectDir,
|
||||
)
|
||||
import qualified Wasp.Psl.Ast.Schema as Psl.Schema
|
||||
import Wasp.Util (orElse)
|
||||
import Wasp.Util.Aeson (encodeToString)
|
||||
import qualified Wasp.Util.IO as IOUtil
|
||||
import Wasp.Util.StrongPath (replaceRelExtension)
|
||||
|
||||
data CompiledWaspJsFile
|
||||
|
||||
data AppSpecDeclsJsonFile
|
||||
|
||||
findWaspFile :: Path' Abs (Dir WaspProjectDir) -> IO (Either String WaspFilePath)
|
||||
findWaspFile waspDir = do
|
||||
files <- fst <$> IOUtil.listDirectory waspDir
|
||||
return $ case (findWaspTsFile files, findWaspLangFile files) of
|
||||
(Just _, Just _) -> Left bothFilesFoundMessage
|
||||
(Nothing, Nothing) -> Left fileNotFoundMessage
|
||||
(Just waspTsFile, Nothing) -> Right waspTsFile
|
||||
(Nothing, Just waspLangFile) -> Right waspLangFile
|
||||
where
|
||||
findWaspTsFile files = WaspTs <$> findFileThatEndsWith ".wasp.ts" files
|
||||
findWaspLangFile files = WaspLang <$> findFileThatEndsWith ".wasp" files
|
||||
findFileThatEndsWith suffix files = castFile . (waspDir </>) <$> find ((suffix `isSuffixOf`) . fromRelFile) files
|
||||
|
||||
fileNotFoundMessage = "Couldn't find the *.wasp or a *.wasp.ts file in the " ++ fromAbsDir waspDir ++ " directory"
|
||||
bothFilesFoundMessage =
|
||||
"Found both *.wasp and *.wasp.ts files in the project directory. "
|
||||
++ "You must choose how you want to define your app (using Wasp or TypeScript) and only keep one of them."
|
||||
|
||||
analyzeWaspFile ::
|
||||
Path' Abs (Dir WaspProjectDir) ->
|
||||
Psl.Schema.Schema ->
|
||||
WaspFilePath ->
|
||||
IO (Either [CompileError] [AS.Decl])
|
||||
analyzeWaspFile waspDir prismaSchemaAst = \case
|
||||
WaspLang waspFilePath -> analyzeWaspLangFile prismaSchemaAst waspFilePath
|
||||
WaspTs waspFilePath -> analyzeWaspTsFile waspDir prismaSchemaAst waspFilePath
|
||||
|
||||
analyzeWaspTsFile ::
|
||||
Path' Abs (Dir WaspProjectDir) ->
|
||||
Psl.Schema.Schema ->
|
||||
Path' Abs (File WaspTsFile) ->
|
||||
IO (Either [CompileError] [AS.Decl])
|
||||
analyzeWaspTsFile waspProjectDir prismaSchemaAst waspFilePath = runExceptT $ do
|
||||
-- TODO: I'm not yet sure where tsconfig.node.json location should come from
|
||||
-- because we also need that knowledge when generating a TS SDK project.
|
||||
compiledWaspJsFile <- ExceptT $ compileWaspTsFile waspProjectDir [relfile|tsconfig.wasp.json|] waspFilePath
|
||||
declsJsonFile <- ExceptT $ executeMainWaspJsFileAndGetDeclsFile waspProjectDir prismaSchemaAst compiledWaspJsFile
|
||||
ExceptT $ readDecls prismaSchemaAst declsJsonFile
|
||||
|
||||
analyzeWaspLangFile :: Psl.Schema.Schema -> Path' Abs (File WaspLangFile) -> IO (Either [CompileError] [AS.Decl])
|
||||
analyzeWaspLangFile prismaSchemaAst waspFilePath = do
|
||||
waspFileContent <- IOUtil.readFile waspFilePath
|
||||
left (map $ showCompilerErrorForTerminal (waspFilePath, waspFileContent))
|
||||
<$> analyzeWaspFileContent prismaSchemaAst waspFileContent
|
||||
|
||||
analyzeWaspFileContent :: Psl.Schema.Schema -> String -> IO (Either [(String, Ctx)] [AS.Decl])
|
||||
analyzeWaspFileContent prismaSchemaAst =
|
||||
return
|
||||
. left (map Analyzer.getErrorMessageAndCtx)
|
||||
. Analyzer.analyze prismaSchemaAst
|
||||
|
||||
compileWaspTsFile ::
|
||||
Path' Abs (Dir WaspProjectDir) ->
|
||||
Path' (Rel WaspProjectDir) File' ->
|
||||
Path' Abs (File WaspTsFile) ->
|
||||
IO (Either [CompileError] (Path' Abs (File CompiledWaspJsFile)))
|
||||
compileWaspTsFile waspProjectDir tsconfigNodeFileInWaspProjectDir waspFilePath = do
|
||||
chan <- newChan
|
||||
(_, tscExitCode) <-
|
||||
concurrently
|
||||
(readJobMessagesAndPrintThemPrefixed chan)
|
||||
( runNodeCommandAsJob
|
||||
waspProjectDir
|
||||
"npx"
|
||||
[ "tsc",
|
||||
"-p",
|
||||
fromAbsFile (waspProjectDir </> tsconfigNodeFileInWaspProjectDir),
|
||||
"--noEmit",
|
||||
"false",
|
||||
"--outDir",
|
||||
fromAbsDir outDir
|
||||
]
|
||||
J.Wasp
|
||||
chan
|
||||
)
|
||||
return $ case tscExitCode of
|
||||
ExitFailure _status -> Left ["Got TypeScript compiler errors for " ++ fromAbsFile waspFilePath ++ "."]
|
||||
ExitSuccess -> Right absCompiledWaspJsFile
|
||||
where
|
||||
outDir = waspProjectDir </> dotWaspDirInWaspProjectDir
|
||||
absCompiledWaspJsFile = outDir </> compiledWaspJsFileInDotWaspDir
|
||||
compiledWaspJsFileInDotWaspDir =
|
||||
castFile $
|
||||
replaceRelExtension (basename waspFilePath) ".js"
|
||||
`orElse` error ("Couldn't calculate the compiled JS file path for " ++ fromAbsFile waspFilePath ++ ".")
|
||||
|
||||
executeMainWaspJsFileAndGetDeclsFile ::
|
||||
Path' Abs (Dir WaspProjectDir) ->
|
||||
Psl.Schema.Schema ->
|
||||
Path' Abs (File CompiledWaspJsFile) ->
|
||||
IO (Either [CompileError] (Path' Abs (File AppSpecDeclsJsonFile)))
|
||||
executeMainWaspJsFileAndGetDeclsFile waspProjectDir prismaSchemaAst absCompiledMainWaspJsFile = do
|
||||
chan <- newChan
|
||||
(_, runExitCode) <- do
|
||||
concurrently
|
||||
(readJobMessagesAndPrintThemPrefixed chan)
|
||||
( runNodeCommandAsJob
|
||||
waspProjectDir
|
||||
"npx"
|
||||
-- TODO: Figure out how to keep running instructions in a single
|
||||
-- place (e.g., this is string the same as the package name, but it's
|
||||
-- repeated in two places).
|
||||
-- Before this, I had the entrypoint file hardcoded, which was bad
|
||||
-- too: waspProjectDir </> [relfile|node_modules/wasp-config/dist/run.js|]
|
||||
[ "wasp-config",
|
||||
fromAbsFile absCompiledMainWaspJsFile,
|
||||
fromAbsFile absDeclsOutputFile,
|
||||
encodeToString allowedEntityNames
|
||||
]
|
||||
J.Wasp
|
||||
chan
|
||||
)
|
||||
case runExitCode of
|
||||
ExitFailure _status -> return $ Left ["Error while running the compiled *.wasp.ts file."]
|
||||
ExitSuccess -> return $ Right absDeclsOutputFile
|
||||
where
|
||||
absDeclsOutputFile = waspProjectDir </> dotWaspDirInWaspProjectDir </> [relfile|decls.json|]
|
||||
allowedEntityNames = Psl.Schema.getModelNames prismaSchemaAst
|
||||
|
||||
readDecls :: Psl.Schema.Schema -> Path' Abs (File AppSpecDeclsJsonFile) -> IO (Either [CompileError] [AS.Decl])
|
||||
readDecls prismaSchemaAst declsJsonFile = runExceptT $ do
|
||||
entityDecls <- liftEither entityDeclsOrErrors
|
||||
remainingDecls <- ExceptT $ left (: []) <$> declsFromJsonOrError
|
||||
return $ entityDecls ++ remainingDecls
|
||||
where
|
||||
entityDeclsOrErrors =
|
||||
left (map fst) $
|
||||
left (map Analyzer.getErrorMessageAndCtx) $
|
||||
Analyzer.getEntityDecls prismaSchemaAst
|
||||
|
||||
declsFromJsonOrError = do
|
||||
declsBytestring <- IOUtil.readFileBytes declsJsonFile
|
||||
return $
|
||||
left ("Error while reading the declarations from JSON: " ++) $
|
||||
Aeson.eitherDecode declsBytestring
|
@ -34,6 +34,7 @@ module Wasp.Util
|
||||
kebabToCamelCase,
|
||||
maybeToEither,
|
||||
eitherToMaybe,
|
||||
orElse,
|
||||
whenM,
|
||||
naiveTrimJSON,
|
||||
textToLazyBS,
|
||||
@ -250,6 +251,9 @@ eitherToMaybe :: Either e a -> Maybe a
|
||||
eitherToMaybe (Right x) = Just x
|
||||
eitherToMaybe (Left _) = Nothing
|
||||
|
||||
orElse :: Maybe a -> a -> a
|
||||
orElse = flip fromMaybe
|
||||
|
||||
getEnvVarDefinition :: (String, String) -> String
|
||||
getEnvVarDefinition (name, value) = concat [name, "=", value]
|
||||
|
||||
|
@ -365,10 +365,10 @@ library
|
||||
Wasp.Project.Analyze
|
||||
Wasp.Project.Common
|
||||
Wasp.Project.Db
|
||||
Wasp.Project.Db.Migrations
|
||||
Wasp.Project.Db.Dev
|
||||
Wasp.Project.Db.Dev.Postgres
|
||||
Wasp.Project.Db.Dev.Sqlite
|
||||
Wasp.Project.Db.Migrations
|
||||
Wasp.Project.Deployment
|
||||
Wasp.Project.Env
|
||||
Wasp.Project.ExternalConfig
|
||||
@ -377,6 +377,7 @@ library
|
||||
Wasp.Project.ExternalFiles
|
||||
Wasp.Project.Studio
|
||||
Wasp.Project.Vite
|
||||
Wasp.Project.WaspFile
|
||||
Wasp.Psl.Ast.Argument
|
||||
Wasp.Psl.Ast.Attribute
|
||||
Wasp.Psl.Ast.Common
|
||||
|
Loading…
Reference in New Issue
Block a user