module Compiler.Lexer.CommentsSpec where import Test.Hspec import "spade" Common import Compiler.Lexer.Comments import Compiler.Lexer.Tokens import Compiler.Lexer.Whitespaces import Parser.Lib import Parser.Parser spec :: Spec spec = do describe "Comments parsing" $ do it "can parse simple comment" $ runParser parser ("-- comment" :: TextWithOffset) `shouldReturn` (Just $ Comment "comment") it "can parse simple consecutive comments" $ runParser parser ("-- comment\n-- comment 2" :: TextWithOffset) `shouldReturn` (Just $ [Comment "comment", Comment "comment 2"]) it "can parse simple consecutive indented comments" $ runParser @[Token] parser (" -- comment\n -- comment 2" :: TextWithOffset) `shouldReturn` (Just $ [Token {tkRaw = TkWhitespace (Space 3), tkLocation = emptyLocation, tkOffsetEnd = 3},Token {tkRaw = TkComment (Comment "comment"), tkLocation = emptyLocation, tkOffsetEnd = 14},Token {tkRaw = TkWhitespace (Space 3), tkLocation = emptyLocation, tkOffsetEnd = 17},Token {tkRaw = TkComment (Comment "comment 2"), tkLocation = emptyLocation, tkOffsetEnd = 30}])