1 /++
2 This module was automatically generated from the following grammar:
3 
4 
5 # This is the PEG extended grammar used by Pegged
6 Pegged:
7 
8 # Syntactic rules:
9 Grammar      <- Spacing GrammarName Definition+ :eoi
10 Definition   <- LhsName Arrow Expression
11 Expression   <- :OR? Sequence (:OR Sequence)*
12 Sequence     <- Prefix+
13 Prefix       <- (POS / NEG / FUSE / DISCARD / KEEP / DROP / PROPAGATE)* Suffix
14 Suffix       <- Primary (OPTION / ZEROORMORE / ONEORMORE / Action)*
15 Primary      <- !(LhsName Arrow)
16                 ( RhsName
17                 / :OPEN Expression :CLOSE
18                 / Literal
19                 / CharClass
20                 / ANY)
21 # Lexical syntax
22 Identifier   <- identifier
23 GrammarName  <- Identifier ParamList? Spacing :':' Spacing
24 LhsName      <- Identifier ParamList? Spacing
25 RhsName      <- Identifier ArgList? (NAMESEP Identifier ArgList?)* Spacing         # NAMESEP is *not* discarded
26 ParamList    <- :OPEN Param (:SEPARATOR Param)*  :CLOSE
27 Param        <- DefaultParam / SingleParam
28 DefaultParam <- Identifier Spacing :ASSIGN Expression
29 SingleParam  <- Identifier Spacing
30 ArgList      <- :OPEN Expression (:SEPARATOR Expression)* :CLOSE
31 
32 Literal      <- quote       ~(!quote Char)*       quote       Spacing
33               / doublequote ~(!doublequote Char)* doublequote Spacing
34 CharClass    <- :'[' (!']' CharRange)* :']' Spacing
35 CharRange    <- Char '-' Char / Char
36 
37 # Terminals
38 Char         <~ backslash ( quote
39                           / doublequote
40                           / backquote
41                           / backslash
42                           / '-'
43                           / '['
44                           / ']'
45                           / [nrt]
46                           / [0-2][0-7][0-7]
47                           / [0-7][0-7]?
48                           / 'x' hexDigit hexDigit
49                           / 'u' hexDigit hexDigit hexDigit hexDigit
50                           / 'U' hexDigit hexDigit hexDigit hexDigit hexDigit hexDigit hexDigit hexDigit
51                           )
52               / . # or anything else
53 
54 Arrow        <- LEFTARROW / FUSEARROW / DISCARDARROW / KEEPARROW / DROPARROW / PROPAGATEARROW / ACTIONARROW / SPACEARROW
55 LEFTARROW    <- '<-' Spacing
56 FUSEARROW    <- '<~' Spacing
57 DISCARDARROW <- '<:' Spacing
58 KEEPARROW    <- '<^' Spacing
59 DROPARROW    <- '<;' Spacing
60 PROPAGATEARROW <- '<%' Spacing
61 SPACEARROW   <- '<' Spacing
62 ACTIONARROW  <- '<' Action Spacing
63 
64 OR           <- '/' Spacing
65 
66 POS          <- '&' Spacing
67 NEG          <- '!' Spacing
68 FUSE         <- '~' Spacing
69 DISCARD      <- ':' Spacing
70 KEEP         <- '^' Spacing
71 DROP         <- ';' Spacing
72 PROPAGATE    <- '%' Spacing
73 
74 OPTION       <- '?' Spacing
75 ZEROORMORE   <- '*' Spacing
76 ONEORMORE    <- '+' Spacing
77 ACTIONOPEN   <- '{' Spacing
78 ACTIONCLOSE  <- '}' Spacing
79 SEPARATOR    <- ',' Spacing
80 ASSIGN       <- '=' Spacing
81 NAMESEP      <- '.'   # No Spacing
82 OPEN         <- '(' Spacing
83 CLOSE        <- ')' Spacing
84 ANY          <- '.' Spacing
85 Spacing      <: (blank / Comment)*
86 Comment      <- '#' (!eol .)* :eol
87 Space        <- spacing / "\\t" / "\\n" / "\\r"
88 
89 # Action Rule
90 Action      <- :ACTIONOPEN Spacing ((Lambda / qualifiedIdentifier)
91 (:SEPARATOR (Lambda / qualifiedIdentifier))*) Spacing :ACTIONCLOSE
92 Lambda      <~ (!(ACTIONCLOSE/SEPARATOR) (LambdaItems / NestedList('{',LambdaItems,'}') / .))*
93 
94 LambdaItems <- ~DComment / ~DString / ~DParamList
95 DString     <- WYSString / DBQString / TKNString / DLMString
96 
97 WYSString   <- 'r' doublequote (!doublequote .)* doublequote /
98                backquote (!backquote .)* backquote
99 
100 DBQString   <- doublequote (!doublequote Char)* doublequote
101 
102 TKNString   <- (&'q{' ('q' NestedList('{',DString,'}')))
103 
104 DLMString   <- ('q' doublequote) ( (&'{' NestedList('{',DString,'}'))
105                                  / (&'[' NestedList('[',DString,']'))
106                                  / (&'(' NestedList('(',DString,')'))
107                                  / (&'<' NestedList('<',DString,'>'))
108                                  ) doublequote
109 
110 DComment             <- DLineComment / DBlockComment / DNestingBlockComment
111 
112 DLineComment         <- "//" (!endOfLine .)* endOfLine
113 DBlockComment        <- "/*" (!"*/" .)* "*/"
114 DNestingBlockComment <- NestedList("/+","+/")
115 
116 DParamList <- NestedList('(',')')
117 
118 # Linear nested lists with and without special items
119 NestedList(L,Items,R)   <- ^L ( !(L/R/Items) . )* ( Items
120                                                   / NestedList(L,Items,R)
121                                                   / ( !(L/R/Items) . )*
122                                                   )* ( !(L/R/Items) . )* ^R
123 
124 NestedList(L,R) <- ^L ( !(L/R) . )* (NestedList(L,R) / ( !(L/R) . )*)* ( !(L/R) . )* ^R
125 
126 
127 +/
128 module pegged.parser;
129 
130 public import pegged.peg;
131 import std.algorithm: startsWith;
132 import std.functional: toDelegate;
133 
134 struct GenericPegged(TParseTree)
135 {
136     import pegged.dynamic.grammar;
137     struct Pegged
138     {
139     enum name = "Pegged";
140     static ParseTree delegate(ParseTree)[string] before;
141     static ParseTree delegate(ParseTree)[string] after;
142     static ParseTree delegate(ParseTree)[string] rules;
143 
144     static this()
145     {
146         rules["Grammar"] = toDelegate(&Pegged.Grammar);
147         rules["Definition"] = toDelegate(&Pegged.Definition);
148         rules["Expression"] = toDelegate(&Pegged.Expression);
149         rules["Sequence"] = toDelegate(&Pegged.Sequence);
150         rules["Prefix"] = toDelegate(&Pegged.Prefix);
151         rules["Suffix"] = toDelegate(&Pegged.Suffix);
152         rules["Primary"] = toDelegate(&Pegged.Primary);
153         rules["Identifier"] = toDelegate(&Pegged.Identifier);
154         rules["GrammarName"] = toDelegate(&Pegged.GrammarName);
155         rules["LhsName"] = toDelegate(&Pegged.LhsName);
156         rules["RhsName"] = toDelegate(&Pegged.RhsName);
157         rules["ParamList"] = toDelegate(&Pegged.ParamList);
158         rules["Param"] = toDelegate(&Pegged.Param);
159         rules["DefaultParam"] = toDelegate(&Pegged.DefaultParam);
160         rules["SingleParam"] = toDelegate(&Pegged.SingleParam);
161         rules["ArgList"] = toDelegate(&Pegged.ArgList);
162         rules["Literal"] = toDelegate(&Pegged.Literal);
163         rules["CharClass"] = toDelegate(&Pegged.CharClass);
164         rules["CharRange"] = toDelegate(&Pegged.CharRange);
165         rules["Char"] = toDelegate(&Pegged.Char);
166         rules["Arrow"] = toDelegate(&Pegged.Arrow);
167         rules["LEFTARROW"] = toDelegate(&Pegged.LEFTARROW);
168         rules["FUSEARROW"] = toDelegate(&Pegged.FUSEARROW);
169         rules["DISCARDARROW"] = toDelegate(&Pegged.DISCARDARROW);
170         rules["KEEPARROW"] = toDelegate(&Pegged.KEEPARROW);
171         rules["DROPARROW"] = toDelegate(&Pegged.DROPARROW);
172         rules["PROPAGATEARROW"] = toDelegate(&Pegged.PROPAGATEARROW);
173         rules["SPACEARROW"] = toDelegate(&Pegged.SPACEARROW);
174         rules["ACTIONARROW"] = toDelegate(&Pegged.ACTIONARROW);
175         rules["OR"] = toDelegate(&Pegged.OR);
176         rules["POS"] = toDelegate(&Pegged.POS);
177         rules["NEG"] = toDelegate(&Pegged.NEG);
178         rules["FUSE"] = toDelegate(&Pegged.FUSE);
179         rules["DISCARD"] = toDelegate(&Pegged.DISCARD);
180         rules["KEEP"] = toDelegate(&Pegged.KEEP);
181         rules["DROP"] = toDelegate(&Pegged.DROP);
182         rules["PROPAGATE"] = toDelegate(&Pegged.PROPAGATE);
183         rules["OPTION"] = toDelegate(&Pegged.OPTION);
184         rules["ZEROORMORE"] = toDelegate(&Pegged.ZEROORMORE);
185         rules["ONEORMORE"] = toDelegate(&Pegged.ONEORMORE);
186         rules["ACTIONOPEN"] = toDelegate(&Pegged.ACTIONOPEN);
187         rules["ACTIONCLOSE"] = toDelegate(&Pegged.ACTIONCLOSE);
188         rules["SEPARATOR"] = toDelegate(&Pegged.SEPARATOR);
189         rules["ASSIGN"] = toDelegate(&Pegged.ASSIGN);
190         rules["NAMESEP"] = toDelegate(&Pegged.NAMESEP);
191         rules["OPEN"] = toDelegate(&Pegged.OPEN);
192         rules["CLOSE"] = toDelegate(&Pegged.CLOSE);
193         rules["ANY"] = toDelegate(&Pegged.ANY);
194         rules["Spacing"] = toDelegate(&Pegged.Spacing);
195    }
196 
197     template hooked(alias r, string name)
198     {
199         static ParseTree hooked(ParseTree p)
200         {
201             ParseTree result;
202 
203             if (name in before)
204             {
205                 result = before[name](p);
206                 if (result.successful)
207                     return result;
208             }
209 
210             result = r(p);
211             if (result.successful || name !in after)
212                 return result;
213 
214             result = after[name](p);
215             return result;
216         }
217 
218         static ParseTree hooked(string input)
219         {
220             return hooked!(r, name)(ParseTree("",false,[],input));
221         }
222     }
223 
224     static void addRuleBefore(string parentRule, string ruleSyntax)
225     {
226         // enum name is the current grammar name
227         DynamicGrammar dg = pegged.dynamic.grammar.grammar(name ~ ": " ~ ruleSyntax, rules);
228         foreach(ruleName,rule; dg.rules)
229             if (ruleName != "Spacing") // Keep the local Spacing rule, do not overwrite it
230                 rules[ruleName] = rule;
231         before[parentRule] = rules[dg.startingRule];
232     }
233 
234     static void addRuleAfter(string parentRule, string ruleSyntax)
235     {
236         // enum name is the current grammar named
237         DynamicGrammar dg = pegged.dynamic.grammar.grammar(name ~ ": " ~ ruleSyntax, rules);
238         foreach(name,rule; dg.rules)
239         {
240             if (name != "Spacing")
241                 rules[name] = rule;
242         }
243         after[parentRule] = rules[dg.startingRule];
244     }
245 
246     static bool isRule(string s)
247     {
248         return s.startsWith("Pegged.");
249     }
250     mixin decimateTree;
251     static TParseTree Grammar(TParseTree p)
252     {
253         if(__ctfe)
254             return         pegged.peg.named!(pegged.peg.and!(Spacing, GrammarName, pegged.peg.oneOrMore!(Definition), pegged.peg.discard!(eoi)), "Pegged.Grammar")(p);
255         else
256             return hooked!(pegged.peg.named!(pegged.peg.and!(Spacing, GrammarName, pegged.peg.oneOrMore!(Definition), pegged.peg.discard!(eoi)), "Pegged.Grammar"), "Grammar")(p);
257     }
258     static TParseTree Grammar(string s)
259     {
260         if(__ctfe)
261             return         pegged.peg.named!(pegged.peg.and!(Spacing, GrammarName, pegged.peg.oneOrMore!(Definition), pegged.peg.discard!(eoi)), "Pegged.Grammar")(TParseTree("", false,[], s));
262         else
263             return hooked!(pegged.peg.named!(pegged.peg.and!(Spacing, GrammarName, pegged.peg.oneOrMore!(Definition), pegged.peg.discard!(eoi)), "Pegged.Grammar"), "Grammar")(TParseTree("", false,[], s));
264     }
265     static string Grammar(GetName g)
266     {
267         return "Pegged.Grammar";
268     }
269 
270     static TParseTree Definition(TParseTree p)
271     {
272         if(__ctfe)
273             return         pegged.peg.named!(pegged.peg.and!(LhsName, Arrow, Expression), "Pegged.Definition")(p);
274         else
275             return hooked!(pegged.peg.named!(pegged.peg.and!(LhsName, Arrow, Expression), "Pegged.Definition"), "Definition")(p);
276     }
277     static TParseTree Definition(string s)
278     {
279         if(__ctfe)
280             return         pegged.peg.named!(pegged.peg.and!(LhsName, Arrow, Expression), "Pegged.Definition")(TParseTree("", false,[], s));
281         else
282             return hooked!(pegged.peg.named!(pegged.peg.and!(LhsName, Arrow, Expression), "Pegged.Definition"), "Definition")(TParseTree("", false,[], s));
283     }
284     static string Definition(GetName g)
285     {
286         return "Pegged.Definition";
287     }
288 
289     static TParseTree Expression(TParseTree p)
290     {
291         if(__ctfe)
292             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(pegged.peg.option!(OR)), Sequence, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(OR), Sequence))), "Pegged.Expression")(p);
293         else
294             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(pegged.peg.option!(OR)), Sequence, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(OR), Sequence))), "Pegged.Expression"), "Expression")(p);
295     }
296     static TParseTree Expression(string s)
297     {
298         if(__ctfe)
299             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(pegged.peg.option!(OR)), Sequence, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(OR), Sequence))), "Pegged.Expression")(TParseTree("", false,[], s));
300         else
301             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(pegged.peg.option!(OR)), Sequence, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(OR), Sequence))), "Pegged.Expression"), "Expression")(TParseTree("", false,[], s));
302     }
303     static string Expression(GetName g)
304     {
305         return "Pegged.Expression";
306     }
307 
308     static TParseTree Sequence(TParseTree p)
309     {
310         if(__ctfe)
311             return         pegged.peg.named!(pegged.peg.oneOrMore!(Prefix), "Pegged.Sequence")(p);
312         else
313             return hooked!(pegged.peg.named!(pegged.peg.oneOrMore!(Prefix), "Pegged.Sequence"), "Sequence")(p);
314     }
315     static TParseTree Sequence(string s)
316     {
317         if(__ctfe)
318             return         pegged.peg.named!(pegged.peg.oneOrMore!(Prefix), "Pegged.Sequence")(TParseTree("", false,[], s));
319         else
320             return hooked!(pegged.peg.named!(pegged.peg.oneOrMore!(Prefix), "Pegged.Sequence"), "Sequence")(TParseTree("", false,[], s));
321     }
322     static string Sequence(GetName g)
323     {
324         return "Pegged.Sequence";
325     }
326 
327     static TParseTree Prefix(TParseTree p)
328     {
329         if(__ctfe)
330             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.zeroOrMore!(pegged.peg.or!(POS, NEG, FUSE, DISCARD, KEEP, DROP, PROPAGATE)), Suffix), "Pegged.Prefix")(p);
331         else
332             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.zeroOrMore!(pegged.peg.or!(POS, NEG, FUSE, DISCARD, KEEP, DROP, PROPAGATE)), Suffix), "Pegged.Prefix"), "Prefix")(p);
333     }
334     static TParseTree Prefix(string s)
335     {
336         if(__ctfe)
337             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.zeroOrMore!(pegged.peg.or!(POS, NEG, FUSE, DISCARD, KEEP, DROP, PROPAGATE)), Suffix), "Pegged.Prefix")(TParseTree("", false,[], s));
338         else
339             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.zeroOrMore!(pegged.peg.or!(POS, NEG, FUSE, DISCARD, KEEP, DROP, PROPAGATE)), Suffix), "Pegged.Prefix"), "Prefix")(TParseTree("", false,[], s));
340     }
341     static string Prefix(GetName g)
342     {
343         return "Pegged.Prefix";
344     }
345 
346     static TParseTree Suffix(TParseTree p)
347     {
348         if(__ctfe)
349             return         pegged.peg.named!(pegged.peg.and!(Primary, pegged.peg.zeroOrMore!(pegged.peg.or!(OPTION, ZEROORMORE, ONEORMORE, Action))), "Pegged.Suffix")(p);
350         else
351             return hooked!(pegged.peg.named!(pegged.peg.and!(Primary, pegged.peg.zeroOrMore!(pegged.peg.or!(OPTION, ZEROORMORE, ONEORMORE, Action))), "Pegged.Suffix"), "Suffix")(p);
352     }
353     static TParseTree Suffix(string s)
354     {
355         if(__ctfe)
356             return         pegged.peg.named!(pegged.peg.and!(Primary, pegged.peg.zeroOrMore!(pegged.peg.or!(OPTION, ZEROORMORE, ONEORMORE, Action))), "Pegged.Suffix")(TParseTree("", false,[], s));
357         else
358             return hooked!(pegged.peg.named!(pegged.peg.and!(Primary, pegged.peg.zeroOrMore!(pegged.peg.or!(OPTION, ZEROORMORE, ONEORMORE, Action))), "Pegged.Suffix"), "Suffix")(TParseTree("", false,[], s));
359     }
360     static string Suffix(GetName g)
361     {
362         return "Pegged.Suffix";
363     }
364 
365     static TParseTree Primary(TParseTree p)
366     {
367         if(__ctfe)
368             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.and!(LhsName, Arrow)), pegged.peg.or!(RhsName, pegged.peg.and!(pegged.peg.discard!(OPEN), Expression, pegged.peg.discard!(CLOSE)), Literal, CharClass, ANY)), "Pegged.Primary")(p);
369         else
370             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.and!(LhsName, Arrow)), pegged.peg.or!(RhsName, pegged.peg.and!(pegged.peg.discard!(OPEN), Expression, pegged.peg.discard!(CLOSE)), Literal, CharClass, ANY)), "Pegged.Primary"), "Primary")(p);
371     }
372     static TParseTree Primary(string s)
373     {
374         if(__ctfe)
375             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.and!(LhsName, Arrow)), pegged.peg.or!(RhsName, pegged.peg.and!(pegged.peg.discard!(OPEN), Expression, pegged.peg.discard!(CLOSE)), Literal, CharClass, ANY)), "Pegged.Primary")(TParseTree("", false,[], s));
376         else
377             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.and!(LhsName, Arrow)), pegged.peg.or!(RhsName, pegged.peg.and!(pegged.peg.discard!(OPEN), Expression, pegged.peg.discard!(CLOSE)), Literal, CharClass, ANY)), "Pegged.Primary"), "Primary")(TParseTree("", false,[], s));
378     }
379     static string Primary(GetName g)
380     {
381         return "Pegged.Primary";
382     }
383 
384     static TParseTree Identifier(TParseTree p)
385     {
386         if(__ctfe)
387             return         pegged.peg.named!(identifier, "Pegged.Identifier")(p);
388         else
389             return hooked!(pegged.peg.named!(identifier, "Pegged.Identifier"), "Identifier")(p);
390     }
391     static TParseTree Identifier(string s)
392     {
393         if(__ctfe)
394             return         pegged.peg.named!(identifier, "Pegged.Identifier")(TParseTree("", false,[], s));
395         else
396             return hooked!(pegged.peg.named!(identifier, "Pegged.Identifier"), "Identifier")(TParseTree("", false,[], s));
397     }
398     static string Identifier(GetName g)
399     {
400         return "Pegged.Identifier";
401     }
402 
403     static TParseTree GrammarName(TParseTree p)
404     {
405         if(__ctfe)
406             return         pegged.peg.named!(pegged.peg.and!(Identifier, pegged.peg.option!(ParamList), Spacing, pegged.peg.discard!(pegged.peg.literal!(":")), Spacing), "Pegged.GrammarName")(p);
407         else
408             return hooked!(pegged.peg.named!(pegged.peg.and!(Identifier, pegged.peg.option!(ParamList), Spacing, pegged.peg.discard!(pegged.peg.literal!(":")), Spacing), "Pegged.GrammarName"), "GrammarName")(p);
409     }
410     static TParseTree GrammarName(string s)
411     {
412         if(__ctfe)
413             return         pegged.peg.named!(pegged.peg.and!(Identifier, pegged.peg.option!(ParamList), Spacing, pegged.peg.discard!(pegged.peg.literal!(":")), Spacing), "Pegged.GrammarName")(TParseTree("", false,[], s));
414         else
415             return hooked!(pegged.peg.named!(pegged.peg.and!(Identifier, pegged.peg.option!(ParamList), Spacing, pegged.peg.discard!(pegged.peg.literal!(":")), Spacing), "Pegged.GrammarName"), "GrammarName")(TParseTree("", false,[], s));
416     }
417     static string GrammarName(GetName g)
418     {
419         return "Pegged.GrammarName";
420     }
421 
422     static TParseTree LhsName(TParseTree p)
423     {
424         if(__ctfe)
425             return         pegged.peg.named!(pegged.peg.and!(Identifier, pegged.peg.option!(ParamList), Spacing), "Pegged.LhsName")(p);
426         else
427             return hooked!(pegged.peg.named!(pegged.peg.and!(Identifier, pegged.peg.option!(ParamList), Spacing), "Pegged.LhsName"), "LhsName")(p);
428     }
429     static TParseTree LhsName(string s)
430     {
431         if(__ctfe)
432             return         pegged.peg.named!(pegged.peg.and!(Identifier, pegged.peg.option!(ParamList), Spacing), "Pegged.LhsName")(TParseTree("", false,[], s));
433         else
434             return hooked!(pegged.peg.named!(pegged.peg.and!(Identifier, pegged.peg.option!(ParamList), Spacing), "Pegged.LhsName"), "LhsName")(TParseTree("", false,[], s));
435     }
436     static string LhsName(GetName g)
437     {
438         return "Pegged.LhsName";
439     }
440 
441     static TParseTree RhsName(TParseTree p)
442     {
443         if(__ctfe)
444             return         pegged.peg.named!(pegged.peg.and!(Identifier, pegged.peg.option!(ArgList), pegged.peg.zeroOrMore!(pegged.peg.and!(NAMESEP, Identifier, pegged.peg.option!(ArgList))), Spacing), "Pegged.RhsName")(p);
445         else
446             return hooked!(pegged.peg.named!(pegged.peg.and!(Identifier, pegged.peg.option!(ArgList), pegged.peg.zeroOrMore!(pegged.peg.and!(NAMESEP, Identifier, pegged.peg.option!(ArgList))), Spacing), "Pegged.RhsName"), "RhsName")(p);
447     }
448     static TParseTree RhsName(string s)
449     {
450         if(__ctfe)
451             return         pegged.peg.named!(pegged.peg.and!(Identifier, pegged.peg.option!(ArgList), pegged.peg.zeroOrMore!(pegged.peg.and!(NAMESEP, Identifier, pegged.peg.option!(ArgList))), Spacing), "Pegged.RhsName")(TParseTree("", false,[], s));
452         else
453             return hooked!(pegged.peg.named!(pegged.peg.and!(Identifier, pegged.peg.option!(ArgList), pegged.peg.zeroOrMore!(pegged.peg.and!(NAMESEP, Identifier, pegged.peg.option!(ArgList))), Spacing), "Pegged.RhsName"), "RhsName")(TParseTree("", false,[], s));
454     }
455     static string RhsName(GetName g)
456     {
457         return "Pegged.RhsName";
458     }
459 
460     static TParseTree ParamList(TParseTree p)
461     {
462         if(__ctfe)
463             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(OPEN), Param, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(SEPARATOR), Param)), pegged.peg.discard!(CLOSE)), "Pegged.ParamList")(p);
464         else
465             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(OPEN), Param, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(SEPARATOR), Param)), pegged.peg.discard!(CLOSE)), "Pegged.ParamList"), "ParamList")(p);
466     }
467     static TParseTree ParamList(string s)
468     {
469         if(__ctfe)
470             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(OPEN), Param, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(SEPARATOR), Param)), pegged.peg.discard!(CLOSE)), "Pegged.ParamList")(TParseTree("", false,[], s));
471         else
472             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(OPEN), Param, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(SEPARATOR), Param)), pegged.peg.discard!(CLOSE)), "Pegged.ParamList"), "ParamList")(TParseTree("", false,[], s));
473     }
474     static string ParamList(GetName g)
475     {
476         return "Pegged.ParamList";
477     }
478 
479     static TParseTree Param(TParseTree p)
480     {
481         if(__ctfe)
482             return         pegged.peg.named!(pegged.peg.or!(DefaultParam, SingleParam), "Pegged.Param")(p);
483         else
484             return hooked!(pegged.peg.named!(pegged.peg.or!(DefaultParam, SingleParam), "Pegged.Param"), "Param")(p);
485     }
486     static TParseTree Param(string s)
487     {
488         if(__ctfe)
489             return         pegged.peg.named!(pegged.peg.or!(DefaultParam, SingleParam), "Pegged.Param")(TParseTree("", false,[], s));
490         else
491             return hooked!(pegged.peg.named!(pegged.peg.or!(DefaultParam, SingleParam), "Pegged.Param"), "Param")(TParseTree("", false,[], s));
492     }
493     static string Param(GetName g)
494     {
495         return "Pegged.Param";
496     }
497 
498     static TParseTree DefaultParam(TParseTree p)
499     {
500         if(__ctfe)
501             return         pegged.peg.named!(pegged.peg.and!(Identifier, Spacing, pegged.peg.discard!(ASSIGN), Expression), "Pegged.DefaultParam")(p);
502         else
503             return hooked!(pegged.peg.named!(pegged.peg.and!(Identifier, Spacing, pegged.peg.discard!(ASSIGN), Expression), "Pegged.DefaultParam"), "DefaultParam")(p);
504     }
505     static TParseTree DefaultParam(string s)
506     {
507         if(__ctfe)
508             return         pegged.peg.named!(pegged.peg.and!(Identifier, Spacing, pegged.peg.discard!(ASSIGN), Expression), "Pegged.DefaultParam")(TParseTree("", false,[], s));
509         else
510             return hooked!(pegged.peg.named!(pegged.peg.and!(Identifier, Spacing, pegged.peg.discard!(ASSIGN), Expression), "Pegged.DefaultParam"), "DefaultParam")(TParseTree("", false,[], s));
511     }
512     static string DefaultParam(GetName g)
513     {
514         return "Pegged.DefaultParam";
515     }
516 
517     static TParseTree SingleParam(TParseTree p)
518     {
519         if(__ctfe)
520             return         pegged.peg.named!(pegged.peg.and!(Identifier, Spacing), "Pegged.SingleParam")(p);
521         else
522             return hooked!(pegged.peg.named!(pegged.peg.and!(Identifier, Spacing), "Pegged.SingleParam"), "SingleParam")(p);
523     }
524     static TParseTree SingleParam(string s)
525     {
526         if(__ctfe)
527             return         pegged.peg.named!(pegged.peg.and!(Identifier, Spacing), "Pegged.SingleParam")(TParseTree("", false,[], s));
528         else
529             return hooked!(pegged.peg.named!(pegged.peg.and!(Identifier, Spacing), "Pegged.SingleParam"), "SingleParam")(TParseTree("", false,[], s));
530     }
531     static string SingleParam(GetName g)
532     {
533         return "Pegged.SingleParam";
534     }
535 
536     static TParseTree ArgList(TParseTree p)
537     {
538         if(__ctfe)
539             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(OPEN), Expression, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(SEPARATOR), Expression)), pegged.peg.discard!(CLOSE)), "Pegged.ArgList")(p);
540         else
541             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(OPEN), Expression, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(SEPARATOR), Expression)), pegged.peg.discard!(CLOSE)), "Pegged.ArgList"), "ArgList")(p);
542     }
543     static TParseTree ArgList(string s)
544     {
545         if(__ctfe)
546             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(OPEN), Expression, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(SEPARATOR), Expression)), pegged.peg.discard!(CLOSE)), "Pegged.ArgList")(TParseTree("", false,[], s));
547         else
548             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(OPEN), Expression, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(SEPARATOR), Expression)), pegged.peg.discard!(CLOSE)), "Pegged.ArgList"), "ArgList")(TParseTree("", false,[], s));
549     }
550     static string ArgList(GetName g)
551     {
552         return "Pegged.ArgList";
553     }
554 
555     static TParseTree Literal(TParseTree p)
556     {
557         if(__ctfe)
558             return         pegged.peg.named!(pegged.peg.or!(pegged.peg.and!(quote, pegged.peg.fuse!(pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(quote), Char))), quote, Spacing), pegged.peg.and!(doublequote, pegged.peg.fuse!(pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(doublequote), Char))), doublequote, Spacing)), "Pegged.Literal")(p);
559         else
560             return hooked!(pegged.peg.named!(pegged.peg.or!(pegged.peg.and!(quote, pegged.peg.fuse!(pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(quote), Char))), quote, Spacing), pegged.peg.and!(doublequote, pegged.peg.fuse!(pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(doublequote), Char))), doublequote, Spacing)), "Pegged.Literal"), "Literal")(p);
561     }
562     static TParseTree Literal(string s)
563     {
564         if(__ctfe)
565             return         pegged.peg.named!(pegged.peg.or!(pegged.peg.and!(quote, pegged.peg.fuse!(pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(quote), Char))), quote, Spacing), pegged.peg.and!(doublequote, pegged.peg.fuse!(pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(doublequote), Char))), doublequote, Spacing)), "Pegged.Literal")(TParseTree("", false,[], s));
566         else
567             return hooked!(pegged.peg.named!(pegged.peg.or!(pegged.peg.and!(quote, pegged.peg.fuse!(pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(quote), Char))), quote, Spacing), pegged.peg.and!(doublequote, pegged.peg.fuse!(pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(doublequote), Char))), doublequote, Spacing)), "Pegged.Literal"), "Literal")(TParseTree("", false,[], s));
568     }
569     static string Literal(GetName g)
570     {
571         return "Pegged.Literal";
572     }
573 
574     static TParseTree CharClass(TParseTree p)
575     {
576         if(__ctfe)
577             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(pegged.peg.literal!("[")), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.literal!("]")), CharRange)), pegged.peg.discard!(pegged.peg.literal!("]")), Spacing), "Pegged.CharClass")(p);
578         else
579             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(pegged.peg.literal!("[")), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.literal!("]")), CharRange)), pegged.peg.discard!(pegged.peg.literal!("]")), Spacing), "Pegged.CharClass"), "CharClass")(p);
580     }
581     static TParseTree CharClass(string s)
582     {
583         if(__ctfe)
584             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(pegged.peg.literal!("[")), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.literal!("]")), CharRange)), pegged.peg.discard!(pegged.peg.literal!("]")), Spacing), "Pegged.CharClass")(TParseTree("", false,[], s));
585         else
586             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(pegged.peg.literal!("[")), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.literal!("]")), CharRange)), pegged.peg.discard!(pegged.peg.literal!("]")), Spacing), "Pegged.CharClass"), "CharClass")(TParseTree("", false,[], s));
587     }
588     static string CharClass(GetName g)
589     {
590         return "Pegged.CharClass";
591     }
592 
593     static TParseTree CharRange(TParseTree p)
594     {
595         if(__ctfe)
596             return         pegged.peg.named!(pegged.peg.or!(pegged.peg.and!(Char, pegged.peg.literal!("-"), Char), Char), "Pegged.CharRange")(p);
597         else
598             return hooked!(pegged.peg.named!(pegged.peg.or!(pegged.peg.and!(Char, pegged.peg.literal!("-"), Char), Char), "Pegged.CharRange"), "CharRange")(p);
599     }
600     static TParseTree CharRange(string s)
601     {
602         if(__ctfe)
603             return         pegged.peg.named!(pegged.peg.or!(pegged.peg.and!(Char, pegged.peg.literal!("-"), Char), Char), "Pegged.CharRange")(TParseTree("", false,[], s));
604         else
605             return hooked!(pegged.peg.named!(pegged.peg.or!(pegged.peg.and!(Char, pegged.peg.literal!("-"), Char), Char), "Pegged.CharRange"), "CharRange")(TParseTree("", false,[], s));
606     }
607     static string CharRange(GetName g)
608     {
609         return "Pegged.CharRange";
610     }
611 
612     static TParseTree Char(TParseTree p)
613     {
614         if(__ctfe)
615             return         pegged.peg.named!(pegged.peg.fuse!(pegged.peg.or!(pegged.peg.and!(backslash, pegged.peg.or!(quote, doublequote, backquote, backslash, pegged.peg.literal!("-"), pegged.peg.literal!("["), pegged.peg.literal!("]"), pegged.peg.or!(pegged.peg.literal!("n"), pegged.peg.literal!("r"), pegged.peg.literal!("t")), pegged.peg.and!(pegged.peg.charRange!('0', '2'), pegged.peg.charRange!('0', '7'), pegged.peg.charRange!('0', '7')), pegged.peg.and!(pegged.peg.charRange!('0', '7'), pegged.peg.option!(pegged.peg.charRange!('0', '7'))), pegged.peg.and!(pegged.peg.literal!("x"), hexDigit, hexDigit), pegged.peg.and!(pegged.peg.literal!("u"), hexDigit, hexDigit, hexDigit, hexDigit), pegged.peg.and!(pegged.peg.literal!("U"), hexDigit, hexDigit, hexDigit, hexDigit, hexDigit, hexDigit, hexDigit, hexDigit))), pegged.peg.any)), "Pegged.Char")(p);
616         else
617             return hooked!(pegged.peg.named!(pegged.peg.fuse!(pegged.peg.or!(pegged.peg.and!(backslash, pegged.peg.or!(quote, doublequote, backquote, backslash, pegged.peg.literal!("-"), pegged.peg.literal!("["), pegged.peg.literal!("]"), pegged.peg.or!(pegged.peg.literal!("n"), pegged.peg.literal!("r"), pegged.peg.literal!("t")), pegged.peg.and!(pegged.peg.charRange!('0', '2'), pegged.peg.charRange!('0', '7'), pegged.peg.charRange!('0', '7')), pegged.peg.and!(pegged.peg.charRange!('0', '7'), pegged.peg.option!(pegged.peg.charRange!('0', '7'))), pegged.peg.and!(pegged.peg.literal!("x"), hexDigit, hexDigit), pegged.peg.and!(pegged.peg.literal!("u"), hexDigit, hexDigit, hexDigit, hexDigit), pegged.peg.and!(pegged.peg.literal!("U"), hexDigit, hexDigit, hexDigit, hexDigit, hexDigit, hexDigit, hexDigit, hexDigit))), pegged.peg.any)), "Pegged.Char"), "Char")(p);
618     }
619     static TParseTree Char(string s)
620     {
621         if(__ctfe)
622             return         pegged.peg.named!(pegged.peg.fuse!(pegged.peg.or!(pegged.peg.and!(backslash, pegged.peg.or!(quote, doublequote, backquote, backslash, pegged.peg.literal!("-"), pegged.peg.literal!("["), pegged.peg.literal!("]"), pegged.peg.or!(pegged.peg.literal!("n"), pegged.peg.literal!("r"), pegged.peg.literal!("t")), pegged.peg.and!(pegged.peg.charRange!('0', '2'), pegged.peg.charRange!('0', '7'), pegged.peg.charRange!('0', '7')), pegged.peg.and!(pegged.peg.charRange!('0', '7'), pegged.peg.option!(pegged.peg.charRange!('0', '7'))), pegged.peg.and!(pegged.peg.literal!("x"), hexDigit, hexDigit), pegged.peg.and!(pegged.peg.literal!("u"), hexDigit, hexDigit, hexDigit, hexDigit), pegged.peg.and!(pegged.peg.literal!("U"), hexDigit, hexDigit, hexDigit, hexDigit, hexDigit, hexDigit, hexDigit, hexDigit))), pegged.peg.any)), "Pegged.Char")(TParseTree("", false,[], s));
623         else
624             return hooked!(pegged.peg.named!(pegged.peg.fuse!(pegged.peg.or!(pegged.peg.and!(backslash, pegged.peg.or!(quote, doublequote, backquote, backslash, pegged.peg.literal!("-"), pegged.peg.literal!("["), pegged.peg.literal!("]"), pegged.peg.or!(pegged.peg.literal!("n"), pegged.peg.literal!("r"), pegged.peg.literal!("t")), pegged.peg.and!(pegged.peg.charRange!('0', '2'), pegged.peg.charRange!('0', '7'), pegged.peg.charRange!('0', '7')), pegged.peg.and!(pegged.peg.charRange!('0', '7'), pegged.peg.option!(pegged.peg.charRange!('0', '7'))), pegged.peg.and!(pegged.peg.literal!("x"), hexDigit, hexDigit), pegged.peg.and!(pegged.peg.literal!("u"), hexDigit, hexDigit, hexDigit, hexDigit), pegged.peg.and!(pegged.peg.literal!("U"), hexDigit, hexDigit, hexDigit, hexDigit, hexDigit, hexDigit, hexDigit, hexDigit))), pegged.peg.any)), "Pegged.Char"), "Char")(TParseTree("", false,[], s));
625     }
626     static string Char(GetName g)
627     {
628         return "Pegged.Char";
629     }
630 
631     static TParseTree Arrow(TParseTree p)
632     {
633         if(__ctfe)
634             return         pegged.peg.named!(pegged.peg.or!(LEFTARROW, FUSEARROW, DISCARDARROW, KEEPARROW, DROPARROW, PROPAGATEARROW, ACTIONARROW, SPACEARROW), "Pegged.Arrow")(p);
635         else
636             return hooked!(pegged.peg.named!(pegged.peg.or!(LEFTARROW, FUSEARROW, DISCARDARROW, KEEPARROW, DROPARROW, PROPAGATEARROW, ACTIONARROW, SPACEARROW), "Pegged.Arrow"), "Arrow")(p);
637     }
638     static TParseTree Arrow(string s)
639     {
640         if(__ctfe)
641             return         pegged.peg.named!(pegged.peg.or!(LEFTARROW, FUSEARROW, DISCARDARROW, KEEPARROW, DROPARROW, PROPAGATEARROW, ACTIONARROW, SPACEARROW), "Pegged.Arrow")(TParseTree("", false,[], s));
642         else
643             return hooked!(pegged.peg.named!(pegged.peg.or!(LEFTARROW, FUSEARROW, DISCARDARROW, KEEPARROW, DROPARROW, PROPAGATEARROW, ACTIONARROW, SPACEARROW), "Pegged.Arrow"), "Arrow")(TParseTree("", false,[], s));
644     }
645     static string Arrow(GetName g)
646     {
647         return "Pegged.Arrow";
648     }
649 
650     static TParseTree LEFTARROW(TParseTree p)
651     {
652         if(__ctfe)
653             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<-"), Spacing), "Pegged.LEFTARROW")(p);
654         else
655             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<-"), Spacing), "Pegged.LEFTARROW"), "LEFTARROW")(p);
656     }
657     static TParseTree LEFTARROW(string s)
658     {
659         if(__ctfe)
660             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<-"), Spacing), "Pegged.LEFTARROW")(TParseTree("", false,[], s));
661         else
662             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<-"), Spacing), "Pegged.LEFTARROW"), "LEFTARROW")(TParseTree("", false,[], s));
663     }
664     static string LEFTARROW(GetName g)
665     {
666         return "Pegged.LEFTARROW";
667     }
668 
669     static TParseTree FUSEARROW(TParseTree p)
670     {
671         if(__ctfe)
672             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<~"), Spacing), "Pegged.FUSEARROW")(p);
673         else
674             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<~"), Spacing), "Pegged.FUSEARROW"), "FUSEARROW")(p);
675     }
676     static TParseTree FUSEARROW(string s)
677     {
678         if(__ctfe)
679             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<~"), Spacing), "Pegged.FUSEARROW")(TParseTree("", false,[], s));
680         else
681             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<~"), Spacing), "Pegged.FUSEARROW"), "FUSEARROW")(TParseTree("", false,[], s));
682     }
683     static string FUSEARROW(GetName g)
684     {
685         return "Pegged.FUSEARROW";
686     }
687 
688     static TParseTree DISCARDARROW(TParseTree p)
689     {
690         if(__ctfe)
691             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<:"), Spacing), "Pegged.DISCARDARROW")(p);
692         else
693             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<:"), Spacing), "Pegged.DISCARDARROW"), "DISCARDARROW")(p);
694     }
695     static TParseTree DISCARDARROW(string s)
696     {
697         if(__ctfe)
698             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<:"), Spacing), "Pegged.DISCARDARROW")(TParseTree("", false,[], s));
699         else
700             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<:"), Spacing), "Pegged.DISCARDARROW"), "DISCARDARROW")(TParseTree("", false,[], s));
701     }
702     static string DISCARDARROW(GetName g)
703     {
704         return "Pegged.DISCARDARROW";
705     }
706 
707     static TParseTree KEEPARROW(TParseTree p)
708     {
709         if(__ctfe)
710             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<^"), Spacing), "Pegged.KEEPARROW")(p);
711         else
712             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<^"), Spacing), "Pegged.KEEPARROW"), "KEEPARROW")(p);
713     }
714     static TParseTree KEEPARROW(string s)
715     {
716         if(__ctfe)
717             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<^"), Spacing), "Pegged.KEEPARROW")(TParseTree("", false,[], s));
718         else
719             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<^"), Spacing), "Pegged.KEEPARROW"), "KEEPARROW")(TParseTree("", false,[], s));
720     }
721     static string KEEPARROW(GetName g)
722     {
723         return "Pegged.KEEPARROW";
724     }
725 
726     static TParseTree DROPARROW(TParseTree p)
727     {
728         if(__ctfe)
729             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<;"), Spacing), "Pegged.DROPARROW")(p);
730         else
731             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<;"), Spacing), "Pegged.DROPARROW"), "DROPARROW")(p);
732     }
733     static TParseTree DROPARROW(string s)
734     {
735         if(__ctfe)
736             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<;"), Spacing), "Pegged.DROPARROW")(TParseTree("", false,[], s));
737         else
738             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<;"), Spacing), "Pegged.DROPARROW"), "DROPARROW")(TParseTree("", false,[], s));
739     }
740     static string DROPARROW(GetName g)
741     {
742         return "Pegged.DROPARROW";
743     }
744 
745     static TParseTree PROPAGATEARROW(TParseTree p)
746     {
747         if(__ctfe)
748             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<%"), Spacing), "Pegged.PROPAGATEARROW")(p);
749         else
750             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<%"), Spacing), "Pegged.PROPAGATEARROW"), "PROPAGATEARROW")(p);
751     }
752     static TParseTree PROPAGATEARROW(string s)
753     {
754         if(__ctfe)
755             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<%"), Spacing), "Pegged.PROPAGATEARROW")(TParseTree("", false,[], s));
756         else
757             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<%"), Spacing), "Pegged.PROPAGATEARROW"), "PROPAGATEARROW")(TParseTree("", false,[], s));
758     }
759     static string PROPAGATEARROW(GetName g)
760     {
761         return "Pegged.PROPAGATEARROW";
762     }
763 
764     static TParseTree SPACEARROW(TParseTree p)
765     {
766         if(__ctfe)
767             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<"), Spacing), "Pegged.SPACEARROW")(p);
768         else
769             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<"), Spacing), "Pegged.SPACEARROW"), "SPACEARROW")(p);
770     }
771     static TParseTree SPACEARROW(string s)
772     {
773         if(__ctfe)
774             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<"), Spacing), "Pegged.SPACEARROW")(TParseTree("", false,[], s));
775         else
776             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<"), Spacing), "Pegged.SPACEARROW"), "SPACEARROW")(TParseTree("", false,[], s));
777     }
778     static string SPACEARROW(GetName g)
779     {
780         return "Pegged.SPACEARROW";
781     }
782 
783     static TParseTree ACTIONARROW(TParseTree p)
784     {
785         if(__ctfe)
786             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<"), Action, Spacing), "Pegged.ACTIONARROW")(p);
787         else
788             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<"), Action, Spacing), "Pegged.ACTIONARROW"), "ACTIONARROW")(p);
789     }
790     static TParseTree ACTIONARROW(string s)
791     {
792         if(__ctfe)
793             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<"), Action, Spacing), "Pegged.ACTIONARROW")(TParseTree("", false,[], s));
794         else
795             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("<"), Action, Spacing), "Pegged.ACTIONARROW"), "ACTIONARROW")(TParseTree("", false,[], s));
796     }
797     static string ACTIONARROW(GetName g)
798     {
799         return "Pegged.ACTIONARROW";
800     }
801 
802     static TParseTree OR(TParseTree p)
803     {
804         if(__ctfe)
805             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("/"), Spacing), "Pegged.OR")(p);
806         else
807             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("/"), Spacing), "Pegged.OR"), "OR")(p);
808     }
809     static TParseTree OR(string s)
810     {
811         if(__ctfe)
812             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("/"), Spacing), "Pegged.OR")(TParseTree("", false,[], s));
813         else
814             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("/"), Spacing), "Pegged.OR"), "OR")(TParseTree("", false,[], s));
815     }
816     static string OR(GetName g)
817     {
818         return "Pegged.OR";
819     }
820 
821     static TParseTree POS(TParseTree p)
822     {
823         if(__ctfe)
824             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("&"), Spacing), "Pegged.POS")(p);
825         else
826             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("&"), Spacing), "Pegged.POS"), "POS")(p);
827     }
828     static TParseTree POS(string s)
829     {
830         if(__ctfe)
831             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("&"), Spacing), "Pegged.POS")(TParseTree("", false,[], s));
832         else
833             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("&"), Spacing), "Pegged.POS"), "POS")(TParseTree("", false,[], s));
834     }
835     static string POS(GetName g)
836     {
837         return "Pegged.POS";
838     }
839 
840     static TParseTree NEG(TParseTree p)
841     {
842         if(__ctfe)
843             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("!"), Spacing), "Pegged.NEG")(p);
844         else
845             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("!"), Spacing), "Pegged.NEG"), "NEG")(p);
846     }
847     static TParseTree NEG(string s)
848     {
849         if(__ctfe)
850             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("!"), Spacing), "Pegged.NEG")(TParseTree("", false,[], s));
851         else
852             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("!"), Spacing), "Pegged.NEG"), "NEG")(TParseTree("", false,[], s));
853     }
854     static string NEG(GetName g)
855     {
856         return "Pegged.NEG";
857     }
858 
859     static TParseTree FUSE(TParseTree p)
860     {
861         if(__ctfe)
862             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("~"), Spacing), "Pegged.FUSE")(p);
863         else
864             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("~"), Spacing), "Pegged.FUSE"), "FUSE")(p);
865     }
866     static TParseTree FUSE(string s)
867     {
868         if(__ctfe)
869             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("~"), Spacing), "Pegged.FUSE")(TParseTree("", false,[], s));
870         else
871             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("~"), Spacing), "Pegged.FUSE"), "FUSE")(TParseTree("", false,[], s));
872     }
873     static string FUSE(GetName g)
874     {
875         return "Pegged.FUSE";
876     }
877 
878     static TParseTree DISCARD(TParseTree p)
879     {
880         if(__ctfe)
881             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(":"), Spacing), "Pegged.DISCARD")(p);
882         else
883             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(":"), Spacing), "Pegged.DISCARD"), "DISCARD")(p);
884     }
885     static TParseTree DISCARD(string s)
886     {
887         if(__ctfe)
888             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(":"), Spacing), "Pegged.DISCARD")(TParseTree("", false,[], s));
889         else
890             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(":"), Spacing), "Pegged.DISCARD"), "DISCARD")(TParseTree("", false,[], s));
891     }
892     static string DISCARD(GetName g)
893     {
894         return "Pegged.DISCARD";
895     }
896 
897     static TParseTree KEEP(TParseTree p)
898     {
899         if(__ctfe)
900             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("^"), Spacing), "Pegged.KEEP")(p);
901         else
902             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("^"), Spacing), "Pegged.KEEP"), "KEEP")(p);
903     }
904     static TParseTree KEEP(string s)
905     {
906         if(__ctfe)
907             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("^"), Spacing), "Pegged.KEEP")(TParseTree("", false,[], s));
908         else
909             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("^"), Spacing), "Pegged.KEEP"), "KEEP")(TParseTree("", false,[], s));
910     }
911     static string KEEP(GetName g)
912     {
913         return "Pegged.KEEP";
914     }
915 
916     static TParseTree DROP(TParseTree p)
917     {
918         if(__ctfe)
919             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(";"), Spacing), "Pegged.DROP")(p);
920         else
921             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(";"), Spacing), "Pegged.DROP"), "DROP")(p);
922     }
923     static TParseTree DROP(string s)
924     {
925         if(__ctfe)
926             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(";"), Spacing), "Pegged.DROP")(TParseTree("", false,[], s));
927         else
928             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(";"), Spacing), "Pegged.DROP"), "DROP")(TParseTree("", false,[], s));
929     }
930     static string DROP(GetName g)
931     {
932         return "Pegged.DROP";
933     }
934 
935     static TParseTree PROPAGATE(TParseTree p)
936     {
937         if(__ctfe)
938             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("%"), Spacing), "Pegged.PROPAGATE")(p);
939         else
940             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("%"), Spacing), "Pegged.PROPAGATE"), "PROPAGATE")(p);
941     }
942     static TParseTree PROPAGATE(string s)
943     {
944         if(__ctfe)
945             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("%"), Spacing), "Pegged.PROPAGATE")(TParseTree("", false,[], s));
946         else
947             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("%"), Spacing), "Pegged.PROPAGATE"), "PROPAGATE")(TParseTree("", false,[], s));
948     }
949     static string PROPAGATE(GetName g)
950     {
951         return "Pegged.PROPAGATE";
952     }
953 
954     static TParseTree OPTION(TParseTree p)
955     {
956         if(__ctfe)
957             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("?"), Spacing), "Pegged.OPTION")(p);
958         else
959             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("?"), Spacing), "Pegged.OPTION"), "OPTION")(p);
960     }
961     static TParseTree OPTION(string s)
962     {
963         if(__ctfe)
964             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("?"), Spacing), "Pegged.OPTION")(TParseTree("", false,[], s));
965         else
966             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("?"), Spacing), "Pegged.OPTION"), "OPTION")(TParseTree("", false,[], s));
967     }
968     static string OPTION(GetName g)
969     {
970         return "Pegged.OPTION";
971     }
972 
973     static TParseTree ZEROORMORE(TParseTree p)
974     {
975         if(__ctfe)
976             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("*"), Spacing), "Pegged.ZEROORMORE")(p);
977         else
978             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("*"), Spacing), "Pegged.ZEROORMORE"), "ZEROORMORE")(p);
979     }
980     static TParseTree ZEROORMORE(string s)
981     {
982         if(__ctfe)
983             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("*"), Spacing), "Pegged.ZEROORMORE")(TParseTree("", false,[], s));
984         else
985             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("*"), Spacing), "Pegged.ZEROORMORE"), "ZEROORMORE")(TParseTree("", false,[], s));
986     }
987     static string ZEROORMORE(GetName g)
988     {
989         return "Pegged.ZEROORMORE";
990     }
991 
992     static TParseTree ONEORMORE(TParseTree p)
993     {
994         if(__ctfe)
995             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("+"), Spacing), "Pegged.ONEORMORE")(p);
996         else
997             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("+"), Spacing), "Pegged.ONEORMORE"), "ONEORMORE")(p);
998     }
999     static TParseTree ONEORMORE(string s)
1000     {
1001         if(__ctfe)
1002             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("+"), Spacing), "Pegged.ONEORMORE")(TParseTree("", false,[], s));
1003         else
1004             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("+"), Spacing), "Pegged.ONEORMORE"), "ONEORMORE")(TParseTree("", false,[], s));
1005     }
1006     static string ONEORMORE(GetName g)
1007     {
1008         return "Pegged.ONEORMORE";
1009     }
1010 
1011     static TParseTree ACTIONOPEN(TParseTree p)
1012     {
1013         if(__ctfe)
1014             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("{"), Spacing), "Pegged.ACTIONOPEN")(p);
1015         else
1016             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("{"), Spacing), "Pegged.ACTIONOPEN"), "ACTIONOPEN")(p);
1017     }
1018     static TParseTree ACTIONOPEN(string s)
1019     {
1020         if(__ctfe)
1021             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("{"), Spacing), "Pegged.ACTIONOPEN")(TParseTree("", false,[], s));
1022         else
1023             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("{"), Spacing), "Pegged.ACTIONOPEN"), "ACTIONOPEN")(TParseTree("", false,[], s));
1024     }
1025     static string ACTIONOPEN(GetName g)
1026     {
1027         return "Pegged.ACTIONOPEN";
1028     }
1029 
1030     static TParseTree ACTIONCLOSE(TParseTree p)
1031     {
1032         if(__ctfe)
1033             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("}"), Spacing), "Pegged.ACTIONCLOSE")(p);
1034         else
1035             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("}"), Spacing), "Pegged.ACTIONCLOSE"), "ACTIONCLOSE")(p);
1036     }
1037     static TParseTree ACTIONCLOSE(string s)
1038     {
1039         if(__ctfe)
1040             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("}"), Spacing), "Pegged.ACTIONCLOSE")(TParseTree("", false,[], s));
1041         else
1042             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("}"), Spacing), "Pegged.ACTIONCLOSE"), "ACTIONCLOSE")(TParseTree("", false,[], s));
1043     }
1044     static string ACTIONCLOSE(GetName g)
1045     {
1046         return "Pegged.ACTIONCLOSE";
1047     }
1048 
1049     static TParseTree SEPARATOR(TParseTree p)
1050     {
1051         if(__ctfe)
1052             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(","), Spacing), "Pegged.SEPARATOR")(p);
1053         else
1054             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(","), Spacing), "Pegged.SEPARATOR"), "SEPARATOR")(p);
1055     }
1056     static TParseTree SEPARATOR(string s)
1057     {
1058         if(__ctfe)
1059             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(","), Spacing), "Pegged.SEPARATOR")(TParseTree("", false,[], s));
1060         else
1061             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(","), Spacing), "Pegged.SEPARATOR"), "SEPARATOR")(TParseTree("", false,[], s));
1062     }
1063     static string SEPARATOR(GetName g)
1064     {
1065         return "Pegged.SEPARATOR";
1066     }
1067 
1068     static TParseTree ASSIGN(TParseTree p)
1069     {
1070         if(__ctfe)
1071             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("="), Spacing), "Pegged.ASSIGN")(p);
1072         else
1073             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("="), Spacing), "Pegged.ASSIGN"), "ASSIGN")(p);
1074     }
1075     static TParseTree ASSIGN(string s)
1076     {
1077         if(__ctfe)
1078             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("="), Spacing), "Pegged.ASSIGN")(TParseTree("", false,[], s));
1079         else
1080             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("="), Spacing), "Pegged.ASSIGN"), "ASSIGN")(TParseTree("", false,[], s));
1081     }
1082     static string ASSIGN(GetName g)
1083     {
1084         return "Pegged.ASSIGN";
1085     }
1086 
1087     static TParseTree NAMESEP(TParseTree p)
1088     {
1089         if(__ctfe)
1090             return         pegged.peg.named!(pegged.peg.literal!("."), "Pegged.NAMESEP")(p);
1091         else
1092             return hooked!(pegged.peg.named!(pegged.peg.literal!("."), "Pegged.NAMESEP"), "NAMESEP")(p);
1093     }
1094     static TParseTree NAMESEP(string s)
1095     {
1096         if(__ctfe)
1097             return         pegged.peg.named!(pegged.peg.literal!("."), "Pegged.NAMESEP")(TParseTree("", false,[], s));
1098         else
1099             return hooked!(pegged.peg.named!(pegged.peg.literal!("."), "Pegged.NAMESEP"), "NAMESEP")(TParseTree("", false,[], s));
1100     }
1101     static string NAMESEP(GetName g)
1102     {
1103         return "Pegged.NAMESEP";
1104     }
1105 
1106     static TParseTree OPEN(TParseTree p)
1107     {
1108         if(__ctfe)
1109             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("("), Spacing), "Pegged.OPEN")(p);
1110         else
1111             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("("), Spacing), "Pegged.OPEN"), "OPEN")(p);
1112     }
1113     static TParseTree OPEN(string s)
1114     {
1115         if(__ctfe)
1116             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("("), Spacing), "Pegged.OPEN")(TParseTree("", false,[], s));
1117         else
1118             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("("), Spacing), "Pegged.OPEN"), "OPEN")(TParseTree("", false,[], s));
1119     }
1120     static string OPEN(GetName g)
1121     {
1122         return "Pegged.OPEN";
1123     }
1124 
1125     static TParseTree CLOSE(TParseTree p)
1126     {
1127         if(__ctfe)
1128             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(")"), Spacing), "Pegged.CLOSE")(p);
1129         else
1130             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(")"), Spacing), "Pegged.CLOSE"), "CLOSE")(p);
1131     }
1132     static TParseTree CLOSE(string s)
1133     {
1134         if(__ctfe)
1135             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(")"), Spacing), "Pegged.CLOSE")(TParseTree("", false,[], s));
1136         else
1137             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!(")"), Spacing), "Pegged.CLOSE"), "CLOSE")(TParseTree("", false,[], s));
1138     }
1139     static string CLOSE(GetName g)
1140     {
1141         return "Pegged.CLOSE";
1142     }
1143 
1144     static TParseTree ANY(TParseTree p)
1145     {
1146         if(__ctfe)
1147             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("."), Spacing), "Pegged.ANY")(p);
1148         else
1149             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("."), Spacing), "Pegged.ANY"), "ANY")(p);
1150     }
1151     static TParseTree ANY(string s)
1152     {
1153         if(__ctfe)
1154             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("."), Spacing), "Pegged.ANY")(TParseTree("", false,[], s));
1155         else
1156             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("."), Spacing), "Pegged.ANY"), "ANY")(TParseTree("", false,[], s));
1157     }
1158     static string ANY(GetName g)
1159     {
1160         return "Pegged.ANY";
1161     }
1162 
1163     static TParseTree Spacing(TParseTree p)
1164     {
1165         if(__ctfe)
1166             return         pegged.peg.named!(pegged.peg.discard!(pegged.peg.zeroOrMore!(pegged.peg.or!(blank, Comment))), "Pegged.Spacing")(p);
1167         else
1168             return hooked!(pegged.peg.named!(pegged.peg.discard!(pegged.peg.zeroOrMore!(pegged.peg.or!(blank, Comment))), "Pegged.Spacing"), "Spacing")(p);
1169     }
1170     static TParseTree Spacing(string s)
1171     {
1172         if(__ctfe)
1173             return         pegged.peg.named!(pegged.peg.discard!(pegged.peg.zeroOrMore!(pegged.peg.or!(blank, Comment))), "Pegged.Spacing")(TParseTree("", false,[], s));
1174         else
1175             return hooked!(pegged.peg.named!(pegged.peg.discard!(pegged.peg.zeroOrMore!(pegged.peg.or!(blank, Comment))), "Pegged.Spacing"), "Spacing")(TParseTree("", false,[], s));
1176     }
1177     static string Spacing(GetName g)
1178     {
1179         return "Pegged.Spacing";
1180     }
1181 
1182     static TParseTree Comment(TParseTree p)
1183     {
1184         if(__ctfe)
1185             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("#"), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(eol), pegged.peg.any)), pegged.peg.discard!(eol)), "Pegged.Comment")(p);
1186         else
1187             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("#"), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(eol), pegged.peg.any)), pegged.peg.discard!(eol)), "Pegged.Comment"), "Comment")(p);
1188     }
1189     static TParseTree Comment(string s)
1190     {
1191         if(__ctfe)
1192             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("#"), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(eol), pegged.peg.any)), pegged.peg.discard!(eol)), "Pegged.Comment")(TParseTree("", false,[], s));
1193         else
1194             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("#"), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(eol), pegged.peg.any)), pegged.peg.discard!(eol)), "Pegged.Comment"), "Comment")(TParseTree("", false,[], s));
1195     }
1196     static string Comment(GetName g)
1197     {
1198         return "Pegged.Comment";
1199     }
1200 
1201     static TParseTree Space(TParseTree p)
1202     {
1203         if(__ctfe)
1204             return         pegged.peg.named!(pegged.peg.or!(spacing, pegged.peg.literal!("\\t"), pegged.peg.literal!("\\n"), pegged.peg.literal!("\\r")), "Pegged.Space")(p);
1205         else
1206             return hooked!(pegged.peg.named!(pegged.peg.or!(spacing, pegged.peg.literal!("\\t"), pegged.peg.literal!("\\n"), pegged.peg.literal!("\\r")), "Pegged.Space"), "Space")(p);
1207     }
1208     static TParseTree Space(string s)
1209     {
1210         if(__ctfe)
1211             return         pegged.peg.named!(pegged.peg.or!(spacing, pegged.peg.literal!("\\t"), pegged.peg.literal!("\\n"), pegged.peg.literal!("\\r")), "Pegged.Space")(TParseTree("", false,[], s));
1212         else
1213             return hooked!(pegged.peg.named!(pegged.peg.or!(spacing, pegged.peg.literal!("\\t"), pegged.peg.literal!("\\n"), pegged.peg.literal!("\\r")), "Pegged.Space"), "Space")(TParseTree("", false,[], s));
1214     }
1215     static string Space(GetName g)
1216     {
1217         return "Pegged.Space";
1218     }
1219 
1220     static TParseTree Action(TParseTree p)
1221     {
1222         if(__ctfe)
1223             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(ACTIONOPEN), Spacing, pegged.peg.and!(pegged.peg.or!(Lambda, qualifiedIdentifier), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(SEPARATOR), pegged.peg.or!(Lambda, qualifiedIdentifier)))), Spacing, pegged.peg.discard!(ACTIONCLOSE)), "Pegged.Action")(p);
1224         else
1225             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(ACTIONOPEN), Spacing, pegged.peg.and!(pegged.peg.or!(Lambda, qualifiedIdentifier), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(SEPARATOR), pegged.peg.or!(Lambda, qualifiedIdentifier)))), Spacing, pegged.peg.discard!(ACTIONCLOSE)), "Pegged.Action"), "Action")(p);
1226     }
1227     static TParseTree Action(string s)
1228     {
1229         if(__ctfe)
1230             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(ACTIONOPEN), Spacing, pegged.peg.and!(pegged.peg.or!(Lambda, qualifiedIdentifier), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(SEPARATOR), pegged.peg.or!(Lambda, qualifiedIdentifier)))), Spacing, pegged.peg.discard!(ACTIONCLOSE)), "Pegged.Action")(TParseTree("", false,[], s));
1231         else
1232             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.discard!(ACTIONOPEN), Spacing, pegged.peg.and!(pegged.peg.or!(Lambda, qualifiedIdentifier), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.discard!(SEPARATOR), pegged.peg.or!(Lambda, qualifiedIdentifier)))), Spacing, pegged.peg.discard!(ACTIONCLOSE)), "Pegged.Action"), "Action")(TParseTree("", false,[], s));
1233     }
1234     static string Action(GetName g)
1235     {
1236         return "Pegged.Action";
1237     }
1238 
1239     static TParseTree Lambda(TParseTree p)
1240     {
1241         if(__ctfe)
1242             return         pegged.peg.named!(pegged.peg.fuse!(pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(ACTIONCLOSE, SEPARATOR)), pegged.peg.or!(LambdaItems, NestedList!(pegged.peg.literal!("{"), LambdaItems, pegged.peg.literal!("}")), pegged.peg.any)))), "Pegged.Lambda")(p);
1243         else
1244             return hooked!(pegged.peg.named!(pegged.peg.fuse!(pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(ACTIONCLOSE, SEPARATOR)), pegged.peg.or!(LambdaItems, NestedList!(pegged.peg.literal!("{"), LambdaItems, pegged.peg.literal!("}")), pegged.peg.any)))), "Pegged.Lambda"), "Lambda")(p);
1245     }
1246     static TParseTree Lambda(string s)
1247     {
1248         if(__ctfe)
1249             return         pegged.peg.named!(pegged.peg.fuse!(pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(ACTIONCLOSE, SEPARATOR)), pegged.peg.or!(LambdaItems, NestedList!(pegged.peg.literal!("{"), LambdaItems, pegged.peg.literal!("}")), pegged.peg.any)))), "Pegged.Lambda")(TParseTree("", false,[], s));
1250         else
1251             return hooked!(pegged.peg.named!(pegged.peg.fuse!(pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(ACTIONCLOSE, SEPARATOR)), pegged.peg.or!(LambdaItems, NestedList!(pegged.peg.literal!("{"), LambdaItems, pegged.peg.literal!("}")), pegged.peg.any)))), "Pegged.Lambda"), "Lambda")(TParseTree("", false,[], s));
1252     }
1253     static string Lambda(GetName g)
1254     {
1255         return "Pegged.Lambda";
1256     }
1257 
1258     static TParseTree LambdaItems(TParseTree p)
1259     {
1260         if(__ctfe)
1261             return         pegged.peg.named!(pegged.peg.or!(pegged.peg.fuse!(DComment), pegged.peg.fuse!(DString), pegged.peg.fuse!(DParamList)), "Pegged.LambdaItems")(p);
1262         else
1263             return hooked!(pegged.peg.named!(pegged.peg.or!(pegged.peg.fuse!(DComment), pegged.peg.fuse!(DString), pegged.peg.fuse!(DParamList)), "Pegged.LambdaItems"), "LambdaItems")(p);
1264     }
1265     static TParseTree LambdaItems(string s)
1266     {
1267         if(__ctfe)
1268             return         pegged.peg.named!(pegged.peg.or!(pegged.peg.fuse!(DComment), pegged.peg.fuse!(DString), pegged.peg.fuse!(DParamList)), "Pegged.LambdaItems")(TParseTree("", false,[], s));
1269         else
1270             return hooked!(pegged.peg.named!(pegged.peg.or!(pegged.peg.fuse!(DComment), pegged.peg.fuse!(DString), pegged.peg.fuse!(DParamList)), "Pegged.LambdaItems"), "LambdaItems")(TParseTree("", false,[], s));
1271     }
1272     static string LambdaItems(GetName g)
1273     {
1274         return "Pegged.LambdaItems";
1275     }
1276 
1277     static TParseTree DString(TParseTree p)
1278     {
1279         if(__ctfe)
1280             return         pegged.peg.named!(pegged.peg.or!(WYSString, DBQString, TKNString, DLMString), "Pegged.DString")(p);
1281         else
1282             return hooked!(pegged.peg.named!(pegged.peg.or!(WYSString, DBQString, TKNString, DLMString), "Pegged.DString"), "DString")(p);
1283     }
1284     static TParseTree DString(string s)
1285     {
1286         if(__ctfe)
1287             return         pegged.peg.named!(pegged.peg.or!(WYSString, DBQString, TKNString, DLMString), "Pegged.DString")(TParseTree("", false,[], s));
1288         else
1289             return hooked!(pegged.peg.named!(pegged.peg.or!(WYSString, DBQString, TKNString, DLMString), "Pegged.DString"), "DString")(TParseTree("", false,[], s));
1290     }
1291     static string DString(GetName g)
1292     {
1293         return "Pegged.DString";
1294     }
1295 
1296     static TParseTree WYSString(TParseTree p)
1297     {
1298         if(__ctfe)
1299             return         pegged.peg.named!(pegged.peg.or!(pegged.peg.and!(pegged.peg.literal!("r"), doublequote, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(doublequote), pegged.peg.any)), doublequote), pegged.peg.and!(backquote, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(backquote), pegged.peg.any)), backquote)), "Pegged.WYSString")(p);
1300         else
1301             return hooked!(pegged.peg.named!(pegged.peg.or!(pegged.peg.and!(pegged.peg.literal!("r"), doublequote, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(doublequote), pegged.peg.any)), doublequote), pegged.peg.and!(backquote, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(backquote), pegged.peg.any)), backquote)), "Pegged.WYSString"), "WYSString")(p);
1302     }
1303     static TParseTree WYSString(string s)
1304     {
1305         if(__ctfe)
1306             return         pegged.peg.named!(pegged.peg.or!(pegged.peg.and!(pegged.peg.literal!("r"), doublequote, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(doublequote), pegged.peg.any)), doublequote), pegged.peg.and!(backquote, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(backquote), pegged.peg.any)), backquote)), "Pegged.WYSString")(TParseTree("", false,[], s));
1307         else
1308             return hooked!(pegged.peg.named!(pegged.peg.or!(pegged.peg.and!(pegged.peg.literal!("r"), doublequote, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(doublequote), pegged.peg.any)), doublequote), pegged.peg.and!(backquote, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(backquote), pegged.peg.any)), backquote)), "Pegged.WYSString"), "WYSString")(TParseTree("", false,[], s));
1309     }
1310     static string WYSString(GetName g)
1311     {
1312         return "Pegged.WYSString";
1313     }
1314 
1315     static TParseTree DBQString(TParseTree p)
1316     {
1317         if(__ctfe)
1318             return         pegged.peg.named!(pegged.peg.and!(doublequote, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(doublequote), Char)), doublequote), "Pegged.DBQString")(p);
1319         else
1320             return hooked!(pegged.peg.named!(pegged.peg.and!(doublequote, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(doublequote), Char)), doublequote), "Pegged.DBQString"), "DBQString")(p);
1321     }
1322     static TParseTree DBQString(string s)
1323     {
1324         if(__ctfe)
1325             return         pegged.peg.named!(pegged.peg.and!(doublequote, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(doublequote), Char)), doublequote), "Pegged.DBQString")(TParseTree("", false,[], s));
1326         else
1327             return hooked!(pegged.peg.named!(pegged.peg.and!(doublequote, pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(doublequote), Char)), doublequote), "Pegged.DBQString"), "DBQString")(TParseTree("", false,[], s));
1328     }
1329     static string DBQString(GetName g)
1330     {
1331         return "Pegged.DBQString";
1332     }
1333 
1334     static TParseTree TKNString(TParseTree p)
1335     {
1336         if(__ctfe)
1337             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("q{")), pegged.peg.and!(pegged.peg.literal!("q"), NestedList!(pegged.peg.literal!("{"), DString, pegged.peg.literal!("}")))), "Pegged.TKNString")(p);
1338         else
1339             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("q{")), pegged.peg.and!(pegged.peg.literal!("q"), NestedList!(pegged.peg.literal!("{"), DString, pegged.peg.literal!("}")))), "Pegged.TKNString"), "TKNString")(p);
1340     }
1341     static TParseTree TKNString(string s)
1342     {
1343         if(__ctfe)
1344             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("q{")), pegged.peg.and!(pegged.peg.literal!("q"), NestedList!(pegged.peg.literal!("{"), DString, pegged.peg.literal!("}")))), "Pegged.TKNString")(TParseTree("", false,[], s));
1345         else
1346             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("q{")), pegged.peg.and!(pegged.peg.literal!("q"), NestedList!(pegged.peg.literal!("{"), DString, pegged.peg.literal!("}")))), "Pegged.TKNString"), "TKNString")(TParseTree("", false,[], s));
1347     }
1348     static string TKNString(GetName g)
1349     {
1350         return "Pegged.TKNString";
1351     }
1352 
1353     static TParseTree DLMString(TParseTree p)
1354     {
1355         if(__ctfe)
1356             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.and!(pegged.peg.literal!("q"), doublequote), pegged.peg.or!(pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("{")), NestedList!(pegged.peg.literal!("{"), DString, pegged.peg.literal!("}"))), pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("[")), NestedList!(pegged.peg.literal!("["), DString, pegged.peg.literal!("]"))), pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("(")), NestedList!(pegged.peg.literal!("("), DString, pegged.peg.literal!(")"))), pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("<")), NestedList!(pegged.peg.literal!("<"), DString, pegged.peg.literal!(">")))), doublequote), "Pegged.DLMString")(p);
1357         else
1358             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.and!(pegged.peg.literal!("q"), doublequote), pegged.peg.or!(pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("{")), NestedList!(pegged.peg.literal!("{"), DString, pegged.peg.literal!("}"))), pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("[")), NestedList!(pegged.peg.literal!("["), DString, pegged.peg.literal!("]"))), pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("(")), NestedList!(pegged.peg.literal!("("), DString, pegged.peg.literal!(")"))), pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("<")), NestedList!(pegged.peg.literal!("<"), DString, pegged.peg.literal!(">")))), doublequote), "Pegged.DLMString"), "DLMString")(p);
1359     }
1360     static TParseTree DLMString(string s)
1361     {
1362         if(__ctfe)
1363             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.and!(pegged.peg.literal!("q"), doublequote), pegged.peg.or!(pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("{")), NestedList!(pegged.peg.literal!("{"), DString, pegged.peg.literal!("}"))), pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("[")), NestedList!(pegged.peg.literal!("["), DString, pegged.peg.literal!("]"))), pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("(")), NestedList!(pegged.peg.literal!("("), DString, pegged.peg.literal!(")"))), pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("<")), NestedList!(pegged.peg.literal!("<"), DString, pegged.peg.literal!(">")))), doublequote), "Pegged.DLMString")(TParseTree("", false,[], s));
1364         else
1365             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.and!(pegged.peg.literal!("q"), doublequote), pegged.peg.or!(pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("{")), NestedList!(pegged.peg.literal!("{"), DString, pegged.peg.literal!("}"))), pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("[")), NestedList!(pegged.peg.literal!("["), DString, pegged.peg.literal!("]"))), pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("(")), NestedList!(pegged.peg.literal!("("), DString, pegged.peg.literal!(")"))), pegged.peg.and!(pegged.peg.posLookahead!(pegged.peg.literal!("<")), NestedList!(pegged.peg.literal!("<"), DString, pegged.peg.literal!(">")))), doublequote), "Pegged.DLMString"), "DLMString")(TParseTree("", false,[], s));
1366     }
1367     static string DLMString(GetName g)
1368     {
1369         return "Pegged.DLMString";
1370     }
1371 
1372     static TParseTree DComment(TParseTree p)
1373     {
1374         if(__ctfe)
1375             return         pegged.peg.named!(pegged.peg.or!(DLineComment, DBlockComment, DNestingBlockComment), "Pegged.DComment")(p);
1376         else
1377             return hooked!(pegged.peg.named!(pegged.peg.or!(DLineComment, DBlockComment, DNestingBlockComment), "Pegged.DComment"), "DComment")(p);
1378     }
1379     static TParseTree DComment(string s)
1380     {
1381         if(__ctfe)
1382             return         pegged.peg.named!(pegged.peg.or!(DLineComment, DBlockComment, DNestingBlockComment), "Pegged.DComment")(TParseTree("", false,[], s));
1383         else
1384             return hooked!(pegged.peg.named!(pegged.peg.or!(DLineComment, DBlockComment, DNestingBlockComment), "Pegged.DComment"), "DComment")(TParseTree("", false,[], s));
1385     }
1386     static string DComment(GetName g)
1387     {
1388         return "Pegged.DComment";
1389     }
1390 
1391     static TParseTree DLineComment(TParseTree p)
1392     {
1393         if(__ctfe)
1394             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("//"), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(endOfLine), pegged.peg.any)), endOfLine), "Pegged.DLineComment")(p);
1395         else
1396             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("//"), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(endOfLine), pegged.peg.any)), endOfLine), "Pegged.DLineComment"), "DLineComment")(p);
1397     }
1398     static TParseTree DLineComment(string s)
1399     {
1400         if(__ctfe)
1401             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("//"), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(endOfLine), pegged.peg.any)), endOfLine), "Pegged.DLineComment")(TParseTree("", false,[], s));
1402         else
1403             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("//"), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(endOfLine), pegged.peg.any)), endOfLine), "Pegged.DLineComment"), "DLineComment")(TParseTree("", false,[], s));
1404     }
1405     static string DLineComment(GetName g)
1406     {
1407         return "Pegged.DLineComment";
1408     }
1409 
1410     static TParseTree DBlockComment(TParseTree p)
1411     {
1412         if(__ctfe)
1413             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("/*"), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.literal!("*/")), pegged.peg.any)), pegged.peg.literal!("*/")), "Pegged.DBlockComment")(p);
1414         else
1415             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("/*"), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.literal!("*/")), pegged.peg.any)), pegged.peg.literal!("*/")), "Pegged.DBlockComment"), "DBlockComment")(p);
1416     }
1417     static TParseTree DBlockComment(string s)
1418     {
1419         if(__ctfe)
1420             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("/*"), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.literal!("*/")), pegged.peg.any)), pegged.peg.literal!("*/")), "Pegged.DBlockComment")(TParseTree("", false,[], s));
1421         else
1422             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.literal!("/*"), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.literal!("*/")), pegged.peg.any)), pegged.peg.literal!("*/")), "Pegged.DBlockComment"), "DBlockComment")(TParseTree("", false,[], s));
1423     }
1424     static string DBlockComment(GetName g)
1425     {
1426         return "Pegged.DBlockComment";
1427     }
1428 
1429     static TParseTree DNestingBlockComment(TParseTree p)
1430     {
1431         if(__ctfe)
1432             return         pegged.peg.named!(NestedList!(pegged.peg.literal!("/+"), pegged.peg.literal!("+/")), "Pegged.DNestingBlockComment")(p);
1433         else
1434             return hooked!(pegged.peg.named!(NestedList!(pegged.peg.literal!("/+"), pegged.peg.literal!("+/")), "Pegged.DNestingBlockComment"), "DNestingBlockComment")(p);
1435     }
1436     static TParseTree DNestingBlockComment(string s)
1437     {
1438         if(__ctfe)
1439             return         pegged.peg.named!(NestedList!(pegged.peg.literal!("/+"), pegged.peg.literal!("+/")), "Pegged.DNestingBlockComment")(TParseTree("", false,[], s));
1440         else
1441             return hooked!(pegged.peg.named!(NestedList!(pegged.peg.literal!("/+"), pegged.peg.literal!("+/")), "Pegged.DNestingBlockComment"), "DNestingBlockComment")(TParseTree("", false,[], s));
1442     }
1443     static string DNestingBlockComment(GetName g)
1444     {
1445         return "Pegged.DNestingBlockComment";
1446     }
1447 
1448     static TParseTree DParamList(TParseTree p)
1449     {
1450         if(__ctfe)
1451             return         pegged.peg.named!(NestedList!(pegged.peg.literal!("("), pegged.peg.literal!(")")), "Pegged.DParamList")(p);
1452         else
1453             return hooked!(pegged.peg.named!(NestedList!(pegged.peg.literal!("("), pegged.peg.literal!(")")), "Pegged.DParamList"), "DParamList")(p);
1454     }
1455     static TParseTree DParamList(string s)
1456     {
1457         if(__ctfe)
1458             return         pegged.peg.named!(NestedList!(pegged.peg.literal!("("), pegged.peg.literal!(")")), "Pegged.DParamList")(TParseTree("", false,[], s));
1459         else
1460             return hooked!(pegged.peg.named!(NestedList!(pegged.peg.literal!("("), pegged.peg.literal!(")")), "Pegged.DParamList"), "DParamList")(TParseTree("", false,[], s));
1461     }
1462     static string DParamList(GetName g)
1463     {
1464         return "Pegged.DParamList";
1465     }
1466 
1467     template NestedList(alias L, alias Items, alias R)
1468     {
1469     static TParseTree NestedList(TParseTree p)
1470     {
1471         if(__ctfe)
1472             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.keep!(L), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R, Items)), pegged.peg.any)), pegged.peg.zeroOrMore!(pegged.peg.or!(Items, NestedList!(L, Items, R), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R, Items)), pegged.peg.any)))), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R, Items)), pegged.peg.any)), pegged.peg.keep!(R)), "Pegged.NestedList!(" ~ pegged.peg.getName!(L)() ~ ", " ~ pegged.peg.getName!(Items)() ~ ", " ~ pegged.peg.getName!(R) ~ ")")(p);
1473         else
1474             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.keep!(L), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R, Items)), pegged.peg.any)), pegged.peg.zeroOrMore!(pegged.peg.or!(Items, NestedList!(L, Items, R), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R, Items)), pegged.peg.any)))), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R, Items)), pegged.peg.any)), pegged.peg.keep!(R)), "Pegged.NestedList!(" ~ pegged.peg.getName!(L)() ~ ", " ~ pegged.peg.getName!(Items)() ~ ", " ~ pegged.peg.getName!(R) ~ ")"), "NestedList_3")(p);
1475     }
1476     static TParseTree NestedList(string s)
1477     {
1478         if(__ctfe)
1479             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.keep!(L), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R, Items)), pegged.peg.any)), pegged.peg.zeroOrMore!(pegged.peg.or!(Items, NestedList!(L, Items, R), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R, Items)), pegged.peg.any)))), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R, Items)), pegged.peg.any)), pegged.peg.keep!(R)), "Pegged.NestedList!(" ~ pegged.peg.getName!(L)() ~ ", " ~ pegged.peg.getName!(Items)() ~ ", " ~ pegged.peg.getName!(R) ~ ")")(TParseTree("", false,[], s));
1480         else
1481             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.keep!(L), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R, Items)), pegged.peg.any)), pegged.peg.zeroOrMore!(pegged.peg.or!(Items, NestedList!(L, Items, R), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R, Items)), pegged.peg.any)))), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R, Items)), pegged.peg.any)), pegged.peg.keep!(R)), "Pegged.NestedList!(" ~ pegged.peg.getName!(L)() ~ ", " ~ pegged.peg.getName!(Items)() ~ ", " ~ pegged.peg.getName!(R) ~ ")"), "NestedList_3")(TParseTree("", false,[], s));
1482     }
1483     static string NestedList(GetName g)
1484     {
1485         return "Pegged.NestedList!(" ~ pegged.peg.getName!(L)() ~ ", " ~ pegged.peg.getName!(Items)() ~ ", " ~ pegged.peg.getName!(R) ~ ")";
1486     }
1487 
1488     }
1489     template NestedList(alias L, alias R)
1490     {
1491     static TParseTree NestedList(TParseTree p)
1492     {
1493         if(__ctfe)
1494             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.keep!(L), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R)), pegged.peg.any)), pegged.peg.zeroOrMore!(pegged.peg.or!(NestedList!(L, R), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R)), pegged.peg.any)))), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R)), pegged.peg.any)), pegged.peg.keep!(R)), "Pegged.NestedList!(" ~ pegged.peg.getName!(L)() ~ ", " ~ pegged.peg.getName!(R) ~ ")")(p);
1495         else
1496             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.keep!(L), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R)), pegged.peg.any)), pegged.peg.zeroOrMore!(pegged.peg.or!(NestedList!(L, R), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R)), pegged.peg.any)))), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R)), pegged.peg.any)), pegged.peg.keep!(R)), "Pegged.NestedList!(" ~ pegged.peg.getName!(L)() ~ ", " ~ pegged.peg.getName!(R) ~ ")"), "NestedList_2")(p);
1497     }
1498     static TParseTree NestedList(string s)
1499     {
1500         if(__ctfe)
1501             return         pegged.peg.named!(pegged.peg.and!(pegged.peg.keep!(L), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R)), pegged.peg.any)), pegged.peg.zeroOrMore!(pegged.peg.or!(NestedList!(L, R), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R)), pegged.peg.any)))), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R)), pegged.peg.any)), pegged.peg.keep!(R)), "Pegged.NestedList!(" ~ pegged.peg.getName!(L)() ~ ", " ~ pegged.peg.getName!(R) ~ ")")(TParseTree("", false,[], s));
1502         else
1503             return hooked!(pegged.peg.named!(pegged.peg.and!(pegged.peg.keep!(L), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R)), pegged.peg.any)), pegged.peg.zeroOrMore!(pegged.peg.or!(NestedList!(L, R), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R)), pegged.peg.any)))), pegged.peg.zeroOrMore!(pegged.peg.and!(pegged.peg.negLookahead!(pegged.peg.or!(L, R)), pegged.peg.any)), pegged.peg.keep!(R)), "Pegged.NestedList!(" ~ pegged.peg.getName!(L)() ~ ", " ~ pegged.peg.getName!(R) ~ ")"), "NestedList_2")(TParseTree("", false,[], s));
1504     }
1505     static string NestedList(GetName g)
1506     {
1507         return "Pegged.NestedList!(" ~ pegged.peg.getName!(L)() ~ ", " ~ pegged.peg.getName!(R) ~ ")";
1508     }
1509 
1510     }
1511     static TParseTree opCall(TParseTree p)
1512     {
1513         TParseTree result = decimateTree(Grammar(p));
1514         result.children = [result];
1515         result.name = "Pegged";
1516         return result;
1517     }
1518 
1519     static TParseTree opCall(string input)
1520     {
1521         return Pegged(TParseTree(``, false, [], input, 0, 0));
1522 }
1523     static string opCall(GetName g)
1524     {
1525         return "Pegged";
1526     }
1527 
1528     }
1529 }
1530 
1531 alias GenericPegged!(ParseTree).Pegged Pegged;
1532