mirror of
https://github.com/wasp-lang/wasp.git
synced 2024-11-23 19:29:17 +03:00
App spec validation (#459)
This commit is contained in:
parent
244e66cec3
commit
2a16bfd3cf
@ -11,3 +11,5 @@
|
||||
- ignore: {name: Use newtype instead of data} # We can decide this on our own.
|
||||
- ignore: {name: Use $>} # I find it makes code harder to read if enforced.
|
||||
- ignore: {name: Use list comprehension} # We can decide this on our own.
|
||||
- ignore: {name: Use list comprehension} # We can decide this on our own.
|
||||
- ignore: {name: Use ++} # I sometimes prefer concat over ++ due to the nicer formatting / extensibility.
|
||||
|
@ -2,6 +2,7 @@ module Main where
|
||||
|
||||
import Control.Concurrent (threadDelay)
|
||||
import qualified Control.Concurrent.Async as Async
|
||||
import qualified Control.Exception as E
|
||||
import Control.Monad (void)
|
||||
import Data.Char (isSpace)
|
||||
import Data.Version (showVersion)
|
||||
@ -21,10 +22,11 @@ import Wasp.Cli.Command.Info (info)
|
||||
import Wasp.Cli.Command.Start (start)
|
||||
import qualified Wasp.Cli.Command.Telemetry as Telemetry
|
||||
import Wasp.Cli.Terminal (title)
|
||||
import Wasp.Util (indent)
|
||||
import qualified Wasp.Util.Terminal as Term
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
main = (`E.catch` handleInternalErrors) $ do
|
||||
args <- getArgs
|
||||
let commandCall = case args of
|
||||
["new", projectName] -> Command.Call.New projectName
|
||||
@ -68,6 +70,9 @@ main = do
|
||||
let microsecondsInASecond = 1000000
|
||||
in threadDelay . (* microsecondsInASecond)
|
||||
|
||||
handleInternalErrors :: E.ErrorCall -> IO ()
|
||||
handleInternalErrors e = putStrLn $ "\nInternal Wasp error (bug in compiler):\n" ++ indent 2 (show e)
|
||||
|
||||
printUsage :: IO ()
|
||||
printUsage =
|
||||
putStrLn $
|
||||
|
@ -7,21 +7,19 @@ module Wasp.AppSpec
|
||||
takeDecls,
|
||||
Ref,
|
||||
refName,
|
||||
getApp,
|
||||
getActions,
|
||||
getQueries,
|
||||
getEntities,
|
||||
getPages,
|
||||
getRoutes,
|
||||
isAuthEnabled,
|
||||
resolveRef,
|
||||
)
|
||||
where
|
||||
|
||||
import Data.Maybe (isJust)
|
||||
import Data.List (find)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import StrongPath (Abs, Dir, File', Path')
|
||||
import Wasp.AppSpec.Action (Action)
|
||||
import Wasp.AppSpec.App (App)
|
||||
import qualified Wasp.AppSpec.App as App
|
||||
import Wasp.AppSpec.Core.Decl (Decl, IsDecl, takeDecls)
|
||||
import Wasp.AppSpec.Core.Ref (Ref, refName)
|
||||
import Wasp.AppSpec.Entity (Entity)
|
||||
@ -60,36 +58,26 @@ data AppSpec = AppSpec
|
||||
getDecls :: IsDecl a => AppSpec -> [(String, a)]
|
||||
getDecls = takeDecls . decls
|
||||
|
||||
-- TODO: This will fail with an error if there is no `app` declaration (because of `head`)!
|
||||
-- However, returning a Maybe here would be PITA later in the code.
|
||||
-- It would be cool instead if we had an extra step that somehow ensures that app exists and
|
||||
-- throws nice error if it doesn't. Some step that validated AppSpec. Maybe we could
|
||||
-- have a function that returns `Validated AppSpec` -> so basically smart constructor,
|
||||
-- validates AppSpec and returns it wrapped with `Validated`,
|
||||
-- I created a github issue for it: https://github.com/wasp-lang/wasp/issues/425 .
|
||||
getApp :: AppSpec -> (String, App)
|
||||
getApp spec = case takeDecls @App (decls spec) of
|
||||
[app] -> app
|
||||
apps ->
|
||||
error $
|
||||
"Compiler error: expected exactly 1 'app' declaration in your wasp code, but you have "
|
||||
++ show (length apps)
|
||||
++ "!"
|
||||
|
||||
getQueries :: AppSpec -> [(String, Query)]
|
||||
getQueries spec = takeDecls @Query (decls spec)
|
||||
getQueries = getDecls @Query
|
||||
|
||||
getActions :: AppSpec -> [(String, Action)]
|
||||
getActions spec = takeDecls @Action (decls spec)
|
||||
getActions = getDecls @Action
|
||||
|
||||
getEntities :: AppSpec -> [(String, Entity)]
|
||||
getEntities spec = takeDecls @Entity (decls spec)
|
||||
getEntities = getDecls @Entity
|
||||
|
||||
getPages :: AppSpec -> [(String, Page)]
|
||||
getPages spec = takeDecls @Page (decls spec)
|
||||
getPages = getDecls @Page
|
||||
|
||||
getRoutes :: AppSpec -> [(String, Route)]
|
||||
getRoutes spec = takeDecls @Route (decls spec)
|
||||
getRoutes = getDecls @Route
|
||||
|
||||
isAuthEnabled :: AppSpec -> Bool
|
||||
isAuthEnabled spec = isJust (App.auth $ snd $ getApp spec)
|
||||
resolveRef :: (IsDecl d) => AppSpec -> Ref d -> (String, d)
|
||||
resolveRef spec ref =
|
||||
fromMaybe
|
||||
( error $
|
||||
"Failed to resolve declaration reference: " ++ refName ref ++ "."
|
||||
++ " This should never happen, as Analyzer should ensure all references in AppSpec are valid."
|
||||
)
|
||||
$ find ((== refName ref) . fst) $ getDecls spec
|
||||
|
99
waspc/src/Wasp/AppSpec/Valid.hs
Normal file
99
waspc/src/Wasp/AppSpec/Valid.hs
Normal file
@ -0,0 +1,99 @@
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
|
||||
module Wasp.AppSpec.Valid
|
||||
( validateAppSpec,
|
||||
ValidationError (..),
|
||||
getApp,
|
||||
isAuthEnabled,
|
||||
)
|
||||
where
|
||||
|
||||
import Data.List (find)
|
||||
import Data.Maybe (isJust)
|
||||
import Wasp.AppSpec (AppSpec)
|
||||
import qualified Wasp.AppSpec as AS
|
||||
import Wasp.AppSpec.App (App)
|
||||
import qualified Wasp.AppSpec.App as App
|
||||
import qualified Wasp.AppSpec.App.Auth as Auth
|
||||
import Wasp.AppSpec.Core.Decl (takeDecls)
|
||||
import qualified Wasp.AppSpec.Entity as Entity
|
||||
import qualified Wasp.AppSpec.Entity.Field as Entity.Field
|
||||
import qualified Wasp.AppSpec.Page as Page
|
||||
|
||||
data ValidationError = GenericValidationError String
|
||||
deriving (Show, Eq)
|
||||
|
||||
validateAppSpec :: AppSpec -> [ValidationError]
|
||||
validateAppSpec spec =
|
||||
case validateExactlyOneAppExists spec of
|
||||
Just err -> [err]
|
||||
Nothing ->
|
||||
-- NOTE: We check these only if App exists because they all rely on it existing.
|
||||
concat
|
||||
[ validateAppAuthIsSetIfAnyPageRequiresAuth spec,
|
||||
validateAuthUserEntityHasCorrectFieldsIfEmailAndPasswordAuthIsUsed spec
|
||||
]
|
||||
|
||||
validateExactlyOneAppExists :: AppSpec -> Maybe ValidationError
|
||||
validateExactlyOneAppExists spec =
|
||||
case AS.takeDecls @App (AS.decls spec) of
|
||||
[] -> Just $ GenericValidationError "You are missing an 'app' declaration in your Wasp app."
|
||||
[_] -> Nothing
|
||||
apps ->
|
||||
Just $
|
||||
GenericValidationError $
|
||||
"You have more than one 'app' declaration in your Wasp app. You have " ++ show (length apps) ++ "."
|
||||
|
||||
validateAppAuthIsSetIfAnyPageRequiresAuth :: AppSpec -> [ValidationError]
|
||||
validateAppAuthIsSetIfAnyPageRequiresAuth spec =
|
||||
if anyPageRequiresAuth && not (isAuthEnabled spec)
|
||||
then
|
||||
[ GenericValidationError
|
||||
"Expected app.auth to be defined since there are Pages with authRequired set to true."
|
||||
]
|
||||
else []
|
||||
where
|
||||
anyPageRequiresAuth = any ((== Just True) . Page.authRequired) (snd <$> AS.getPages spec)
|
||||
|
||||
validateAuthUserEntityHasCorrectFieldsIfEmailAndPasswordAuthIsUsed :: AppSpec -> [ValidationError]
|
||||
validateAuthUserEntityHasCorrectFieldsIfEmailAndPasswordAuthIsUsed spec = case App.auth (snd $ getApp spec) of
|
||||
Nothing -> []
|
||||
Just auth ->
|
||||
if Auth.EmailAndPassword `notElem` Auth.methods auth
|
||||
then []
|
||||
else
|
||||
let userEntity = snd $ AS.resolveRef spec (Auth.userEntity auth)
|
||||
userEntityFields = Entity.getFields userEntity
|
||||
maybeEmailField = find ((== "email") . Entity.Field.fieldName) userEntityFields
|
||||
maybePasswordField = find ((== "password") . Entity.Field.fieldName) userEntityFields
|
||||
in concat
|
||||
[ case maybeEmailField of
|
||||
Just emailField
|
||||
| Entity.Field.fieldType emailField == Entity.Field.FieldTypeScalar Entity.Field.String -> []
|
||||
_ ->
|
||||
[ GenericValidationError
|
||||
"Expected an Entity referenced by app.auth.userEntity to have field 'email' of type 'string'."
|
||||
],
|
||||
case maybePasswordField of
|
||||
Just passwordField
|
||||
| Entity.Field.fieldType passwordField == Entity.Field.FieldTypeScalar Entity.Field.String -> []
|
||||
_ ->
|
||||
[ GenericValidationError
|
||||
"Expected an Entity referenced by app.auth.userEntity to have field 'password' of type 'string'."
|
||||
]
|
||||
]
|
||||
|
||||
-- | This function assumes that @AppSpec@ it operates on was validated beforehand (with @validateAppSpec@ function).
|
||||
-- TODO: It would be great if we could ensure this at type level, but we decided that was too much work for now.
|
||||
-- Check https://github.com/wasp-lang/wasp/pull/455 for considerations on this and analysis of different approaches.
|
||||
getApp :: AppSpec -> (String, App)
|
||||
getApp spec = case takeDecls @App (AS.decls spec) of
|
||||
[app] -> app
|
||||
apps ->
|
||||
error $
|
||||
("Expected exactly 1 'app' declaration in your wasp code, but you have " ++ show (length apps) ++ ".")
|
||||
++ " This should never happen as it should have been caught during validation of AppSpec."
|
||||
|
||||
-- | This function assumes that @AppSpec@ it operates on was validated beforehand (with @validateAppSpec@ function).
|
||||
isAuthEnabled :: AppSpec -> Bool
|
||||
isAuthEnabled spec = isJust (App.auth $ snd $ getApp spec)
|
@ -18,6 +18,7 @@ import qualified Wasp.AppSpec as AS
|
||||
import qualified Wasp.AppSpec.App as AS.App
|
||||
import qualified Wasp.AppSpec.App.Db as AS.Db
|
||||
import qualified Wasp.AppSpec.Entity as AS.Entity
|
||||
import Wasp.AppSpec.Valid (getApp)
|
||||
import Wasp.Generator.Common (ProjectRootDir)
|
||||
import Wasp.Generator.DbGenerator.Common
|
||||
( dbMigrationsDirInDbRootDir,
|
||||
@ -59,7 +60,7 @@ genPrismaSchema spec = do
|
||||
where
|
||||
dstPath = dbSchemaFileInProjectRootDir
|
||||
tmplSrcPath = dbTemplatesDirInTemplatesDir </> dbSchemaFileInDbTemplatesDir
|
||||
dbSystem = fromMaybe AS.Db.SQLite (AS.Db.system =<< AS.App.db (snd $ AS.getApp spec))
|
||||
dbSystem = fromMaybe AS.Db.SQLite (AS.Db.system =<< AS.App.db (snd $ getApp spec))
|
||||
|
||||
entityToPslModelSchema :: (String, AS.Entity.Entity) -> String
|
||||
entityToPslModelSchema (entityName, entity) =
|
||||
|
@ -23,9 +23,9 @@ import Data.Maybe (fromMaybe)
|
||||
import qualified Data.Maybe as Maybe
|
||||
import GHC.Generics
|
||||
import Wasp.AppSpec (AppSpec)
|
||||
import qualified Wasp.AppSpec as AS
|
||||
import qualified Wasp.AppSpec.App as AS.App
|
||||
import qualified Wasp.AppSpec.App.Dependency as D
|
||||
import qualified Wasp.AppSpec.Valid as ASV
|
||||
import Wasp.Generator.Monad (Generator, GeneratorError (..), logAndThrowGeneratorError)
|
||||
|
||||
data NpmDepsForFullStack = NpmDepsForFullStack
|
||||
@ -108,7 +108,7 @@ buildNpmDepsForFullStack spec forServer forWebApp =
|
||||
getUserNpmDepsForPackage :: AppSpec -> NpmDepsForUser
|
||||
getUserNpmDepsForPackage spec =
|
||||
NpmDepsForUser
|
||||
{ userDependencies = fromMaybe [] $ AS.App.dependencies $ snd $ AS.getApp spec,
|
||||
{ userDependencies = fromMaybe [] $ AS.App.dependencies $ snd $ ASV.getApp spec,
|
||||
-- Should we allow user devDependencies? https://github.com/wasp-lang/wasp/issues/456
|
||||
userDevDependencies = []
|
||||
}
|
||||
|
@ -21,6 +21,7 @@ import qualified Wasp.AppSpec.App.Auth as AS.App.Auth
|
||||
import qualified Wasp.AppSpec.App.Dependency as AS.Dependency
|
||||
import qualified Wasp.AppSpec.App.Server as AS.App.Server
|
||||
import qualified Wasp.AppSpec.Entity as AS.Entity
|
||||
import Wasp.AppSpec.Valid (getApp, isAuthEnabled)
|
||||
import Wasp.Generator.Common (nodeVersionAsText, prismaVersion)
|
||||
import Wasp.Generator.ExternalCodeGenerator (generateExternalCodeDir)
|
||||
import Wasp.Generator.ExternalCodeGenerator.Common (GeneratedExternalCodeDir)
|
||||
@ -158,7 +159,7 @@ genSrcDir spec =
|
||||
genDbClient :: AppSpec -> Generator FileDraft
|
||||
genDbClient spec = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
maybeAuth = AS.App.auth $ snd $ AS.getApp spec
|
||||
maybeAuth = AS.App.auth $ snd $ getApp spec
|
||||
|
||||
dbClientRelToSrcP = [relfile|dbClient.js|]
|
||||
tmplFile = C.asTmplFile $ [reldir|src|] </> dbClientRelToSrcP
|
||||
@ -187,7 +188,7 @@ genServerJs spec =
|
||||
]
|
||||
)
|
||||
where
|
||||
maybeSetupJsFunction = AS.App.Server.setupFn =<< AS.App.server (snd $ AS.getApp spec)
|
||||
maybeSetupJsFunction = AS.App.Server.setupFn =<< AS.App.server (snd $ getApp spec)
|
||||
maybeSetupJsFnImportDetails = getJsImportDetailsForExtFnImport relPosixPathFromSrcDirToExtSrcDir <$> maybeSetupJsFunction
|
||||
(maybeSetupJsFnImportIdentifier, maybeSetupJsFnImportStmt) =
|
||||
(fst <$> maybeSetupJsFnImportDetails, snd <$> maybeSetupJsFnImportDetails)
|
||||
@ -207,7 +208,7 @@ genRoutesDir spec =
|
||||
( Just $
|
||||
object
|
||||
[ "operationsRouteInRootRouter" .= (operationsRouteInRootRouter :: String),
|
||||
"isAuthEnabled" .= (AS.isAuthEnabled spec :: Bool)
|
||||
"isAuthEnabled" .= (isAuthEnabled spec :: Bool)
|
||||
]
|
||||
)
|
||||
]
|
||||
|
@ -9,6 +9,7 @@ import Wasp.AppSpec (AppSpec)
|
||||
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.AppSpec.Valid (getApp)
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
import qualified Wasp.Generator.ServerGenerator.Common as C
|
||||
@ -28,7 +29,7 @@ genAuth spec = case maybeAuth of
|
||||
]
|
||||
Nothing -> return []
|
||||
where
|
||||
maybeAuth = AS.App.auth $ snd $ AS.getApp spec
|
||||
maybeAuth = AS.App.auth $ snd $ getApp spec
|
||||
|
||||
-- | Generates core/auth file which contains auth middleware and createUser() function.
|
||||
genCoreAuth :: AS.Auth.Auth -> Generator FileDraft
|
||||
@ -48,6 +49,12 @@ genCoreAuth auth = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmpl
|
||||
genAuthMiddleware :: AS.Auth.Auth -> Generator FileDraft
|
||||
genAuthMiddleware auth = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
-- TODO(martin): In prismaMiddleware.js, we assume that 'email' and 'password' are defined in user entity.
|
||||
-- This was promised to us by AppSpec, which has validation checks for this.
|
||||
-- Names of these fields are currently hardcoded, and we are not in any way relyin on AppSpec directly here.
|
||||
-- In the future we might want to figure out a way to better encode these assumptions, either by
|
||||
-- reusing the names for 'email' and 'password' fields by importing them from AppSpec, or smth similar
|
||||
-- in that direction.
|
||||
authMiddlewareRelToSrc = [relfile|core/auth/prismaMiddleware.js|]
|
||||
tmplFile = C.asTmplFile $ [reldir|src|] </> authMiddlewareRelToSrc
|
||||
dstFile = C.serverSrcDirInServerRootDir </> C.asServerSrcFile authMiddlewareRelToSrc
|
||||
|
@ -8,7 +8,7 @@ import Data.Aeson (object, (.=))
|
||||
import StrongPath (File', Path', Rel, relfile, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import Wasp.AppSpec (AppSpec)
|
||||
import qualified Wasp.AppSpec as AS
|
||||
import Wasp.AppSpec.Valid (isAuthEnabled)
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
import qualified Wasp.Generator.ServerGenerator.Common as C
|
||||
@ -20,7 +20,7 @@ genConfigFile spec = return $ C.mkTmplFdWithDstAndData tmplFile dstFile (Just tm
|
||||
dstFile = C.serverSrcDirInServerRootDir </> configFileInSrcDir
|
||||
tmplData =
|
||||
object
|
||||
[ "isAuthEnabled" .= (AS.isAuthEnabled spec :: Bool)
|
||||
[ "isAuthEnabled" .= (isAuthEnabled spec :: Bool)
|
||||
]
|
||||
|
||||
configFileInSrcDir :: Path' (Rel C.ServerSrcDir) File'
|
||||
|
@ -11,13 +11,14 @@ import qualified Data.Aeson as Aeson
|
||||
import Data.Maybe (fromJust, fromMaybe, isJust)
|
||||
import StrongPath (Dir, File', Path, Path', Posix, Rel, reldir, reldirP, relfile, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import Wasp.AppSpec (AppSpec, getApp)
|
||||
import Wasp.AppSpec (AppSpec)
|
||||
import qualified Wasp.AppSpec as AS
|
||||
import qualified Wasp.AppSpec.Action as AS.Action
|
||||
import qualified Wasp.AppSpec.App as AS.App
|
||||
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.AppSpec.Valid (getApp, isAuthEnabled)
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.Monad (Generator, GeneratorError (GenericGeneratorError), logAndThrowGeneratorError)
|
||||
import qualified Wasp.Generator.ServerGenerator.Common as C
|
||||
@ -112,7 +113,7 @@ genOperationsRouter spec
|
||||
"isUsingAuth" .= isAuthEnabledForOperation operation
|
||||
]
|
||||
|
||||
isAuthEnabledGlobally = AS.isAuthEnabled spec
|
||||
isAuthEnabledGlobally = isAuthEnabled spec
|
||||
isAuthEnabledForOperation operation = fromMaybe isAuthEnabledGlobally (AS.Operation.getAuth operation)
|
||||
isAuthSpecifiedForOperation operation = isJust $ AS.Operation.getAuth operation
|
||||
|
||||
|
@ -14,10 +14,11 @@ import StrongPath
|
||||
relfile,
|
||||
(</>),
|
||||
)
|
||||
import Wasp.AppSpec (AppSpec, getApp)
|
||||
import Wasp.AppSpec (AppSpec)
|
||||
import qualified Wasp.AppSpec as AS
|
||||
import qualified Wasp.AppSpec.App as AS.App
|
||||
import qualified Wasp.AppSpec.App.Dependency as AS.Dependency
|
||||
import Wasp.AppSpec.Valid (getApp)
|
||||
import Wasp.Generator.ExternalCodeGenerator (generateExternalCodeDir)
|
||||
import Wasp.Generator.FileDraft
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
|
@ -8,9 +8,9 @@ import Data.Aeson.Types (Pair)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import StrongPath (File', Path', Rel', reldir, relfile, (</>))
|
||||
import Wasp.AppSpec (AppSpec)
|
||||
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.AppSpec.Valid (getApp)
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
import Wasp.Generator.WebAppGenerator.Common as C
|
||||
@ -30,7 +30,7 @@ genAuth spec =
|
||||
<++> genAuthForms auth
|
||||
Nothing -> return []
|
||||
where
|
||||
maybeAuth = AS.App.auth $ snd $ AS.getApp spec
|
||||
maybeAuth = AS.App.auth $ snd $ getApp spec
|
||||
|
||||
-- | Generates file with signup function to be used by Wasp developer.
|
||||
genSignup :: Generator FileDraft
|
||||
|
@ -16,6 +16,7 @@ import qualified Wasp.AppSpec as AS
|
||||
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.AppSpec.Valid (isAuthEnabled)
|
||||
import Wasp.Generator.FileDraft (FileDraft)
|
||||
import Wasp.Generator.Monad (Generator)
|
||||
import Wasp.Generator.WebAppGenerator.Common (asTmplFile, asWebAppSrcFile)
|
||||
@ -77,7 +78,7 @@ createRouterTemplateData spec =
|
||||
RouterTemplateData
|
||||
{ _routes = routes,
|
||||
_pagesToImport = pages,
|
||||
_isAuthEnabled = AS.isAuthEnabled spec
|
||||
_isAuthEnabled = isAuthEnabled spec
|
||||
}
|
||||
where
|
||||
routes = map (createRouteTemplateData spec) $ AS.getRoutes spec
|
||||
|
@ -13,6 +13,7 @@ import System.Directory (doesDirectoryExist, doesFileExist)
|
||||
import qualified Wasp.Analyzer as Analyzer
|
||||
import Wasp.Analyzer.AnalyzeError (getErrorMessageAndCtx)
|
||||
import qualified Wasp.AppSpec as AS
|
||||
import qualified Wasp.AppSpec.Valid as ASV
|
||||
import Wasp.Common (DbMigrationsDir, WaspProjectDir, dbMigrationsDirInWaspProjectDir)
|
||||
import Wasp.CompileOptions (CompileOptions, sendMessage)
|
||||
import qualified Wasp.CompileOptions as CompileOptions
|
||||
@ -60,8 +61,12 @@ compile waspDir outDir options = do
|
||||
AS.dotEnvFile = maybeDotEnvFile,
|
||||
AS.isBuild = CompileOptions.isBuild options
|
||||
}
|
||||
(generatorWarnings, generatorErrors) <- Generator.writeWebAppCode appSpec outDir (sendMessage options)
|
||||
return (map show generatorWarnings, map show generatorErrors)
|
||||
case ASV.validateAppSpec appSpec of
|
||||
[] -> do
|
||||
(generatorWarnings, generatorErrors) <- Generator.writeWebAppCode appSpec outDir (sendMessage options)
|
||||
return (map show generatorWarnings, map show generatorErrors)
|
||||
validationErrors -> do
|
||||
return ([], map show validationErrors)
|
||||
|
||||
findWaspFile :: Path' Abs (Dir WaspProjectDir) -> IO (Maybe (Path' Abs File'))
|
||||
findWaspFile waspDir = do
|
||||
|
159
waspc/test/AppSpec/ValidTest.hs
Normal file
159
waspc/test/AppSpec/ValidTest.hs
Normal file
@ -0,0 +1,159 @@
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
|
||||
module AppSpec.ValidTest where
|
||||
|
||||
import Data.Maybe (fromJust)
|
||||
import Fixtures (systemSPRoot)
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
import qualified Wasp.AppSpec as AS
|
||||
import qualified Wasp.AppSpec.App as AS.App
|
||||
import qualified Wasp.AppSpec.App.Auth as AS.Auth
|
||||
import qualified Wasp.AppSpec.Core.Decl as AS.Decl
|
||||
import qualified Wasp.AppSpec.Core.Ref as AS.Core.Ref
|
||||
import qualified Wasp.AppSpec.Entity as AS.Entity
|
||||
import qualified Wasp.AppSpec.ExtImport as AS.ExtImport
|
||||
import qualified Wasp.AppSpec.Page as AS.Page
|
||||
import qualified Wasp.AppSpec.Valid as ASV
|
||||
import qualified Wasp.Psl.Ast.Model as PslM
|
||||
|
||||
spec_AppSpecValid :: Spec
|
||||
spec_AppSpecValid = do
|
||||
describe "validateAppSpec" $ do
|
||||
describe "should validate that AppSpec has exactly 1 'app' declaration." $ do
|
||||
it "returns no error if there is exactly 1 'app' declaration." $ do
|
||||
ASV.validateAppSpec (basicAppSpec {AS.decls = [basicAppDecl]}) `shouldBe` []
|
||||
it "returns an error if there is no 'app' declaration." $ do
|
||||
ASV.validateAppSpec (basicAppSpec {AS.decls = []})
|
||||
`shouldBe` [ ASV.GenericValidationError
|
||||
"You are missing an 'app' declaration in your Wasp app."
|
||||
]
|
||||
it "returns an error if there are 2 'app' declarations." $ do
|
||||
ASV.validateAppSpec
|
||||
( basicAppSpec
|
||||
{ AS.decls =
|
||||
[ AS.Decl.makeDecl "app1" basicApp,
|
||||
AS.Decl.makeDecl "app2" basicApp
|
||||
]
|
||||
}
|
||||
)
|
||||
`shouldBe` [ ASV.GenericValidationError
|
||||
"You have more than one 'app' declaration in your Wasp app. You have 2."
|
||||
]
|
||||
|
||||
describe "auth-related validation" $ do
|
||||
let userEntityName = "User"
|
||||
let validUserEntity =
|
||||
AS.Entity.makeEntity
|
||||
( PslM.Body
|
||||
[ PslM.ElementField $ makeBasicPslField "email" PslM.String,
|
||||
PslM.ElementField $ makeBasicPslField "password" PslM.String
|
||||
]
|
||||
)
|
||||
let validAppAuth =
|
||||
AS.Auth.Auth
|
||||
{ AS.Auth.userEntity = AS.Core.Ref.Ref userEntityName,
|
||||
AS.Auth.methods = [AS.Auth.EmailAndPassword],
|
||||
AS.Auth.onAuthFailedRedirectTo = "/",
|
||||
AS.Auth.onAuthSucceededRedirectTo = Nothing
|
||||
}
|
||||
|
||||
describe "should validate that when a page has authRequired, app.auth is also set." $ do
|
||||
let makeSpec = \appAuth pageAuthRequired ->
|
||||
basicAppSpec
|
||||
{ AS.decls =
|
||||
[ AS.Decl.makeDecl "TestApp" $
|
||||
basicApp {AS.App.auth = appAuth},
|
||||
AS.Decl.makeDecl "TestPage" $
|
||||
basicPage {AS.Page.authRequired = pageAuthRequired},
|
||||
AS.Decl.makeDecl userEntityName validUserEntity
|
||||
]
|
||||
}
|
||||
|
||||
it "returns no error if there is no page with authRequired and app.auth is not set" $ do
|
||||
ASV.validateAppSpec (makeSpec Nothing Nothing) `shouldBe` []
|
||||
ASV.validateAppSpec (makeSpec Nothing (Just False)) `shouldBe` []
|
||||
it "returns no error if there is a page with authRequired and app.auth is set" $ do
|
||||
ASV.validateAppSpec (makeSpec (Just validAppAuth) (Just True)) `shouldBe` []
|
||||
it "returns an error if there is a page with authRequired and app.auth is not set" $ do
|
||||
ASV.validateAppSpec (makeSpec Nothing (Just True))
|
||||
`shouldBe` [ ASV.GenericValidationError
|
||||
"Expected app.auth to be defined since there are Pages with authRequired set to true."
|
||||
]
|
||||
|
||||
describe "should validate that when app.auth is using EmailAndPassword, user entity is of valid shape." $ do
|
||||
let makeSpec = \appAuth userEntity ->
|
||||
basicAppSpec
|
||||
{ AS.decls =
|
||||
[ AS.Decl.makeDecl "TestApp" $
|
||||
basicApp {AS.App.auth = appAuth},
|
||||
AS.Decl.makeDecl userEntityName (userEntity :: AS.Entity.Entity)
|
||||
]
|
||||
}
|
||||
let invalidUserEntity =
|
||||
AS.Entity.makeEntity
|
||||
( PslM.Body
|
||||
[ PslM.ElementField $ makeBasicPslField "username" PslM.String,
|
||||
PslM.ElementField $ makeBasicPslField "password" PslM.String
|
||||
]
|
||||
)
|
||||
let invalidUserEntity2 =
|
||||
AS.Entity.makeEntity
|
||||
( PslM.Body
|
||||
[ PslM.ElementField $ makeBasicPslField "email" PslM.String
|
||||
]
|
||||
)
|
||||
|
||||
it "returns no error if app.auth is not set, regardless of shape of user entity" $ do
|
||||
ASV.validateAppSpec (makeSpec Nothing invalidUserEntity) `shouldBe` []
|
||||
ASV.validateAppSpec (makeSpec Nothing validUserEntity) `shouldBe` []
|
||||
it "returns no error if app.auth is set and user entity is of valid shape" $ do
|
||||
ASV.validateAppSpec (makeSpec (Just validAppAuth) validUserEntity) `shouldBe` []
|
||||
it "returns an error if app.auth is set and user entity is of invalid shape" $ do
|
||||
ASV.validateAppSpec (makeSpec (Just validAppAuth) invalidUserEntity)
|
||||
`shouldBe` [ ASV.GenericValidationError
|
||||
"Expected an Entity referenced by app.auth.userEntity to have field 'email' of type 'string'."
|
||||
]
|
||||
ASV.validateAppSpec (makeSpec (Just validAppAuth) invalidUserEntity2)
|
||||
`shouldBe` [ ASV.GenericValidationError
|
||||
"Expected an Entity referenced by app.auth.userEntity to have field 'password' of type 'string'."
|
||||
]
|
||||
where
|
||||
makeBasicPslField name typ =
|
||||
PslM.Field
|
||||
{ PslM._name = name,
|
||||
PslM._type = typ,
|
||||
PslM._typeModifiers = [],
|
||||
PslM._attrs = []
|
||||
}
|
||||
|
||||
basicApp =
|
||||
AS.App.App
|
||||
{ AS.App.title = "Test App",
|
||||
AS.App.db = Nothing,
|
||||
AS.App.server = Nothing,
|
||||
AS.App.auth = Nothing,
|
||||
AS.App.dependencies = Nothing,
|
||||
AS.App.head = Nothing
|
||||
}
|
||||
|
||||
basicAppDecl = AS.Decl.makeDecl "TestApp" basicApp
|
||||
|
||||
basicAppSpec =
|
||||
AS.AppSpec
|
||||
{ AS.decls = [basicAppDecl],
|
||||
AS.externalCodeDirPath = systemSPRoot SP.</> [SP.reldir|test/src|],
|
||||
AS.externalCodeFiles = [],
|
||||
AS.isBuild = False,
|
||||
AS.migrationsDir = Nothing,
|
||||
AS.dotEnvFile = Nothing
|
||||
}
|
||||
|
||||
basicPage =
|
||||
AS.Page.Page
|
||||
{ AS.Page.component =
|
||||
AS.ExtImport.ExtImport
|
||||
(AS.ExtImport.ExtImportModule "Home")
|
||||
(fromJust $ SP.parseRelFileP "pages/Main"),
|
||||
AS.Page.authRequired = Nothing
|
||||
}
|
@ -171,6 +171,7 @@ library
|
||||
Wasp.AppSpec.Page
|
||||
Wasp.AppSpec.Query
|
||||
Wasp.AppSpec.Route
|
||||
Wasp.AppSpec.Valid
|
||||
Wasp.Common
|
||||
Wasp.CompileOptions
|
||||
Wasp.Data
|
||||
@ -320,6 +321,7 @@ test-suite waspc-test
|
||||
Analyzer.TypeChecker.InternalTest
|
||||
Analyzer.TypeCheckerTest
|
||||
AnalyzerTest
|
||||
AppSpec.ValidTest
|
||||
ErrorTest
|
||||
FilePath.ExtraTest
|
||||
Fixtures
|
||||
|
Loading…
Reference in New Issue
Block a user