Skip to content

Commit

Permalink
Add parser for multiline
Browse files Browse the repository at this point in the history
  • Loading branch information
Saverio976 committed Dec 27, 2023
1 parent 5873206 commit 2a9acb1
Show file tree
Hide file tree
Showing 4 changed files with 78 additions and 21 deletions.
12 changes: 9 additions & 3 deletions lvtc/src/Expression.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,9 +6,10 @@
-}

module Expression (
Expression (..),
parseExpresion,
) where
Expression (..),
parseExpresion,
parseAllExpression,
) where

import Parser
import Control.Applicative
Expand Down Expand Up @@ -38,3 +39,8 @@ parseComment = Comment <$> ((++) <$> parseString "//" <*> parseAllCharUntil "\n"

parseExpresion :: Parser Expression
parseExpresion = parseAlias <|> parseFunction <|> parseComment

parseAllExpression :: Parser [Expression]
parseAllExpression = some p
where
p = parseExpresion <* many (parseAnyChar "\n")
22 changes: 11 additions & 11 deletions lvtc/src/ParseUtil.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,17 +6,17 @@
-}

module ParseUtil (
parseChar,
parseAnyChar,
parseUInt,
parseSign,
parseInt,
parseString,
parseBetween,
parseAfter,
parseBefore,
parseAllCharUntil,
) where
parseChar,
parseAnyChar,
parseUInt,
parseSign,
parseInt,
parseString,
parseBetween,
parseAfter,
parseBefore,
parseAllCharUntil,
) where

import Parser
import Data.Int (Int32)
Expand Down
4 changes: 2 additions & 2 deletions lvtc/src/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@
-}

module Parser (
Parser (..),
) where
Parser (..),
) where

import Control.Applicative

Expand Down
61 changes: 56 additions & 5 deletions lvtc/test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,17 +15,21 @@ main :: IO ()
main = defaultMain tests

tests :: TestTree
tests = testGroup "Leviator Tests - Compiler" [ utParserExpression ]
tests = testGroup "Leviator Tests - Compiler"
[
utParserExpression,
utParserExpressions
]

testParserHelper :: String -> String -> Expression -> IO ()
testParserHelper str restExpected expressionExpected =
case runParser (parseExpresion) str of
Just (parsed, rest) -> assertEqual str restExpected rest >>=
(\_ -> assertEqual str expressionExpected parsed)
case runParser parseExpresion str of
Just (parsed, rest) -> assertEqual str restExpected rest >>
assertEqual str expressionExpected parsed
Nothing -> assertFailure ("Parsing failed: " ++ str)

testParserHelperFail :: String -> IO ()
testParserHelperFail str = case runParser (parseExpresion) str of
testParserHelperFail str = case runParser parseExpresion str of
Just _ -> assertFailure ("Parsing should have failed: " ++ str)
Nothing -> assertEqual str "" ""

Expand Down Expand Up @@ -87,3 +91,50 @@ utParserExpression = testGroup "Parse Expression"
testParserHelperFail
"export abc()"
]


testParserHelpers :: String -> String -> [Expression] -> IO ()
testParserHelpers str restExpected expressionExpected =
case runParser parseAllExpression str of
Just (parsed, rest) -> assertEqual str restExpected rest >>
assertEqual str expressionExpected parsed
Nothing -> assertFailure ("Parsing failed: " ++ str)

testParserHelperFails :: String -> IO ()
testParserHelperFails str = case runParser parseAllExpression str of
Just (x, _) -> assertFailure ("Parsing should have failed: `" ++ str ++ "` But got: `" ++ show x ++ "`")
Nothing -> assertEqual str "" ""

utParserExpressions :: TestTree
utParserExpressions = testGroup "Parse Expressions"
[
-- function
testCase "function main" $
testParserHelpers
"fn main() -> Int \n{\n <- 0;\n};\nexport fn main() -> Int \n{\n <- 0;\n};\n"
""
[Function "fn main() -> Int \n{\n <- 0;\n};\n", Function "export fn main() -> Int \n{\n <- 0;\n};\n"]
, testCase "function bad formated (no end `}`)" $
testParserHelperFails
"fn main() -> Int \n{\n <- 0;\n};\nfn main() -> Int \n{\n <- 0;\n"
, testCase "function bad formated (no end `;`)" $
testParserHelperFails
"fn main() -> Int \n{\n <- 0;\n}\nfn main() -> Int \n{\n <- 0;\n};\n"
-- alias
, testCase "alias" $
testParserHelpers
"alias abc def;\nalias def def;\n"
""
[Alias "alias abc def;\n", Alias "alias def def;\n"]
, testCase "alias multiline" $
testParserHelpers
"alias abc def\nefg hij;\n"
""
[Alias "alias abc def\nefg hij;\n"]
-- comment
, testCase "comment" $
testParserHelpers
"// this is a comment\nalias abc def;\n"
""
[Comment "// this is a comment\n", Alias "alias abc def;\n"]
]

0 comments on commit 2a9acb1

Please sign in to comment.