BNFC-2.9.4.1: A compiler front-end generator.
Safe HaskellNone
LanguageHaskell2010

BNFC.Lex

Synopsis

Documentation

data AlexAddr Source #

Constructors

AlexA# Addr# 

data AlexAcc user Source #

tok :: (String -> Tok) -> Posn -> String -> Token Source #

Create a token with position.

data Tok Source #

Token without position.

Constructors

TK !TokSymbol

Reserved word or symbol.

TL !String

String literal.

TI !String

Integer literal.

TV !String

Identifier.

TD !String

Float literal.

TC !String

Character literal.

T_Identifier !String 

Instances

Instances details
Eq Tok Source # 
Instance details

Defined in BNFC.Lex

Methods

(==) :: Tok -> Tok -> Bool Source #

(/=) :: Tok -> Tok -> Bool Source #

Ord Tok Source # 
Instance details

Defined in BNFC.Lex

Methods

compare :: Tok -> Tok -> Ordering Source #

(<) :: Tok -> Tok -> Bool Source #

(<=) :: Tok -> Tok -> Bool Source #

(>) :: Tok -> Tok -> Bool Source #

(>=) :: Tok -> Tok -> Bool Source #

max :: Tok -> Tok -> Tok Source #

min :: Tok -> Tok -> Tok Source #

Show Tok Source # 
Instance details

Defined in BNFC.Lex

pattern TS :: String -> Int -> Tok Source #

Smart constructor for Tok for the sake of backwards compatibility.

data TokSymbol Source #

Keyword or symbol tokens have a unique ID.

Constructors

TokSymbol 

Fields

Instances

Instances details
Eq TokSymbol Source #

Keyword/symbol equality is determined by the unique ID.

Instance details

Defined in BNFC.Lex

Ord TokSymbol Source #

Keyword/symbol ordering is determined by the unique ID.

Instance details

Defined in BNFC.Lex

Show TokSymbol Source # 
Instance details

Defined in BNFC.Lex

data Token Source #

Token with position.

Constructors

PT Posn Tok 
Err Posn 

Instances

Instances details
Eq Token Source # 
Instance details

Defined in BNFC.Lex

Methods

(==) :: Token -> Token -> Bool Source #

(/=) :: Token -> Token -> Bool Source #

Ord Token Source # 
Instance details

Defined in BNFC.Lex

Show Token Source # 
Instance details

Defined in BNFC.Lex

printPosn :: Posn -> String Source #

Pretty print a position.

tokenPos :: [Token] -> String Source #

Pretty print the position of the first token in the list.

tokenPosn :: Token -> Posn Source #

Get the position of a token.

tokenLineCol :: Token -> (Int, Int) Source #

Get line and column of a token.

posLineCol :: Posn -> (Int, Int) Source #

Get line and column of a position.

mkPosToken :: Token -> ((Int, Int), String) Source #

Convert a token into "position token" form.

tokenText :: Token -> String Source #

Convert a token to its text.

prToken :: Token -> String Source #

Convert a token to a string.

data BTree Source #

Finite map from text to token organized as binary search tree.

Constructors

N

Nil (leaf).

B String Tok BTree BTree

Binary node.

Instances

Instances details
Show BTree Source # 
Instance details

Defined in BNFC.Lex

eitherResIdent :: (String -> Tok) -> String -> Tok Source #

Convert potential keyword into token or use fallback conversion.

resWords :: BTree Source #

The keywords and symbols of the language organized as binary search tree.

unescapeInitTail :: String -> String Source #

Unquote string literal.

data Posn Source #

Constructors

Pn !Int !Int !Int 

Instances

Instances details
Eq Posn Source # 
Instance details

Defined in BNFC.Lex

Methods

(==) :: Posn -> Posn -> Bool Source #

(/=) :: Posn -> Posn -> Bool Source #

Ord Posn Source # 
Instance details

Defined in BNFC.Lex

Show Posn Source # 
Instance details

Defined in BNFC.Lex

utf8Encode :: Char -> [Word8] Source #

Encode a Haskell String to a list of Word8 values, in UTF8 format.