Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Lua.Parser
- parseLua :: String -> String -> Chunk NodeInfo
- parseLuaWith :: LuaGrammar f -> String -> String -> f NodeInfo
- data LuaParseException
- = LuaLexException !Pos
- | LuaParseException !FilePath !(Report String [L Token])
- | LuaAmbiguousParseException !FilePath !(Report String [L Token])
- type LuaGrammar f = forall r. Grammar r (Prod r String (L Token) (f NodeInfo))
- luaChunk :: LuaGrammar Chunk
- luaStatement :: LuaGrammar Statement
- luaExpression :: LuaGrammar Expression
- data NodeInfo = NodeInfo {}
- nodeLoc :: Lens' NodeInfo Loc
- nodeTokens :: Lens' NodeInfo (Seq (L Token))
- data Report e i :: * -> * -> * = Report {
- position :: Int
- expected :: [e]
- unconsumed :: i
- data Result s e i a :: * -> * -> * -> * -> *
- allParses :: (forall s. ST s (i -> ST s (Result s e i a))) -> i -> ([(a, Int)], Report e i)
- fullParses :: ListLike i t => (forall s. ST s (i -> ST s (Result s e i a))) -> i -> ([a], Report e i)
- parser :: ListLike i t => (forall r. Grammar r (Prod r e t a)) -> ST s (i -> ST s (Result s e i a))
- report :: ListLike i t => (forall s. ST s (i -> ST s (Result s e i a))) -> i -> Report e i
Lua parsers
Parse a Lua file. May throw LuaParseException
.
parseLua
=parseLuaWith
luaChunk
Arguments
:: LuaGrammar f | Grammar to parse with. |
-> String | Source filename (used in locations). |
-> String | Source contents. |
-> f NodeInfo |
Parse Lua code with the given grammar. May throw LuaParseException
.
>>>
parseLuaWith luaExprssion "" "5+5"
Binop (NodeInfo { nodeLoc = Loc (Pos "" 1 1 0) (Pos "" 1 3 2) , nodeTokens = fromList [TkIntLit "5",TkPlus,TkIntLit "5"] }) (Plus (NodeInfo { nodeLoc = Loc (Pos "" 1 2 1) (Pos "" 1 2 1) , nodeTokens = fromList [TkPlus] })) (Integer (NodeInfo { nodeLoc = Loc (Pos "" 1 1 0) (Pos "" 1 1 0) , nodeTokens = fromList [TkIntLit "5"] }) "5") (Integer (NodeInfo { nodeLoc = Loc (Pos "" 1 3 2) (Pos "" 1 3 2) , nodeTokens = fromList [TkIntLit "5"] }) "5")
All AST nodes are Functor
s over their annotation:
>>>
(() <$) <$> parseLuaWith luaExpression "" "5+5"
Binop () (Plus ()) (Integer () "5") (Integer () "5")
data LuaParseException Source
Constructors
LuaLexException !Pos | |
LuaParseException !FilePath !(Report String [L Token]) | |
LuaAmbiguousParseException !FilePath !(Report String [L Token]) |
Lua grammars
luaChunk :: LuaGrammar Chunk Source
Grammar for a Lua chunk; i.e. a Lua compilation unit, defined as a list of statements. This is the grammar you should use to parse real Lua code.
luaStatement :: LuaGrammar Statement Source
Grammar for a single Lua statement. Mostly subsumed by luaChunk
.
luaExpression :: LuaGrammar Expression Source
Grammar for a Lua expression. Provided for smaller REPL-like parsing that operates only on expressions.
AST node source location and constituent tokens. The tokens are provided for style-checking purposes; with them, you may assert proper whitespace protocol, alignment, trailing commas on table constructors, and whatever other subjectivities.
Constructors
NodeInfo | |
Earley re-exports
These are provided if you want more control over parsing than what
parseLua
or parseLuaWith
provides.
data Report e i :: * -> * -> *
A parsing report, which contains fields that are useful for presenting errors to the user if a parse is deemed a failure. Note however that we get a report even when we successfully parse something.
Constructors
Report | |
Fields
|
data Result s e i a :: * -> * -> * -> * -> *
The result of a parse.
Constructors
Ended (Report e i) | The parser ended. |
Parsed (ST s [a]) Int i (ST s (Result s e i a)) | The parser parsed a number of |
allParses :: (forall s. ST s (i -> ST s (Result s e i a))) -> i -> ([(a, Int)], Report e i)
Return all parses from the result of a given parser. The result may
contain partial parses. The Int
s are the position at which a result was
produced.
fullParses :: ListLike i t => (forall s. ST s (i -> ST s (Result s e i a))) -> i -> ([a], Report e i)
Return all parses that reached the end of the input from the result of a given parser.