]> git.lizzy.rs Git - metalua.git/blob - metalua/grammar/generator.lua
Merge branch 'master' of ssh://git.eclipse.org/gitroot/koneki/org.eclipse.koneki...
[metalua.git] / metalua / grammar / generator.lua
1 --------------------------------------------------------------------------------
2 -- Copyright (c) 2006-2013 Fabien Fleutot and others.
3 --
4 -- All rights reserved.
5 --
6 -- This program and the accompanying materials are made available
7 -- under the terms of the Eclipse Public License v1.0 which
8 -- accompanies this distribution, and is available at
9 -- http://www.eclipse.org/legal/epl-v10.html
10 --
11 -- This program and the accompanying materials are also made available
12 -- under the terms of the MIT public license which accompanies this
13 -- distribution, and is available at http://www.lua.org/license.html
14 --
15 -- Contributors:
16 --     Fabien Fleutot - API and implementation
17 --
18 --------------------------------------------------------------------------------
19
20 --------------------------------------------------------------------------------
21 --
22 -- Summary: parser generator. Collection of higher order functors,
23 --   which allow to build and combine parsers. Relies on a lexer
24 --   that supports the same API as the one exposed in mll.lua.
25 --
26 --------------------------------------------------------------------------------
27
28 --------------------------------------------------------------------------------
29 --
30 -- Exported API:
31 --
32 -- Parser generators:
33 -- * [gg.sequence()]
34 -- * [gg.multisequence()]
35 -- * [gg.expr()]
36 -- * [gg.list()]
37 -- * [gg.onkeyword()]
38 -- * [gg.optkeyword()]
39 --
40 -- Other functions:
41 -- * [gg.parse_error()]
42 -- * [gg.make_parser()]
43 -- * [gg.is_parser()]
44 --
45 --------------------------------------------------------------------------------
46
47 local M = { }
48
49 local lexer = require 'metalua.grammar.lexer'
50
51 --------------------------------------------------------------------------------
52 -- Symbol generator: [gensym()] returns a guaranteed-to-be-unique identifier.
53 -- The main purpose is to avoid variable capture in macros.
54 --
55 -- If a string is passed as an argument, theis string will be part of the
56 -- id name (helpful for macro debugging)
57 --------------------------------------------------------------------------------
58 local gensymidx = 0
59
60 function M.gensym (arg)
61    gensymidx = gensymidx + 1
62    return { tag="Id", string.format(".%i.%s", gensymidx, arg or "")}
63 end
64
65
66 -------------------------------------------------------------------------------
67 -- parser metatable, which maps __call to method parse, and adds some
68 -- error tracing boilerplate.
69 -------------------------------------------------------------------------------
70 local parser_metatable = { }
71
72 function parser_metatable :__call (lx, ...)
73     return self :parse (lx, ...)
74 end
75
76 -------------------------------------------------------------------------------
77 -- Turn a table into a parser, mainly by setting the metatable.
78 -------------------------------------------------------------------------------
79 function M.make_parser(kind, p)
80    p.kind = kind
81    if not p.transformers then p.transformers = { } end
82    function p.transformers:add (x)
83       table.insert (self, x)
84    end
85    setmetatable (p, parser_metatable)
86    return p
87 end
88
89 -------------------------------------------------------------------------------
90 -- Return true iff [x] is a parser.
91 -- If it's a gg-generated parser, return the name of its kind.
92 -------------------------------------------------------------------------------
93 function M.is_parser (x)
94    return type(x)=="function" or getmetatable(x)==parser_metatable and x.kind
95 end
96
97 -------------------------------------------------------------------------------
98 -- Parse a sequence, without applying builder nor transformers.
99 -------------------------------------------------------------------------------
100 local function raw_parse_sequence (lx, p)
101     local r = { }
102     for i=1, #p do
103         local e=p[i]
104         if type(e) == "string" then
105             local kw = lx :next()
106             if not lx :is_keyword (kw, e) then
107                 M.parse_error(
108                     lx, "A keyword was expected, probably `%s'.", e)
109             end
110         elseif M.is_parser (e) then
111             table.insert (r, e(lx))
112         else -- Invalid parser definition, this is *not* a parsing error
113             error(string.format(
114                       "Sequence `%s': element #%i is neither a string nor a parser: %s",
115                       p.name, i, table.tostring(e)))
116         end
117     end
118     return r
119 end
120
121 -------------------------------------------------------------------------------
122 -- Parse a multisequence, without applying multisequence transformers.
123 -- The sequences are completely parsed.
124 -------------------------------------------------------------------------------
125 local function raw_parse_multisequence (lx, sequence_table, default)
126    local seq_parser = sequence_table[lx:is_keyword(lx:peek())]
127    if seq_parser  then return seq_parser (lx)
128    elseif default then return default (lx)
129    else return false end
130 end
131
132 -------------------------------------------------------------------------------
133 -- Applies all transformers listed in parser on ast.
134 -------------------------------------------------------------------------------
135 local function transform (ast, parser, fli, lli)
136    if parser.transformers then
137       for _, t in ipairs (parser.transformers) do ast = t(ast) or ast end
138    end
139    if type(ast) == 'table' then
140       local ali = ast.lineinfo
141       if not ali or ali.first~=fli or ali.last~=lli then
142          ast.lineinfo = lexer.new_lineinfo(fli, lli)
143       end
144    end
145    return ast
146 end
147
148 -------------------------------------------------------------------------------
149 -- Generate a tracable parsing error (not implemented yet)
150 -------------------------------------------------------------------------------
151 function M.parse_error(lx, fmt, ...)
152    local li = lx:lineinfo_left()
153    local file, line, column, offset, positions
154    if li then
155       file, line, column, offset = li.source, li.line, li.column, li.offset
156       positions = { first = li, last = li }
157    else
158       line, column, offset = -1, -1, -1
159    end
160
161    local msg  = string.format("line %i, char %i: "..fmt, line, column, ...)
162    if file and file~='?' then msg = "file "..file..", "..msg end
163
164    local src = lx.src
165    if offset>0 and src then
166       local i, j = offset, offset
167       while src:sub(i,i) ~= '\n' and i>=0    do i=i-1 end
168       while src:sub(j,j) ~= '\n' and j<=#src do j=j+1 end
169       local srcline = src:sub (i+1, j-1)
170       local idx  = string.rep (" ", column).."^"
171       msg = string.format("%s\n>>> %s\n>>> %s", msg, srcline, idx)
172    end
173    --lx :kill()
174    error(msg)
175 end
176
177 -------------------------------------------------------------------------------
178 --
179 -- Sequence parser generator
180 --
181 -------------------------------------------------------------------------------
182 -- Input fields:
183 --
184 -- * [builder]: how to build an AST out of sequence parts. let [x] be the list
185 --   of subparser results (keywords are simply omitted). [builder] can be:
186 --    - [nil], in which case the result of parsing is simply [x]
187 --    - a string, which is then put as a tag on [x]
188 --    - a function, which takes [x] as a parameter and returns an AST.
189 --
190 -- * [name]: the name of the parser. Used for debug messages
191 --
192 -- * [transformers]: a list of AST->AST functions, applied in order on ASTs
193 --   returned by the parser.
194 --
195 -- * Table-part entries corresponds to keywords (strings) and subparsers
196 --   (function and callable objects).
197 --
198 -- After creation, the following fields are added:
199 -- * [parse] the parsing function lexer->AST
200 -- * [kind] == "sequence"
201 -- * [name] is set, if it wasn't in the input.
202 --
203 -------------------------------------------------------------------------------
204 function M.sequence (p)
205    M.make_parser ("sequence", p)
206
207    -------------------------------------------------------------------
208    -- Parsing method
209    -------------------------------------------------------------------
210    function p:parse (lx)
211
212       -- Raw parsing:
213       local fli = lx:lineinfo_right()
214       local seq = raw_parse_sequence (lx, self)
215       local lli = lx:lineinfo_left()
216
217       -- Builder application:
218       local builder, tb = self.builder, type (self.builder)
219       if tb == "string" then seq.tag = builder
220       elseif tb == "function" or builder and builder.__call then seq = builder(seq)
221       elseif builder == nil then -- nothing
222       else error ("Invalid builder of type "..tb.." in sequence") end
223       seq = transform (seq, self, fli, lli)
224       assert (not seq or seq.lineinfo)
225       return seq
226    end
227
228    -------------------------------------------------------------------
229    -- Construction
230    -------------------------------------------------------------------
231    -- Try to build a proper name
232    if p.name then
233       -- don't touch existing name
234    elseif type(p[1])=="string" then -- find name based on 1st keyword
235       if #p==1 then p.name=p[1]
236       elseif type(p[#p])=="string" then
237          p.name = p[1] .. " ... " .. p[#p]
238       else p.name = p[1] .. " ..." end
239    else -- can't find a decent name
240       p.name = "unnamed_sequence"
241    end
242
243    return p
244 end --</sequence>
245
246
247 -------------------------------------------------------------------------------
248 --
249 -- Multiple, keyword-driven, sequence parser generator
250 --
251 -------------------------------------------------------------------------------
252 -- in [p], useful fields are:
253 --
254 -- * [transformers]: as usual
255 --
256 -- * [name]: as usual
257 --
258 -- * Table-part entries must be sequence parsers, or tables which can
259 --   be turned into a sequence parser by [gg.sequence]. These
260 --   sequences must start with a keyword, and this initial keyword
261 --   must be different for each sequence.  The table-part entries will
262 --   be removed after [gg.multisequence] returns.
263 --
264 -- * [default]: the parser to run if the next keyword in the lexer is
265 --   none of the registered initial keywords. If there's no default
266 --   parser and no suitable initial keyword, the multisequence parser
267 --   simply returns [false].
268 --
269 -- After creation, the following fields are added:
270 --
271 -- * [parse] the parsing function lexer->AST
272 --
273 -- * [sequences] the table of sequences, indexed by initial keywords.
274 --
275 -- * [add] method takes a sequence parser or a config table for
276 --   [gg.sequence], and adds/replaces the corresponding sequence
277 --   parser. If the keyword was already used, the former sequence is
278 --   removed and a warning is issued.
279 --
280 -- * [get] method returns a sequence by its initial keyword
281 --
282 -- * [kind] == "multisequence"
283 --
284 -------------------------------------------------------------------------------
285 function M.multisequence (p)
286    M.make_parser ("multisequence", p)
287
288    -------------------------------------------------------------------
289    -- Add a sequence (might be just a config table for [gg.sequence])
290    -------------------------------------------------------------------
291    function p :add (s)
292       -- compile if necessary:
293       local keyword = type(s)=='table' and s[1]
294       if type(s)=='table' and not M.is_parser(s) then M.sequence(s) end
295       if M.is_parser(s)~='sequence' or type(keyword)~='string' then
296          if self.default then -- two defaults
297             error ("In a multisequence parser, all but one sequences "..
298                    "must start with a keyword")
299          else self.default = s end -- first default
300      else
301          if self.sequences[keyword] then -- duplicate keyword
302              -- TODO: warn that initial keyword `keyword` is overloaded in multiseq
303          end
304          self.sequences[keyword] = s
305      end
306    end -- </multisequence.add>
307
308    -------------------------------------------------------------------
309    -- Get the sequence starting with this keyword. [kw :: string]
310    -------------------------------------------------------------------
311    function p :get (kw) return self.sequences [kw] end
312
313    -------------------------------------------------------------------
314    -- Remove the sequence starting with keyword [kw :: string]
315    -------------------------------------------------------------------
316    function p :del (kw)
317       if not self.sequences[kw] then
318           -- TODO: warn that we try to delete a non-existent entry
319       end
320       local removed = self.sequences[kw]
321       self.sequences[kw] = nil
322       return removed
323    end
324
325    -------------------------------------------------------------------
326    -- Parsing method
327    -------------------------------------------------------------------
328    function p :parse (lx)
329       local fli = lx:lineinfo_right()
330       local x = raw_parse_multisequence (lx, self.sequences, self.default)
331       local lli = lx:lineinfo_left()
332       return transform (x, self, fli, lli)
333    end
334
335    -------------------------------------------------------------------
336    -- Construction
337    -------------------------------------------------------------------
338    -- Register the sequences passed to the constructor. They're going
339    -- from the array part of the parser to the hash part of field
340    -- [sequences]
341    p.sequences = { }
342    for i=1, #p do p :add (p[i]); p[i] = nil end
343
344    -- FIXME: why is this commented out?
345    --if p.default and not is_parser(p.default) then sequence(p.default) end
346    return p
347 end --</multisequence>
348
349
350 -------------------------------------------------------------------------------
351 --
352 -- Expression parser generator
353 --
354 -------------------------------------------------------------------------------
355 --
356 -- Expression configuration relies on three tables: [prefix], [infix]
357 -- and [suffix]. Moreover, the primary parser can be replaced by a
358 -- table: in this case the [primary] table will be passed to
359 -- [gg.multisequence] to create a parser.
360 --
361 -- Each of these tables is a modified multisequence parser: the
362 -- differences with respect to regular multisequence config tables are:
363 --
364 -- * the builder takes specific parameters:
365 --   - for [prefix], it takes the result of the prefix sequence parser,
366 --     and the prefixed expression
367 --   - for [infix], it takes the left-hand-side expression, the results
368 --     of the infix sequence parser, and the right-hand-side expression.
369 --   - for [suffix], it takes the suffixed expression, and the result
370 --     of the suffix sequence parser.
371 --
372 -- * the default field is a list, with parameters:
373 --   - [parser] the raw parsing function
374 --   - [transformers], as usual
375 --   - [prec], the operator's precedence
376 --   - [assoc] for [infix] table, the operator's associativity, which
377 --     can be "left", "right" or "flat" (default to left)
378 --
379 -- In [p], useful fields are:
380 -- * [transformers]: as usual
381 -- * [name]: as usual
382 -- * [primary]: the atomic expression parser, or a multisequence config
383 --   table (mandatory)
384 -- * [prefix]:  prefix  operators config table, see above.
385 -- * [infix]:   infix   operators config table, see above.
386 -- * [suffix]: suffix operators config table, see above.
387 --
388 -- After creation, these fields are added:
389 -- * [kind] == "expr"
390 -- * [parse] as usual
391 -- * each table is turned into a multisequence, and therefore has an
392 --   [add] method
393 --
394 -------------------------------------------------------------------------------
395 function M.expr (p)
396    M.make_parser ("expr", p)
397
398    -------------------------------------------------------------------
399    -- parser method.
400    -- In addition to the lexer, it takes an optional precedence:
401    -- it won't read expressions whose precedence is lower or equal
402    -- to [prec].
403    -------------------------------------------------------------------
404    function p :parse (lx, prec)
405       prec = prec or 0
406
407       ------------------------------------------------------
408       -- Extract the right parser and the corresponding
409       -- options table, for (pre|in|suff)fix operators.
410       -- Options include prec, assoc, transformers.
411       ------------------------------------------------------
412       local function get_parser_info (tab)
413          local p2 = tab :get (lx :is_keyword (lx :peek()))
414          if p2 then -- keyword-based sequence found
415             local function parser(lx) return raw_parse_sequence(lx, p2) end
416             return parser, p2
417          else -- Got to use the default parser
418             local d = tab.default
419             if d then return d.parse or d.parser, d
420             else return false, false end
421          end
422       end
423
424       ------------------------------------------------------
425       -- Look for a prefix sequence. Multiple prefixes are
426       -- handled through the recursive [p.parse] call.
427       -- Notice the double-transform: one for the primary
428       -- expr, and one for the one with the prefix op.
429       ------------------------------------------------------
430       local function handle_prefix ()
431          local fli = lx :lineinfo_right()
432          local p2_func, p2 = get_parser_info (self.prefix)
433          local op = p2_func and p2_func (lx)
434          if op then -- Keyword-based sequence found
435             local ili = lx :lineinfo_right() -- Intermediate LineInfo
436             local e = p2.builder (op, self :parse (lx, p2.prec))
437             local lli = lx :lineinfo_left()
438             return transform (transform (e, p2, ili, lli), self, fli, lli)
439          else -- No prefix found, get a primary expression
440             local e = self.primary(lx)
441             local lli = lx :lineinfo_left()
442             return transform (e, self, fli, lli)
443          end
444       end --</expr.parse.handle_prefix>
445
446       ------------------------------------------------------
447       -- Look for an infix sequence+right-hand-side operand.
448       -- Return the whole binary expression result,
449       -- or false if no operator was found.
450       ------------------------------------------------------
451       local function handle_infix (e)
452          local p2_func, p2 = get_parser_info (self.infix)
453          if not p2 then return false end
454
455          -----------------------------------------
456          -- Handle flattening operators: gather all operands
457          -- of the series in [list]; when a different operator
458          -- is found, stop, build from [list], [transform] and
459          -- return.
460          -----------------------------------------
461          if (not p2.prec or p2.prec>prec) and p2.assoc=="flat" then
462             local fli = lx:lineinfo_right()
463             local pflat, list = p2, { e }
464             repeat
465                local op = p2_func(lx)
466                if not op then break end
467                table.insert (list, self:parse (lx, p2.prec))
468                local _ -- We only care about checking that p2==pflat
469                _, p2 = get_parser_info (self.infix)
470             until p2 ~= pflat
471             local e2 = pflat.builder (list)
472             local lli = lx:lineinfo_left()
473             return transform (transform (e2, pflat, fli, lli), self, fli, lli)
474
475          -----------------------------------------
476          -- Handle regular infix operators: [e] the LHS is known,
477          -- just gather the operator and [e2] the RHS.
478          -- Result goes in [e3].
479          -----------------------------------------
480          elseif p2.prec and p2.prec>prec or
481                 p2.prec==prec and p2.assoc=="right" then
482             local fli = e.lineinfo.first -- lx:lineinfo_right()
483             local op = p2_func(lx)
484             if not op then return false end
485             local e2 = self:parse (lx, p2.prec)
486             local e3 = p2.builder (e, op, e2)
487             local lli = lx:lineinfo_left()
488             return transform (transform (e3, p2, fli, lli), self, fli, lli)
489
490          -----------------------------------------
491          -- Check for non-associative operators, and complain if applicable.
492          -----------------------------------------
493          elseif p2.assoc=="none" and p2.prec==prec then
494             M.parse_error (lx, "non-associative operator!")
495
496          -----------------------------------------
497          -- No infix operator suitable at that precedence
498          -----------------------------------------
499          else return false end
500
501       end --</expr.parse.handle_infix>
502
503       ------------------------------------------------------
504       -- Look for a suffix sequence.
505       -- Return the result of suffix operator on [e],
506       -- or false if no operator was found.
507       ------------------------------------------------------
508       local function handle_suffix (e)
509          -- FIXME bad fli, must take e.lineinfo.first
510          local p2_func, p2 = get_parser_info (self.suffix)
511          if not p2 then return false end
512          if not p2.prec or p2.prec>=prec then
513             --local fli = lx:lineinfo_right()
514             local fli = e.lineinfo.first
515             local op = p2_func(lx)
516             if not op then return false end
517             local lli = lx:lineinfo_left()
518             e = p2.builder (e, op)
519             e = transform (transform (e, p2, fli, lli), self, fli, lli)
520             return e
521          end
522          return false
523       end --</expr.parse.handle_suffix>
524
525       ------------------------------------------------------
526       -- Parser body: read suffix and (infix+operand)
527       -- extensions as long as we're able to fetch more at
528       -- this precedence level.
529       ------------------------------------------------------
530       local e = handle_prefix()
531       repeat
532          local x = handle_suffix (e); e = x or e
533          local y = handle_infix   (e); e = y or e
534       until not (x or y)
535
536       -- No transform: it already happened in operators handling
537       return e
538    end --</expr.parse>
539
540    -------------------------------------------------------------------
541    -- Construction
542    -------------------------------------------------------------------
543    if not p.primary then p.primary=p[1]; p[1]=nil end
544    for _, t in ipairs{ "primary", "prefix", "infix", "suffix" } do
545       if not p[t] then p[t] = { } end
546       if not M.is_parser(p[t]) then M.multisequence(p[t]) end
547    end
548    function p:add(...) return self.primary:add(...) end
549    return p
550 end --</expr>
551
552
553 -------------------------------------------------------------------------------
554 --
555 -- List parser generator
556 --
557 -------------------------------------------------------------------------------
558 -- In [p], the following fields can be provided in input:
559 --
560 -- * [builder]: takes list of subparser results, returns AST
561 -- * [transformers]: as usual
562 -- * [name]: as usual
563 --
564 -- * [terminators]: list of strings representing the keywords which
565 --   might mark the end of the list. When non-empty, the list is
566 --   allowed to be empty. A string is treated as a single-element
567 --   table, whose element is that string, e.g. ["do"] is the same as
568 --   [{"do"}].
569 --
570 -- * [separators]: list of strings representing the keywords which can
571 --   separate elements of the list. When non-empty, one of these
572 --   keyword has to be found between each element. Lack of a separator
573 --   indicates the end of the list. A string is treated as a
574 --   single-element table, whose element is that string, e.g. ["do"]
575 --   is the same as [{"do"}]. If [terminators] is empty/nil, then
576 --   [separators] has to be non-empty.
577 --
578 -- After creation, the following fields are added:
579 -- * [parse] the parsing function lexer->AST
580 -- * [kind] == "list"
581 --
582 -------------------------------------------------------------------------------
583 function M.list (p)
584    M.make_parser ("list", p)
585
586    -------------------------------------------------------------------
587    -- Parsing method
588    -------------------------------------------------------------------
589    function p :parse (lx)
590
591       ------------------------------------------------------
592       -- Used to quickly check whether there's a terminator
593       -- or a separator immediately ahead
594       ------------------------------------------------------
595       local function peek_is_in (keywords)
596          return keywords and lx:is_keyword(lx:peek(), unpack(keywords)) end
597
598       local x = { }
599       local fli = lx :lineinfo_right()
600
601       -- if there's a terminator to start with, don't bother trying
602       local is_empty_list = self.terminators and (peek_is_in (self.terminators) or lx:peek().tag=="Eof")
603       if not is_empty_list then
604          repeat
605              local item = self.primary(lx)
606              table.insert (x, item) -- read one element
607          until
608             -- There's a separator list specified, and next token isn't in it.
609             -- Otherwise, consume it with [lx:next()]
610             self.separators and not(peek_is_in (self.separators) and lx:next()) or
611             -- Terminator token ahead
612             peek_is_in (self.terminators) or
613             -- Last reason: end of file reached
614             lx:peek().tag=="Eof"
615       end
616
617       local lli = lx:lineinfo_left()
618
619       -- Apply the builder. It can be a string, or a callable value,
620       -- or simply nothing.
621       local b = self.builder
622       if b then
623          if type(b)=="string" then x.tag = b -- b is a string, use it as a tag
624          elseif type(b)=="function" then x=b(x)
625          else
626             local bmt = getmetatable(b)
627             if bmt and bmt.__call then x=b(x) end
628          end
629       end
630       return transform (x, self, fli, lli)
631    end --</list.parse>
632
633    -------------------------------------------------------------------
634    -- Construction
635    -------------------------------------------------------------------
636    if not p.primary then p.primary = p[1]; p[1] = nil end
637    if type(p.terminators) == "string" then p.terminators = { p.terminators }
638    elseif p.terminators and #p.terminators == 0 then p.terminators = nil end
639    if type(p.separators) == "string" then p.separators = { p.separators }
640    elseif p.separators and #p.separators == 0 then p.separators = nil end
641
642    return p
643 end --</list>
644
645
646 -------------------------------------------------------------------------------
647 --
648 -- Keyword-conditioned parser generator
649 --
650 -------------------------------------------------------------------------------
651 --
652 -- Only apply a parser if a given keyword is found. The result of
653 -- [gg.onkeyword] parser is the result of the subparser (modulo
654 -- [transformers] applications).
655 --
656 -- lineinfo: the keyword is *not* included in the boundaries of the
657 -- resulting lineinfo. A review of all usages of gg.onkeyword() in the
658 -- implementation of metalua has shown that it was the appropriate choice
659 -- in every case.
660 --
661 -- Input fields:
662 --
663 -- * [name]: as usual
664 --
665 -- * [transformers]: as usual
666 --
667 -- * [peek]: if non-nil, the conditioning keyword is left in the lexeme
668 --   stream instead of being consumed.
669 --
670 -- * [primary]: the subparser.
671 --
672 -- * [keywords]: list of strings representing triggering keywords.
673 --
674 -- * Table-part entries can contain strings, and/or exactly one parser.
675 --   Strings are put in [keywords], and the parser is put in [primary].
676 --
677 -- After the call, the following fields will be set:
678 --
679 -- * [parse] the parsing method
680 -- * [kind] == "onkeyword"
681 -- * [primary]
682 -- * [keywords]
683 --
684 -------------------------------------------------------------------------------
685 function M.onkeyword (p)
686    M.make_parser ("onkeyword", p)
687
688    -------------------------------------------------------------------
689    -- Parsing method
690    -------------------------------------------------------------------
691    function p :parse (lx)
692       if lx :is_keyword (lx:peek(), unpack(self.keywords)) then
693          local fli = lx:lineinfo_right()
694          if not self.peek then lx:next() end
695          local content = self.primary (lx)
696          local lli = lx:lineinfo_left()
697          local li = content.lineinfo or { }
698          fli, lli = li.first or fli, li.last or lli
699          return transform (content, p, fli, lli)
700       else return false end
701    end
702
703    -------------------------------------------------------------------
704    -- Construction
705    -------------------------------------------------------------------
706    if not p.keywords then p.keywords = { } end
707    for _, x in ipairs(p) do
708       if type(x)=="string" then table.insert (p.keywords, x)
709       else assert (not p.primary and M.is_parser (x)); p.primary = x end
710    end
711    assert (next (p.keywords), "Missing trigger keyword in gg.onkeyword")
712    assert (p.primary, 'no primary parser in gg.onkeyword')
713    return p
714 end --</onkeyword>
715
716
717 -------------------------------------------------------------------------------
718 --
719 -- Optional keyword consummer pseudo-parser generator
720 --
721 -------------------------------------------------------------------------------
722 --
723 -- This doesn't return a real parser, just a function. That function parses
724 -- one of the keywords passed as parameters, and returns it. It returns
725 -- [false] if no matching keyword is found.
726 --
727 -- Notice that tokens returned by lexer already carry lineinfo, therefore
728 -- there's no need to add them, as done usually through transform() calls.
729 -------------------------------------------------------------------------------
730 function M.optkeyword (...)
731    local args = {...}
732    if type (args[1]) == "table" then
733       assert (#args == 1)
734       args = args[1]
735    end
736    for _, v in ipairs(args) do assert (type(v)=="string") end
737    return function (lx)
738       local x = lx:is_keyword (lx:peek(), unpack (args))
739       if x then lx:next(); return x
740       else return false end
741    end
742 end
743
744
745 -------------------------------------------------------------------------------
746 --
747 -- Run a parser with a special lexer
748 --
749 -------------------------------------------------------------------------------
750 --
751 -- This doesn't return a real parser, just a function.
752 -- First argument is the lexer class to be used with the parser,
753 -- 2nd is the parser itself.
754 -- The resulting parser returns whatever the argument parser does.
755 --
756 -------------------------------------------------------------------------------
757 function M.with_lexer(new_lexer, parser)
758
759    -------------------------------------------------------------------
760    -- Most gg functions take their parameters in a table, so it's
761    -- better to silently accept when with_lexer{ } is called with
762    -- its arguments in a list:
763    -------------------------------------------------------------------
764    if not parser and #new_lexer==2 and type(new_lexer[1])=='table' then
765       return M.with_lexer(unpack(new_lexer))
766    end
767
768    -------------------------------------------------------------------
769    -- Save the current lexer, switch it for the new one, run the parser,
770    -- restore the previous lexer, even if the parser caused an error.
771    -------------------------------------------------------------------
772    return function (lx)
773       local old_lexer = getmetatable(lx)
774       lx:sync()
775       setmetatable(lx, new_lexer)
776       local status, result = pcall(parser, lx)
777       lx:sync()
778       setmetatable(lx, old_lexer)
779       if status then return result else error(result) end
780    end
781 end
782
783 --------------------------------------------------------------------------------
784 --
785 -- Make sure a parser is used and returns successfully.
786 --
787 --------------------------------------------------------------------------------
788 function M.nonempty(primary)
789     local p = M.make_parser('non-empty list', { primary = primary, name=primary.name })
790     function p :parse (lx)
791          local fli = lx:lineinfo_right()
792          local content = self.primary (lx)
793          local lli = lx:lineinfo_left()
794          local li = content.lineinfo or { }
795          fli, lli = li.first or fli, li.last or lli
796          if #content == 0 then
797            M.parse_error (lx, "`%s' must not be empty.", self.name or "list")
798        else
799            return transform (content, self, fli, lli)
800        end
801     end
802     return p
803 end
804
805 local FUTURE_MT = { }
806 function FUTURE_MT:__tostring() return "<Proxy parser module>" end
807 function FUTURE_MT:__newindex(key, value) error "don't write in futures" end
808 function FUTURE_MT :__index (parser_name)
809     return function(...)
810         local p, m = rawget(self, '__path'), self.__module
811         if p then for _, name in ipairs(p) do
812             m=rawget(m, name)
813             if not m then error ("Submodule '"..name.."' undefined") end
814         end end
815         local f = rawget(m, parser_name)
816         if not f then error ("Parser '"..parser_name.."' undefined") end
817         return f(...)
818     end
819 end
820
821 function M.future(module, ...)
822     checks('table')
823     local path = ... and {...}
824     if path then for _, x in ipairs(path) do 
825         assert(type(x)=='string', "Bad future arg")
826     end end
827     local self = { __module = module,
828                    __path   = path }
829     return setmetatable(self, FUTURE_MT)
830 end
831
832 return M