1 module pegged.examples.cparser;
2 
3 import pegged.grammar;
4 
5 struct C
6 {
7     enum names = [`TranslationUnit`:true, `ExternalDeclaration`:true, `FunctionDefinition`:true, `PrimaryExpression`:true,
8     `PostfixExpression`:true, `ArgumentExpressionList`:true, `UnaryExpression`:true, `IncrementExpression`:true, `PlusPlus`:true,
9     `DecrementExpression`:true, `UnaryOperator`:true, `CastExpression`:true, `MultiplicativeExpression`:true, `AdditiveExpression`:true,
10     `ShiftExpression`:true, `RelationalExpression`:true, `EqualityExpression`:true, `ANDExpression`:true, `ExclusiveORExpression`:true,
11     `InclusiveORExpression`:true, `LogicalANDExpression`:true, `LogicalORExpression`:true, `ConditionalExpression`:true, `AssignmentExpression`:true,
12     `AssignmentOperator`:true, `Expression`:true, `ConstantExpression`:true, `Declaration`:true, `DeclarationSpecifiers`:true, `InitDeclaratorList`:true,
13     `InitDeclarator`:true, `StorageClassSpecifier`:true, `TypeSpecifier`:true, `StructOrUnionSpecifier`:true, `StructDeclarationList`:true,
14     `StructDeclaration`:true, `SpecifierQualifierList`:true, `StructDeclaratorList`:true, `StructDeclarator`:true, `EnumSpecifier`:true,
15     `EnumeratorList`:true, `Enumerator`:true, `EnumerationConstant`:true, `TypeQualifier`:true, `Declarator`:true, `DirectDeclarator`:true,
16     `Pointer`:true, `TypeQualifierList`:true, `ParameterTypeList`:true, `ParameterList`:true, `ParameterDeclaration`:true, `IdentifierList`:true,
17     `TypeName`:true, `AbstractDeclarator`:true, `DirectAbstractDeclarator`:true, `TypedefName`:true, `Initializer`:true, `InitializerList`:true,
18     `Statement`:true, `LabeledStatement`:true, `CompoundStatement`:true, `DeclarationList`:true, `StatementList`:true, `ExpressionStatement`:true,
19     `IfStatement`:true, `SwitchStatement`:true, `IterationStatement`:true, `WhileStatement`:true, `DoStatement`:true, `ForStatement`:true,
20     `GotoStatement`:true, `ContinueStatement`:true, `BreakStatement`:true, `ReturnStatement`:true, `Return`:true, `Identifier`:true,
21     `Keyword`:true, `Spacing`:true, `Comment`:true, `StringLiteral`:true, `DQChar`:true, `EscapeSequence`:true, `CharLiteral`:true, `IntegerLiteral`:true,
22     `Integer`:true, `IntegerSuffix`:true, `FloatLiteral`:true, `Sign`:true];
23 
24     mixin decimateTree;
25 
26     static ParseTree TranslationUnit(ParseTree p)
27     {
28         return named!(and!(ExternalDeclaration, zeroOrMore!(and!(discard!(Spacing), ExternalDeclaration))), "TranslationUnit")(p);
29     }
30 
31     static ParseTree ExternalDeclaration(ParseTree p)
32     {
33         return named!(or!(spaceAnd!(Spacing, FunctionDefinition), spaceAnd!(Spacing, Declaration)), "ExternalDeclaration")(p);
34     }
35 
36     static ParseTree FunctionDefinition(ParseTree p)
37     {
38         return named!(spaceAnd!(Spacing, option!(DeclarationSpecifiers), Declarator, option!(DeclarationList), CompoundStatement), "FunctionDefinition")(p);
39     }
40 
41     static ParseTree PrimaryExpression(ParseTree p)
42     {
43         return named!(or!(spaceAnd!(Spacing, Identifier), spaceAnd!(Spacing, CharLiteral), spaceAnd!(Spacing, StringLiteral), spaceAnd!(Spacing, FloatLiteral), spaceAnd!(Spacing, IntegerLiteral), spaceAnd!(Spacing, literal!("("), Expression, literal!(")"))), "PrimaryExpression")(p);
44     }
45 
46     static ParseTree PostfixExpression(ParseTree p)
47     {
48         return named!(spaceAnd!(Spacing, PrimaryExpression, zeroOrMore!(or!(spaceAnd!(Spacing, literal!("["), Expression, literal!("]")), spaceAnd!(Spacing, literal!("("), literal!(")")), spaceAnd!(Spacing, literal!("("), ArgumentExpressionList, literal!(")")), spaceAnd!(Spacing, literal!("."), Identifier), spaceAnd!(Spacing, literal!("->"), Identifier), spaceAnd!(Spacing, literal!("++")), spaceAnd!(Spacing, literal!("--"))))), "PostfixExpression")(p);
49     }
50 
51     static ParseTree ArgumentExpressionList(ParseTree p)
52     {
53         return named!(spaceAnd!(Spacing, AssignmentExpression, zeroOrMore!(spaceAnd!(Spacing, literal!(","), AssignmentExpression))), "ArgumentExpressionList")(p);
54     }
55 
56     static ParseTree UnaryExpression(ParseTree p)
57     {
58         return named!(or!(spaceAnd!(Spacing, PostfixExpression), spaceAnd!(Spacing, IncrementExpression), spaceAnd!(Spacing, DecrementExpression), spaceAnd!(Spacing, UnaryOperator, CastExpression), spaceAnd!(Spacing, literal!("sizeof"), UnaryExpression), spaceAnd!(Spacing, literal!("sizeof"), literal!("("), TypeName, literal!(")"))), "UnaryExpression")(p);
59     }
60 
61     static ParseTree IncrementExpression(ParseTree p)
62     {
63         return named!(spaceAnd!(Spacing, PlusPlus, UnaryExpression), "IncrementExpression")(p);
64     }
65 
66     static ParseTree PlusPlus(ParseTree p)
67     {
68         return named!(and!(literal!("++")), "PlusPlus")(p);
69     }
70 
71     static ParseTree DecrementExpression(ParseTree p)
72     {
73         return named!(spaceAnd!(Spacing, literal!("--"), UnaryExpression), "DecrementExpression")(p);
74     }
75 
76     static ParseTree UnaryOperator(ParseTree p)
77     {
78         return named!(and!(or!(literal!("-"), literal!("&"), literal!("*"), literal!("+"), literal!("~"), literal!("!"))), "UnaryOperator")(p);
79     }
80 
81     static ParseTree CastExpression(ParseTree p)
82     {
83         return named!(or!(spaceAnd!(Spacing, UnaryExpression), spaceAnd!(Spacing, literal!("("), TypeName, literal!(")"), CastExpression)), "CastExpression")(p);
84     }
85 
86     static ParseTree MultiplicativeExpression(ParseTree p)
87     {
88         return named!(spaceAnd!(Spacing, CastExpression, zeroOrMore!(spaceAnd!(Spacing, or!(literal!("*"), literal!("%"), literal!("/")), MultiplicativeExpression))), "MultiplicativeExpression")(p);
89     }
90 
91     static ParseTree AdditiveExpression(ParseTree p)
92     {
93         return named!(spaceAnd!(Spacing, MultiplicativeExpression, zeroOrMore!(spaceAnd!(Spacing, or!(literal!("-"), literal!("+")), AdditiveExpression))), "AdditiveExpression")(p);
94     }
95 
96     static ParseTree ShiftExpression(ParseTree p)
97     {
98         return named!(spaceAnd!(Spacing, AdditiveExpression, zeroOrMore!(spaceAnd!(Spacing, or!(spaceAnd!(Spacing, literal!("<<")), spaceAnd!(Spacing, literal!(">>"))), ShiftExpression))), "ShiftExpression")(p);
99     }
100 
101     static ParseTree RelationalExpression(ParseTree p)
102     {
103         return named!(spaceAnd!(Spacing, ShiftExpression, zeroOrMore!(spaceAnd!(Spacing, or!(spaceAnd!(Spacing, literal!("<=")), spaceAnd!(Spacing, literal!(">=")), spaceAnd!(Spacing, literal!("<")), spaceAnd!(Spacing, literal!(">"))), RelationalExpression))), "RelationalExpression")(p);
104     }
105 
106     static ParseTree EqualityExpression(ParseTree p)
107     {
108         return named!(spaceAnd!(Spacing, RelationalExpression, zeroOrMore!(spaceAnd!(Spacing, or!(spaceAnd!(Spacing, literal!("==")), spaceAnd!(Spacing, literal!("!="))), EqualityExpression))), "EqualityExpression")(p);
109     }
110 
111     static ParseTree ANDExpression(ParseTree p)
112     {
113         return named!(spaceAnd!(Spacing, EqualityExpression, zeroOrMore!(spaceAnd!(Spacing, literal!("&"), ANDExpression))), "ANDExpression")(p);
114     }
115 
116     static ParseTree ExclusiveORExpression(ParseTree p)
117     {
118         return named!(spaceAnd!(Spacing, ANDExpression, zeroOrMore!(spaceAnd!(Spacing, literal!("^"), ExclusiveORExpression))), "ExclusiveORExpression")(p);
119     }
120 
121     static ParseTree InclusiveORExpression(ParseTree p)
122     {
123         return named!(spaceAnd!(Spacing, ExclusiveORExpression, zeroOrMore!(spaceAnd!(Spacing, literal!("|"), InclusiveORExpression))), "InclusiveORExpression")(p);
124     }
125 
126     static ParseTree LogicalANDExpression(ParseTree p)
127     {
128         return named!(spaceAnd!(Spacing, InclusiveORExpression, zeroOrMore!(spaceAnd!(Spacing, literal!("&&"), LogicalANDExpression))), "LogicalANDExpression")(p);
129     }
130 
131     static ParseTree LogicalORExpression(ParseTree p)
132     {
133         return named!(spaceAnd!(Spacing, LogicalANDExpression, zeroOrMore!(spaceAnd!(Spacing, literal!("||"), LogicalORExpression))), "LogicalORExpression")(p);
134     }
135 
136     static ParseTree ConditionalExpression(ParseTree p)
137     {
138         return named!(spaceAnd!(Spacing, LogicalORExpression, option!(spaceAnd!(Spacing, literal!("?"), Expression, literal!(":"), ConditionalExpression))), "ConditionalExpression")(p);
139     }
140 
141     static ParseTree AssignmentExpression(ParseTree p)
142     {
143         return named!(or!(spaceAnd!(Spacing, UnaryExpression, AssignmentOperator, AssignmentExpression), spaceAnd!(Spacing, ConditionalExpression)), "AssignmentExpression")(p);
144     }
145 
146     static ParseTree AssignmentOperator(ParseTree p)
147     {
148         return named!(or!(and!(literal!("=")), and!(literal!("*=")), and!(literal!("/=")), and!(literal!("%=")), and!(literal!("+=")), and!(literal!("-=")), and!(literal!("<<=")), and!(literal!(">>=")), and!(literal!("&=")), and!(literal!("^=")), and!(literal!("|="))), "AssignmentOperator")(p);
149     }
150 
151     static ParseTree Expression(ParseTree p)
152     {
153         return named!(spaceAnd!(Spacing, AssignmentExpression, zeroOrMore!(spaceAnd!(Spacing, literal!(","), AssignmentExpression))), "Expression")(p);
154     }
155 
156     static ParseTree ConstantExpression(ParseTree p)
157     {
158         return named!(and!(ConditionalExpression), "ConstantExpression")(p);
159     }
160 
161     static ParseTree Declaration(ParseTree p)
162     {
163         return named!(spaceAnd!(Spacing, DeclarationSpecifiers, option!(InitDeclaratorList), literal!(";")), "Declaration")(p);
164     }
165 
166     static ParseTree DeclarationSpecifiers(ParseTree p)
167     {
168         return named!(spaceAnd!(Spacing, or!(spaceAnd!(Spacing, StorageClassSpecifier), spaceAnd!(Spacing, TypeSpecifier), spaceAnd!(Spacing, TypeQualifier)), option!(DeclarationSpecifiers)), "DeclarationSpecifiers")(p);
169     }
170 
171     static ParseTree InitDeclaratorList(ParseTree p)
172     {
173         return named!(spaceAnd!(Spacing, InitDeclarator, zeroOrMore!(spaceAnd!(Spacing, literal!(","), InitDeclarator))), "InitDeclaratorList")(p);
174     }
175 
176     static ParseTree InitDeclarator(ParseTree p)
177     {
178         return named!(spaceAnd!(Spacing, Declarator, option!(spaceAnd!(Spacing, literal!("="), Initializer))), "InitDeclarator")(p);
179     }
180 
181     static ParseTree StorageClassSpecifier(ParseTree p)
182     {
183         return named!(or!(and!(literal!("typedef")), and!(literal!("extern")), and!(literal!("static")), and!(literal!("auto")), and!(literal!("register"))), "StorageClassSpecifier")(p);
184     }
185 
186     static ParseTree TypeSpecifier(ParseTree p)
187     {
188         return named!(or!(and!(literal!("void")), and!(literal!("char")), and!(literal!("short")), and!(literal!("int")), and!(literal!("long")), and!(literal!("float")), and!(literal!("double")), and!(literal!("signed")), and!(literal!("unsigned")), and!(StructOrUnionSpecifier), and!(EnumSpecifier)), "TypeSpecifier")(p);
189     }
190 
191     static ParseTree StructOrUnionSpecifier(ParseTree p)
192     {
193         return named!(spaceAnd!(Spacing, or!(spaceAnd!(Spacing, literal!("struct")), spaceAnd!(Spacing, literal!("union"))), or!(spaceAnd!(Spacing, Identifier, option!(spaceAnd!(Spacing, literal!("{"), StructDeclarationList, literal!("}")))), spaceAnd!(Spacing, literal!("{"), StructDeclarationList, literal!("}")))), "StructOrUnionSpecifier")(p);
194     }
195 
196     static ParseTree StructDeclarationList(ParseTree p)
197     {
198         return named!(and!(StructDeclaration, zeroOrMore!(and!(discard!(Spacing), StructDeclaration))), "StructDeclarationList")(p);
199     }
200 
201     static ParseTree StructDeclaration(ParseTree p)
202     {
203         return named!(spaceAnd!(Spacing, SpecifierQualifierList, StructDeclaratorList, literal!(";")), "StructDeclaration")(p);
204     }
205 
206     static ParseTree SpecifierQualifierList(ParseTree p)
207     {
208         return named!(and!(or!(and!(TypeQualifier), and!(TypeSpecifier)), zeroOrMore!(and!(discard!(Spacing), or!(and!(TypeQualifier), and!(TypeSpecifier))))), "SpecifierQualifierList")(p);
209     }
210 
211     static ParseTree StructDeclaratorList(ParseTree p)
212     {
213         return named!(spaceAnd!(Spacing, StructDeclarator, zeroOrMore!(spaceAnd!(Spacing, literal!(","), StructDeclarator))), "StructDeclaratorList")(p);
214     }
215 
216     static ParseTree StructDeclarator(ParseTree p)
217     {
218         return named!(spaceAnd!(Spacing, or!(spaceAnd!(Spacing, Declarator, option!(ConstantExpression)), spaceAnd!(Spacing, ConstantExpression))), "StructDeclarator")(p);
219     }
220 
221     static ParseTree EnumSpecifier(ParseTree p)
222     {
223         return named!(spaceAnd!(Spacing, literal!("enum"), or!(spaceAnd!(Spacing, Identifier, option!(spaceAnd!(Spacing, literal!("{"), EnumeratorList, literal!("}")))), spaceAnd!(Spacing, literal!("{"), EnumeratorList, literal!("}")))), "EnumSpecifier")(p);
224     }
225 
226     static ParseTree EnumeratorList(ParseTree p)
227     {
228         return named!(spaceAnd!(Spacing, Enumerator, zeroOrMore!(spaceAnd!(Spacing, literal!(","), Enumerator))), "EnumeratorList")(p);
229     }
230 
231     static ParseTree Enumerator(ParseTree p)
232     {
233         return named!(spaceAnd!(Spacing, EnumerationConstant, option!(spaceAnd!(Spacing, literal!("="), ConstantExpression))), "Enumerator")(p);
234     }
235 
236     static ParseTree EnumerationConstant(ParseTree p)
237     {
238         return named!(and!(Identifier), "EnumerationConstant")(p);
239     }
240 
241     static ParseTree TypeQualifier(ParseTree p)
242     {
243         return named!(or!(and!(literal!("const")), and!(literal!("volatile"))), "TypeQualifier")(p);
244     }
245 
246     static ParseTree Declarator(ParseTree p)
247     {
248         return named!(spaceAnd!(Spacing, option!(Pointer), DirectDeclarator), "Declarator")(p);
249     }
250 
251     static ParseTree DirectDeclarator(ParseTree p)
252     {
253         return named!(spaceAnd!(Spacing, or!(spaceAnd!(Spacing, Identifier), spaceAnd!(Spacing, literal!("("), Declarator, literal!(")"))), zeroOrMore!(or!(spaceAnd!(Spacing, literal!("["), literal!("]")), spaceAnd!(Spacing, literal!("["), ConstantExpression, literal!("]")), spaceAnd!(Spacing, literal!("("), literal!(")")), spaceAnd!(Spacing, literal!("("), ParameterTypeList, literal!(")")), spaceAnd!(Spacing, literal!("("), IdentifierList, literal!(")"))))), "DirectDeclarator")(p);
254     }
255 
256     static ParseTree Pointer(ParseTree p)
257     {
258         return named!(spaceAnd!(Spacing, zeroOrMore!(spaceAnd!(Spacing, literal!("*"), zeroOrMore!(TypeQualifier)))), "Pointer")(p);
259     }
260 
261     static ParseTree TypeQualifierList(ParseTree p)
262     {
263         return named!(and!(TypeQualifier, zeroOrMore!(and!(discard!(Spacing), TypeQualifier))), "TypeQualifierList")(p);
264     }
265 
266     static ParseTree ParameterTypeList(ParseTree p)
267     {
268         return named!(spaceAnd!(Spacing, ParameterList, option!(spaceAnd!(Spacing, literal!(","), literal!("...")))), "ParameterTypeList")(p);
269     }
270 
271     static ParseTree ParameterList(ParseTree p)
272     {
273         return named!(spaceAnd!(Spacing, ParameterDeclaration, zeroOrMore!(spaceAnd!(Spacing, literal!(","), ParameterDeclaration))), "ParameterList")(p);
274     }
275 
276     static ParseTree ParameterDeclaration(ParseTree p)
277     {
278         return named!(spaceAnd!(Spacing, DeclarationSpecifiers, option!(or!(spaceAnd!(Spacing, Declarator), spaceAnd!(Spacing, AbstractDeclarator)))), "ParameterDeclaration")(p);
279     }
280 
281     static ParseTree IdentifierList(ParseTree p)
282     {
283         return named!(spaceAnd!(Spacing, Identifier, zeroOrMore!(spaceAnd!(Spacing, literal!(","), Identifier))), "IdentifierList")(p);
284     }
285 
286     static ParseTree TypeName(ParseTree p)
287     {
288         return named!(spaceAnd!(Spacing, SpecifierQualifierList, option!(AbstractDeclarator)), "TypeName")(p);
289     }
290 
291     static ParseTree AbstractDeclarator(ParseTree p)
292     {
293         return named!(or!(spaceAnd!(Spacing, Pointer, DirectAbstractDeclarator), spaceAnd!(Spacing, DirectAbstractDeclarator), spaceAnd!(Spacing, Pointer)), "AbstractDeclarator")(p);
294     }
295 
296     static ParseTree DirectAbstractDeclarator(ParseTree p)
297     {
298         return named!(spaceAnd!(Spacing, or!(spaceAnd!(Spacing, literal!("("), AbstractDeclarator, literal!(")")), spaceAnd!(Spacing, literal!("["), literal!("]")), spaceAnd!(Spacing, literal!("["), ConstantExpression, literal!("]")), spaceAnd!(Spacing, literal!("("), literal!(")")), spaceAnd!(Spacing, literal!("("), ParameterTypeList, literal!(")"))), zeroOrMore!(or!(spaceAnd!(Spacing, literal!("["), literal!("]")), spaceAnd!(Spacing, literal!("["), ConstantExpression, literal!("]")), spaceAnd!(Spacing, literal!("("), literal!(")")), spaceAnd!(Spacing, literal!("("), ParameterTypeList, literal!(")"))))), "DirectAbstractDeclarator")(p);
299     }
300 
301     static ParseTree TypedefName(ParseTree p)
302     {
303         return named!(and!(Identifier), "TypedefName")(p);
304     }
305 
306     static ParseTree Initializer(ParseTree p)
307     {
308         return named!(or!(spaceAnd!(Spacing, AssignmentExpression), spaceAnd!(Spacing, literal!("{"), InitializerList, option!(literal!(",")), literal!("}"))), "Initializer")(p);
309     }
310 
311     static ParseTree InitializerList(ParseTree p)
312     {
313         return named!(spaceAnd!(Spacing, Initializer, zeroOrMore!(spaceAnd!(Spacing, literal!(","), Initializer))), "InitializerList")(p);
314     }
315 
316     static ParseTree Statement(ParseTree p)
317     {
318         return named!(or!(spaceAnd!(Spacing, LabeledStatement), spaceAnd!(Spacing, CompoundStatement), spaceAnd!(Spacing, ExpressionStatement), spaceAnd!(Spacing, IfStatement), spaceAnd!(Spacing, SwitchStatement), spaceAnd!(Spacing, IterationStatement), spaceAnd!(Spacing, GotoStatement), spaceAnd!(Spacing, ContinueStatement), spaceAnd!(Spacing, BreakStatement), spaceAnd!(Spacing, ReturnStatement)), "Statement")(p);
319     }
320 
321     static ParseTree LabeledStatement(ParseTree p)
322     {
323         return named!(or!(spaceAnd!(Spacing, Identifier, literal!(":"), Statement), spaceAnd!(Spacing, literal!("case"), ConstantExpression, literal!(":"), Statement), spaceAnd!(Spacing, literal!("default"), literal!(":"), Statement)), "LabeledStatement")(p);
324     }
325 
326     static ParseTree CompoundStatement(ParseTree p)
327     {
328         return named!(or!(spaceAnd!(Spacing, literal!("{"), literal!("}")), spaceAnd!(Spacing, literal!("{"), DeclarationList, literal!("}")), spaceAnd!(Spacing, literal!("{"), StatementList, literal!("}")), spaceAnd!(Spacing, literal!("{"), DeclarationList, StatementList, literal!("}"))), "CompoundStatement")(p);
329     }
330 
331     static ParseTree DeclarationList(ParseTree p)
332     {
333         return named!(and!(Declaration, zeroOrMore!(and!(discard!(Spacing), Declaration))), "DeclarationList")(p);
334     }
335 
336     static ParseTree StatementList(ParseTree p)
337     {
338         return named!(and!(Statement, zeroOrMore!(and!(discard!(Spacing), Statement))), "StatementList")(p);
339     }
340 
341     static ParseTree ExpressionStatement(ParseTree p)
342     {
343         return named!(spaceAnd!(Spacing, option!(Expression), literal!(";")), "ExpressionStatement")(p);
344     }
345 
346     static ParseTree IfStatement(ParseTree p)
347     {
348         return named!(spaceAnd!(Spacing, literal!("if"), literal!("("), Expression, literal!(")"), Statement, option!(spaceAnd!(Spacing, literal!("else"), Statement))), "IfStatement")(p);
349     }
350 
351     static ParseTree SwitchStatement(ParseTree p)
352     {
353         return named!(spaceAnd!(Spacing, literal!("switch"), literal!("("), Expression, literal!(")"), Statement), "SwitchStatement")(p);
354     }
355 
356     static ParseTree IterationStatement(ParseTree p)
357     {
358         return named!(or!(spaceAnd!(Spacing, WhileStatement), spaceAnd!(Spacing, DoStatement), spaceAnd!(Spacing, ForStatement)), "IterationStatement")(p);
359     }
360 
361     static ParseTree WhileStatement(ParseTree p)
362     {
363         return named!(spaceAnd!(Spacing, literal!("while"), literal!("("), Expression, literal!(")"), Statement), "WhileStatement")(p);
364     }
365 
366     static ParseTree DoStatement(ParseTree p)
367     {
368         return named!(spaceAnd!(Spacing, literal!("do"), Statement, literal!("while"), literal!("("), Expression, literal!(")"), literal!(";")), "DoStatement")(p);
369     }
370 
371     static ParseTree ForStatement(ParseTree p)
372     {
373         return named!(spaceAnd!(Spacing, literal!("for"), literal!("("), option!(Expression), literal!(";"), option!(Expression), literal!(";"), option!(Expression), literal!(")"), Statement), "ForStatement")(p);
374     }
375 
376     static ParseTree GotoStatement(ParseTree p)
377     {
378         return named!(spaceAnd!(Spacing, literal!("goto"), Identifier, literal!(";")), "GotoStatement")(p);
379     }
380 
381     static ParseTree ContinueStatement(ParseTree p)
382     {
383         return named!(spaceAnd!(Spacing, literal!("continue"), literal!(";")), "ContinueStatement")(p);
384     }
385 
386     static ParseTree BreakStatement(ParseTree p)
387     {
388         return named!(spaceAnd!(Spacing, literal!("break"), literal!(";")), "BreakStatement")(p);
389     }
390 
391     static ParseTree ReturnStatement(ParseTree p)
392     {
393         return named!(spaceAnd!(Spacing, Return, option!(Expression), discard!(literal!(";"))), "ReturnStatement")(p);
394     }
395 
396     static ParseTree Return(ParseTree p)
397     {
398         return named!(and!(literal!("return")), "Return")(p);
399     }
400 
401     static ParseTree Identifier(ParseTree p)
402     {
403         return named!(fuse!(and!(negLookahead!(Keyword), or!(charRange!('a', 'z'), charRange!('A', 'Z'), literal!("_")), zeroOrMore!(or!(charRange!('a', 'z'), charRange!('A', 'Z'), charRange!('0', '9'), literal!("_"))))), "Identifier")(p);
404     }
405 
406     static ParseTree Keyword(ParseTree p)
407     {
408         return named!(or!(and!(literal!("auto")), and!(literal!("break")), and!(literal!("case")), and!(literal!("char")), and!(literal!("const")), and!(literal!("continue")), and!(literal!("default")), and!(literal!("double")), and!(literal!("do")), and!(literal!("else")), and!(literal!("enum")), and!(literal!("extern")), and!(literal!("float")), and!(literal!("for")), and!(literal!("goto")), and!(literal!("if")), and!(literal!("inline")), and!(literal!("int")), and!(literal!("long")), and!(literal!("register")), and!(literal!("restrict")), and!(literal!("return")), and!(literal!("short")), and!(literal!("signed")), and!(literal!("sizeof")), and!(literal!("static")), and!(literal!("struct")), and!(literal!("switch")), and!(literal!("typedef")), and!(literal!("union")), and!(literal!("unsigned")), and!(literal!("void")), and!(literal!("volatile")), and!(literal!("while")), and!(literal!("_Bool")), and!(literal!("_Complex")), and!(literal!("_Imaginary"))), "Keyword")(p);
409     }
410 
411     static ParseTree Spacing(ParseTree p)
412     {
413         return named!(fuse!(and!(zeroOrMore!(or!(and!(space), and!(blank), and!(endOfLine), and!(Comment))))), "Spacing")(p);
414     }
415 
416     static ParseTree Comment(ParseTree p)
417     {
418         return named!(fuse!(and!(literal!("//"), zeroOrMore!(and!(negLookahead!(endOfLine), fparse.any)), endOfLine)), "Comment")(p);
419     }
420 
421     static ParseTree StringLiteral(ParseTree p)
422     {
423         return named!(fuse!(and!(doublequote, zeroOrMore!(and!(DQChar)), doublequote)), "StringLiteral")(p);
424     }
425 
426     static ParseTree DQChar(ParseTree p)
427     {
428         return named!(or!(and!(EscapeSequence), and!(negLookahead!(doublequote), fparse.any)), "DQChar")(p);
429     }
430 
431     static ParseTree EscapeSequence(ParseTree p)
432     {
433         return named!(fuse!(and!(backslash, or!(and!(quote), and!(doublequote), and!(backslash), and!(or!(literal!("a"), literal!("b"), literal!("f"), literal!("n"), literal!("r"), literal!("t"), literal!("v")))))), "EscapeSequence")(p);
434     }
435 
436     static ParseTree CharLiteral(ParseTree p)
437     {
438         return named!(fuse!(and!(quote, and!(negLookahead!(quote), or!(and!(EscapeSequence), and!(fparse.any))), quote)), "CharLiteral")(p);
439     }
440 
441     static ParseTree IntegerLiteral(ParseTree p)
442     {
443         return named!(fuse!(and!(option!(Sign), Integer, option!(IntegerSuffix))), "IntegerLiteral")(p);
444     }
445 
446     static ParseTree Integer(ParseTree p)
447     {
448         return named!(fuse!(and!(oneOrMore!(digit))), "Integer")(p);
449     }
450 
451     static ParseTree IntegerSuffix(ParseTree p)
452     {
453         return named!(or!(and!(literal!("Lu")), and!(literal!("LU")), and!(literal!("uL")), and!(literal!("UL")), and!(literal!("L")), and!(literal!("u")), and!(literal!("U"))), "IntegerSuffix")(p);
454     }
455 
456     static ParseTree FloatLiteral(ParseTree p)
457     {
458         return named!(fuse!(and!(option!(Sign), Integer, literal!("."), option!(Integer), option!(and!(or!(and!(literal!("e")), and!(literal!("E"))), option!(Sign), Integer)))), "FloatLiteral")(p);
459     }
460 
461     static ParseTree Sign(ParseTree p)
462     {
463         return named!(or!(and!(literal!("-")), and!(literal!("+"))), "Sign")(p);
464     }
465 
466     static ParseTree opCall(ParseTree p)
467     {
468         ParseTree result = decimateTree(TranslationUnit(p));
469         result.children = [result];
470         result.name = "C";
471         return result;
472     }
473 
474     static ParseTree opCall(string input)
475     {
476         return C(ParseTree(``, false, [], input, 0, 0));
477     }
478 }