glualint-1.24.6: Attempts to fix your syntax erroring Lua files.
Safe HaskellSafe-Inferred
LanguageHaskell2010

GLua.Parser

Description

Synopsis

Documentation

data MTokenPos Source #

MTokens with the positions of the next MToken (used in the advance of parser)

Constructors

MTokenPos MToken Region 

Instances

Instances details
Show MTokenPos Source # 
Instance details

Defined in GLua.Parser

IsLocationUpdatedBy RegionProgression MTokenPos Source #

RegionProgression is a location that can be updated by MTokens

Instance details

Defined in GLua.Parser

data RegionProgression Source #

Instances

Instances details
Show RegionProgression Source # 
Instance details

Defined in GLua.Parser

IsLocationUpdatedBy RegionProgression MTokenPos Source #

RegionProgression is a location that can be updated by MTokens

Instance details

Defined in GLua.Parser

type AParser a = P (Str MTokenPos [MTokenPos] RegionProgression) a Source #

Custom parser that parses MTokens

parseGLua :: [MToken] -> (AST, [Error Region]) Source #

Parse Garry's mod Lua tokens to an abstract syntax tree. Also returns parse errors

parseGLuaFromString :: String -> (AST, [Error Region]) Source #

Parse a string directly into an AST

parseFromString :: AParser a -> String -> (a, [Error Region]) Source #

Parse a string directly

createString :: [MToken] -> Str MTokenPos [MTokenPos] RegionProgression Source #

Create a parsable string from MTokens

pPos' :: AParser Region Source #

Position in Region (as opposed to RegionProgression)

execAParser :: AParser a -> [MToken] -> (a, [Error RegionProgression]) Source #

Text.ParserCombinators.UU.Utils.execParser modified to parse MTokens The first MToken might not be on the first line, so use the first MToken's position to start

pMTok :: Token -> AParser MToken Source #

Parse a single Metatoken, based on a positionless token (much like pSym)

parseNameList :: AParser [MToken] Source #

Parse a list of identifiers

parseParList :: AParser [MToken] Source #

Parse list of function parameters

parseChunk :: [MToken] -> AParser AST Source #

Parses the full AST Its first parameter contains all comments Assumes the mtokens fed to the AParser have no comments

parseBlock :: AParser Block Source #

Parse a block with an optional return value

annotated :: (Region -> a -> b) -> AParser a -> AParser b Source #

A thing of which the region is to be parsed

pInterleaved :: AParser a -> AParser b -> AParser [b] Source #

Parser that is interleaved with 0 or more of the other parser

parseCallDef :: AParser Stat Source #

Behemoth parser that parses either function call statements or global declaration statements Big in size and complexity because prefix expressions are BITCHES The problem lies in the complexity of prefix expressions: hotten.totten["tenten"](tentoonstelling) -- This is a function call hotten.totten["tenten"] = tentoonstelling -- This is a declaration. hotten.totten["tenten"], tentoonstelling = 1, 2 -- This is also a declaration. One may find an arbitrary amount of expression suffixes (indexations/calls) before finding a comma or equals sign that proves that it is a declaration. Also, goto can be an identifier

parseStat :: AParser Stat Source #

Parse a single statement

parseIf :: AParser Stat Source #

Parse if then elseif then else end expressions

parseFor :: AParser Stat Source #

Parse numeric and generic for loops

parseReturn :: AParser AReturn Source #

Parse a return value

parseFuncName :: AParser FuncName Source #

Function name (includes dot indices and meta indices)

parseLocFuncName :: AParser FuncName Source #

Local function name. Does not include dot and meta indices, since they're not allowed in meta functions

parseNumber :: AParser Expr Source #

Parse a number into an expression

parseString :: AParser MToken Source #

Parse any kind of string

pName :: AParser MToken Source #

Parse an identifier

parseVarList :: AParser [PrefixExp] Source #

Parse variable list (var1, var2, var3)

parseLocalVarList :: AParser [PrefixExp] Source #

Parse local variable list (var1, var2, var3), without suffixes

parseExpressionList :: AParser [MExpr] Source #

list of expressions

parseSubExpression :: AParser Expr Source #

Subexpressions, i.e. without operators

parseAnonymFunc :: AParser Expr Source #

Separate parser for anonymous function subexpression

samePrioL :: [(Token, BinOp)] -> AParser MExpr -> AParser MExpr Source #

Parse operators of the same precedence in a chain

parseUnOp :: AParser UnOp Source #

Parse unary operator (-, not, #)

lvl1 :: [(Token, BinOp)] Source #

Operators, sorted by priority Priority from: http://www.lua.org/manual/5.2/manual.html#3.4.7

lvl2 :: [(Token, BinOp)] Source #

Operators, sorted by priority Priority from: http://www.lua.org/manual/5.2/manual.html#3.4.7

lvl3 :: [(Token, BinOp)] Source #

Operators, sorted by priority Priority from: http://www.lua.org/manual/5.2/manual.html#3.4.7

lvl4 :: [(Token, BinOp)] Source #

Operators, sorted by priority Priority from: http://www.lua.org/manual/5.2/manual.html#3.4.7

lvl5 :: [(Token, BinOp)] Source #

Operators, sorted by priority Priority from: http://www.lua.org/manual/5.2/manual.html#3.4.7

lvl6 :: [(Token, BinOp)] Source #

Operators, sorted by priority Priority from: http://www.lua.org/manual/5.2/manual.html#3.4.7

lvl8 :: [(Token, BinOp)] Source #

Operators, sorted by priority Priority from: http://www.lua.org/manual/5.2/manual.html#3.4.7

parseExpression :: AParser MExpr Source #

Parse chains of binary and unary operators

parseBinOp :: AParser BinOp Source #

Parses a binary operator

parsePrefixExp :: AParser PrefixExp Source #

Prefix expressions can have any arbitrary list of expression suffixes

pPrefixExp :: AParser [PFExprSuffix] -> AParser PrefixExp Source #

Prefix expressions The suffixes define rules on the allowed suffixes

pPFExprSuffix :: AParser PFExprSuffix Source #

Parse any expression suffix

pPFExprCallSuffix :: AParser PFExprSuffix Source #

Parse an indexing expression suffix

pPFExprIndexSuffix :: AParser PFExprSuffix Source #

Parse an indexing expression suffix

pFunctionCall :: AParser PrefixExp Source #

Function calls are prefix expressions, but the last suffix MUST be either a function call or a metafunction call

parseVar :: AParser PrefixExp Source #

single variable. Note: definition differs from reference to circumvent the left recursion var ::= Name [{PFExprSuffix}* indexation] | '(' exp ')' {PFExprSuffix}* indexation where "{PFExprSuffix}* indexation" is any arbitrary sequence of prefix expression suffixes that end with an indexation

parseArgs :: AParser Args Source #

Arguments of a function call (including brackets)

parseFieldList :: AParser [Field] Source #

A list of table entries Grammar: field {separator field} [separator]

makeUnNamedField :: Maybe (BinOp, MExpr) -> ExprSuffixList -> (Region, MToken) -> FieldSep -> Field Source #

Makes an unnamed field out of a list of suffixes, a position and a name. This function gets called when we know a field is unnamed and contains an expression that starts with a PrefixExp See the parseField parser where it is used

parseField :: AParser (FieldSep -> Field) Source #

A field in a table