mirror of
https://github.com/wasp-lang/wasp.git
synced 2024-12-25 10:03:07 +03:00
feat: Adds Generator monad for more flexible error and warning handling (#433)
Closes #123
This commit is contained in:
parent
a4ab848c0b
commit
82cb481c96
@ -5,16 +5,18 @@ module Wasp.Cli.Command.Compile
|
||||
)
|
||||
where
|
||||
|
||||
import Control.Monad.Except (runExceptT, throwError)
|
||||
import Control.Monad.Except (throwError)
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import Data.List (intercalate)
|
||||
import StrongPath (Abs, Dir, Path', (</>))
|
||||
import Wasp.Cli.Command (Command, CommandError (..))
|
||||
import Wasp.Cli.Command.Common
|
||||
( findWaspProjectRootDirFromCwd,
|
||||
waspSaysC,
|
||||
)
|
||||
import Wasp.Cli.Common (waspWarns)
|
||||
import qualified Wasp.Cli.Common as Common
|
||||
import Wasp.Cli.Terminal (asWaspFailureMessage, asWaspStartMessage, asWaspSuccessMessage)
|
||||
import Wasp.Cli.Terminal (asWaspFailureMessage, asWaspStartMessage, asWaspSuccessMessage, asWaspWarningMessage)
|
||||
import Wasp.Common (WaspProjectDir)
|
||||
import Wasp.CompileOptions (CompileOptions (..))
|
||||
import qualified Wasp.Lib
|
||||
@ -51,7 +53,15 @@ compileIOWithOptions ::
|
||||
Path' Abs (Dir Common.WaspProjectDir) ->
|
||||
Path' Abs (Dir Wasp.Lib.ProjectRootDir) ->
|
||||
IO (Either String ())
|
||||
compileIOWithOptions options waspProjectDir outDir = runExceptT $ do
|
||||
-- TODO: Use throwIO instead of Either to return exceptions?
|
||||
liftIO (Wasp.Lib.compile waspProjectDir outDir options)
|
||||
>>= either throwError return
|
||||
compileIOWithOptions options waspProjectDir outDir = do
|
||||
(generatorWarnings, generatorErrors) <- Wasp.Lib.compile waspProjectDir outDir options
|
||||
case generatorErrors of
|
||||
[] -> do
|
||||
displayWarnings generatorWarnings
|
||||
return $ Right ()
|
||||
errors -> return $ Left $ formatMessages errors
|
||||
where
|
||||
formatMessages messages = intercalate "\n" $ map ("- " ++) messages
|
||||
displayWarnings [] = return ()
|
||||
displayWarnings warnings =
|
||||
waspWarns $ asWaspWarningMessage "Your project compiled with warnings:" ++ formatMessages warnings ++ "\n\n"
|
||||
|
@ -14,7 +14,7 @@ import qualified StrongPath as SP
|
||||
import qualified System.FSNotify as FSN
|
||||
import qualified System.FilePath as FP
|
||||
import Wasp.Cli.Command.Compile (compileIO)
|
||||
import Wasp.Cli.Common (waspSays)
|
||||
import Wasp.Cli.Common (waspSays, waspScreams)
|
||||
import qualified Wasp.Cli.Common as Common
|
||||
import Wasp.Cli.Terminal (asWaspFailureMessage, asWaspStartMessage, asWaspSuccessMessage)
|
||||
import qualified Wasp.Lib
|
||||
@ -82,7 +82,7 @@ watch waspProjectDir outDir = FSN.withManager $ \mgr -> do
|
||||
waspSays $ asWaspStartMessage "Recompiling on file change..."
|
||||
compilationResult <- compileIO waspProjectDir outDir
|
||||
case compilationResult of
|
||||
Left err -> waspSays $ asWaspFailureMessage "Recompilation on file change failed:" ++ err
|
||||
Left err -> waspScreams $ asWaspFailureMessage "Recompilation on file change failed:" ++ err
|
||||
Right () -> waspSays $ asWaspSuccessMessage "Recompilation on file change succeeded."
|
||||
return ()
|
||||
|
||||
|
@ -9,6 +9,8 @@ module Wasp.Cli.Common
|
||||
generatedCodeDirInDotWaspDir,
|
||||
buildDirInDotWaspDir,
|
||||
waspSays,
|
||||
waspWarns,
|
||||
waspScreams,
|
||||
)
|
||||
where
|
||||
|
||||
@ -44,3 +46,9 @@ extCodeDirInWaspProjectDir = [reldir|ext|]
|
||||
|
||||
waspSays :: String -> IO ()
|
||||
waspSays what = putStrLn $ Term.applyStyles [Term.Yellow] what
|
||||
|
||||
waspWarns :: String -> IO ()
|
||||
waspWarns what = putStrLn $ Term.applyStyles [Term.Magenta] what
|
||||
|
||||
waspScreams :: String -> IO ()
|
||||
waspScreams what = putStrLn $ Term.applyStyles [Term.Red] what
|
||||
|
@ -4,6 +4,7 @@ module Wasp.Cli.Terminal
|
||||
asWaspStartMessage,
|
||||
asWaspSuccessMessage,
|
||||
asWaspFailureMessage,
|
||||
asWaspWarningMessage,
|
||||
)
|
||||
where
|
||||
|
||||
@ -21,6 +22,11 @@ asWaspStartMessage = waspMessageWithEmoji "🐝"
|
||||
asWaspSuccessMessage :: String -> String
|
||||
asWaspSuccessMessage = waspMessageWithEmoji "✅"
|
||||
|
||||
asWaspWarningMessage :: String -> String
|
||||
asWaspWarningMessage str = concat ["\n", waspMessageWithEmoji "👀" errorStr, "\n"]
|
||||
where
|
||||
errorStr = "[Warning] " ++ str
|
||||
|
||||
asWaspFailureMessage :: String -> String
|
||||
-- Add a bit more padding on errors for more pronounced
|
||||
-- visibility and better display of any following error context.
|
||||
|
@ -5,6 +5,7 @@ module Wasp.Generator
|
||||
)
|
||||
where
|
||||
|
||||
import Data.List.NonEmpty (toList)
|
||||
import qualified Data.Text
|
||||
import qualified Data.Text.IO
|
||||
import Data.Time.Clock
|
||||
@ -18,26 +19,40 @@ import Wasp.Generator.DbGenerator (genDb)
|
||||
import qualified Wasp.Generator.DbGenerator as DbGenerator
|
||||
import Wasp.Generator.DockerGenerator (genDockerFiles)
|
||||
import Wasp.Generator.FileDraft (FileDraft, write)
|
||||
import Wasp.Generator.Monad (Generator, GeneratorError, GeneratorWarning, runGenerator)
|
||||
import Wasp.Generator.ServerGenerator (genServer)
|
||||
import qualified Wasp.Generator.ServerGenerator as ServerGenerator
|
||||
import qualified Wasp.Generator.Setup
|
||||
import qualified Wasp.Generator.Start
|
||||
import Wasp.Generator.WebAppGenerator (generateWebApp)
|
||||
import Wasp.Util ((<++>))
|
||||
|
||||
-- | Generates web app code from given Wasp and writes it to given destination directory.
|
||||
-- If dstDir does not exist yet, it will be created.
|
||||
-- If there are any errors returned, that means that generator failed and no new code was written.
|
||||
-- If no errors were returned, this means generator was successful and generated a new version of the project
|
||||
-- (regardless of the warnings returned).
|
||||
-- NOTE(martin): What if there is already smth in the dstDir? It is probably best
|
||||
-- if we clean it up first? But we don't want this to end up with us deleting stuff
|
||||
-- from user's machine. Maybe we just overwrite and we are good?
|
||||
writeWebAppCode :: AppSpec -> Path' Abs (Dir ProjectRootDir) -> IO ()
|
||||
writeWebAppCode :: AppSpec -> Path' Abs (Dir ProjectRootDir) -> IO ([GeneratorWarning], [GeneratorError])
|
||||
writeWebAppCode spec dstDir = do
|
||||
writeFileDrafts dstDir (generateWebApp spec)
|
||||
let (generatorWarnings, generatorResult) = runGenerator $ genApp spec
|
||||
case generatorResult of
|
||||
Left generatorErrors -> return (generatorWarnings, toList generatorErrors)
|
||||
Right fileDrafts -> do
|
||||
ServerGenerator.preCleanup spec dstDir
|
||||
writeFileDrafts dstDir (genServer spec)
|
||||
DbGenerator.preCleanup spec dstDir
|
||||
writeFileDrafts dstDir (genDb spec)
|
||||
writeFileDrafts dstDir (genDockerFiles spec)
|
||||
writeFileDrafts dstDir fileDrafts
|
||||
writeDotWaspInfo dstDir
|
||||
return (generatorWarnings, [])
|
||||
|
||||
genApp :: AppSpec -> Generator [FileDraft]
|
||||
genApp spec =
|
||||
generateWebApp spec
|
||||
<++> genServer spec
|
||||
<++> genDb spec
|
||||
<++> genDockerFiles spec
|
||||
|
||||
-- | Writes file drafts while using given destination dir as root dir.
|
||||
-- TODO(martin): We could/should parallelize this.
|
||||
|
@ -23,9 +23,11 @@ import qualified Wasp.AppSpec.Entity as AS.Entity
|
||||
import Wasp.Common (DbMigrationsDir)
|
||||
import Wasp.Generator.Common (ProjectRootDir)
|
||||
import Wasp.Generator.FileDraft (FileDraft, createCopyDirFileDraft, createTemplateFileDraft)
|
||||
import Wasp.Generator.Monad (Generator, GeneratorError (..), logAndThrowGeneratorError)
|
||||
import Wasp.Generator.Templates (TemplatesDir)
|
||||
import qualified Wasp.Psl.Ast.Model as Psl.Ast.Model
|
||||
import qualified Wasp.Psl.Generator.Model as Psl.Generator.Model
|
||||
import Wasp.Util ((<:>))
|
||||
|
||||
data DbRootDir
|
||||
|
||||
@ -55,10 +57,9 @@ preCleanup :: AppSpec -> Path' Abs (Dir ProjectRootDir) -> IO ()
|
||||
preCleanup spec projectRootDir = do
|
||||
deleteGeneratedMigrationsDirIfRedundant spec projectRootDir
|
||||
|
||||
-- * Db generator
|
||||
|
||||
genDb :: AppSpec -> [FileDraft]
|
||||
genDb spec = genPrismaSchema spec : maybeToList (genMigrationsDir spec)
|
||||
genDb :: AppSpec -> Generator [FileDraft]
|
||||
genDb spec =
|
||||
genPrismaSchema spec <:> (maybeToList <$> genMigrationsDir spec)
|
||||
|
||||
deleteGeneratedMigrationsDirIfRedundant :: AppSpec -> Path' Abs (Dir ProjectRootDir) -> IO ()
|
||||
deleteGeneratedMigrationsDirIfRedundant spec projectRootDir = do
|
||||
@ -72,35 +73,36 @@ deleteGeneratedMigrationsDirIfRedundant spec projectRootDir = do
|
||||
where
|
||||
projectMigrationsDirAbsFilePath = SP.fromAbsDir $ projectRootDir </> dbRootDirInProjectRootDir </> dbMigrationsDirInDbRootDir
|
||||
|
||||
genPrismaSchema :: AppSpec -> FileDraft
|
||||
genPrismaSchema spec = createTemplateFileDraft dstPath tmplSrcPath (Just templateData)
|
||||
where
|
||||
dstPath = dbSchemaFileInProjectRootDir
|
||||
tmplSrcPath = dbTemplatesDirInTemplatesDir </> dbSchemaFileInDbTemplatesDir
|
||||
genPrismaSchema :: AppSpec -> Generator FileDraft
|
||||
genPrismaSchema spec = do
|
||||
(datasourceProvider, datasourceUrl) <- case dbSystem of
|
||||
AS.Db.PostgreSQL -> return ("postgresql", "env(\"DATABASE_URL\")")
|
||||
AS.Db.SQLite ->
|
||||
if AS.isBuild spec
|
||||
then logAndThrowGeneratorError $ GenericGeneratorError "SQLite (a default database) is not supported in production. To build your Wasp app for production, switch to a different database. Switching to PostgreSQL: https://wasp-lang.dev/docs/language/features/#migrating-from-sqlite-to-postgresql ."
|
||||
else return ("sqlite", "\"file:./dev.db\"")
|
||||
|
||||
templateData =
|
||||
let templateData =
|
||||
object
|
||||
[ "modelSchemas" .= map entityToPslModelSchema (AS.getDecls @AS.Entity.Entity spec),
|
||||
"datasourceProvider" .= (datasourceProvider :: String),
|
||||
"datasourceUrl" .= (datasourceUrl :: String)
|
||||
]
|
||||
|
||||
return $ createTemplateFileDraft dstPath tmplSrcPath (Just templateData)
|
||||
where
|
||||
dstPath = dbSchemaFileInProjectRootDir
|
||||
tmplSrcPath = dbTemplatesDirInTemplatesDir </> dbSchemaFileInDbTemplatesDir
|
||||
dbSystem = fromMaybe AS.Db.SQLite (AS.Db.system =<< AS.App.db (snd $ AS.getApp spec))
|
||||
(datasourceProvider, datasourceUrl) = case dbSystem of
|
||||
AS.Db.PostgreSQL -> ("postgresql", "env(\"DATABASE_URL\")")
|
||||
-- TODO: Report this error with some better mechanism, not `error`.
|
||||
AS.Db.SQLite ->
|
||||
if AS.isBuild spec
|
||||
then error "SQLite (a default database) is not supported in production. To build your Wasp app for production, switch to a different database. Switching to PostgreSQL: https://wasp-lang.dev/docs/language/features/#migrating-from-sqlite-to-postgresql ."
|
||||
else ("sqlite", "\"file:./dev.db\"")
|
||||
|
||||
entityToPslModelSchema :: (String, AS.Entity.Entity) -> String
|
||||
entityToPslModelSchema (entityName, entity) =
|
||||
Psl.Generator.Model.generateModel $
|
||||
Psl.Ast.Model.Model entityName (AS.Entity.getPslModelBody entity)
|
||||
|
||||
genMigrationsDir :: AppSpec -> Maybe FileDraft
|
||||
genMigrationsDir :: AppSpec -> Generator (Maybe FileDraft)
|
||||
genMigrationsDir spec =
|
||||
return $
|
||||
AS.migrationsDir spec >>= \waspMigrationsDir ->
|
||||
Just $ createCopyDirFileDraft (SP.castDir genProjectMigrationsDir) (SP.castDir waspMigrationsDir)
|
||||
where
|
||||
|
@ -12,14 +12,16 @@ import qualified Wasp.AppSpec as AS
|
||||
import qualified Wasp.AppSpec.Entity as AS.Entity
|
||||
import Wasp.Generator.Common (ProjectRootDir)
|
||||
import Wasp.Generator.FileDraft (FileDraft, createTemplateFileDraft)
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
import Wasp.Generator.Templates (TemplatesDir)
|
||||
|
||||
genDockerFiles :: AppSpec -> [FileDraft]
|
||||
genDockerFiles spec = genDockerfile spec : [genDockerignore spec]
|
||||
genDockerFiles :: AppSpec -> Generator [FileDraft]
|
||||
genDockerFiles spec = sequence [genDockerfile spec, genDockerignore spec]
|
||||
|
||||
-- TODO: Inject paths to server and db files/dirs, right now they are hardcoded in the templates.
|
||||
genDockerfile :: AppSpec -> FileDraft
|
||||
genDockerfile :: AppSpec -> Generator FileDraft
|
||||
genDockerfile spec =
|
||||
return $
|
||||
createTemplateFileDraft
|
||||
([relfile|Dockerfile|] :: Path' (Rel ProjectRootDir) File')
|
||||
([relfile|Dockerfile|] :: Path' (Rel TemplatesDir) File')
|
||||
@ -29,8 +31,9 @@ genDockerfile spec =
|
||||
]
|
||||
)
|
||||
|
||||
genDockerignore :: AppSpec -> FileDraft
|
||||
genDockerignore :: AppSpec -> Generator FileDraft
|
||||
genDockerignore _ =
|
||||
return $
|
||||
createTemplateFileDraft
|
||||
([relfile|.dockerignore|] :: Path' (Rel ProjectRootDir) File')
|
||||
([relfile|dockerignore|] :: Path' (Rel TemplatesDir) File')
|
||||
|
@ -10,22 +10,23 @@ import qualified Wasp.AppSpec.ExternalCode as EC
|
||||
import qualified Wasp.Generator.ExternalCodeGenerator.Common as C
|
||||
import Wasp.Generator.ExternalCodeGenerator.Js (generateJsFile)
|
||||
import qualified Wasp.Generator.FileDraft as FD
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
|
||||
-- | Takes external code files from Wasp and generates them in new location as part of the generated project.
|
||||
-- It might not just copy them but also do some changes on them, as needed.
|
||||
generateExternalCodeDir ::
|
||||
C.ExternalCodeGeneratorStrategy ->
|
||||
[EC.File] ->
|
||||
[FD.FileDraft]
|
||||
generateExternalCodeDir strategy = map (generateFile strategy)
|
||||
Generator [FD.FileDraft]
|
||||
generateExternalCodeDir strategy = mapM (generateFile strategy)
|
||||
|
||||
generateFile :: C.ExternalCodeGeneratorStrategy -> EC.File -> FD.FileDraft
|
||||
generateFile :: C.ExternalCodeGeneratorStrategy -> EC.File -> Generator FD.FileDraft
|
||||
generateFile strategy file
|
||||
| extension `elem` [".js", ".jsx"] = generateJsFile strategy file
|
||||
| otherwise =
|
||||
let relDstPath = C._extCodeDirInProjectRootDir strategy </> dstPathInGenExtCodeDir
|
||||
absSrcPath = EC.fileAbsPath file
|
||||
in FD.createCopyFileDraft relDstPath absSrcPath
|
||||
in return $ FD.createCopyFileDraft relDstPath absSrcPath
|
||||
where
|
||||
dstPathInGenExtCodeDir :: Path' (Rel C.GeneratedExternalCodeDir) File'
|
||||
dstPathInGenExtCodeDir = C.castRelPathFromSrcToGenExtCodeDir $ EC.filePathInExtCodeDir file
|
||||
|
@ -15,9 +15,10 @@ import qualified Wasp.AppSpec.ExternalCode as EC
|
||||
import Wasp.Generator.ExternalCodeGenerator.Common (GeneratedExternalCodeDir)
|
||||
import qualified Wasp.Generator.ExternalCodeGenerator.Common as C
|
||||
import qualified Wasp.Generator.FileDraft as FD
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
|
||||
generateJsFile :: C.ExternalCodeGeneratorStrategy -> EC.File -> FD.FileDraft
|
||||
generateJsFile strategy file = FD.createTextFileDraft dstPath text'
|
||||
generateJsFile :: C.ExternalCodeGeneratorStrategy -> EC.File -> Generator FD.FileDraft
|
||||
generateJsFile strategy file = return $ FD.createTextFileDraft dstPath text'
|
||||
where
|
||||
filePathInSrcExtCodeDir = EC.filePathInExtCodeDir file
|
||||
|
||||
|
84
waspc/src/Wasp/Generator/Monad.hs
Normal file
84
waspc/src/Wasp/Generator/Monad.hs
Normal file
@ -0,0 +1,84 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
|
||||
module Wasp.Generator.Monad
|
||||
( Generator,
|
||||
GeneratorError (..),
|
||||
GeneratorWarning (..),
|
||||
catchGeneratorError,
|
||||
logAndThrowGeneratorError,
|
||||
logGeneratorWarning,
|
||||
runGenerator,
|
||||
)
|
||||
where
|
||||
|
||||
import Control.Monad.Except (ExceptT, MonadError (throwError), runExceptT)
|
||||
import qualified Control.Monad.Except as MonadExcept
|
||||
import Control.Monad.Identity (Identity (runIdentity))
|
||||
import Control.Monad.State (MonadState, StateT (runStateT), modify)
|
||||
import Data.List.NonEmpty (NonEmpty, fromList)
|
||||
|
||||
-- | Generator is a monad transformer stack where we abstract away the underlying
|
||||
-- concrete monad transformers with the helper functions below. This will allow us
|
||||
-- to refactor and add more transformers (or swap them) without any caller changes.
|
||||
--
|
||||
-- The outer Either layer represents the last error that halted generation. Any error logged and thrown is fatal.
|
||||
-- The mechanism to catch errors is only there to assist in collecting more errors, not recover.
|
||||
-- There may optionally be additional errors or non-fatal warnings logged in the State.
|
||||
newtype Generator a = Generator
|
||||
{ _runGenerator :: ExceptT GeneratorError (StateT GeneratorState Identity) a
|
||||
}
|
||||
deriving
|
||||
( Functor,
|
||||
Applicative,
|
||||
Monad,
|
||||
MonadState GeneratorState,
|
||||
MonadError GeneratorError
|
||||
)
|
||||
|
||||
data GeneratorState = GeneratorState
|
||||
{ warnings :: [GeneratorWarning],
|
||||
errors :: [GeneratorError]
|
||||
}
|
||||
|
||||
data GeneratorError = GenericGeneratorError String
|
||||
|
||||
instance Show GeneratorError where
|
||||
show (GenericGeneratorError e) = e
|
||||
|
||||
data GeneratorWarning = GenericGeneratorWarning String
|
||||
|
||||
instance Show GeneratorWarning where
|
||||
show (GenericGeneratorWarning 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).
|
||||
-- Even if successful there may be warnings, so they are always included.
|
||||
runGenerator :: Generator a -> ([GeneratorWarning], Either (NonEmpty GeneratorError) a)
|
||||
runGenerator generator =
|
||||
let (errorOrResult, finalState) = runIdentity $ runStateT (runExceptT (_runGenerator generator)) initialState
|
||||
in (warnings finalState, loggedErrorsOrResult (errorOrResult, errors finalState))
|
||||
where
|
||||
initialState = GeneratorState {warnings = [], errors = []}
|
||||
|
||||
loggedErrorsOrResult (Right result, []) = Right result
|
||||
loggedErrorsOrResult (Left _, []) = error "Generator produced error, but had empty log - this should never happen!"
|
||||
loggedErrorsOrResult (_, loggedErrors) = Left $ fromList loggedErrors
|
||||
|
||||
-- This logs a warning but does not short circuit the computation.
|
||||
logGeneratorWarning :: GeneratorWarning -> Generator ()
|
||||
logGeneratorWarning w = modify $ \GeneratorState {errors = errors', warnings = warnings'} ->
|
||||
GeneratorState {errors = errors', warnings = w : warnings'}
|
||||
|
||||
-- This logs an error and does throw, thus short-circuiting the computation until caught.
|
||||
logAndThrowGeneratorError :: GeneratorError -> Generator a
|
||||
logAndThrowGeneratorError e = logGeneratorError >> throwError e
|
||||
where
|
||||
logGeneratorError :: Generator ()
|
||||
logGeneratorError = modify $ \GeneratorState {errors = errors', warnings = warnings'} ->
|
||||
GeneratorState {errors = e : errors', warnings = warnings'}
|
||||
|
||||
-- This stops the short-circuiting from above, if ever desired, but cannot be used for full recovery.
|
||||
-- Once one error is logged and thrown the result will be error. This function exists to log
|
||||
-- more errors on the way up.
|
||||
catchGeneratorError :: Generator a -> (GeneratorError -> Generator a) -> Generator a
|
||||
catchGeneratorError = MonadExcept.catchError
|
@ -34,6 +34,7 @@ import Wasp.Generator.ExternalCodeGenerator (generateExternalCodeDir)
|
||||
import Wasp.Generator.ExternalCodeGenerator.Common (GeneratedExternalCodeDir)
|
||||
import Wasp.Generator.FileDraft (FileDraft, createCopyFileDraft)
|
||||
import Wasp.Generator.JsImport (getJsImportDetailsForExtFnImport)
|
||||
import Wasp.Generator.Monad (Generator, GeneratorError (..), logAndThrowGeneratorError)
|
||||
import Wasp.Generator.PackageJsonGenerator
|
||||
( npmDepsToPackageJsonEntry,
|
||||
npmDevDepsToPackageJsonEntry,
|
||||
@ -50,19 +51,20 @@ import Wasp.Generator.ServerGenerator.ConfigG (genConfigFile)
|
||||
import qualified Wasp.Generator.ServerGenerator.ExternalCodeGenerator as ServerExternalCodeGenerator
|
||||
import Wasp.Generator.ServerGenerator.OperationsG (genOperations)
|
||||
import Wasp.Generator.ServerGenerator.OperationsRoutesG (genOperationsRoutes)
|
||||
import Wasp.Util ((<++>))
|
||||
|
||||
genServer :: AppSpec -> [FileDraft]
|
||||
genServer :: AppSpec -> Generator [FileDraft]
|
||||
genServer spec =
|
||||
concat
|
||||
[ [genReadme],
|
||||
[genPackageJson spec waspNpmDeps waspNpmDevDeps],
|
||||
[genNpmrc],
|
||||
[genNvmrc],
|
||||
[genGitignore],
|
||||
genSrcDir spec,
|
||||
generateExternalCodeDir ServerExternalCodeGenerator.generatorStrategy (AS.externalCodeFiles spec),
|
||||
genDotEnv spec
|
||||
sequence
|
||||
[ genReadme,
|
||||
genPackageJson spec waspNpmDeps waspNpmDevDeps,
|
||||
genNpmrc,
|
||||
genNvmrc,
|
||||
genGitignore
|
||||
]
|
||||
<++> genSrcDir spec
|
||||
<++> generateExternalCodeDir ServerExternalCodeGenerator.generatorStrategy (AS.externalCodeFiles spec)
|
||||
<++> genDotEnv spec
|
||||
|
||||
-- Cleanup to be performed before generating new server code.
|
||||
-- This might be needed in case if outDir is not empty (e.g. we already generated server code there before).
|
||||
@ -78,8 +80,8 @@ preCleanup _ outDir = do
|
||||
where
|
||||
dotEnvAbsFilePath = SP.toFilePath $ outDir </> C.serverRootDirInProjectRootDir </> dotEnvInServerRootDir
|
||||
|
||||
genDotEnv :: AppSpec -> [FileDraft]
|
||||
genDotEnv spec =
|
||||
genDotEnv :: AppSpec -> Generator [FileDraft]
|
||||
genDotEnv spec = return $
|
||||
case AS.dotEnvFile spec of
|
||||
Just srcFilePath ->
|
||||
[ createCopyFileDraft
|
||||
@ -91,11 +93,17 @@ genDotEnv spec =
|
||||
dotEnvInServerRootDir :: Path' (Rel C.ServerRootDir) File'
|
||||
dotEnvInServerRootDir = [relfile|.env|]
|
||||
|
||||
genReadme :: FileDraft
|
||||
genReadme = C.mkTmplFd (asTmplFile [relfile|README.md|])
|
||||
genReadme :: Generator FileDraft
|
||||
genReadme = return $ C.mkTmplFd (asTmplFile [relfile|README.md|])
|
||||
|
||||
genPackageJson :: AppSpec -> [AS.Dependency.Dependency] -> [AS.Dependency.Dependency] -> FileDraft
|
||||
genPackageJson spec waspDeps waspDevDeps =
|
||||
genPackageJson :: AppSpec -> [AS.Dependency.Dependency] -> [AS.Dependency.Dependency] -> Generator FileDraft
|
||||
genPackageJson spec waspDeps waspDevDeps = do
|
||||
(resolvedWaspDeps, resolvedUserDeps) <-
|
||||
case resolveNpmDeps waspDeps userDeps of
|
||||
Right deps -> return deps
|
||||
Left depsAndErrors -> logAndThrowGeneratorError $ GenericGeneratorError $ intercalate " ; " $ map snd depsAndErrors
|
||||
|
||||
return $
|
||||
C.mkTmplFdWithDstAndData
|
||||
(asTmplFile [relfile|package.json|])
|
||||
(asServerFile [relfile|package.json|])
|
||||
@ -105,19 +113,12 @@ genPackageJson spec waspDeps waspDevDeps =
|
||||
"devDepsChunk" .= npmDevDepsToPackageJsonEntry waspDevDeps,
|
||||
"nodeVersion" .= nodeVersionAsText,
|
||||
"startProductionScript"
|
||||
.= if not (null $ AS.getDecls @AS.Entity.Entity spec)
|
||||
then "npm run db-migrate-prod && "
|
||||
else
|
||||
""
|
||||
.= ( (if not (null $ AS.getDecls @AS.Entity.Entity spec) then "npm run db-migrate-prod && " else "")
|
||||
++ "NODE_ENV=production node ./src/server.js"
|
||||
)
|
||||
]
|
||||
)
|
||||
where
|
||||
(resolvedWaspDeps, resolvedUserDeps) =
|
||||
case resolveNpmDeps waspDeps userDeps of
|
||||
Right deps -> deps
|
||||
Left depsAndErrors -> error $ intercalate " ; " $ map snd depsAndErrors
|
||||
|
||||
userDeps :: [AS.Dependency.Dependency]
|
||||
userDeps = fromMaybe [] $ AS.App.dependencies $ snd $ AS.getApp spec
|
||||
|
||||
@ -144,46 +145,49 @@ waspNpmDevDeps =
|
||||
("prisma", "2.22.1")
|
||||
]
|
||||
|
||||
genNpmrc :: FileDraft
|
||||
genNpmrc :: Generator FileDraft
|
||||
genNpmrc =
|
||||
return $
|
||||
C.mkTmplFdWithDstAndData
|
||||
(asTmplFile [relfile|npmrc|])
|
||||
(asServerFile [relfile|.npmrc|])
|
||||
Nothing
|
||||
|
||||
genNvmrc :: FileDraft
|
||||
genNvmrc :: Generator FileDraft
|
||||
genNvmrc =
|
||||
return $
|
||||
C.mkTmplFdWithDstAndData
|
||||
(asTmplFile [relfile|nvmrc|])
|
||||
(asServerFile [relfile|.nvmrc|])
|
||||
(Just (object ["nodeVersion" .= ('v' : nodeVersionAsText)]))
|
||||
|
||||
genGitignore :: FileDraft
|
||||
genGitignore :: Generator FileDraft
|
||||
genGitignore =
|
||||
return $
|
||||
C.mkTmplFdWithDstAndData
|
||||
(asTmplFile [relfile|gitignore|])
|
||||
(asServerFile [relfile|.gitignore|])
|
||||
Nothing
|
||||
|
||||
genSrcDir :: AppSpec -> [FileDraft]
|
||||
genSrcDir :: AppSpec -> Generator [FileDraft]
|
||||
genSrcDir spec =
|
||||
concat
|
||||
[ [C.mkSrcTmplFd $ C.asTmplSrcFile [relfile|app.js|]],
|
||||
[C.mkSrcTmplFd $ C.asTmplSrcFile [relfile|server.js|]],
|
||||
[C.mkSrcTmplFd $ C.asTmplSrcFile [relfile|utils.js|]],
|
||||
[C.mkSrcTmplFd $ C.asTmplSrcFile [relfile|core/AuthError.js|]],
|
||||
[C.mkSrcTmplFd $ C.asTmplSrcFile [relfile|core/HttpError.js|]],
|
||||
[genDbClient spec],
|
||||
[genConfigFile spec],
|
||||
genRoutesDir spec,
|
||||
genOperationsRoutes spec,
|
||||
genOperations spec,
|
||||
genAuth spec,
|
||||
[genServerJs spec]
|
||||
sequence
|
||||
[ return $ C.mkSrcTmplFd $ C.asTmplSrcFile [relfile|app.js|],
|
||||
return $ C.mkSrcTmplFd $ C.asTmplSrcFile [relfile|server.js|],
|
||||
return $ C.mkSrcTmplFd $ C.asTmplSrcFile [relfile|utils.js|],
|
||||
return $ C.mkSrcTmplFd $ C.asTmplSrcFile [relfile|core/AuthError.js|],
|
||||
return $ C.mkSrcTmplFd $ C.asTmplSrcFile [relfile|core/HttpError.js|],
|
||||
genDbClient spec,
|
||||
genConfigFile spec,
|
||||
genServerJs spec
|
||||
]
|
||||
<++> genRoutesDir spec
|
||||
<++> genOperationsRoutes spec
|
||||
<++> genOperations spec
|
||||
<++> genAuth spec
|
||||
|
||||
genDbClient :: AppSpec -> FileDraft
|
||||
genDbClient spec = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
genDbClient :: AppSpec -> Generator FileDraft
|
||||
genDbClient spec = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
maybeAuth = AS.App.auth $ snd $ AS.getApp spec
|
||||
|
||||
@ -200,8 +204,9 @@ genDbClient spec = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
]
|
||||
else object []
|
||||
|
||||
genServerJs :: AppSpec -> FileDraft
|
||||
genServerJs :: AppSpec -> Generator FileDraft
|
||||
genServerJs spec =
|
||||
return $
|
||||
C.mkTmplFdWithDstAndData
|
||||
(asTmplFile [relfile|src/server.js|])
|
||||
(asServerFile [relfile|src/server.js|])
|
||||
@ -222,10 +227,11 @@ genServerJs spec =
|
||||
relPosixPathFromSrcDirToExtSrcDir :: Path Posix (Rel (Dir ServerSrcDir)) (Dir GeneratedExternalCodeDir)
|
||||
relPosixPathFromSrcDirToExtSrcDir = [reldirP|./ext-src|]
|
||||
|
||||
genRoutesDir :: AppSpec -> [FileDraft]
|
||||
genRoutesDir :: AppSpec -> Generator [FileDraft]
|
||||
genRoutesDir spec =
|
||||
-- TODO(martin): We will probably want to extract "routes" path here same as we did with "src", to avoid hardcoding,
|
||||
-- but I did not bother with it yet since it is used only here for now.
|
||||
return
|
||||
[ C.mkTmplFdWithDstAndData
|
||||
(asTmplFile [relfile|src/routes/index.js|])
|
||||
(asServerFile [relfile|src/routes/index.js|])
|
||||
|
@ -10,12 +10,14 @@ import qualified Wasp.AppSpec as AS
|
||||
import qualified Wasp.AppSpec.App as AS.App
|
||||
import qualified Wasp.AppSpec.App.Auth as AS.Auth
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
import qualified Wasp.Generator.ServerGenerator.Common as C
|
||||
import qualified Wasp.Util as Util
|
||||
|
||||
genAuth :: AppSpec -> [FileDraft]
|
||||
genAuth :: AppSpec -> Generator [FileDraft]
|
||||
genAuth spec = case maybeAuth of
|
||||
Just auth ->
|
||||
sequence
|
||||
[ genCoreAuth auth,
|
||||
genAuthMiddleware auth,
|
||||
-- Auth routes
|
||||
@ -24,13 +26,13 @@ genAuth spec = case maybeAuth of
|
||||
genSignupRoute auth,
|
||||
genMeRoute auth
|
||||
]
|
||||
Nothing -> []
|
||||
Nothing -> return []
|
||||
where
|
||||
maybeAuth = AS.App.auth $ snd $ AS.getApp spec
|
||||
|
||||
-- | Generates core/auth file which contains auth middleware and createUser() function.
|
||||
genCoreAuth :: AS.Auth.Auth -> FileDraft
|
||||
genCoreAuth auth = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
genCoreAuth :: AS.Auth.Auth -> Generator FileDraft
|
||||
genCoreAuth auth = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
coreAuthRelToSrc = [relfile|core/auth.js|]
|
||||
tmplFile = C.asTmplFile $ [reldir|src|] </> coreAuthRelToSrc
|
||||
@ -43,8 +45,8 @@ genCoreAuth auth = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
"userEntityLower" .= (Util.toLowerFirst userEntityName :: String)
|
||||
]
|
||||
|
||||
genAuthMiddleware :: AS.Auth.Auth -> FileDraft
|
||||
genAuthMiddleware auth = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
genAuthMiddleware :: AS.Auth.Auth -> Generator FileDraft
|
||||
genAuthMiddleware auth = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
authMiddlewareRelToSrc = [relfile|core/auth/prismaMiddleware.js|]
|
||||
tmplFile = C.asTmplFile $ [reldir|src|] </> authMiddlewareRelToSrc
|
||||
@ -56,11 +58,11 @@ genAuthMiddleware auth = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplDat
|
||||
[ "userEntityUpper" .= (userEntityName :: String)
|
||||
]
|
||||
|
||||
genAuthRoutesIndex :: FileDraft
|
||||
genAuthRoutesIndex = C.mkSrcTmplFd (C.asTmplSrcFile [relfile|routes/auth/index.js|])
|
||||
genAuthRoutesIndex :: Generator FileDraft
|
||||
genAuthRoutesIndex = return $ C.mkSrcTmplFd (C.asTmplSrcFile [relfile|routes/auth/index.js|])
|
||||
|
||||
genLoginRoute :: AS.Auth.Auth -> FileDraft
|
||||
genLoginRoute auth = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
genLoginRoute :: AS.Auth.Auth -> Generator FileDraft
|
||||
genLoginRoute auth = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
loginRouteRelToSrc = [relfile|routes/auth/login.js|]
|
||||
tmplFile = C.asTmplFile $ [reldir|src|] </> loginRouteRelToSrc
|
||||
@ -73,8 +75,8 @@ genLoginRoute auth = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
"userEntityLower" .= (Util.toLowerFirst userEntityName :: String)
|
||||
]
|
||||
|
||||
genSignupRoute :: AS.Auth.Auth -> FileDraft
|
||||
genSignupRoute auth = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
genSignupRoute :: AS.Auth.Auth -> Generator FileDraft
|
||||
genSignupRoute auth = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
signupRouteRelToSrc = [relfile|routes/auth/signup.js|]
|
||||
tmplFile = C.asTmplFile $ [reldir|src|] </> signupRouteRelToSrc
|
||||
@ -85,8 +87,8 @@ genSignupRoute auth = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
[ "userEntityLower" .= (Util.toLowerFirst (AS.refName $ AS.Auth.userEntity auth) :: String)
|
||||
]
|
||||
|
||||
genMeRoute :: AS.Auth.Auth -> FileDraft
|
||||
genMeRoute auth = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
genMeRoute :: AS.Auth.Auth -> Generator FileDraft
|
||||
genMeRoute auth = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
meRouteRelToSrc = [relfile|routes/auth/me.js|]
|
||||
tmplFile = C.asTmplFile $ [reldir|src|] </> meRouteRelToSrc
|
||||
|
@ -10,10 +10,11 @@ import qualified StrongPath as SP
|
||||
import Wasp.AppSpec (AppSpec)
|
||||
import qualified Wasp.AppSpec as AS
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
import qualified Wasp.Generator.ServerGenerator.Common as C
|
||||
|
||||
genConfigFile :: AppSpec -> FileDraft
|
||||
genConfigFile spec = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
genConfigFile :: AppSpec -> Generator FileDraft
|
||||
genConfigFile spec = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
tmplFile = C.srcDirInServerTemplatesDir </> SP.castRel configFileInSrcDir
|
||||
dstFile = C.serverSrcDirInServerRootDir </> configFileInSrcDir
|
||||
|
@ -22,22 +22,24 @@ import qualified Wasp.AppSpec.Query as AS.Query
|
||||
import Wasp.Generator.ExternalCodeGenerator.Common (GeneratedExternalCodeDir)
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.JsImport (getJsImportDetailsForExtFnImport)
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
import qualified Wasp.Generator.ServerGenerator.Common as C
|
||||
import Wasp.Util ((<++>))
|
||||
|
||||
genOperations :: AppSpec -> [FileDraft]
|
||||
genOperations spec = genQueries spec ++ genActions spec
|
||||
genOperations :: AppSpec -> Generator [FileDraft]
|
||||
genOperations spec = genQueries spec <++> genActions spec
|
||||
|
||||
genQueries :: AppSpec -> [FileDraft]
|
||||
genQueries spec = map (genQuery spec) (AS.getQueries spec)
|
||||
genQueries :: AppSpec -> Generator [FileDraft]
|
||||
genQueries spec = mapM (genQuery spec) (AS.getQueries spec)
|
||||
|
||||
genActions :: AppSpec -> [FileDraft]
|
||||
genActions spec = map (genAction spec) (AS.getActions spec)
|
||||
genActions :: AppSpec -> Generator [FileDraft]
|
||||
genActions spec = mapM (genAction spec) (AS.getActions spec)
|
||||
|
||||
-- | Here we generate JS file that basically imports JS query function provided by user,
|
||||
-- decorates it (mostly injects stuff into it) and exports. Idea is that the rest of the server,
|
||||
-- and user also, should use this new JS function, and not the old one directly.
|
||||
genQuery :: AppSpec -> (String, AS.Query.Query) -> FileDraft
|
||||
genQuery _ (queryName, query) = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
genQuery :: AppSpec -> (String, AS.Query.Query) -> Generator FileDraft
|
||||
genQuery _ (queryName, query) = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
operation = AS.Operation.QueryOp queryName query
|
||||
tmplFile = C.asTmplFile [relfile|src/queries/_query.js|]
|
||||
@ -45,8 +47,8 @@ genQuery _ (queryName, query) = C.mkTmplFdWithDstAndData tmplFile dstFile (Just
|
||||
tmplData = operationTmplData operation
|
||||
|
||||
-- | Analogous to genQuery.
|
||||
genAction :: AppSpec -> (String, AS.Action.Action) -> FileDraft
|
||||
genAction _ (actionName, action) = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
genAction :: AppSpec -> (String, AS.Action.Action) -> Generator FileDraft
|
||||
genAction _ (actionName, action) = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
operation = AS.Operation.ActionOp actionName action
|
||||
tmplFile = [relfile|src/actions/_action.js|]
|
||||
|
@ -19,32 +19,33 @@ import qualified Wasp.AppSpec.App.Auth as AS.Auth
|
||||
import qualified Wasp.AppSpec.Operation as AS.Operation
|
||||
import qualified Wasp.AppSpec.Query as AS.Query
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.Monad (Generator, GeneratorError (GenericGeneratorError), logAndThrowGeneratorError)
|
||||
import qualified Wasp.Generator.ServerGenerator.Common as C
|
||||
import Wasp.Generator.ServerGenerator.OperationsG (operationFileInSrcDir)
|
||||
import qualified Wasp.Util as U
|
||||
|
||||
genOperationsRoutes :: AppSpec -> [FileDraft]
|
||||
genOperationsRoutes :: AppSpec -> Generator [FileDraft]
|
||||
genOperationsRoutes spec =
|
||||
concat
|
||||
sequence . concat $
|
||||
[ map (genActionRoute spec) (AS.getActions spec),
|
||||
map (genQueryRoute spec) (AS.getQueries spec),
|
||||
[genOperationsRouter spec]
|
||||
]
|
||||
|
||||
genActionRoute :: AppSpec -> (String, AS.Action.Action) -> FileDraft
|
||||
genActionRoute :: AppSpec -> (String, AS.Action.Action) -> Generator FileDraft
|
||||
genActionRoute spec (actionName, action) = genOperationRoute spec op tmplFile
|
||||
where
|
||||
op = AS.Operation.ActionOp actionName action
|
||||
tmplFile = C.asTmplFile [relfile|src/routes/operations/_action.js|]
|
||||
|
||||
genQueryRoute :: AppSpec -> (String, AS.Query.Query) -> FileDraft
|
||||
genQueryRoute :: AppSpec -> (String, AS.Query.Query) -> Generator FileDraft
|
||||
genQueryRoute spec (queryName, query) = genOperationRoute spec op tmplFile
|
||||
where
|
||||
op = AS.Operation.QueryOp queryName query
|
||||
tmplFile = C.asTmplFile [relfile|src/routes/operations/_query.js|]
|
||||
|
||||
genOperationRoute :: AppSpec -> AS.Operation.Operation -> Path' (Rel C.ServerTemplatesDir) File' -> FileDraft
|
||||
genOperationRoute spec operation tmplFile = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
genOperationRoute :: AppSpec -> AS.Operation.Operation -> Path' (Rel C.ServerTemplatesDir) File' -> Generator FileDraft
|
||||
genOperationRoute spec operation tmplFile = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
dstFile = operationsRoutesDirInServerRootDir </> operationRouteFileInOperationsRoutesDir operation
|
||||
|
||||
@ -81,11 +82,11 @@ operationRouteFileInOperationsRoutesDir operation = fromJust $ SP.parseRelFile $
|
||||
relPosixPathFromOperationsRoutesDirToSrcDir :: Path Posix (Rel OperationsRoutesDir) (Dir C.ServerSrcDir)
|
||||
relPosixPathFromOperationsRoutesDirToSrcDir = [reldirP|../..|]
|
||||
|
||||
genOperationsRouter :: AppSpec -> FileDraft
|
||||
genOperationsRouter :: AppSpec -> Generator FileDraft
|
||||
genOperationsRouter spec
|
||||
-- TODO: Right now we are throwing error here, but we should instead perform this check in parsing/analyzer phase, as a semantic check, since we have all the info we need then already.
|
||||
| any isAuthSpecifiedForOperation operations && not isAuthEnabledGlobally = error "`auth` cannot be specified for specific operations if it is not enabled for the whole app!"
|
||||
| otherwise = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
| any isAuthSpecifiedForOperation operations && not isAuthEnabledGlobally = logAndThrowGeneratorError $ GenericGeneratorError "`auth` cannot be specified for specific operations if it is not enabled for the whole app!"
|
||||
| otherwise = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
tmplFile = C.asTmplFile [relfile|src/routes/operations/index.js|]
|
||||
dstFile = operationsRoutesDirInServerRootDir </> [relfile|index.js|]
|
||||
|
@ -21,6 +21,7 @@ import qualified Wasp.AppSpec.App as AS.App
|
||||
import qualified Wasp.AppSpec.App.Dependency as AS.Dependency
|
||||
import Wasp.Generator.ExternalCodeGenerator (generateExternalCodeDir)
|
||||
import Wasp.Generator.FileDraft
|
||||
import Wasp.Generator.Monad (Generator, GeneratorError (..), logAndThrowGeneratorError)
|
||||
import Wasp.Generator.PackageJsonGenerator
|
||||
( npmDepsToPackageJsonEntry,
|
||||
resolveNpmDeps,
|
||||
@ -35,24 +36,31 @@ import qualified Wasp.Generator.WebAppGenerator.Common as C
|
||||
import qualified Wasp.Generator.WebAppGenerator.ExternalCodeGenerator as WebAppExternalCodeGenerator
|
||||
import Wasp.Generator.WebAppGenerator.OperationsGenerator (genOperations)
|
||||
import qualified Wasp.Generator.WebAppGenerator.RouterGenerator as RouterGenerator
|
||||
import Wasp.Util ((<++>))
|
||||
|
||||
generateWebApp :: AppSpec -> [FileDraft]
|
||||
generateWebApp spec =
|
||||
concat
|
||||
[ [generateReadme],
|
||||
[genPackageJson spec waspNpmDeps],
|
||||
[generateGitignore],
|
||||
generatePublicDir spec,
|
||||
generateSrcDir spec,
|
||||
generateExternalCodeDir WebAppExternalCodeGenerator.generatorStrategy (AS.externalCodeFiles spec),
|
||||
[C.mkTmplFd $ asTmplFile [relfile|netlify.toml|]]
|
||||
generateWebApp :: AppSpec -> Generator [FileDraft]
|
||||
generateWebApp spec = do
|
||||
sequence
|
||||
[ generateReadme,
|
||||
genPackageJson spec waspNpmDeps,
|
||||
generateGitignore,
|
||||
return $ C.mkTmplFd $ asTmplFile [relfile|netlify.toml|]
|
||||
]
|
||||
<++> generatePublicDir spec
|
||||
<++> generateSrcDir spec
|
||||
<++> generateExternalCodeDir WebAppExternalCodeGenerator.generatorStrategy (AS.externalCodeFiles spec)
|
||||
|
||||
generateReadme :: FileDraft
|
||||
generateReadme = C.mkTmplFd $ asTmplFile [relfile|README.md|]
|
||||
generateReadme :: Generator FileDraft
|
||||
generateReadme = return $ C.mkTmplFd $ asTmplFile [relfile|README.md|]
|
||||
|
||||
genPackageJson :: AppSpec -> [AS.Dependency.Dependency] -> FileDraft
|
||||
genPackageJson spec waspDeps =
|
||||
genPackageJson :: AppSpec -> [AS.Dependency.Dependency] -> Generator FileDraft
|
||||
genPackageJson spec waspDeps = do
|
||||
(resolvedWaspDeps, resolvedUserDeps) <-
|
||||
case resolveNpmDeps waspDeps userDeps of
|
||||
Right deps -> return deps
|
||||
Left depsAndErrors -> logAndThrowGeneratorError $ GenericGeneratorError $ intercalate " ; " $ map snd depsAndErrors
|
||||
|
||||
return $
|
||||
C.mkTmplFdWithDstAndData
|
||||
(C.asTmplFile [relfile|package.json|])
|
||||
(C.asWebAppFile [relfile|package.json|])
|
||||
@ -63,11 +71,6 @@ genPackageJson spec waspDeps =
|
||||
]
|
||||
)
|
||||
where
|
||||
(resolvedWaspDeps, resolvedUserDeps) =
|
||||
case resolveNpmDeps waspDeps userDeps of
|
||||
Right deps -> deps
|
||||
Left depsAndErrors -> error $ intercalate " ; " $ map snd depsAndErrors
|
||||
|
||||
userDeps :: [AS.Dependency.Dependency]
|
||||
userDeps = fromMaybe [] $ AS.App.dependencies $ snd $ getApp spec
|
||||
|
||||
@ -86,16 +89,19 @@ waspNpmDeps =
|
||||
|
||||
-- TODO: Also extract devDependencies like we did dependencies (waspNpmDeps).
|
||||
|
||||
generateGitignore :: FileDraft
|
||||
generateGitignore :: Generator FileDraft
|
||||
generateGitignore =
|
||||
return $
|
||||
C.mkTmplFdWithDst
|
||||
(asTmplFile [relfile|gitignore|])
|
||||
(asWebAppFile [relfile|.gitignore|])
|
||||
|
||||
generatePublicDir :: AppSpec -> [FileDraft]
|
||||
generatePublicDir spec =
|
||||
generatePublicDir :: AppSpec -> Generator [FileDraft]
|
||||
generatePublicDir spec = do
|
||||
publicIndexHtmlFd <- generatePublicIndexHtml spec
|
||||
return $
|
||||
C.mkTmplFd (asTmplFile [relfile|public/favicon.ico|]) :
|
||||
generatePublicIndexHtml spec :
|
||||
publicIndexHtmlFd :
|
||||
( let tmplData = object ["appName" .= (fst (getApp spec) :: String)]
|
||||
processPublicTmpl path = C.mkTmplFdWithData (asTmplFile $ [reldir|public|] </> path) tmplData
|
||||
in processPublicTmpl
|
||||
@ -103,8 +109,9 @@ generatePublicDir spec =
|
||||
]
|
||||
)
|
||||
|
||||
generatePublicIndexHtml :: AppSpec -> FileDraft
|
||||
generatePublicIndexHtml :: AppSpec -> Generator FileDraft
|
||||
generatePublicIndexHtml spec =
|
||||
return $
|
||||
C.mkTmplFdWithDstAndData
|
||||
(asTmplFile [relfile|public/index.html|])
|
||||
targetPath
|
||||
@ -131,10 +138,15 @@ srcDir = C.webAppSrcDirInWebAppRootDir
|
||||
genApi :: FileDraft
|
||||
genApi = C.mkTmplFd (C.asTmplFile [relfile|src/api.js|])
|
||||
|
||||
generateSrcDir :: AppSpec -> [FileDraft]
|
||||
generateSrcDir spec =
|
||||
generateSrcDir :: AppSpec -> Generator [FileDraft]
|
||||
generateSrcDir spec = do
|
||||
routerFd <- RouterGenerator.generateRouter spec
|
||||
operationsFds <- genOperations spec
|
||||
authFds <- AuthG.genAuth spec
|
||||
|
||||
return $
|
||||
generateLogo :
|
||||
RouterGenerator.generateRouter spec :
|
||||
routerFd :
|
||||
genApi :
|
||||
map
|
||||
processSrcTmpl
|
||||
@ -145,8 +157,8 @@ generateSrcDir spec =
|
||||
[relfile|queryCache.js|],
|
||||
[relfile|utils.js|]
|
||||
]
|
||||
++ genOperations spec
|
||||
++ AuthG.genAuth spec
|
||||
++ operationsFds
|
||||
++ authFds
|
||||
where
|
||||
generateLogo =
|
||||
C.mkTmplFdWithDstAndData
|
||||
|
@ -12,36 +12,40 @@ import qualified Wasp.AppSpec as AS
|
||||
import qualified Wasp.AppSpec.App as AS.App
|
||||
import qualified Wasp.AppSpec.App.Auth as AS.Auth
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
import Wasp.Generator.WebAppGenerator.Common as C
|
||||
import Wasp.Util ((<++>))
|
||||
|
||||
genAuth :: AppSpec -> [FileDraft]
|
||||
genAuth spec = case maybeAuth of
|
||||
genAuth :: AppSpec -> Generator [FileDraft]
|
||||
genAuth spec =
|
||||
case maybeAuth of
|
||||
Just auth ->
|
||||
sequence
|
||||
[ genSignup,
|
||||
genLogin,
|
||||
genLogout,
|
||||
genUseAuth,
|
||||
genCreateAuthRequiredPage auth
|
||||
]
|
||||
++ genAuthForms auth
|
||||
Nothing -> []
|
||||
<++> genAuthForms auth
|
||||
Nothing -> return []
|
||||
where
|
||||
maybeAuth = AS.App.auth $ snd $ AS.getApp spec
|
||||
|
||||
-- | Generates file with signup function to be used by Wasp developer.
|
||||
genSignup :: FileDraft
|
||||
genSignup = C.mkTmplFd (C.asTmplFile [relfile|src/auth/signup.js|])
|
||||
genSignup :: Generator FileDraft
|
||||
genSignup = return $ C.mkTmplFd (C.asTmplFile [relfile|src/auth/signup.js|])
|
||||
|
||||
-- | Generates file with login function to be used by Wasp developer.
|
||||
genLogin :: FileDraft
|
||||
genLogin = C.mkTmplFd (C.asTmplFile [relfile|src/auth/login.js|])
|
||||
genLogin :: Generator FileDraft
|
||||
genLogin = return $ C.mkTmplFd (C.asTmplFile [relfile|src/auth/login.js|])
|
||||
|
||||
-- | Generates file with logout function to be used by Wasp developer.
|
||||
genLogout :: FileDraft
|
||||
genLogout = C.mkTmplFd (C.asTmplFile [relfile|src/auth/logout.js|])
|
||||
genLogout :: Generator FileDraft
|
||||
genLogout = return $ C.mkTmplFd (C.asTmplFile [relfile|src/auth/logout.js|])
|
||||
|
||||
-- | Generates HOC that handles auth for the given page.
|
||||
genCreateAuthRequiredPage :: AS.Auth.Auth -> FileDraft
|
||||
genCreateAuthRequiredPage :: AS.Auth.Auth -> Generator FileDraft
|
||||
genCreateAuthRequiredPage auth =
|
||||
compileTmplToSamePath
|
||||
[relfile|auth/pages/createAuthRequiredPage.js|]
|
||||
@ -50,16 +54,17 @@ genCreateAuthRequiredPage auth =
|
||||
-- | Generates React hook that Wasp developer can use in a component to get
|
||||
-- access to the currently logged in user (and check whether user is logged in
|
||||
-- ot not).
|
||||
genUseAuth :: FileDraft
|
||||
genUseAuth = C.mkTmplFd (C.asTmplFile [relfile|src/auth/useAuth.js|])
|
||||
genUseAuth :: Generator FileDraft
|
||||
genUseAuth = return $ C.mkTmplFd (C.asTmplFile [relfile|src/auth/useAuth.js|])
|
||||
|
||||
genAuthForms :: AS.Auth.Auth -> [FileDraft]
|
||||
genAuthForms :: AS.Auth.Auth -> Generator [FileDraft]
|
||||
genAuthForms auth =
|
||||
sequence
|
||||
[ genLoginForm auth,
|
||||
genSignupForm auth
|
||||
]
|
||||
|
||||
genLoginForm :: AS.Auth.Auth -> FileDraft
|
||||
genLoginForm :: AS.Auth.Auth -> Generator FileDraft
|
||||
genLoginForm auth =
|
||||
-- TODO: Logic that says "/" is a default redirect on success is duplicated here and in the function below.
|
||||
-- We should remove that duplication.
|
||||
@ -67,14 +72,15 @@ genLoginForm auth =
|
||||
[relfile|auth/forms/Login.js|]
|
||||
["onAuthSucceededRedirectTo" .= fromMaybe "/" (AS.Auth.onAuthSucceededRedirectTo auth)]
|
||||
|
||||
genSignupForm :: AS.Auth.Auth -> FileDraft
|
||||
genSignupForm :: AS.Auth.Auth -> Generator FileDraft
|
||||
genSignupForm auth =
|
||||
compileTmplToSamePath
|
||||
[relfile|auth/forms/Signup.js|]
|
||||
["onAuthSucceededRedirectTo" .= fromMaybe "/" (AS.Auth.onAuthSucceededRedirectTo auth)]
|
||||
|
||||
compileTmplToSamePath :: Path' Rel' File' -> [Pair] -> FileDraft
|
||||
compileTmplToSamePath :: Path' Rel' File' -> [Pair] -> Generator FileDraft
|
||||
compileTmplToSamePath tmplFileInTmplSrcDir keyValuePairs =
|
||||
return $
|
||||
C.mkTmplFdWithDstAndData
|
||||
(asTmplFile $ [reldir|src|] </> tmplFileInTmplSrcDir)
|
||||
targetPath
|
||||
|
@ -18,31 +18,31 @@ import qualified Wasp.AppSpec.Action as AS.Action
|
||||
import qualified Wasp.AppSpec.Operation as AS.Operation
|
||||
import qualified Wasp.AppSpec.Query as AS.Query
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
import qualified Wasp.Generator.ServerGenerator as ServerGenerator
|
||||
import qualified Wasp.Generator.ServerGenerator.OperationsRoutesG as ServerOperationsRoutesG
|
||||
import qualified Wasp.Generator.WebAppGenerator.Common as C
|
||||
import qualified Wasp.Generator.WebAppGenerator.OperationsGenerator.ResourcesG as Resources
|
||||
import Wasp.Util ((<++>))
|
||||
|
||||
genOperations :: AppSpec -> [FileDraft]
|
||||
genOperations :: AppSpec -> Generator [FileDraft]
|
||||
genOperations spec =
|
||||
concat
|
||||
[ genQueries spec,
|
||||
genActions spec,
|
||||
[C.mkTmplFd $ C.asTmplFile [relfile|src/operations/index.js|]],
|
||||
Resources.genResources spec
|
||||
]
|
||||
genQueries spec
|
||||
<++> genActions spec
|
||||
<++> return [C.mkTmplFd $ C.asTmplFile [relfile|src/operations/index.js|]]
|
||||
<++> Resources.genResources spec
|
||||
|
||||
genQueries :: AppSpec -> [FileDraft]
|
||||
genQueries spec =
|
||||
map (genQuery spec) (AS.getQueries spec)
|
||||
++ [C.mkTmplFd $ C.asTmplFile [relfile|src/queries/index.js|]]
|
||||
genQueries :: AppSpec -> Generator [FileDraft]
|
||||
genQueries spec = do
|
||||
queriesFds <- mapM (genQuery spec) (AS.getQueries spec)
|
||||
return $ queriesFds ++ [C.mkTmplFd $ C.asTmplFile [relfile|src/queries/index.js|]]
|
||||
|
||||
genActions :: AppSpec -> [FileDraft]
|
||||
genActions :: AppSpec -> Generator [FileDraft]
|
||||
genActions spec =
|
||||
map (genAction spec) (AS.getActions spec)
|
||||
mapM (genAction spec) (AS.getActions spec)
|
||||
|
||||
genQuery :: AppSpec -> (String, AS.Query.Query) -> FileDraft
|
||||
genQuery _ (queryName, query) = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
genQuery :: AppSpec -> (String, AS.Query.Query) -> Generator FileDraft
|
||||
genQuery _ (queryName, query) = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
tmplFile = C.asTmplFile [relfile|src/queries/_query.js|]
|
||||
|
||||
@ -59,8 +59,8 @@ genQuery _ (queryName, query) = C.mkTmplFdWithDstAndData tmplFile dstFile (Just
|
||||
]
|
||||
operation = AS.Operation.QueryOp queryName query
|
||||
|
||||
genAction :: AppSpec -> (String, AS.Action.Action) -> FileDraft
|
||||
genAction _ (actionName, action) = C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
genAction :: AppSpec -> (String, AS.Action.Action) -> Generator FileDraft
|
||||
genAction _ (actionName, action) = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
tmplFile = C.asTmplFile [relfile|src/actions/_action.js|]
|
||||
|
||||
|
@ -7,10 +7,11 @@ import Data.Aeson (object)
|
||||
import StrongPath (relfile)
|
||||
import Wasp.AppSpec (AppSpec)
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
import qualified Wasp.Generator.WebAppGenerator.Common as C
|
||||
|
||||
genResources :: AppSpec -> [FileDraft]
|
||||
genResources _ = [C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)]
|
||||
genResources :: AppSpec -> Generator [FileDraft]
|
||||
genResources _ = return [C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)]
|
||||
where
|
||||
tmplFile = C.asTmplFile [relfile|src/operations/resources.js|]
|
||||
dstFile = C.asWebAppFile [relfile|src/operations/resources.js|] -- TODO: Un-hardcode this by combining path to operations dir with path to resources file in it.
|
||||
|
@ -17,6 +17,7 @@ import qualified Wasp.AppSpec.ExtImport as AS.ExtImport
|
||||
import qualified Wasp.AppSpec.Page as AS.Page
|
||||
import qualified Wasp.AppSpec.Route as AS.Route
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
import Wasp.Generator.WebAppGenerator.Common (asTmplFile, asWebAppSrcFile)
|
||||
import qualified Wasp.Generator.WebAppGenerator.Common as C
|
||||
|
||||
@ -59,8 +60,9 @@ instance ToJSON PageTemplateData where
|
||||
"importFrom" .= _importFrom pageTD
|
||||
]
|
||||
|
||||
generateRouter :: AppSpec -> FileDraft
|
||||
generateRouter spec =
|
||||
generateRouter :: AppSpec -> Generator FileDraft
|
||||
generateRouter spec = do
|
||||
return $
|
||||
C.mkTmplFdWithDstAndData
|
||||
(asTmplFile $ [reldir|src|] </> routerPath)
|
||||
targetPath
|
||||
@ -88,6 +90,7 @@ createRouteTemplateData spec namedRoute@(_, route) =
|
||||
_targetComponent = determineRouteTargetComponent spec namedRoute
|
||||
}
|
||||
|
||||
-- NOTE: This should be prevented by Analyzer, so use error since it should not be possible
|
||||
determineRouteTargetComponent :: AppSpec -> (String, AS.Route.Route) -> String
|
||||
determineRouteTargetComponent spec (_, route) =
|
||||
maybe
|
||||
|
@ -25,24 +25,28 @@ import qualified Wasp.Util.IO as Util.IO
|
||||
|
||||
type CompileError = String
|
||||
|
||||
type CompileWarning = String
|
||||
|
||||
compile ::
|
||||
Path' Abs (Dir WaspProjectDir) ->
|
||||
Path' Abs (Dir ProjectRootDir) ->
|
||||
CompileOptions ->
|
||||
IO (Either CompileError ())
|
||||
IO ([CompileWarning], [CompileError])
|
||||
compile waspDir outDir options = do
|
||||
maybeWaspFilePath <- findWaspFile waspDir
|
||||
case maybeWaspFilePath of
|
||||
Nothing -> return $ Left "Couldn't find a single *.wasp file."
|
||||
Nothing -> return ([], ["Couldn't find a single *.wasp file."])
|
||||
Just waspFilePath -> do
|
||||
waspFileContent <- readFile (SP.fromAbsFile waspFilePath)
|
||||
case Analyzer.analyze waspFileContent of
|
||||
Left analyzeError ->
|
||||
return $
|
||||
Left $
|
||||
showCompilerErrorForTerminal
|
||||
return
|
||||
( [],
|
||||
[ showCompilerErrorForTerminal
|
||||
(waspFilePath, waspFileContent)
|
||||
(getErrorMessageAndCtx analyzeError)
|
||||
]
|
||||
)
|
||||
Right decls -> do
|
||||
externalCodeFiles <-
|
||||
ExternalCode.readFiles (CompileOptions.externalCodeDirPath options)
|
||||
@ -57,7 +61,8 @@ compile waspDir outDir options = do
|
||||
AS.dotEnvFile = maybeDotEnvFile,
|
||||
AS.isBuild = CompileOptions.isBuild options
|
||||
}
|
||||
Right <$> Generator.writeWebAppCode appSpec outDir
|
||||
(generatorWarnings, generatorErrors) <- Generator.writeWebAppCode appSpec outDir
|
||||
return (map show generatorWarnings, map show generatorErrors)
|
||||
|
||||
findWaspFile :: Path' Abs (Dir WaspProjectDir) -> IO (Maybe (Path' Abs File'))
|
||||
findWaspFile waspDir = do
|
||||
|
@ -10,9 +10,12 @@ module Wasp.Util
|
||||
concatPrefixAndText,
|
||||
insertAt,
|
||||
leftPad,
|
||||
(<++>),
|
||||
(<:>),
|
||||
)
|
||||
where
|
||||
|
||||
import Control.Monad (liftM2)
|
||||
import qualified Data.Aeson as Aeson
|
||||
import Data.Char (isUpper, toLower, toUpper)
|
||||
import qualified Data.HashMap.Strict as M
|
||||
@ -118,3 +121,13 @@ insertAt :: [a] -> Int -> [a] -> [a]
|
||||
insertAt theInsert idx host =
|
||||
let (before, after) = splitAt idx host
|
||||
in before ++ theInsert ++ after
|
||||
|
||||
infixr 5 <++>
|
||||
|
||||
(<++>) :: Monad m => m [a] -> m [a] -> m [a]
|
||||
(<++>) = liftM2 (++)
|
||||
|
||||
infixr 5 <:>
|
||||
|
||||
(<:>) :: Monad m => m a -> m [a] -> m [a]
|
||||
(<:>) = liftM2 (:)
|
||||
|
@ -12,6 +12,7 @@ import qualified Wasp.Generator.FileDraft.CopyDirFileDraft as CopyDirFD
|
||||
import qualified Wasp.Generator.FileDraft.CopyFileDraft as CopyFD
|
||||
import qualified Wasp.Generator.FileDraft.TemplateFileDraft as TmplFD
|
||||
import qualified Wasp.Generator.FileDraft.TextFileDraft as TextFD
|
||||
import Wasp.Generator.Monad (runGenerator)
|
||||
import Wasp.Generator.WebAppGenerator
|
||||
import qualified Wasp.Generator.WebAppGenerator.Common as Common
|
||||
|
||||
@ -46,7 +47,7 @@ spec_WebAppGenerator = do
|
||||
-- that they will successfully be written, it checks only that their
|
||||
-- destinations are correct.
|
||||
it "Given a simple AppSpec, creates file drafts at expected destinations" $ do
|
||||
let fileDrafts = generateWebApp testAppSpec
|
||||
let (_, Right fileDrafts) = runGenerator $ generateWebApp testAppSpec
|
||||
let expectedFileDraftDstPaths =
|
||||
map (SP.toFilePath Common.webAppRootDirInProjectRootDir </>) $
|
||||
concat
|
||||
|
Loading…
Reference in New Issue
Block a user