language-lua2-0.1.0.5: Lua parser and pretty printer

Safe HaskellNone
LanguageHaskell2010

Language.Lua.Parser

Contents

Synopsis

Lua parsers

parseLua Source

Arguments

:: String

Source filename (used in locations).

-> String

Source contents.

-> Chunk NodeInfo 

Parse a Lua file. May throw LuaParseException.

parseLua = parseLuaWith luaChunk

parseLuaWith Source

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 Functors over their annotation:

>>> (() <$) <$> parseLuaWith luaExpression "" "5+5"
Binop () (Plus ()) (Integer () "5") (Integer () "5")

Lua grammars

type LuaGrammar f = forall r. Grammar r (Prod r String (L Token) (f NodeInfo)) Source

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.

data NodeInfo Source

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 

Fields

_nodeLoc :: !Loc

Source location; spans the entirety of the node.

_nodeTokens :: !(Seq (L Token))

Parsed tokens involved in node production.

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

position :: Int

The final position in the input (0-based) that the parser reached.

expected :: [e]

The named productions processed at the final position.

unconsumed :: i

The part of the input string that was not consumed, which may be empty.

Instances

(Eq e, Eq i) => Eq (Report e i) 
(Ord e, Ord i) => Ord (Report e i) 
(Read e, Read i) => Read (Report e i) 
(Show e, Show i) => Show (Report e i) 

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 as. These are given as a computation, ST s [a] that constructs the as when run. We can thus save some work by ignoring this computation if we do not care about the results. The Int is the position in the input where these results were obtained, the i the rest of the input, and the last component is the continuation.

Instances

Functor (Result s e i) 

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 Ints 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.

parser :: ListLike i t => (forall r. Grammar r (Prod r e t a)) -> ST s (i -> ST s (Result s e i a))

Create a parser from the given grammar.

report :: ListLike i t => (forall s. ST s (i -> ST s (Result s e i a))) -> i -> Report e i

See e.g. how far the parser is able to parse the input string before it fails. This can be much faster than getting the parse results for highly ambiguous grammars.