mirror of
https://github.com/wasp-lang/wasp.git
synced 2024-11-27 14:55:20 +03:00
Polished AppSpec: added missing fields + deps are not tuples. (#417)
This commit is contained in:
parent
5f534f7bcf
commit
fe915158d9
@ -6,6 +6,7 @@ module Wasp.Analyzer.StdTypeDefinitions
|
||||
)
|
||||
where
|
||||
|
||||
import Wasp.Analyzer.StdTypeDefinitions.App.Dependency ()
|
||||
import Wasp.Analyzer.StdTypeDefinitions.Entity ()
|
||||
import qualified Wasp.Analyzer.TypeDefinitions as TD
|
||||
import Wasp.Analyzer.TypeDefinitions.TH (makeDeclType, makeEnumType)
|
||||
|
24
waspc/src/Wasp/Analyzer/StdTypeDefinitions/App/Dependency.hs
Normal file
24
waspc/src/Wasp/Analyzer/StdTypeDefinitions/App/Dependency.hs
Normal file
@ -0,0 +1,24 @@
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||
|
||||
module Wasp.Analyzer.StdTypeDefinitions.App.Dependency () where
|
||||
|
||||
import qualified Wasp.Analyzer.Evaluator.Evaluation as E
|
||||
import qualified Wasp.Analyzer.Evaluator.EvaluationError as ER
|
||||
import qualified Wasp.Analyzer.Type as Type
|
||||
import Wasp.Analyzer.TypeChecker (WithCtx (..))
|
||||
import qualified Wasp.Analyzer.TypeChecker.AST as TypedAST
|
||||
import Wasp.Analyzer.TypeDefinitions.Class.HasCustomEvaluation (HasCustomEvaluation (..))
|
||||
import qualified Wasp.AppSpec.App.Dependency as D
|
||||
|
||||
instance HasCustomEvaluation D.Dependency where
|
||||
waspType = Type.TupleType (Type.StringType, Type.StringType, [])
|
||||
|
||||
evaluation = E.evaluation' . TypedAST.withCtx $ \ctx texpr -> case texpr of
|
||||
TypedAST.Tuple
|
||||
( WithCtx _ (TypedAST.StringLiteral depName),
|
||||
WithCtx _ (TypedAST.StringLiteral depVer),
|
||||
[]
|
||||
)
|
||||
_ -> return $ D.Dependency {D.name = depName, D.version = depVer}
|
||||
_ -> Left $ ER.mkEvaluationError ctx $ ER.ExpectedType (waspType @D.Dependency) (TypedAST.exprType texpr)
|
@ -3,8 +3,10 @@ module Wasp.AppSpec
|
||||
)
|
||||
where
|
||||
|
||||
import StrongPath (Abs, Dir, File', Path')
|
||||
import Wasp.AppSpec.Core.Decl (Decl)
|
||||
import qualified Wasp.AppSpec.ExternalCode as ExternalCode
|
||||
import Wasp.Common (DbMigrationsDir)
|
||||
|
||||
-- | AppSpec is the main/central intermediate representation (IR) of the whole Wasp compiler,
|
||||
-- describing the web app specification with all the details needed to generate it.
|
||||
@ -14,5 +16,11 @@ data AppSpec = AppSpec
|
||||
{ -- | List of declarations like App, Page, Route, ... that describe the web app.
|
||||
decls :: [Decl],
|
||||
-- | List of external code files (they are referenced/used by the declarations).
|
||||
externalCodeFiles :: ExternalCode.File
|
||||
externalCodeFiles :: [ExternalCode.File],
|
||||
-- | Absolute path to the directory in wasp project source that contains external code files.
|
||||
externalCodeDirPath :: !(Path' Abs (Dir ExternalCode.SourceExternalCodeDir)),
|
||||
-- | Absolute path to the directory in wasp project source that contains database migrations.
|
||||
migrationsDir :: Maybe (Path' Abs (Dir DbMigrationsDir)),
|
||||
dotEnvFile :: Maybe (Path' Abs File'),
|
||||
isBuild :: Bool
|
||||
}
|
||||
|
@ -13,7 +13,8 @@ import Wasp.AppSpec.Entity (Entity)
|
||||
data Auth = Auth
|
||||
{ userEntity :: Ref Entity,
|
||||
methods :: [AuthMethod],
|
||||
onAuthFailedRedirectTo :: Maybe String
|
||||
onAuthFailedRedirectTo :: String,
|
||||
onAuthSucceededRedirectTo :: Maybe String
|
||||
}
|
||||
deriving (Show, Eq, Data)
|
||||
|
||||
|
@ -13,7 +13,9 @@ import Wasp.AppSpec.Page
|
||||
-- | NOTE: We have new syntax for route, before it was `route "/task" -> page Task`, now it is a dictionary.
|
||||
data Route = Route
|
||||
{ path :: String,
|
||||
page :: Ref Page
|
||||
-- TODO: In the future we might want to add other types of targets, for example another Route.
|
||||
-- For that the best solution is probably to implement sum types (https://github.com/wasp-lang/wasp/issues/381).
|
||||
to :: Ref Page
|
||||
}
|
||||
deriving (Show, Eq, Data)
|
||||
|
||||
|
@ -41,9 +41,10 @@ spec_Analyzer = do
|
||||
" auth: {",
|
||||
" userEntity: User,",
|
||||
" methods: [EmailAndPassword],",
|
||||
" onAuthFailedRedirectTo: \"/\",",
|
||||
" },",
|
||||
" dependencies: [",
|
||||
" { name: \"redux\", version: \"^4.0.5\" }",
|
||||
" (\"redux\", \"^4.0.5\")",
|
||||
" ],",
|
||||
" server: {",
|
||||
" setupFn: import { setupServer } from \"@ext/bar.js\"",
|
||||
@ -66,7 +67,7 @@ spec_Analyzer = do
|
||||
" authRequired: true",
|
||||
"}",
|
||||
"",
|
||||
"route HomeRoute { path: \"/\", page: HomePage }",
|
||||
"route HomeRoute { path: \"/\", to: HomePage }",
|
||||
"",
|
||||
"query getUsers {",
|
||||
" fn: import { getAllUsers } from \"@ext/foo.js\",",
|
||||
@ -92,7 +93,8 @@ spec_Analyzer = do
|
||||
Auth.Auth
|
||||
{ Auth.userEntity = Ref "User" :: Ref Entity,
|
||||
Auth.methods = [Auth.EmailAndPassword],
|
||||
Auth.onAuthFailedRedirectTo = Nothing
|
||||
Auth.onAuthFailedRedirectTo = "/",
|
||||
Auth.onAuthSucceededRedirectTo = Nothing
|
||||
},
|
||||
App.dependencies =
|
||||
Just
|
||||
@ -143,7 +145,7 @@ spec_Analyzer = do
|
||||
|
||||
let expectedRoutes =
|
||||
[ ( "HomeRoute",
|
||||
Route.Route {Route.path = "/", Route.page = Ref "HomePage"}
|
||||
Route.Route {Route.path = "/", Route.to = Ref "HomePage"}
|
||||
)
|
||||
]
|
||||
takeDecls @Route <$> decls `shouldBe` Right expectedRoutes
|
||||
@ -173,22 +175,22 @@ spec_Analyzer = do
|
||||
it "Returns a type error if unexisting declaration is referenced" $ do
|
||||
let source =
|
||||
unlines
|
||||
[ "route HomeRoute { path: \"/\", page: NonExistentPage }"
|
||||
[ "route HomeRoute { path: \"/\", to: NonExistentPage }"
|
||||
]
|
||||
takeDecls @Route <$> analyze source
|
||||
`shouldBe` Left (TypeError $ TC.mkTypeError (ctx (1, 36) (1, 50)) $ TC.UndefinedIdentifier "NonExistentPage")
|
||||
`shouldBe` Left (TypeError $ TC.mkTypeError (ctx (1, 34) (1, 48)) $ TC.UndefinedIdentifier "NonExistentPage")
|
||||
|
||||
it "Returns a type error if referenced declaration is of wrong type" $ do
|
||||
let source =
|
||||
unlines
|
||||
[ "route HomeRoute { path: \"/\", page: HomeRoute }"
|
||||
[ "route HomeRoute { path: \"/\", to: HomeRoute }"
|
||||
]
|
||||
analyze source
|
||||
`errorMessageShouldBe` ( ctx (1, 37) (1, 45),
|
||||
`errorMessageShouldBe` ( ctx (1, 35) (1, 43),
|
||||
intercalate
|
||||
"\n"
|
||||
[ "Type error:",
|
||||
" For dictionary field 'page':",
|
||||
" For dictionary field 'to':",
|
||||
" Expected type: page (declaration type)",
|
||||
" Actual type: route (declaration type)"
|
||||
]
|
||||
@ -197,7 +199,7 @@ spec_Analyzer = do
|
||||
it "Works when referenced declaration is declared after the reference." $ do
|
||||
let source =
|
||||
unlines
|
||||
[ "route HomeRoute { path: \"/\", page: HomePage }",
|
||||
[ "route HomeRoute { path: \"/\", to: HomePage }",
|
||||
"page HomePage { component: import Home from \"@ext/HomePage.js\" }"
|
||||
]
|
||||
isRight (analyze source) `shouldBe` True
|
||||
@ -209,21 +211,20 @@ spec_Analyzer = do
|
||||
[ "app MyApp {",
|
||||
" title: \"My app\",",
|
||||
" dependencies: [",
|
||||
" { name: \"bar\", version: 13 },",
|
||||
" { name: \"foo\", version: 14 }",
|
||||
" (\"bar\", 13),",
|
||||
" (\"foo\", 14)",
|
||||
" ]",
|
||||
"}"
|
||||
]
|
||||
analyze source
|
||||
`errorMessageShouldBe` ( ctx (4, 29) (4, 30),
|
||||
`errorMessageShouldBe` ( ctx (4, 5) (4, 15),
|
||||
intercalate
|
||||
"\n"
|
||||
[ "Type error:",
|
||||
" For dictionary field 'dependencies':",
|
||||
" For list element:",
|
||||
" For dictionary field 'version':",
|
||||
" Expected type: string",
|
||||
" Actual type: number"
|
||||
" Expected type: (string, string)",
|
||||
" Actual type: (string, number)"
|
||||
]
|
||||
)
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user