Copyright | (c) Sebastian Tee 2023 |
---|---|
License | MIT |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type Grammar token = [TokenSyntax token]
- data TokenSyntax token
- type Lexer token = String -> Either LexException [token]
- data LexException = LexException Int Int String
- hlex :: Grammar token -> Lexer token
Example
Here is an example module for a simple language.
module ExampleLang ( MyToken(..) -- Export the language's tokens and the lexer , myLexer ) where import Hlex data MyToken = Ident String -- String identifier token | Number Float -- Number token and numeric value | Assign -- Assignment operator token deriving(Show) myGrammar :: Grammar MyToken myGrammar = [ JustToken "=" Assign -- "=" Operator becomes the assign token , Tokenize "[a-zA-Z]+" (match -> Ident match) -- Identifier token with string , Tokenize "[0-9]+(\.[0-9]+)?" (match -> Number (read match) -- Number token with the parsed numeric value stored as a Float , Skip "[ \n\r\t]+" -- Skip whitespace ] myLexer :: Lexer MyToken myLexer = hlex myGrammar -- hlex turns a Grammar into a Lexer
Here is the lexer being used on a simple program.
>>>
lexer "x = 1.2"
Right [Ident "x", Assign, Number 1.2]
The lexer uses Either
. Right means the lexer successfully parsed the program to a list of MyTokens.
If Left was returned it would be a LexException
.
Types
type Grammar token = [TokenSyntax token] Source #
Lexical grammar made up of TokenSyntax
rules.
The order is important. The Lexer
will apply each TokenSyntax
rule in the order listed.
data TokenSyntax token Source #
These are the individual rules that make up a Grammar
.
Takes a POSIX regular expression then converts it to a token or skips it.
type Lexer token = String -> Either LexException [token] Source #
Converts a string into a list of tokens.
If the string does not follow the Lexer's Grammar
a LexException
will be returned.
Exceptions
data LexException Source #
Exception thrown when a Lexer
is unable to lex a string.
Instances
Read LexException Source # | |
Defined in Hlex readsPrec :: Int -> ReadS LexException # readList :: ReadS [LexException] # | |
Show LexException Source # | |
Defined in Hlex showsPrec :: Int -> LexException -> ShowS # show :: LexException -> String # showList :: [LexException] -> ShowS # | |
Eq LexException Source # | |
Defined in Hlex (==) :: LexException -> LexException -> Bool # (/=) :: LexException -> LexException -> Bool # |