Resolves issue with parsing comments

This commit is contained in:
2024-12-29 20:29:41 -06:00
committed by James Eversole
parent 8a2dc2dfcf
commit bde89125ba
7 changed files with 82 additions and 69 deletions

View File

@ -2,10 +2,12 @@ module Lexer where
import Research
import Text.Megaparsec
import Text.Megaparsec.Char
import Text.Megaparsec.Char hiding (space)
import Text.Megaparsec.Char.Lexer
import Control.Monad (void)
import Data.Void
import qualified Data.Set as Set
type Lexer = Parsec Void String
@ -23,7 +25,6 @@ data LToken
| LOpenBracket
| LCloseBracket
| LNewline
| LComment String
deriving (Show, Eq, Ord)
keywordT :: Lexer LToken
@ -75,30 +76,34 @@ closeBracket = char ']' *> pure LCloseBracket
lnewline :: Lexer LToken
lnewline = char '\n' *> pure LNewline
comment :: Lexer LToken
comment = do
string "--"
content <- many (satisfy (/= '\n'))
pure (LComment content)
sc :: Lexer ()
sc = skipMany (void (char ' ') <|> void (char '\t') <|> void comment)
sc = space space1 (skipLineComment "--") (skipBlockComment "|-" "-|")
tricuLexer :: Lexer [LToken]
tricuLexer = many (sc *> choice
[ try identifier
, try keywordT
, try integerLiteral
, try stringLiteral
, assign
, colon
, backslash
, openParen
, closeParen
, openBracket
, closeBracket
, lnewline
] <* sc) <* eof
tricuLexer = do
sc
tokens <- many $ do
tok <- choice tricuLexer'
sc
pure tok
sc
eof
pure tokens
where
tricuLexer' =
[ try identifier
, try keywordT
, try integerLiteral
, try stringLiteral
, assign
, colon
, backslash
, openParen
, closeParen
, openBracket
, closeBracket
]
lexTricu :: String -> [LToken]
lexTricu input = case runParser tricuLexer "" input of