mirror of
https://github.com/wasp-lang/wasp.git
synced 2024-12-24 01:22:24 +03:00
Fix wasp file
This commit is contained in:
parent
d2cad4264a
commit
0d8da669e0
@ -21,6 +21,8 @@ import Wasp.Project.Common
|
||||
WaspFilePath (..),
|
||||
WaspProjectDir,
|
||||
)
|
||||
import Wasp.Project.WaspFile.TypeScript (analyzeWaspTsFile)
|
||||
import Wasp.Project.WaspFile.WaspLang (analyzeWaspLangFile)
|
||||
import qualified Wasp.Psl.Ast.Schema as Psl.Schema
|
||||
import qualified Wasp.Util.IO as IOUtil
|
||||
|
||||
@ -53,115 +55,3 @@ analyzeWaspFile ::
|
||||
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.wasp.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,
|
||||
-- When the user is coding main.wasp.ts, TypeScript must know about
|
||||
-- all the available entities to warn the user if they use an
|
||||
-- entity that doesn't exist.
|
||||
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
|
||||
|
Loading…
Reference in New Issue
Block a user