diff --git a/waspc/src/Wasp/Analyzer/Parser/AST/PrettyPrinter.hs b/waspc/src/Wasp/Analyzer/Parser/AST/PrettyPrinter.hs new file mode 100644 index 000000000..39f3ba93e --- /dev/null +++ b/waspc/src/Wasp/Analyzer/Parser/AST/PrettyPrinter.hs @@ -0,0 +1,67 @@ +module Wasp.Analyzer.Parser.AST.PrettyPrinter + ( prettyPrintAST, + prettyPrintStmt, + prettyPrintExpr, + prettyPrintCtx, + prettyPrintWithCtx, + ) +where + +import Wasp.Analyzer.Parser.AST (AST (AST), Expr (..), ExtImportName (..), Stmt (..)) +import Wasp.Analyzer.Parser.Ctx (Ctx (Ctx), WithCtx (..)) +import Wasp.Analyzer.Parser.SourcePosition (SourcePosition (SourcePosition)) +import Wasp.Analyzer.Parser.SourceRegion (SourceRegion (SourceRegion)) +import Wasp.Util (indent) + +prettyPrintAST :: AST -> String +prettyPrintAST (AST stmts) = "(AST\n" ++ indent 2 (concatMap prettyPrintStmt stmts) ++ ")\n" + +prettyPrintStmt :: WithCtx Stmt -> String +prettyPrintStmt (WithCtx ctx (Decl typ name body)) = + prettyPrintWithCtx "(Decl" ctx ++ " type=" ++ typ ++ " name=" ++ name ++ "\n" + ++ indent 2 (prettyPrintExpr body) + ++ ")\n" + +prettyPrintExpr :: WithCtx Expr -> String +prettyPrintExpr (WithCtx ctx expr) = "(" ++ prettyPrintWithCtx (exprName expr) ctx ++ showDetails expr ++ ")\n" + where + exprName (Dict _) = "Dict" + exprName (List _) = "List" + exprName (Tuple _) = "Tuple" + exprName (StringLiteral _) = "String" + exprName (IntegerLiteral _) = "Integer" + exprName (DoubleLiteral _) = "Double" + exprName (BoolLiteral _) = "Bool" + exprName (ExtImport _ _) = "ExtImport" + exprName (Var _) = "Var" + exprName (Quoter _ _) = "Quoter" + + showDetails (Dict []) = "" + showDetails (Dict entries) = "\n" ++ indent 2 (concatMap showEntry entries) + showDetails (List []) = "" + showDetails (List values) = "\n" ++ indent 2 (concatMap prettyPrintExpr values) + showDetails (Tuple (a, b, cs)) = "\n" ++ indent 2 (concatMap prettyPrintExpr (a : b : cs)) + showDetails (StringLiteral s) = showLiteral s + showDetails (IntegerLiteral n) = showLiteral n + showDetails (DoubleLiteral n) = showLiteral n + showDetails (BoolLiteral b) = showLiteral b + showDetails (ExtImport name path) = " " ++ showExtImportName name ++ " path=" ++ show path + showDetails (Var v) = " variable=" ++ v + showDetails (Quoter tag contents) = " tag=" ++ tag ++ "\n" ++ indent 2 ("{=" ++ contents ++ "=}") ++ "\n" + + showEntry (key, value) = "(DictEntry key=" ++ key ++ "\n" ++ indent 2 (prettyPrintExpr value) ++ ")\n" + + showExtImportName (ExtImportField name) = "field=" ++ name + showExtImportName (ExtImportModule name) = "module=" ++ name + + showLiteral :: Show a => a -> String + showLiteral value = " value=" ++ show value + +prettyPrintWithCtx :: String -> Ctx -> String +prettyPrintWithCtx name ctx = name ++ "@" ++ prettyPrintCtx ctx + +prettyPrintCtx :: Ctx -> String +prettyPrintCtx (Ctx (SourceRegion (SourcePosition startLine startColumn) (SourcePosition endLine endColumn))) + | startLine == endLine && startColumn == endColumn = show startLine ++ ":" ++ show startColumn + | startLine == endLine = show startLine ++ ":" ++ show startColumn ++ "-" ++ show endColumn + | otherwise = show startLine ++ ":" ++ show startColumn ++ "-" ++ show endLine ++ ":" ++ show endColumn diff --git a/waspc/src/Wasp/Analyzer/Parser/AbstractParser.hs b/waspc/src/Wasp/Analyzer/Parser/AbstractParser.hs index 29f6704a9..0a38d4f57 100644 --- a/waspc/src/Wasp/Analyzer/Parser/AbstractParser.hs +++ b/waspc/src/Wasp/Analyzer/Parser/AbstractParser.hs @@ -91,7 +91,7 @@ coerceExpr (SyntaxNode kind width children : remaining) | otherwise = do startPos <- gets pstateStartPos expr <- case kind of - S.String -> AST.StringLiteral . tail . init <$> consume width + S.String -> AST.StringLiteral . read <$> consume width S.Int -> AST.IntegerLiteral . read <$> consume width S.Double -> AST.DoubleLiteral . read <$> consume width S.BoolTrue -> advance width >> return (AST.BoolLiteral True) diff --git a/waspc/src/Wasp/Analyzer/Parser/PrettyPrinter.hs b/waspc/src/Wasp/Analyzer/Parser/PrettyPrinter.hs new file mode 100644 index 000000000..15e65966a --- /dev/null +++ b/waspc/src/Wasp/Analyzer/Parser/PrettyPrinter.hs @@ -0,0 +1,16 @@ +module Wasp.Analyzer.Parser.PrettyPrinter + ( prettyPrintParserResult, + ) +where + +import Wasp.Analyzer.Parser.AST (AST) +import Wasp.Analyzer.Parser.AST.PrettyPrinter (prettyPrintAST, prettyPrintCtx) +import Wasp.Analyzer.Parser.ParseError (ParseError, getErrorMessageAndCtx) +import Wasp.Util (indent) + +prettyPrintParserResult :: Either ParseError AST -> String +prettyPrintParserResult (Right ast) = prettyPrintAST ast +prettyPrintParserResult (Left err) = "Parse error at " ++ locationStr ++ ":\n" ++ indent 2 message ++ "\n" + where + (message, ctx) = getErrorMessageAndCtx err + locationStr = prettyPrintCtx ctx diff --git a/waspc/test/Analyzer/ParserTest.hs b/waspc/test/Analyzer/ParserTest.hs index 826058d72..b4db760f1 100644 --- a/waspc/test/Analyzer/ParserTest.hs +++ b/waspc/test/Analyzer/ParserTest.hs @@ -7,8 +7,7 @@ import Test.Tasty (TestTree, testGroup) import Test.Tasty.Golden (findByExtension, goldenVsStringDiff) import Test.Tasty.Hspec import Wasp.Analyzer.Parser hiding (withCtx) -import Wasp.Analyzer.Parser.ParseError (getErrorMessageAndCtx) -import Wasp.Util (indent) +import Wasp.Analyzer.Parser.PrettyPrinter (prettyPrintParserResult) spec_IsValidWaspIdentifier :: Spec spec_IsValidWaspIdentifier = do @@ -29,101 +28,47 @@ spec_ParseExpression = do it "Parses int literals" $ do parseExpression "5" `shouldBe` Right (IntegerLiteral 5) --- | To add more test cases to the parser, create a `.wasp` and `.golden` file --- in the `parserTests` directory with wasp source code to parse and the expected --- output, respectively. --- --- See `declsDictsAndLiterals` for an example of a test case with a successful --- parse. --- --- See `dictNoCloseBracket` for an example of a test case with an unsuccessful --- parse. --- --- While the testing framework will create the `.golden` file for you if it does --- not exist, it is recommended that you manually write the `.golden` file to --- make sure the output is as expected. --- --- When the golden file does not match the actual output, a diff will be shown --- in the terminal. -test_Parser :: IO TestTree -test_Parser = do - waspFiles <- findByExtension [".wasp"] "./test/Analyzer/parserTests" - return $ testGroup "Wasp.Analyzer.Parser" $ map testCase waspFiles +test_ParseStatements :: IO TestTree +test_ParseStatements = do + -- To make writing tests easier, we use golden files to define our tests here. + -- + -- In parseStatementsTests/ dir there are .wasp files and .golden files, where + -- each .wasp source file represents input of a single test, + -- while corresponding .golden file represents expected output of that test. + -- + -- See `declsDictsAndLiterals` for an example of a test case with a successful + -- parse. + -- + -- See `dictNoCloseBracket` for an example of a test case with an unsuccessful + -- parse. + -- + -- While the testing framework will create the `.golden` file for you if it does + -- not exist, it is recommended that you manually write the `.golden` file to + -- make sure the output is as expected. + -- + -- When the golden file does not match the actual output, a diff will be shown + -- in the terminal. + waspFiles <- findByExtension [".wasp"] "./test/Analyzer/ParserTest/parseStatementsTests" + return $ + testGroup "Wasp.Analyzer.Parser.parseStatements" $ + makeParseStatementsGoldenTest <$> waspFiles --- | Run a single golden test case for the given wasp file. -testCase :: FilePath -> TestTree -testCase waspFile = - let astFile = replaceExtension waspFile ".golden" +-- | Make a golden test where given wasp source file is parsed with +-- @parseStatements@ and the AST that is the result of parsing is the output of test. +-- This means that AST will be persisted to codebase as a "golden" output and compared +-- against the next time this test is run -> any difference is reported as failed test. +-- If no such file exists yet on the disk, it is created. +makeParseStatementsGoldenTest :: FilePath -> TestTree +makeParseStatementsGoldenTest waspFile = + let goldenAstFile = replaceExtension waspFile ".golden" + testCaseName = takeBaseName waspFile + diffCmd = \ref new -> ["diff", "-u", ref, new] in goldenVsStringDiff - (takeBaseName waspFile) -- Test case name - (\ref new -> ["diff", "-u", ref, new]) -- Diff command - astFile -- Golden file path + testCaseName + diffCmd + goldenAstFile ( do - -- Read from wasp file and return parse result + -- Read from wasp file and return parse result. source <- BSC.unpack <$> BS.readFile waspFile - return $ BSC.pack $ showResult $ parseStatements source + return $ BSC.pack $ prettyPrintParserResult $ parseStatements source ) - --- | Pretty print the result of a parse. The purpose of a custom implementation --- here is to make golden file diffs readable/useful. --- --- To see examples of pretty prints, see the golden files in `./parserTests`. -showResult :: Either ParseError AST -> String -showResult (Left err) = - let (message, ctx) = getErrorMessageAndCtx err - locationStr = "at " ++ showCtx ctx - in "Parse error " ++ locationStr ++ ":\n" ++ indent 2 message ++ "\n" -showResult (Right ast) = showAST ast - -showAST :: AST -> String -showAST (AST stmts) = "(AST\n" ++ indent 2 (concatMap showStmt stmts) ++ ")\n" - -showStmt :: WithCtx Stmt -> String -showStmt (WithCtx ctx (Decl typ name body)) = - withCtx "(Decl" ctx ++ " type=" ++ typ ++ " name=" ++ name ++ "\n" - ++ indent 2 (showExpr body) - ++ ")\n" - -showExpr :: WithCtx Expr -> String -showExpr (WithCtx ctx expr) = "(" ++ withCtx (exprName expr) ctx ++ showDetails expr ++ ")\n" - where - exprName (Dict _) = "Dict" - exprName (List _) = "List" - exprName (Tuple _) = "Tuple" - exprName (StringLiteral _) = "String" - exprName (IntegerLiteral _) = "Integer" - exprName (DoubleLiteral _) = "Double" - exprName (BoolLiteral _) = "Bool" - exprName (ExtImport _ _) = "ExtImport" - exprName (Var _) = "Var" - exprName (Quoter _ _) = "Quoter" - - showDetails (Dict []) = "" - showDetails (Dict entries) = "\n" ++ indent 2 (concatMap showEntry entries) - showDetails (List []) = "" - showDetails (List values) = "\n" ++ indent 2 (concatMap showExpr values) - showDetails (Tuple (a, b, cs)) = "\n" ++ indent 2 (concatMap showExpr (a : b : cs)) - showDetails (StringLiteral s) = showLiteral s - showDetails (IntegerLiteral n) = showLiteral n - showDetails (DoubleLiteral n) = showLiteral n - showDetails (BoolLiteral b) = showLiteral b - showDetails (ExtImport name path) = " " ++ showExtImportName name ++ " path=" ++ show path - showDetails (Var v) = " variable=" ++ v - showDetails (Quoter tag contents) = " tag=" ++ tag ++ "\n" ++ indent 2 ("{=" ++ contents ++ "=}") ++ "\n" - - showEntry (key, value) = "(DictEntry key=" ++ key ++ "\n" ++ indent 2 (showExpr value) ++ ")\n" - - showExtImportName (ExtImportField name) = "field=" ++ name - showExtImportName (ExtImportModule name) = "module=" ++ name - - showLiteral :: Show a => a -> String - showLiteral value = " value=" ++ show value - -withCtx :: String -> Ctx -> String -withCtx name ctx = name ++ "@" ++ showCtx ctx - -showCtx :: Ctx -> String -showCtx (Ctx (SourceRegion (SourcePosition sl sc) (SourcePosition el ec))) - | sl == el && sc == ec = show sl ++ ":" ++ show sc - | sl == el = show sl ++ ":" ++ show sc ++ "-" ++ show ec - | otherwise = show sl ++ ":" ++ show sc ++ "-" ++ show el ++ ":" ++ show ec diff --git a/waspc/test/Analyzer/parserTests/comments.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/comments.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/comments.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/comments.golden diff --git a/waspc/test/Analyzer/parserTests/comments.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/comments.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/comments.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/comments.wasp diff --git a/waspc/test/Analyzer/parserTests/declsDictsAndLiterals.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/declsDictsAndLiterals.golden similarity index 93% rename from waspc/test/Analyzer/parserTests/declsDictsAndLiterals.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/declsDictsAndLiterals.golden index d6d02f633..ab459fd69 100644 --- a/waspc/test/Analyzer/parserTests/declsDictsAndLiterals.golden +++ b/waspc/test/Analyzer/ParserTest/parseStatementsTests/declsDictsAndLiterals.golden @@ -5,7 +5,7 @@ (String@2:11-25 value="Hello Wasp =}") ) (DictEntry key=escapedString - (String@3:18-29 value="Look, a \\\"") + (String@3:18-29 value="Look, a \"") ) (DictEntry key=integer (Integer@4:12-13 value=42) diff --git a/waspc/test/Analyzer/parserTests/declsDictsAndLiterals.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/declsDictsAndLiterals.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/declsDictsAndLiterals.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/declsDictsAndLiterals.wasp diff --git a/waspc/test/Analyzer/parserTests/dictMissingComma.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/dictMissingComma.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/dictMissingComma.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/dictMissingComma.golden diff --git a/waspc/test/Analyzer/parserTests/dictMissingComma.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/dictMissingComma.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/dictMissingComma.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/dictMissingComma.wasp diff --git a/waspc/test/Analyzer/parserTests/dictNoCloseBracket.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/dictNoCloseBracket.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/dictNoCloseBracket.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/dictNoCloseBracket.golden diff --git a/waspc/test/Analyzer/parserTests/dictNoCloseBracket.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/dictNoCloseBracket.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/dictNoCloseBracket.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/dictNoCloseBracket.wasp diff --git a/waspc/test/Analyzer/parserTests/emptyDictsAndLists.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/emptyDictsAndLists.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/emptyDictsAndLists.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/emptyDictsAndLists.golden diff --git a/waspc/test/Analyzer/parserTests/emptyDictsAndLists.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/emptyDictsAndLists.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/emptyDictsAndLists.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/emptyDictsAndLists.wasp diff --git a/waspc/test/Analyzer/parserTests/externalImports.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/externalImports.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/externalImports.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/externalImports.golden diff --git a/waspc/test/Analyzer/parserTests/externalImports.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/externalImports.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/externalImports.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/externalImports.wasp diff --git a/waspc/test/Analyzer/parserTests/multipleElementList.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/multipleElementList.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/multipleElementList.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/multipleElementList.golden diff --git a/waspc/test/Analyzer/parserTests/multipleElementList.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/multipleElementList.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/multipleElementList.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/multipleElementList.wasp diff --git a/waspc/test/Analyzer/parserTests/multipleQuoters.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/multipleQuoters.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/multipleQuoters.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/multipleQuoters.golden diff --git a/waspc/test/Analyzer/parserTests/multipleQuoters.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/multipleQuoters.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/multipleQuoters.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/multipleQuoters.wasp diff --git a/waspc/test/Analyzer/parserTests/multipleStatements.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/multipleStatements.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/multipleStatements.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/multipleStatements.golden diff --git a/waspc/test/Analyzer/parserTests/multipleStatements.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/multipleStatements.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/multipleStatements.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/multipleStatements.wasp diff --git a/waspc/test/Analyzer/parserTests/nestedQuoters.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/nestedQuoters.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/nestedQuoters.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/nestedQuoters.golden diff --git a/waspc/test/Analyzer/parserTests/nestedQuoters.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/nestedQuoters.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/nestedQuoters.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/nestedQuoters.wasp diff --git a/waspc/test/Analyzer/parserTests/quotedJSON.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quotedJSON.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/quotedJSON.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quotedJSON.golden diff --git a/waspc/test/Analyzer/parserTests/quotedJSON.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quotedJSON.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/quotedJSON.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quotedJSON.wasp diff --git a/waspc/test/Analyzer/parserTests/quotedPSL.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quotedPSL.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/quotedPSL.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quotedPSL.golden diff --git a/waspc/test/Analyzer/parserTests/quotedPSL.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quotedPSL.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/quotedPSL.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quotedPSL.wasp diff --git a/waspc/test/Analyzer/parserTests/quoterDifferentNestedClose.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterDifferentNestedClose.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/quoterDifferentNestedClose.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterDifferentNestedClose.golden diff --git a/waspc/test/Analyzer/parserTests/quoterDifferentNestedClose.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterDifferentNestedClose.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/quoterDifferentNestedClose.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterDifferentNestedClose.wasp diff --git a/waspc/test/Analyzer/parserTests/quoterDifferentNestedOpen.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterDifferentNestedOpen.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/quoterDifferentNestedOpen.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterDifferentNestedOpen.golden diff --git a/waspc/test/Analyzer/parserTests/quoterDifferentNestedOpen.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterDifferentNestedOpen.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/quoterDifferentNestedOpen.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterDifferentNestedOpen.wasp diff --git a/waspc/test/Analyzer/parserTests/quoterSelfNested.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterSelfNested.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/quoterSelfNested.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterSelfNested.golden diff --git a/waspc/test/Analyzer/parserTests/quoterSelfNested.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterSelfNested.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/quoterSelfNested.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterSelfNested.wasp diff --git a/waspc/test/Analyzer/parserTests/quoterTwoClosingTags.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterTwoClosingTags.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/quoterTwoClosingTags.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterTwoClosingTags.golden diff --git a/waspc/test/Analyzer/parserTests/quoterTwoClosingTags.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterTwoClosingTags.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/quoterTwoClosingTags.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterTwoClosingTags.wasp diff --git a/waspc/test/Analyzer/parserTests/quoterTwoOpenTags.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterTwoOpenTags.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/quoterTwoOpenTags.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterTwoOpenTags.golden diff --git a/waspc/test/Analyzer/parserTests/quoterTwoOpenTags.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterTwoOpenTags.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/quoterTwoOpenTags.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterTwoOpenTags.wasp diff --git a/waspc/test/Analyzer/parserTests/quoterUnmatchedTags.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterUnmatchedTags.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/quoterUnmatchedTags.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterUnmatchedTags.golden diff --git a/waspc/test/Analyzer/parserTests/quoterUnmatchedTags.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterUnmatchedTags.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/quoterUnmatchedTags.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/quoterUnmatchedTags.wasp diff --git a/waspc/test/Analyzer/parserTests/trailingCommas.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/trailingCommas.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/trailingCommas.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/trailingCommas.golden diff --git a/waspc/test/Analyzer/parserTests/trailingCommas.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/trailingCommas.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/trailingCommas.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/trailingCommas.wasp diff --git a/waspc/test/Analyzer/parserTests/tuples.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/tuples.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/tuples.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/tuples.golden diff --git a/waspc/test/Analyzer/parserTests/tuples.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/tuples.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/tuples.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/tuples.wasp diff --git a/waspc/test/Analyzer/parserTests/unaryList.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/unaryList.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/unaryList.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/unaryList.golden diff --git a/waspc/test/Analyzer/parserTests/unaryList.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/unaryList.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/unaryList.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/unaryList.wasp diff --git a/waspc/test/Analyzer/parserTests/unexpectedToken.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/unexpectedToken.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/unexpectedToken.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/unexpectedToken.golden diff --git a/waspc/test/Analyzer/parserTests/unexpectedToken.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/unexpectedToken.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/unexpectedToken.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/unexpectedToken.wasp diff --git a/waspc/test/Analyzer/parserTests/unrecognizedCharacter.golden b/waspc/test/Analyzer/ParserTest/parseStatementsTests/unrecognizedCharacter.golden similarity index 100% rename from waspc/test/Analyzer/parserTests/unrecognizedCharacter.golden rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/unrecognizedCharacter.golden diff --git a/waspc/test/Analyzer/parserTests/unrecognizedCharacter.wasp b/waspc/test/Analyzer/ParserTest/parseStatementsTests/unrecognizedCharacter.wasp similarity index 100% rename from waspc/test/Analyzer/parserTests/unrecognizedCharacter.wasp rename to waspc/test/Analyzer/ParserTest/parseStatementsTests/unrecognizedCharacter.wasp diff --git a/waspc/waspc.cabal b/waspc/waspc.cabal index 0b3642a1b..4d2e8b06a 100644 --- a/waspc/waspc.cabal +++ b/waspc/waspc.cabal @@ -128,6 +128,7 @@ library Wasp.Analyzer.Evaluator.EvaluationError Wasp.Analyzer.Parser Wasp.Analyzer.Parser.AST + Wasp.Analyzer.Parser.AST.PrettyPrinter Wasp.Analyzer.Parser.Ctx Wasp.Analyzer.Parser.ConcreteParser Wasp.Analyzer.Parser.ConcreteParser.ParseError @@ -137,6 +138,7 @@ library Wasp.Analyzer.Parser.Lexer.Lexer Wasp.Analyzer.Parser.Lexer.Internal Wasp.Analyzer.Parser.ParseError + Wasp.Analyzer.Parser.PrettyPrinter Wasp.Analyzer.Parser.AbstractParser Wasp.Analyzer.Parser.AbstractParser.Monad Wasp.Analyzer.Parser.SourcePosition