wasp/waspc/test/AppSpec/ValidTest.hs

218 lines
9.4 KiB
Haskell
Raw Normal View History

2022-03-17 14:36:36 +03:00
{-# 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.App.Wasp as AS.Wasp
2022-03-17 14:36:36 +03:00
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
import qualified Wasp.SemanticVersion as SV
import qualified Wasp.Version as WV
2022-03-17 14:36:36 +03:00
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 "'waspVersion' validation" $ do
describe "should validate 'waspVersion' format" $ do
let basicAppWithVersionRange versionRange =
basicApp {AS.App.wasp = AS.Wasp.Wasp {AS.Wasp.version = versionRange}}
let basicAppSpecWithVersionRange versionRange =
basicAppSpec
{ AS.decls =
[ AS.Decl.makeDecl "TestApp" $ basicAppWithVersionRange versionRange
]
}
it "returns no error if waspVersion is compatible" $ do
ASV.validateAppSpec basicAppSpec `shouldBe` []
it "returns an error if 'waspVersion' has an incorrect format" $ do
ASV.validateAppSpec (basicAppSpecWithVersionRange "0.5;2")
`shouldBe` [ ASV.GenericValidationError
"Wasp version should be in the format ^major.minor.patch"
]
it "returns an error if 'waspVersion' is not compatible" $ do
let incompatibleWaspVersion = WV.waspVersion {SV.major = SV.major WV.waspVersion + 1}
ASV.validateAppSpec (basicAppSpecWithVersionRange $ "^" ++ show incompatibleWaspVersion)
`shouldBe` [ ASV.GenericValidationError $
unlines
[ "Your Wasp version does not match the app's requirements.",
"You are running Wasp " ++ show WV.waspVersion ++ ".",
"This app requires Wasp ^" ++ show incompatibleWaspVersion ++ ".",
"To install specific version of Wasp, do:",
" curl -sSL https://get.wasp-lang.dev/installer.sh | sh -s -- -v x.y.z",
"where x.y.z is your desired version.",
"Check https://github.com/wasp-lang/wasp/releases for the list of valid versions."
]
]
2022-03-17 14:36:36 +03:00
describe "auth-related validation" $ do
let userEntityName = "User"
let validUserEntity =
AS.Entity.makeEntity
( PslM.Body
[ PslM.ElementField $ makeBasicPslField "username" PslM.String,
2022-03-17 14:36:36 +03:00
PslM.ElementField $ makeBasicPslField "password" PslM.String
]
)
let validAppAuth =
AS.Auth.Auth
{ AS.Auth.userEntity = AS.Core.Ref.Ref userEntityName,
AS.Auth.externalAuthEntity = Nothing,
AS.Auth.methods =
AS.Auth.AuthMethods
{ AS.Auth.usernameAndPassword = Just AS.Auth.usernameAndPasswordConfig,
AS.Auth.google = Nothing,
AS.Auth.gitHub = Nothing
},
2022-03-17 14:36:36 +03:00
AS.Auth.onAuthFailedRedirectTo = "/",
AS.Auth.onAuthSucceededRedirectTo = Nothing
}
describe "should validate that when a page has authRequired, app.auth is also set." $ do
2022-03-18 14:33:37 +03:00
let makeSpec appAuth pageAuthRequired =
2022-03-17 14:36:36 +03:00
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 UsernameAndPassword, user entity is of valid shape." $ do
2022-03-18 14:33:37 +03:00
let makeSpec appAuth userEntity =
2022-03-17 14:36:36 +03:00
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 "email" PslM.String,
2022-03-17 14:36:36 +03:00
PslM.ElementField $ makeBasicPslField "password" PslM.String
]
)
let invalidUserEntity2 =
AS.Entity.makeEntity
( PslM.Body
[ PslM.ElementField $ makeBasicPslField "username" PslM.String
2022-03-17 14:36:36 +03:00
]
)
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 'username' of type 'String'."
2022-03-17 14:36:36 +03:00
]
ASV.validateAppSpec (makeSpec (Just validAppAuth) invalidUserEntity2)
`shouldBe` [ ASV.GenericValidationError
"Expected an Entity referenced by app.auth.userEntity to have field 'password' of type 'String'."
2022-03-17 14:36:36 +03:00
]
where
makeBasicPslField name typ =
PslM.Field
{ PslM._name = name,
PslM._type = typ,
PslM._typeModifiers = [],
PslM._attrs = []
}
basicApp =
AS.App.App
{ AS.App.wasp =
AS.Wasp.Wasp
{ AS.Wasp.version = "^" ++ show WV.waspVersion
},
AS.App.title = "Test App",
2022-03-17 14:36:36 +03:00
AS.App.db = Nothing,
AS.App.server = Nothing,
AS.App.client = Nothing,
2022-03-17 14:36:36 +03:00
AS.App.auth = Nothing,
AS.App.dependencies = Nothing,
AS.App.head = Nothing,
AS.App.emailSender = Nothing
2022-03-17 14:36:36 +03:00
}
basicAppDecl = AS.Decl.makeDecl "TestApp" basicApp
basicAppSpec =
AS.AppSpec
{ AS.decls = [basicAppDecl],
2022-11-06 16:26:53 +03:00
AS.waspProjectDir = systemSPRoot SP.</> [SP.reldir|test/|],
Separate user code into client, server, shared (#753) * Separate ext code to client and server * Use skeleton in createNewProject and refactor * Refactor Lib.hs to use ExceptT * Fix formatting * Pop up returns * Extract liftIO and add a do block Co-authored-by: Shayne Czyzewski <523636+shayneczyzewski@users.noreply.github.com> * Address some review comments * Add skeleton comment * Extract common CommandError message * Separate skeleton comment into two rows * Move server and client dirs into src * Simplify maybeToEither * Further refactor Lib.hs * Further simplify skeleton comment * Add shared code directory to project structure * Update e2e test inputs * Update e2e test outputs * Fix formatting * Fix bug in compile function Co-authored-by: Martin Šošić <Martinsos@users.noreply.github.com> * Change map to fmap in compile function * Fix formatting * Force git to include empty directories * Remove extra empty line from .gitkeep files * Watch shared directory for changes * Fix regular and e2e tests * Fix cli template packaging and update todoApp * Add a shared function demo to todoApp * Update waspc and e2e tests * Fix compiler warnings and rename function * Rename mkError to mkParserError * Remove redundant empty line * Fix test warnings * Fix formatting * Fix directory tree watching on wasp start * Implement review feedback Co-authored-by: Shayne Czyzewski <523636+shayneczyzewski@users.noreply.github.com> Co-authored-by: Martin Šošić <Martinsos@users.noreply.github.com>
2022-11-11 19:20:49 +03:00
AS.externalClientFiles = [],
AS.externalServerFiles = [],
AS.externalSharedFiles = [],
2022-03-17 14:36:36 +03:00
AS.isBuild = False,
AS.migrationsDir = Nothing,
AS.devEnvVarsClient = [],
AS.devEnvVarsServer = [],
AS.userDockerfileContents = Nothing,
AS.configFiles = [],
AS.devDatabaseUrl = Nothing
2022-03-17 14:36:36 +03:00
}
basicPage =
AS.Page.Page
{ AS.Page.component =
AS.ExtImport.ExtImport
(AS.ExtImport.ExtImportModule "Home")
(fromJust $ SP.parseRelFileP "pages/Main"),
AS.Page.authRequired = Nothing
}