Formatted tests with ormolu.

This commit is contained in:
Martin Sosic 2021-07-21 16:13:21 +02:00
parent 29fd18dbcc
commit 0b02e45354
2 changed files with 67 additions and 64 deletions

View File

@ -1,7 +1,7 @@
module Parser.ActionTest where
import Data.Either (isLeft)
import Data.Char (toLower)
import Data.Either (isLeft)
import Parser.Action (action)
import Parser.Common (runWaspParser)
import qualified StrongPath as SP
@ -18,39 +18,41 @@ spec_parseAction :: Spec
spec_parseAction =
describe "Parsing action declaration" $ do
let parseAction = runWaspParser action
let testWhenAuth auth = it ("When given a valid action declaration, returns correct AST(action.auth = " ++ show auth ++ ")") $
parseAction (genActionCode auth) `shouldBe` Right (genActionAST auth)
let testWhenAuth auth =
it ("When given a valid action declaration, returns correct AST(action.auth = " ++ show auth ++ ")") $
parseAction (genActionCode auth) `shouldBe` Right (genActionAST auth)
testWhenAuth (Just True)
testWhenAuth (Just False)
testWhenAuth (Nothing)
it "When given action wasp declaration without 'fn' property, should return Left" $ do
isLeft (parseAction "action myAction { }") `shouldBe` True
where
genActionAST :: Maybe Bool -> Wasp.Action.Action
genActionAST aApplyAuth = Wasp.Action.Action
{ Wasp.Action._name = testActionName,
Wasp.Action._jsFunction =
Wasp.JsImport.JsImport
{ Wasp.JsImport._defaultImport = Nothing,
Wasp.JsImport._namedImports = [testActionJsFunctionName],
Wasp.JsImport._from = testActionJsFunctionFrom
},
Wasp.Action._entities = Nothing,
Wasp.Action._auth = aApplyAuth
}
genActionCode :: Maybe Bool -> String
genActionCode aApplyAuth = (
"action " ++ testActionName ++ " {\n"
++ " fn: import { "
++ testActionJsFunctionName
++ " } from \"@ext/some/path\""
++ authStr aApplyAuth
++ "}"
)
where
genActionAST :: Maybe Bool -> Wasp.Action.Action
genActionAST aApplyAuth =
Wasp.Action.Action
{ Wasp.Action._name = testActionName,
Wasp.Action._jsFunction =
Wasp.JsImport.JsImport
{ Wasp.JsImport._defaultImport = Nothing,
Wasp.JsImport._namedImports = [testActionJsFunctionName],
Wasp.JsImport._from = testActionJsFunctionFrom
},
Wasp.Action._entities = Nothing,
Wasp.Action._auth = aApplyAuth
}
genActionCode :: Maybe Bool -> String
genActionCode aApplyAuth =
( "action " ++ testActionName ++ " {\n"
++ " fn: import { "
++ testActionJsFunctionName
++ " } from \"@ext/some/path\""
++ authStr aApplyAuth
++ "}"
)
authStr :: Maybe Bool -> String
authStr (Just useAuth) = ",\n auth: " ++ map toLower (show useAuth) ++ "\n"
authStr _ = "\n"
testActionJsFunctionFrom = [SP.relfileP|some/path|]
testActionJsFunctionName = "myJsAction"
testActionName = "myAction"
authStr :: Maybe Bool -> String
authStr (Just useAuth) = ",\n auth: " ++ map toLower (show useAuth) ++ "\n"
authStr _ = "\n"
testActionJsFunctionFrom = [SP.relfileP|some/path|]
testActionJsFunctionName = "myJsAction"
testActionName = "myAction"

View File

@ -1,5 +1,6 @@
module Parser.QueryTest where
import Data.Char (toLower)
import Data.Either (isLeft)
import Parser.Common (runWaspParser)
import Parser.Query (query)
@ -7,47 +8,47 @@ import qualified StrongPath as SP
import Test.Tasty.Hspec
import qualified Wasp.JsImport
import qualified Wasp.Query
import Data.Char (toLower)
spec_parseQuery :: Spec
spec_parseQuery =
describe "Parsing query declaration" $ do
let parseQuery = runWaspParser query
let testWhenAuth auth = it ("When given a valid query declaration, returns correct AST(query.auth = " ++ show auth ++ ")") $
parseQuery (genQueryCode auth) `shouldBe` Right (genQueryAST auth)
let testWhenAuth auth =
it ("When given a valid query declaration, returns correct AST(query.auth = " ++ show auth ++ ")") $
parseQuery (genQueryCode auth) `shouldBe` Right (genQueryAST auth)
testWhenAuth (Just True)
testWhenAuth (Just False)
testWhenAuth (Nothing)
it "When given query wasp declaration without 'fn' property, should return Left" $ do
isLeft (parseQuery "query myQuery { }") `shouldBe` True
where
genQueryCode :: Maybe Bool -> String
genQueryCode qApplyAuth = (
"query " ++ testQueryName ++ " {\n"
++ " fn: import { "
++ testQueryJsFunctionName
++ " } from \"@ext/some/path\",\n"
++ " entities: [Task, Project]"
++ authStr qApplyAuth
++ "}"
)
genQueryAST :: Maybe Bool -> Wasp.Query.Query
genQueryAST qApplyAuth = Wasp.Query.Query
{ Wasp.Query._name = testQueryName,
Wasp.Query._jsFunction =
Wasp.JsImport.JsImport
{ Wasp.JsImport._defaultImport = Nothing,
Wasp.JsImport._namedImports = [testQueryJsFunctionName],
Wasp.JsImport._from = testQueryJsFunctionFrom
},
Wasp.Query._entities = Just ["Task", "Project"],
Wasp.Query._auth = qApplyAuth
}
authStr :: Maybe Bool -> String
authStr (Just useAuth) = ",\n auth: " ++ map toLower (show useAuth) ++ "\n"
authStr _ = "\n"
testQueryName = "myQuery"
testQueryJsFunctionName = "myJsQuery"
testQueryJsFunctionFrom = [SP.relfileP|some/path|]
where
genQueryCode :: Maybe Bool -> String
genQueryCode qApplyAuth =
( "query " ++ testQueryName ++ " {\n"
++ " fn: import { "
++ testQueryJsFunctionName
++ " } from \"@ext/some/path\",\n"
++ " entities: [Task, Project]"
++ authStr qApplyAuth
++ "}"
)
genQueryAST :: Maybe Bool -> Wasp.Query.Query
genQueryAST qApplyAuth =
Wasp.Query.Query
{ Wasp.Query._name = testQueryName,
Wasp.Query._jsFunction =
Wasp.JsImport.JsImport
{ Wasp.JsImport._defaultImport = Nothing,
Wasp.JsImport._namedImports = [testQueryJsFunctionName],
Wasp.JsImport._from = testQueryJsFunctionFrom
},
Wasp.Query._entities = Just ["Task", "Project"],
Wasp.Query._auth = qApplyAuth
}
authStr :: Maybe Bool -> String
authStr (Just useAuth) = ",\n auth: " ++ map toLower (show useAuth) ++ "\n"
authStr _ = "\n"
testQueryName = "myQuery"
testQueryJsFunctionName = "myJsQuery"
testQueryJsFunctionFrom = [SP.relfileP|some/path|]