Support for single line comment syntax using --
This commit is contained in:
		
							
								
								
									
										13
									
								
								src/Lexer.hs
									
									
									
									
									
								
							
							
						
						
									
										13
									
								
								src/Lexer.hs
									
									
									
									
									
								
							| @ -3,6 +3,8 @@ module Lexer where | |||||||
| import Research | import Research | ||||||
| import Text.Megaparsec | import Text.Megaparsec | ||||||
| import Text.Megaparsec.Char | import Text.Megaparsec.Char | ||||||
|  |  | ||||||
|  | import Control.Monad (void) | ||||||
| import Data.Void | import Data.Void | ||||||
| import qualified Data.Set as Set | import qualified Data.Set as Set | ||||||
|  |  | ||||||
| @ -21,6 +23,7 @@ data LToken | |||||||
|   | LOpenBracket |   | LOpenBracket | ||||||
|   | LCloseBracket |   | LCloseBracket | ||||||
|   | LNewline |   | LNewline | ||||||
|  |   | LComment String | ||||||
|   deriving (Show, Eq, Ord) |   deriving (Show, Eq, Ord) | ||||||
|  |  | ||||||
| keywordT :: Lexer LToken | keywordT :: Lexer LToken | ||||||
| @ -72,8 +75,16 @@ closeBracket = char ']' *> pure LCloseBracket | |||||||
| lnewline :: Lexer LToken | lnewline :: Lexer LToken | ||||||
| lnewline = char '\n' *> pure LNewline | lnewline = char '\n' *> pure LNewline | ||||||
|  |  | ||||||
|  | comment :: Lexer LToken | ||||||
|  | comment = do | ||||||
|  |   string "--" | ||||||
|  |   content <- many (satisfy (/= '\n')) | ||||||
|  |   optional (char '\n') | ||||||
|  |   pure (LComment content) | ||||||
|  |  | ||||||
|  |  | ||||||
| sc :: Lexer () | sc :: Lexer () | ||||||
| sc = skipMany (char ' ' <|> char '\t') | sc = skipMany (void (char ' ') <|> void (char '\t') <|> void comment) | ||||||
|  |  | ||||||
| saplingLexer :: Lexer [LToken] | saplingLexer :: Lexer [LToken] | ||||||
| saplingLexer = many (sc *> choice | saplingLexer = many (sc *> choice | ||||||
|  | |||||||
| @ -5,7 +5,6 @@ import Lexer | |||||||
| import Parser | import Parser | ||||||
| import Research | import Research | ||||||
|  |  | ||||||
| import Control.Monad         		 (void) |  | ||||||
| import Data.List                 (intercalate) | import Data.List                 (intercalate) | ||||||
| import qualified Data.Map as Map | import qualified Data.Map as Map | ||||||
| import System.Console.Haskeline | import System.Console.Haskeline | ||||||
|  | |||||||
		Reference in New Issue
	
	Block a user
	 James Eversole
					James Eversole