1 module pegged.examples.dgrammar;
2 
3 import pegged.grammar;
4 
5 enum Dgrammar = `
6 D:
7 
8 Module <- ModuleDeclaration? DeclDefs?
9 
10 DeclDefs < DeclDef+
11 
12 DeclDef < AttributeSpecifier
13         / ImportDeclaration
14         / EnumDeclaration
15         / ClassDeclaration
16         / InterfaceDeclaration
17         / AggregateDeclaration
18         / Declaration
19         / Constructor
20         / Destructor
21         / UnitTest
22         / StaticConstructor
23         / StaticDestructor
24         / SharedStaticConstructor
25         / SharedStaticDestructor
26         / ConditionalDeclaration
27         / DebugSpecification
28         / VersionSpecification
29         / StaticAssert
30         / TemplateDeclaration
31         / TemplateMixinDeclaration
32         / TemplateMixin
33         / MixinDeclaration
34         / MacroDeclaration
35 
36 ### MACROS ADDITION TO THE D GRAMMAR ###
37 
38 MacroDeclaration < "macro" MacroName MacroParameterList
39                    MacroLevel?
40                    MacroBeforeBody "return" MacroAfterBody
41 
42 MacroName < identifier
43 
44 MacroParameterList < :"(" (MacroParameter ("," MacroParameter)*)? :")"
45 
46 MacroParameter < identifier identifier
47 
48 MacroLevel < :":" identifier
49 
50 #Mind the '<-' arrow!
51 MacroBeforeBody <- :"{"
52                    ~(!(endOfLine "}") .)*
53                    :endOfLine :"}"
54 
55 MacroAfterBody < :"{" Statement :"}"
56 
57 
58 ###
59 
60 ModuleDeclaration < "module" qualifiedIdentifier ";"
61 
62 ImportDeclaration < "import" ImportList ";"
63                    / "static" "import"  ImportList ";"
64 
65 ImportList < ImportBindings
66             / Import ("," ImportList)?
67 
68 Import < qualifiedIdentifier "=" qualifiedIdentifier
69         / qualifiedIdentifier
70 
71 ###### Also a space-sep list is needed ##
72 #List(Elem) < Elem (',' Elem)*
73 
74 ImportBindings < Import ":" ImportBind ("," ImportBind)*
75 
76 ImportBind < Identifier ("=" Identifier)?
77 
78 MixinDeclaration < "mixin" "(" AssignExpression ")" ";"
79 
80 # declaration.html
81 Declaration < AliasDeclaration
82              / AliasThisDeclaration
83              / Decl
84 
85 AliasDeclaration < "alias" ( BasicType Declarator
86                            / AliasInitializer ("," AliasInitializer)*)
87 
88 AliasInitializer < Identifier "=" Type
89 
90 AliasThisDeclaration < "alias" ( Identifier "this"
91                                / "this" "=" Identifier)
92 
93 Decl < BasicType Declarators ";"
94       / BasicType Declarator FunctionBody
95       / AutoDeclaration
96       / StorageClasses Decl
97 
98 Declarators < DeclaratorInitializer ("," DeclaratorIdentifier ("," DeclaratorIdentifier)*)?
99 
100 DeclaratorInitializer < Declarator ("=" Initializer)?
101 
102 DeclaratorIdentifier < Identifier ("=" Initializer)?
103 
104 BasicType < BasicTypeX
105            / "." IdentifierList
106            / IdentifierList
107            / Typeof "." IdentifierList
108            / "const(" Type ")"
109            / "immutable(" Type ")"
110            / "shared(" Type ")"
111            / "inout(" Type ")"
112 
113 BasicTypeX < "bool"
114             / "byte" / "ubyte"
115             / "short" / "ushort"
116             / "int" / "uint"
117             / "long" / "ulong"
118             / "char" / "wchar" / "dchar"
119             / "float" / "double" / "real"
120             / "void"
121 
122 BasicType2 < "*"
123             / "[" "]"
124             / "[" AssignExpression "]"
125             / "[" AssignExpression ".." AssignExpression "]"
126             / "[" Type "]"
127             / "delegate" Parameters FunctionAttributes?
128             / "function" Parameters FunctionAttributes?
129 
130 ## Maybe that could factored ##
131 Declarator < BasicType2* "(" Declarator ")" DeclaratorSuffixes?
132             / BasicType2*     Identifier     DeclaratorSuffixes?
133 
134 DeclaratorSuffixes < DeclaratorSuffix+
135 
136 DeclaratorSuffix < "[" "]"
137                   / "[" AssignExpression "]"
138                   / "[" Type "]"
139                   / TemplateParameterList? Parameters MemberFunctionAttributes? Constraint?
140 
141 ## Could be written otherwise? #
142 IdentifierList <  TemplateInstance ("." IdentifierList)?
143                 / Identifier ("." IdentifierList)?
144 
145 StorageClasses < StorageClass+
146 
147 StorageClass < "abstract"
148               / "auto"
149               / "const"
150               / "deprecated"
151               / "enum"
152               / "extern"
153               / "final"
154               / "immutable"
155               / "inout"
156               / "shared"
157               / "nothrow"
158               / "override"
159               / "pure"
160               / "__gshared"
161               / Property
162               / "scope"
163               / "static"
164               / "synchronized"
165 
166 Property < "@" ( "property"
167                / "safe"
168                / "trusted"
169                / "system"
170                / "disable")
171 
172 Type < BasicType Declarator2?
173 
174 Declarator2 < BasicType2* ("(" Declarator2 ")")? DeclaratorSuffixes?
175 
176 Parameters < "(" ParameterList? ")"
177 
178 ParameterList < "..."
179                / Parameter (:',' Parameter)*
180 
181 Parameter < InOut? BasicType Declarator ("..." / "=" DefaultInitializerExpression)?
182           / InOut? Type "..."?
183 
184 InOut < InOutX InOut?
185 
186 InOutX < "auto"
187         / "const"
188         / "final"
189         / "immutable"
190         / "inout"
191         / "in "
192         / "lazy"
193         / "out"
194         / "ref"
195         / "scope"
196         / "shared"
197 
198 FunctionAttributes < FunctionAttribute+
199 
200 FunctionAttribute < "nothrow"
201                    / "pure"
202                    / Property
203 
204 MemberFunctionAttributes < MemberFunctionAttribute+
205 
206 MemberFunctionAttribute < "const"
207                          / "immutable"
208                          / "inout"
209                          / "shared"
210                          / FunctionAttribute
211 
212 DefaultInitializerExpression < AssignExpression
213                               / "__FILE__"
214                               / "__LINE__"
215 
216 Initializer < VoidInitializer / NonVoidInitializer
217 
218 NonVoidInitializer < AssignExpression
219                     / ArrayInitializer
220                     / StructInitializer
221 
222 ArrayInitializer < "[" "]"
223                   / "[" ArrayMemberInitializations "]"
224 
225 ## Crap
226 ArrayMemberInitializations < ArrayMemberInitialization ("," ArrayMemberInitialization?)*
227 
228 ## Verify the order, with PEG
229 ArrayMemberInitialization < NonVoidInitializer
230                            / AssignExpression ":" NonVoidInitializer
231 
232 StructInitializer < "{" "}"
233                    / "{" StructMemberInitializers "}"
234 
235 StructMemberInitializers < StructMemberInitializer ("," StructMemberInitializer?)*
236 
237 StructMemberInitializer < NonVoidInitializer
238                          / Identifier : NonVoidInitializer
239 
240 AutoDeclaration < StorageClasses AutoDeclarationX ";"
241 
242 AutoDeclarationX < Identifier "=" Initializer ("," Identifier "=" Initializer)*
243 
244 Typeof < "typeof" "(" Expression ")"
245         / "typeof" "(" "return" ")"
246 
247 VoidInitializer < "void"
248 
249 ## File statement.html
250 
251 Statement < ";"
252            / NonEmptyStatement
253            / ScopeBlockStatement
254 
255 NoScopeNonEmptyStatement < NonEmptyStatement
256                           / BlockStatement
257 
258 NoScopeStatement < ";"
259                   / NonEmptyStatement
260                   / BlockStatement
261 
262 NonEmptyOrScopeBlockStatement < NonEmptyStatement
263                                / ScopeBlockStatement
264 
265 NonEmptyStatement < NonEmptyStatementNoCaseNoDefault
266                    / CaseStatement
267                    / CaseRangeStatement
268                    / DefaultStatement
269 
270 NonEmptyStatementNoCaseNoDefault <
271     LabeledStatement
272   / ExpressionStatement
273   / DeclarationStatement
274   / IfStatement
275   / WhileStatement
276   / DoStatement
277   / ForStatement
278   / ForeachStatement
279   / SwitchStatement
280   / FinalSwitchStatement
281   / ContinueStatement
282   / BreakStatement
283   / ReturnStatement
284   / GotoStatement
285   / WithStatement
286   / SynchronizedStatement
287   / TryStatement
288   / ScopeGuardStatement
289   / ThrowStatement
290   / AsmStatement
291   / PragmaStatement
292   / MixinStatement
293   / ForeachRangeStatement
294   / ConditionalStatement
295   / StaticAssert
296   / TemplateMixin
297   / ImportDeclaration
298 
299 ScopeStatement < NonEmptyStatement / BlockStatement
300 
301 ScopeBlockStatement < ScopeStatement
302 
303 LabeledStatement < Identifier ":" NoScopeStatement
304 
305 BlockStatement < "{" StatementList? "}"
306 
307 StatementList < Statement+
308 
309 ExpressionStatement < Expression ";"
310 
311 DeclarationStatement < Declaration
312 
313 IfStatement < "if" "(" IfCondition ")" ThenStatement ("else" ElseStatement)?
314 
315 IfCondition < Expression
316              / "auto" Identifier "=" Expression
317              / BasicType Declarator "=" Expression
318 
319 ThenStatement < ScopeStatement
320 
321 ElseStatement < ScopeStatement
322 
323 WhileStatement < "while" "(" Expression ")" ScopeStatement
324 
325 DoStatement < "do" ScopeStatement "while" "(" Expression ")" ";"
326 
327 ForStatement < "for" "(" Initialize Test? ";" Increment? ")" ScopeStatement
328 
329 Initialize < ";" / NoScopeNonEmptyStatement
330 
331 Test < Expression
332 
333 Increment < Expression
334 
335 ForeachStatement < ("foreach" / "foreach_reverse")
336                     "(" ForeachType ("," ForeachType)* ";" Aggregate ")"
337                      NoScopeNonEmptyStatement
338 
339 ForeachType < "ref"? BasicType Declarator
340              / "ref"? Identifier
341 
342 Aggregate < Expression
343 
344 ForeachRangeStatement < "(" ForeachType ";" Expression ".." Expression ")"
345 
346 SwitchStatement < "switch" "(" Expression ")" ScopeStatement
347 
348 CaseStatement < "case" ArgumentList ":" ScopeStatementList
349 
350 CaseRangeStatement < "case" AssignExpression ":"
351                       ".."
352                       "case" AssignExpression ":"
353                       ScopeStatementList
354 
355 DefaultStatement < "default" ":" ScopeStatementList
356 
357 ScopeStatementList < StatementListNoCaseNoDefault
358 
359 StatementListNoCaseNoDefault < StatementNoCaseNoDefault+
360 
361 StatementNoCaseNoDefault < ";"
362                           / NonEmptyStatementNoCaseNoDefault
363                           / ScopeBlockStatement
364 
365 FinalSwitchStatement < "final" "switch" "(" Expression ")"
366                         ScopeStatement
367 
368 ContinueStatement < "continue" Identifier? ";"
369 
370 BreakStatement < "break" Identifier? ";"
371 
372 ReturnStatement < "return" Expression? ";"
373 
374 GotoStatement < "goto" ( "default" ";"
375                         / "case" ";"
376                         / "case" Expression ";"
377                         / Identifier ";")
378 
379 WithStatement < "with"
380                  "(" ( Expression / Symbol / TemplateInstance) ")"
381                  ScopeStatement
382 
383 SynchronizedStatement < "synchronized"
384                         ( "(" Expression ")" )?
385                         ScopeStatement
386 
387 TryStatement < "try" ScopeStatement Catches? FinallyStatement?
388 
389 Catches < LastCatch / Catch Catches?
390 
391 LastCatch < "catch" NoScopeNonEmptyStatement
392 
393 Catch < "catch" "(" CatchParameter ")" NoScopeNonEmptyStatement
394 
395 CatchParameter < BasicType Identifier
396 
397 FinallyStatement < "finally" NoScopeNonEmptyStatement
398 
399 ThrowStatement < "throw" Expression ";"
400 
401 ScopeGuardStatement < ( "scope(exit)"
402                        / "scope(success)"
403                        / "scope(failure)")
404                        NonEmptyOrScopeBlockStatement
405 
406 AsmStatement < "asm" "{" AsmInstructionList? "}"
407 
408 AsmInstructionList < AsmInstruction ";" AsmInstructionList?
409 
410 PragmaStatement < Pragma NoScopeStatement
411 
412 MixinStatement < "mixin" "(" AssignExpression ")" ";"
413 
414 ### File expression.html ###
415 
416 Expression < AssignExpression
417 
418 AssignExpression < ConditionalExpression (Op AssignExpression)?
419 
420 Op < ">>>="
421     / "^^=" / ">>=" / "<<="
422     / "~=" / "+=" / "-=" / "*=" / "^=" / "|=" / "&=" / "/="
423     / "="
424 
425 ConditionalExpression < OrOrExpression
426                         ("?" Expression ":" ConditionalExpression)?
427 
428 OrOrExpression < AndAndExpression ("||" OrOrExpression)?
429 
430 AndAndExpression < (CmpExpression / OrExpression) ("&&" AndAndExpression)?
431 
432 OrExpression < XorExpression ("|" OrExpression)?
433 
434 XorExpression < AndExpression ("^" XorExpression)?
435 
436 AndExpression < ShiftExpression ("&" AndExpression)?
437 
438 CmpExpression <  EqualExpression
439                / IdentityExpression
440                / RelExpression
441                / InExpression
442                / ShiftExpression
443 
444 EqualExpression < ShiftExpression ("==" / "!=") ShiftExpression
445 
446 IdentityExpression < ShiftExpression ("!is" / "is") ShiftExpression
447 
448 RelExpression < ShiftExpression RelOp ShiftExpression
449 
450 RelOp < "!<>="
451        / "!<>" / "!<=" / "!>=" / "<>="
452        / "<=" / ">=" / "<>" / "!>" / "!<"
453        / "<" / ">"
454 
455 InExpression < ShiftExpression (("!in" / "in") ShiftExpression)?
456 
457 ShiftExpression < AddExpression ((">>>" / ">>" / "<<") AddExpression)?
458 
459 AddExpression < (MulExpression / CatExpression)
460                  (("+" / "-") MulExpression)?
461 
462 CatExpression < MulExpression ("~" AddExpression)?
463 
464 MulExpression < UnaryExpression
465                  (("*" / "/" / "%") UnaryExpression)?
466 
467 UnaryExpression < UnaryOp UnaryExpression
468                  / ComplementExpression
469                  / "(" Type ")" "." Identifier
470                  / NewExpression
471                  / DeleteExpression
472                  / CastExpression
473                  / PowExpression
474 
475 UnaryOp < "++" / "--"
476          / "+" / "-" / "&" / "*" / "/" / "!"
477 
478 ComplementExpression < "~" UnaryExpression
479 
480 NewExpression < ("new" AllocatorArguments? Type
481                   ("[" AssignExpression "]" / "(" ArgumentList ")" )?)
482                / NewAnonClassExpression
483 
484 AllocatorArguments < "(" ArgumentList ")"
485 
486 ArgumentList < AssignExpression ("," AssignExpression)*
487 
488 DeleteExpression < "delete" UnaryExpression
489 
490 CastExpression < "cast" "(" (Type / CastEqual)? ")" UnaryExpression
491 
492 CastEqual < "const" "shared"
493            / "shared" "const"
494            / "inout" "shared"
495            / "shared" "inout"
496            / "const"
497            / "inout"
498            / "immutable"
499            / "shared"
500 
501 PowExpression < PostfixExpression ("^^" UnaryExpression)?
502 
503 # Changed
504 PostfixExpression < PrimaryExpression (IndexExpression / SliceExpression)*
505                     ( "." NewExpression
506                     / "." TemplateIdentifier
507                     / "." Identifier
508                     / "++"
509                     / "--"
510                     / "(" ArgumentList? ")"
511                     )?
512 
513 # Changed
514 IndexExpression < "[" ArgumentList "]"
515 
516 # Changed
517 SliceExpression < "[" "]"
518                   "[" AssignExpression ".." AssignExpression "]"
519 
520 PrimaryExpression < "this"
521                    / "super"
522                    / "null"
523                    / "true"
524                    / "false"
525                    / "$"
526                    / "__FILE__"
527                    / "__LINE__"
528                    / TemplateInstance
529                    / "." TemplateInstance
530                    / Identifier
531                    / "." Identifier
532                    / FloatLiteral
533                    / IntegerLiteral
534                    / CharacterLiteral
535                    / StringLiterals
536                    / ArrayLiteral
537                    / AssocArrayLiteral
538                    / Lambda
539                    / FunctionLiteral
540                    / AssertExpression
541                    / MixinExpression
542                    / ImportExpression
543                    / BasicType "." Identifier
544                    / Typeof
545                    / TypeidExpression
546                    / IsExpression
547                    / "(" Expression ")"
548                    / TraitsExpression
549 
550 StringLiterals < StringLiteral+
551 
552 ArrayLiteral < "[" ArgumentList? "]"
553 
554 AssocArrayLiteral < "[" KeyValuePair ("," KeyValuePair)* "]"
555 
556 KeyValuePair < AssignExpression ":" AssignExpression
557 
558 Lambda < Identifier "=>" AssignExpression
559         / ParameterAttributes "=>" AssignExpression
560 
561 FunctionLiteral < (("function" / "delegate") Type?)? ParameterAttributes? FunctionBody
562 
563 ParameterAttributes < Parameters FunctionAttributes?
564 
565 AssertExpression < "assert" "(" AssignExpression ("," AssignExpression)? ")"
566 
567 MixinExpression < "mixin" "(" AssignExpression ")"
568 
569 ImportExpression < "import" "(" AssignExpression ")"
570 
571 TypeidExpression < "typeid" "(" ( Type / Expression ) ")"
572 
573 IsExpression < "is" "(" Type
574                   ( ":" TypeSpecialization
575                   / "==" TypeSpecialization
576                   / Identifier ( ":" TypeSpecialization ("," TemplateParameterList)?
577                                / "==" TypeSpecialization ("," TemplateParameterList)?
578                                )?
579 
580                   )?
581                 ")"
582 
583 TypeSpecialization < Type
584                     / "struct"
585                     / "union"
586                     / "class"
587                     / "interface"
588                     / "enum"
589                     / "function"
590                     / "delegate"
591                     / "super"
592                     / "const"
593                     / "immutable"
594                     / "inout"
595                     / "shared"
596                     / "return"
597 ### file attribute.html
598 
599 AttributeSpecifier < Attribute DeclarationBlock
600                     / Attribute ":"
601 
602 Attribute < LinkageAttribute
603            / AlignAttribute
604            / Pragma
605            / "deprecated"
606            / ProtectionAttribute
607            / "static"
608            / "extern"
609            / "final"
610            / "synchronized"
611            / "override"
612            / "abstract"
613            / "const"
614            / "auto"
615            / "scope"
616            / "__gshared"
617            / "shared"
618            / "immutable"
619            / "inout"
620            / "@disable"
621 
622 DeclarationBlock < DeclDef
623                   / "{" DeclDefs "}"
624 
625 LinkageAttribute < "extern" "(" LinkageType ")"
626 
627 LinkageType < "C++" / "C" / "D" / "Windows" / "Pascal" / "System"
628 
629 AlignAttribute < "align" ("(" IntegerLiteral ")")?
630 
631 ProtectionAttribute < "private"
632                      / "package"
633                      / "protected"
634                      / "public"
635                      / "export"
636 
637 ### class.html
638 
639 ClassDeclaration < "class" Identifier BaseClassList? ClassBody
640                  / ClassTemplateDeclaration
641 
642 ### I don't why the grammar distinguish SuperClass and Interface
643 ### They cannot be differentiated at this step
644 BaseClassList < ":" Identifier ("," Identifier)*
645 
646 ClassBody < "{" ClassBodyDeclarations? "}"
647 
648 ClassBodyDeclarations < ClassBodyDeclaration ClassBodyDeclarations?
649 
650 ClassBodyDeclaration < DeclDef
651                       / Invariant
652                       / ClassAllocator
653                       / ClassDeallocator
654 
655 Constructor < "this" Parameters FunctionBody
656              / TemplatedConstructor
657 
658 Destructor < "~" "this" "(" ")" FunctionBody
659 
660 StaticConstructor < "static" "this" "(" ")" FunctionBody
661 
662 StaticDestructor < "static" "~" "this" "(" ")" FunctionBody
663 
664 SharedStaticConstructor < "shared" "static" "this" "(" ")" FunctionBody
665 
666 SharedStaticDestructor < "shared" "static" "~" "this" "(" ")" FunctionBody
667 
668 Invariant < "invariant" "(" ")" BlockStatement
669 
670 ClassAllocator < "new" Parameters FunctionBody
671 
672 ClassDeallocator < "delete" Parameters FunctionBody
673 
674 AliasThis < "alias" Identifier "this" ";"
675 
676 NewAnonClassExpression < "new" AllocatorArguments? "class" ClassArguments? Identifier ("," Identifier)* ClassBody
677 
678 ClassArguments < "(" ArgumentList? ")"
679 
680 ### enum.html
681 
682 EnumDeclaration < "enum" EnumTag? (":" EnumBaseType)? EnumBody
683 
684 EnumTag < Identifier
685 
686 EnumBaseType < Type
687 
688 EnumBody < ";" / "{" EnumMember ("," EnumMember)* "}"
689 
690 EnumMember < Type "=" AssignExpression
691             / Identifier ("=" AssignExpression)?
692 
693 ### function.html
694 
695 FunctionBody < BlockStatement
696               / BodyStatement
697               / InStatement BodyStatement
698               / OutStatement BodyStatement
699               / InStatement OutStatement BodyStatement
700               / OutStatement InStatement BodyStatement
701 
702 InStatement < "in" BlockStatement
703 
704 OutStatement < "out" ("(" Identifier ")" )? BlockStatement
705 
706 BodyStatement < "body" BlockStatement
707 
708 ### iasm.html
709 
710 AsmInstruction < "align" IntegerExpression
711                 / "even"
712                 / "naked"
713                 / ("db" / "ds" / "di" / "dl" / "df" / "dd" / "de") Operand ("," Operand)*
714                 / Identifier ":" AsmInstruction
715                 / OpCode
716                 / OpCode Operand ("," Operand)*
717 
718 IntegerExpression < IntegerLiteral / Identifier
719 
720 Operand < AsmExp
721 
722 AsmExp < AsmLogOrExp ("?" AsmExp ":" AsmExp)?
723 
724 AsmLogOrExp < AsmLogAndExp ("||" AsmLogAndExp)?
725 
726 AsmLogAndExp < AsmOrExp ("&&" AsmOrExp)?
727 
728 AsmOrExp < AsmXorExp ("|" AsmXorExp)?
729 
730 AsmXorExp < AsmAndExp ("^" AsmAndExp)?
731 
732 AsmAndExp < AsmEqualExp ("&" AsmEqualExp)?
733 
734 AsmEqualExp < AsmRelExp (("=="/"!=") AsmRelExp)?
735 
736 AsmRelExp < AsmShiftExp (("<="/">="/"<"/">") AsmShiftExp)?
737 
738 AsmShiftExp < AsmAddExp ((">>>"/"<<"/">>") AsmAddExp)?
739 
740 AsmAddExp < AsmMulExp (("+"/"-") AsmMulExp)?
741 
742 AsmMulExp < AsmBrExp (("*"/"/"/"%") AsmBrExp)?
743 
744 AsmBrExp < AsmUnaExp ("[" AsmExp "]")?
745 
746 AsmUnaExp < AsmTypePrefix AsmExp
747            / ("offsetof" / "seg") AsmExp
748            / ("+" / "-" / "!" / "~") AsmUnaExp
749            / AsmPrimaryExp
750 
751 AsmPrimaryExp < FloatLiteral
752               / IntegerLiteral
753               / "__LOCAL_SIZE"
754               / "$"
755               / Register
756               / DotIdentifier
757 
758 DotIdentifier < Identifier ("." DotIdentifier)?
759 
760 AsmTypePrefix < ( "near"
761                  / "far"
762                  / "byte"
763                  / "short"
764                  / "int"
765                  / "word"
766                  / "dword"
767                  / "qword"
768                  / "float"
769                  / "double"
770                  / "real") "ptr"
771 
772 ### Argh. I cheat. Not complete. ST(0) not there
773 Register < Identifier
774 OpCode < Identifier
775 
776 ### interface.html
777 
778 InterfaceDeclaration < "interface" Identifier BaseInterfaceList? InterfaceBody
779                       / InterfaceTemplateDeclaration
780 
781 BaseInterfaceList < ":" Identifier ("," Identifier)*
782 
783 InterfaceBody < "{" DeclDefs? "}"
784 
785 ### pragma.html
786 
787 Pragma < "pragma" "(" Identifier ("," ArgumentList)? ")"
788 
789 ### struct.html
790 
791 AggregateDeclaration < ("struct" / "union") Identifier (StructBody / ";")
792                       / StructTemplateDeclaration
793                       / UnionTemplateDeclaration
794 
795 StructBody < "{" StructBodyDeclarations? "}"
796 
797 StructBodyDeclarations < StructBodyDeclaration StructBodyDeclarations?
798 
799 StructBodyDeclaration < DeclDef
800                        / StructAllocator
801                        / StructDeallocator
802                        / StructPostblit
803                        / AliasThis
804 
805 StructAllocator < ClassAllocator
806 
807 StructDeallocator < ClassDeallocator
808 
809 StructPostblit < "this(this)" FunctionBody
810 
811 ### template.html
812 
813 TemplateDeclaration < "template" TemplateIdentifier "(" TemplateParameterList ")" Constraint?
814 
815 TemplateIdentifier < Identifier
816 
817 TemplateParameterList < TemplateParameter ("," TemplateParameter)*
818 
819 TemplateParameter < TemplateTypeParameter
820                    / TemplateValueParameter
821                    / TemplateAliasParameter
822                    / TemplateTupleParameter
823                    / TemplateThisParameter
824 
825 TemplateInstance < TemplateIdentifier ( "!(" TemplateArgument ("," TemplateArgument)* ")"
826                                        / "!" TemplateSingleArgument)
827 
828 TemplateArgument < Type
829                   / AssignExpression
830                   / Symbol
831 
832 Symbol < "."? SymbolTail
833 
834 SymbolTail < TemplateInstance ("." SymbolTail)?
835             / Identifier ("." SymbolTail)?
836 
837 TemplateSingleArgument < BasicTypeX
838                         / CharacterLiteral
839                         / StringLiteral
840                         / FloatLiteral
841                         / IntegerLiteral
842                         / "true"
843                         / "false"
844                         / "null"
845                         / "__LINE__"
846                         / "__FILE__"
847                         / Identifier
848 
849 TemplateTypeParameter < Identifier TTPSpecialization? TTPDefault?
850 
851 TTPSpecialization < ":" Type
852 
853 TTPDefault < "=" Type
854 
855 TemplateThisParameter < "this" TemplateTypeParameter
856 
857 TemplateValueParameter < BasicType Declarator TVPSpecialization? TVPDefault?
858 
859 TVPSpecialization < ":" ConditionalExpression
860 
861 TVPDefault < "=" ("__FILE__" / "__LINE__" / AssignExpression)
862 
863 TemplateAliasParameter < "alias" (BasicType Declarator / Identifier) TAPSpecialization? TAPDefault?
864 
865 TAPSpecialization < ":" (Type / ConditionalExpression)
866 
867 TAPDefault < "=" (Type / ConditionalExpression)
868 
869 TemplateTupleParameter < Identifier "..."
870 
871 TemplatedConstructor < "this" "(" TemplateParameterList ")" Parameters Constraint? FunctionBody
872 
873 ClassTemplateDeclaration < "class" Identifier "(" TemplateParameterList ")" Constraint? BaseClassList? ClassBody
874 
875 StructTemplateDeclaration < "struct" Identifier "(" TemplateParameterList ")" Constraint? StructBody
876 
877 UnionTemplateDeclaration < "union" Identifier "(" TemplateParameterList ")" Constraint? StructBody
878 
879 InterfaceTemplateDeclaration < "interface" Identifier "(" TemplateParameterList ")" Constraint? BaseInterfaceList? InterfaceBody
880 
881 Constraint < "if" "(" Expression ")"
882 
883 ### template-mixin.html
884 
885 TemplateMixinDeclaration < "mixin" "template" TemplateIdentifier "(" TemplateParameterList ")" Constraint? "{" DeclDefs "}"
886 
887 TemplateMixin < "mixin" TemplateIdentifier (("!(" TemplateArgument ("," TemplateArgument)* ")")? MixinIdentifier?) ";"
888 
889 MixinIdentifier < Identifier
890 
891 ### traits.html
892 
893 TraitsExpression < "__traits" "(" TraitsKeyword "," TraitsArgument ("," TraitsArgument)* ")"
894 
895 TraitsKeyword < "isAbstractClass"
896                / "isArithmetic"
897                / "isAssociativeArray"
898                / "isFinalClass"
899                / "isFloating"
900                / "isIntegral"
901                / "isScalar"
902                / "isStaticArray"
903                / "isUnsigned"
904                / "isVitualFunction"
905                / "isVirtualMethod"
906                / "isAbstractFunction"
907                / "isFinalFunction"
908                / "isStaticFunction"
909                / "isRef"
910                / "isOut"
911                / "isLazy"
912                / "hasMember"
913                / "identifier"
914                / "getMember"
915                / "getOverloads"
916                / "getVirtualFunctions"
917                / "getVirtualMethods"
918                / "parent"
919                / "classInstanceSize"
920                / "allMembers"
921                / "derivedMembers"
922                / "isSame"
923                / "compiles"
924 
925 TraitsArgument < AssignExpression
926                 / Type
927 
928 ### unittest.html
929 
930 UnitTest < "unittest" FunctionBody
931 
932 ### version.html
933 
934 ConditionalDeclaration < Condition ":" Declarations
935                         / Condition CCDeclarationBlock ("else" CCDeclarationBlock)?
936 
937 CCDeclarationBlock < Declaration
938                     / "{" Declaration? "}"
939 
940 Declarations < Declaration+
941 
942 ConditionalStatement < Condition NoScopeNonEmptyStatement ("else" NoScopeNonEmptyStatement)?
943 
944 Condition < VersionCondition
945            / DebugCondition
946            / StaticIfCondition
947 
948 VersionCondition < "version" "(" (IntegerLiteral / "unittest" / Identifier) ")"
949 
950 VersionSpecification < "version" "=" (Identifier/IntegerLiteral) ";"
951 
952 DebugCondition < "debug" ("(" (IntegerLiteral / Identifier) ")" )?
953 
954 DebugSpecification < "debug" "=" (Identifier / IntegerLiteral) ";"
955 
956 StaticIfCondition < "static" "if" "(" AssignExpression ")"
957 
958 StaticAssert < "static" "assert" "(" AssignExpression
959                                      ("," AssignExpression)?
960                                    ")" ";"
961 
962 # I had to add it. Otherwise, keywords are recognized as identifiers
963 
964 Identifier <~ !Keyword [a-zA-Z_] [a-zA-Z0-9_]*
965 
966 Keyword < "abstract" / "alias" / "align" / "asm" / "assert" / "auto" / "body" / "bool" / "break" / "byte"
967          / "case" / "cast" / "catch" / "cdouble" / "cent" / "cfloat" / "char" / "class" / "const" / "continue" / "creal" / "dchar"
968          / "debug" / "default" / "delegate" / "delete" / "deprecated" / "double" / "do" / "else" / "enum" / "export" / "extern"
969          / "false" / "finally" / "final" / "float" / "foreach_reverse" / "foreach" / "for" / "function" / "goto" / "idouble" / "if"
970          / "ifloat" / "immutable" / "import" / "inout" / "interface" / "invariant" / "int" / "in" / "ireal" / "is" / "lazy"
971          / "long" / "macro" / "mixin" / "module" / "new" / "nothrow" / "null" / "out" / "override" / "package" / "pragma"
972          / "private" / "protected" / "public" / "pure" / "real" / "ref" / "return" / "scope" / "shared" / "short" / "static"
973          / "struct" / "super" / "switch" / "synchronized" / "template" / "this" / "throw" / "true" / "try" / "typedef" / "typeid"
974          / "typeof" / "ubyte" / "ucent" / "uint" / "ulong" / "union" / "unittest" / "ushort" / "version" / "void" / "volatile"
975          / "wchar" / "while" / "with" / "__FILE__" / "__LINE__" / "__gshared" / "__thread" / "__traits"
976 
977 
978 ## file lex.html
979 
980 Spacing <- (space / Comment)*
981 
982 Comment <- BlockComment
983          / LineComment
984          / NestingBlockComment
985 
986 BlockComment <~ :'/ *' (!'* /' .)* :'* /'
987 
988 LineComment <~ :'//' (!endOfLine .)* :endOfLine
989 
990 #NestingBlockComment < :'/ +' (NestingBlockComment / Text) :'+ /'
991 # / + (please, don't delete this line, it opens a nested block comment in generated module which is closed on the next line
992 #Text < (!'+ /' .)*
993 NestingBlockComment <~ :"/+" (!("/+"/"+/") .)* NestingBlockComment? (!("/+"/"+/") .)* :"+/"
994 
995 StringLiteral < WysiwygString
996                / AlternateWysiwygString
997                / DoublequotedString
998                # No HexString
999                # No DelimitedString
1000                / TokenString
1001 
1002 WysiwygString <- 'r' doublequote (!doublequote .)* doublequote StringPostfix?
1003 
1004 AlternateWysiwygString <- backquote (!backquote .)* backquote StringPostfix?
1005 
1006 DoublequotedString <- doublequote (DQChar)* doublequote StringPostfix?
1007 
1008 DQChar <- EscapeSequence
1009         / !doublequote .
1010 
1011 EscapeSequence <- backslash ( quote
1012                             / doublequote
1013                             / backslash
1014                             / [abfnrtv]
1015                             / 'x' HexDigit HexDigit
1016                             / 'u' HexDigit HexDigit HexDigit HexDigit
1017                             / 'U' HexDigit HexDigit HexDigit HexDigit HexDigit HexDigit HexDigit HexDigit
1018                             )
1019 
1020 StringPostfix < "c" / "w" / "d"
1021 
1022 TokenString <- "q{" (!"}" .)* "}"
1023 
1024 CharacterLiteral <- quote (!quote (EscapeSequence / .)) quote
1025 
1026 ### I'm fed up, I simplify
1027 
1028 IntegerLiteral <- DecimalInteger
1029                 / BinaryInteger
1030                 / HexadecimalInteger
1031 
1032 DecimalInteger <- Integer IntegerSuffix?
1033 
1034 Integer <- digit (digit/"_")*
1035 
1036 IntegerSuffix <- "Lu" / "LU" / "uL" / "UL"
1037                / "L" / "u" / "U"
1038 
1039 BinaryInteger <- ("0b" / "0B") [01] ([01] / "_")*
1040 
1041 HexadecimalInteger <- ("0x"/"0X") HexDigit (HexDigit / "_")*
1042 
1043 HexDigit < [0-9a-fA-F]
1044 
1045 FloatLiteral <- Sign? Integer "." Integer? (("e" / "E") Sign? Integer)?
1046 
1047 Sign <- ("-" / "+")?
1048 `;