xref: /aosp_15_r20/external/antlr/tool/src/main/antlr3/org/antlr/grammar/v3/TreeToNFAConverter.g (revision 16467b971bd3e2009fad32dd79016f2c7e421deb)
1/*
2 [The "BSD license"]
3 Copyright (c) 2005-2011 Terence Parr
4 All rights reserved.
5
6 Grammar conversion to ANTLR v3:
7 Copyright (c) 2011 Sam Harwell
8 All rights reserved.
9
10 Redistribution and use in source and binary forms, with or without
11 modification, are permitted provided that the following conditions
12 are met:
13 1. Redistributions of source code must retain the above copyright
14	notice, this list of conditions and the following disclaimer.
15 2. Redistributions in binary form must reproduce the above copyright
16	notice, this list of conditions and the following disclaimer in the
17	documentation and/or other materials provided with the distribution.
18 3. The name of the author may not be used to endorse or promote products
19	derived from this software without specific prior written permission.
20
21 THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
22 IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
23 OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
24 IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
25 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
26 NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
27 DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
28 THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
29 (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
30 THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
31*/
32
33/** Build an NFA from a tree representing an ANTLR grammar. */
34tree grammar TreeToNFAConverter;
35
36options {
37	language=Java;
38	tokenVocab = ANTLR;
39	ASTLabelType = GrammarAST;
40}
41
42@header {
43package org.antlr.grammar.v3;
44
45import org.antlr.analysis.*;
46import org.antlr.misc.*;
47import org.antlr.tool.*;
48
49import org.antlr.runtime.BitSet;
50import org.antlr.runtime.DFA;
51}
52
53@members {
54/** Factory used to create nodes and submachines */
55protected NFAFactory factory = null;
56
57/** Which NFA object are we filling in? */
58protected NFA nfa = null;
59
60/** Which grammar are we converting an NFA for? */
61protected Grammar grammar = null;
62
63protected String currentRuleName = null;
64
65protected int outerAltNum = 0;
66protected int blockLevel = 0;
67
68protected int inTest = 0;
69
70public TreeToNFAConverter(TreeNodeStream input, Grammar g, NFA nfa, NFAFactory factory) {
71    this(input);
72    this.grammar = g;
73    this.nfa = nfa;
74    this.factory = factory;
75}
76
77public final IntSet setRule(GrammarAST t) throws RecognitionException {
78    TreeToNFAConverter other = new TreeToNFAConverter( new CommonTreeNodeStream( t ), grammar, nfa, factory );
79
80    other.currentRuleName = currentRuleName;
81    other.outerAltNum = outerAltNum;
82    other.blockLevel = blockLevel;
83
84    return other.setRule();
85}
86
87public final int testBlockAsSet( GrammarAST t ) throws RecognitionException {
88    Rule r = grammar.getLocallyDefinedRule( currentRuleName );
89    if ( r.hasRewrite( outerAltNum ) )
90        return -1;
91
92    TreeToNFAConverter other = new TreeToNFAConverter( new CommonTreeNodeStream( t ), grammar, nfa, factory );
93
94    other.state.backtracking++;
95    other.currentRuleName = currentRuleName;
96    other.outerAltNum = outerAltNum;
97    other.blockLevel = blockLevel;
98
99    int result = other.testBlockAsSet();
100    if ( other.state.failed )
101        return -1;
102
103    return result;
104}
105
106public final int testSetRule( GrammarAST t ) throws RecognitionException {
107    TreeToNFAConverter other = new TreeToNFAConverter( new CommonTreeNodeStream( t ), grammar, nfa, factory );
108
109    other.state.backtracking++;
110    other.currentRuleName = currentRuleName;
111    other.outerAltNum = outerAltNum;
112    other.blockLevel = blockLevel;
113
114    int result = other.testSetRule();
115    if ( other.state.failed )
116        state.failed = true;
117
118    return result;
119}
120
121protected void addFollowTransition( String ruleName, NFAState following ) {
122    //System.Console.Out.WriteLine( "adding follow link to rule " + ruleName );
123    // find last link in FOLLOW chain emanating from rule
124    Rule r = grammar.getRule( ruleName );
125    NFAState end = r.stopState;
126    while ( end.transition( 1 ) != null )
127    {
128        end = (NFAState)end.transition( 1 ).target;
129    }
130    if ( end.transition( 0 ) != null )
131    {
132        // already points to a following node
133        // gotta add another node to keep edges to a max of 2
134        NFAState n = factory.newState();
135        Transition e = new Transition( Label.EPSILON, n );
136        end.addTransition( e );
137        end = n;
138    }
139    Transition followEdge = new Transition( Label.EPSILON, following );
140    end.addTransition( followEdge );
141}
142
143protected void finish() {
144    int numEntryPoints = factory.build_EOFStates( grammar.getRules() );
145    if ( numEntryPoints == 0 )
146    {
147        ErrorManager.grammarWarning( ErrorManager.MSG_NO_GRAMMAR_START_RULE,
148                                   grammar,
149                                   null,
150                                   grammar.name );
151    }
152}
153
154@Override
155public void reportError(RecognitionException ex) {
156    if ( inTest > 0 )
157        throw new IllegalStateException(ex);
158
159    Token token = null;
160    if ( ex instanceof MismatchedTokenException )
161    {
162        token = ( (MismatchedTokenException)ex ).token;
163    }
164    else if ( ex instanceof NoViableAltException )
165    {
166        token = ( (NoViableAltException)ex ).token;
167    }
168
169    ErrorManager.syntaxError(
170        ErrorManager.MSG_SYNTAX_ERROR,
171        grammar,
172        token,
173        "buildnfa: " + ex.toString(),
174        ex );
175}
176
177private boolean hasElementOptions(GrammarAST node) {
178    if (node == null)
179        throw new NullPointerException("node");
180    return node.terminalOptions != null && node.terminalOptions.size() > 0;
181}
182}
183
184public
185grammar_
186@after
187{
188	finish();
189}
190	:	(	^( LEXER_GRAMMAR grammarSpec )
191		|	^( PARSER_GRAMMAR grammarSpec )
192		|	^( TREE_GRAMMAR grammarSpec )
193		|	^( COMBINED_GRAMMAR grammarSpec )
194		)
195	;
196
197attrScope
198	:	^( 'scope' ID ( ^(AMPERSAND .*) )* ACTION )
199	;
200
201grammarSpec
202	:	ID
203		(cmt=DOC_COMMENT)?
204		( ^(OPTIONS .*) )?
205		( ^(IMPORT .*) )?
206		( ^(TOKENS .*) )?
207		(attrScope)*
208		( ^(AMPERSAND .*) )* // skip actions
209		rules
210	;
211
212rules
213	:	(rule | ^(PREC_RULE .*))+
214	;
215
216rule
217	:	^(	RULE id=ID
218			{
219				currentRuleName = $id.text;
220				factory.setCurrentRule(grammar.getLocallyDefinedRule(currentRuleName));
221			}
222			(modifier)?
223			^(ARG (ARG_ACTION)?)
224			^(RET (ARG_ACTION)?)
225			(throwsSpec)?
226			( ^(OPTIONS .*) )?
227			( ruleScopeSpec )?
228			( ^(AMPERSAND .*) )*
229			b=block
230			(exceptionGroup)?
231			EOR
232			{
233				StateCluster g = $b.g;
234				if ($b.start.getSetValue() != null)
235				{
236					// if block comes back as a set not BLOCK, make it
237					// a single ALT block
238					g = factory.build_AlternativeBlockFromSet(g);
239				}
240				if (Rule.getRuleType(currentRuleName) == Grammar.PARSER || grammar.type==Grammar.LEXER)
241				{
242					// attach start node to block for this rule
243					Rule thisR = grammar.getLocallyDefinedRule(currentRuleName);
244					NFAState start = thisR.startState;
245					start.associatedASTNode = $id;
246					start.addTransition(new Transition(Label.EPSILON, g.left));
247
248					// track decision if > 1 alts
249					if ( grammar.getNumberOfAltsForDecisionNFA(g.left)>1 )
250					{
251						g.left.setDescription(grammar.grammarTreeToString($start, false));
252						g.left.setDecisionASTNode($b.start);
253						int d = grammar.assignDecisionNumber( g.left );
254						grammar.setDecisionNFA( d, g.left );
255						grammar.setDecisionBlockAST(d, $b.start);
256					}
257
258					// hook to end of rule node
259					NFAState end = thisR.stopState;
260					g.right.addTransition(new Transition(Label.EPSILON,end));
261				}
262			}
263		)
264	;
265
266modifier
267	:	'protected'
268	|	'public'
269	|	'private'
270	|	'fragment'
271	;
272
273throwsSpec
274	:	^('throws' ID+)
275	;
276
277ruleScopeSpec
278	:	^( 'scope' ( ^(AMPERSAND .*) )* (ACTION)? ( ID )* )
279	;
280
281block returns [StateCluster g = null]
282@init
283{
284	List<StateCluster> alts = new ArrayList<StateCluster>();
285	this.blockLevel++;
286	if ( this.blockLevel==1 )
287		this.outerAltNum=1;
288}
289	:	{grammar.isValidSet(this,$start) &&
290		 !currentRuleName.equals(Grammar.ARTIFICIAL_TOKENS_RULENAME)}? =>
291		set {$g = $set.g;}
292
293	|	^(	BLOCK ( ^(OPTIONS .*) )?
294			(	a=alternative rewrite
295				{
296					alts.add($a.g);
297				}
298				{{
299					if ( blockLevel == 1 )
300						outerAltNum++;
301				}}
302			)+
303			EOB
304		)
305		{$g = factory.build_AlternativeBlock(alts);}
306	;
307finally { blockLevel--; }
308
309alternative returns [StateCluster g=null]
310	:	^( ALT (e=element {$g = factory.build_AB($g,$e.g);} )+ EOA )
311		{
312			if ($g==null) { // if alt was a list of actions or whatever
313				$g = factory.build_Epsilon();
314			}
315			else {
316				factory.optimizeAlternative($g);
317			}
318		}
319	;
320
321exceptionGroup
322	:	( exceptionHandler )+ (finallyClause)?
323	|	finallyClause
324	;
325
326exceptionHandler
327	:    ^('catch' ARG_ACTION ACTION)
328	;
329
330finallyClause
331	:    ^('finally' ACTION)
332	;
333
334rewrite
335	:	^(	REWRITES
336			(
337				{
338					if ( grammar.getOption("output")==null )
339					{
340						ErrorManager.grammarError(ErrorManager.MSG_REWRITE_OR_OP_WITH_NO_OUTPUT_OPTION,
341												  grammar, $start.getToken(), currentRuleName);
342					}
343				}
344				^(REWRITE .*)
345			)*
346		)
347	|
348	;
349
350element returns [StateCluster g=null]
351	:   ^(ROOT e=element {$g = $e.g;})
352	|   ^(BANG e=element {$g = $e.g;})
353	|	^(ASSIGN ID e=element {$g = $e.g;})
354	|	^(PLUS_ASSIGN ID e=element {$g = $e.g;})
355	|   ^(RANGE a=atom[null] b=atom[null])
356		{$g = factory.build_Range(grammar.getTokenType($a.text),
357								 grammar.getTokenType($b.text));}
358	|   ^(CHAR_RANGE c1=CHAR_LITERAL c2=CHAR_LITERAL)
359		{
360		if ( grammar.type==Grammar.LEXER ) {
361			$g = factory.build_CharRange($c1.text, $c2.text);
362		}
363		}
364	|   atom_or_notatom {$g = $atom_or_notatom.g;}
365	|   ebnf {$g = $ebnf.g;}
366	|   tree_ {$g = $tree_.g;}
367	|   ^( SYNPRED block )
368	|   ACTION {$g = factory.build_Action($ACTION);}
369	|   FORCED_ACTION {$g = factory.build_Action($FORCED_ACTION);}
370	|   pred=SEMPRED {$g = factory.build_SemanticPredicate($pred);}
371	|   spred=SYN_SEMPRED {$g = factory.build_SemanticPredicate($spred);}
372	|   ^(bpred=BACKTRACK_SEMPRED .*) {$g = factory.build_SemanticPredicate($bpred);}
373	|   gpred=GATED_SEMPRED {$g = factory.build_SemanticPredicate($gpred);}
374	|   EPSILON {$g = factory.build_Epsilon();}
375	;
376
377ebnf returns [StateCluster g=null]
378@init
379{
380	GrammarAST blk = $start;
381	if (blk.getType() != BLOCK) {
382		blk = (GrammarAST)blk.getChild(0);
383	}
384	GrammarAST eob = blk.getLastChild();
385}
386	:	{grammar.isValidSet(this,$start)}? => set {$g = $set.g;}
387
388	|	b=block
389		{
390			// track decision if > 1 alts
391			if ( grammar.getNumberOfAltsForDecisionNFA($b.g.left)>1 )
392			{
393				$b.g.left.setDescription(grammar.grammarTreeToString(blk, false));
394				$b.g.left.setDecisionASTNode(blk);
395				int d = grammar.assignDecisionNumber( $b.g.left );
396				grammar.setDecisionNFA( d, $b.g.left );
397				grammar.setDecisionBlockAST(d, blk);
398			}
399			$g = $b.g;
400		}
401	|	^( OPTIONAL b=block )
402		{
403			StateCluster bg = $b.g;
404			if ( blk.getSetValue()!=null )
405			{
406				// if block comes back SET not BLOCK, make it
407				// a single ALT block
408				bg = factory.build_AlternativeBlockFromSet(bg);
409			}
410			$g = factory.build_Aoptional(bg);
411			$g.left.setDescription(grammar.grammarTreeToString($start, false));
412			// there is always at least one alt even if block has just 1 alt
413			int d = grammar.assignDecisionNumber( $g.left );
414			grammar.setDecisionNFA(d, $g.left);
415			grammar.setDecisionBlockAST(d, blk);
416			$g.left.setDecisionASTNode($start);
417		}
418	|	^( CLOSURE b=block )
419		{
420			StateCluster bg = $b.g;
421			if ( blk.getSetValue()!=null )
422			{
423				bg = factory.build_AlternativeBlockFromSet(bg);
424			}
425			$g = factory.build_Astar(bg);
426			// track the loop back / exit decision point
427			bg.right.setDescription("()* loopback of "+grammar.grammarTreeToString($start, false));
428			int d = grammar.assignDecisionNumber( bg.right );
429			grammar.setDecisionNFA(d, bg.right);
430			grammar.setDecisionBlockAST(d, blk);
431			bg.right.setDecisionASTNode(eob);
432			// make block entry state also have same decision for interpreting grammar
433			NFAState altBlockState = (NFAState)$g.left.transition(0).target;
434			altBlockState.setDecisionASTNode($start);
435			altBlockState.setDecisionNumber(d);
436			$g.left.setDecisionNumber(d); // this is the bypass decision (2 alts)
437			$g.left.setDecisionASTNode($start);
438		}
439	|	^( POSITIVE_CLOSURE b=block )
440		{
441			StateCluster bg = $b.g;
442			if ( blk.getSetValue()!=null )
443			{
444				bg = factory.build_AlternativeBlockFromSet(bg);
445			}
446			$g = factory.build_Aplus(bg);
447			// don't make a decision on left edge, can reuse loop end decision
448			// track the loop back / exit decision point
449			bg.right.setDescription("()+ loopback of "+grammar.grammarTreeToString($start, false));
450			int d = grammar.assignDecisionNumber( bg.right );
451			grammar.setDecisionNFA(d, bg.right);
452			grammar.setDecisionBlockAST(d, blk);
453			bg.right.setDecisionASTNode(eob);
454			// make block entry state also have same decision for interpreting grammar
455			NFAState altBlockState = (NFAState)$g.left.transition(0).target;
456			altBlockState.setDecisionASTNode($start);
457			altBlockState.setDecisionNumber(d);
458		}
459	;
460
461tree_ returns [StateCluster g=null]
462@init
463{
464	StateCluster down=null, up=null;
465}
466	:	^(	TREE_BEGIN
467			e=element { $g = $e.g; }
468			{
469				down = factory.build_Atom(Label.DOWN, $e.start);
470				// TODO set following states for imaginary nodes?
471				//el.followingNFAState = down.right;
472				$g = factory.build_AB($g,down);
473			}
474			( e=element {$g = factory.build_AB($g,$e.g);} )*
475			{
476				up = factory.build_Atom(Label.UP, $e.start);
477				//el.followingNFAState = up.right;
478				$g = factory.build_AB($g,up);
479				// tree roots point at right edge of DOWN for LOOK computation later
480				$start.NFATreeDownState = down.left;
481			}
482		)
483	;
484
485atom_or_notatom returns [StateCluster g=null]
486	:	atom[null] {$g = $atom.g;}
487	|	^(	n=NOT
488			(	c=CHAR_LITERAL (ast1=ast_suffix)?
489				{
490					int ttype=0;
491					if ( grammar.type==Grammar.LEXER )
492					{
493						ttype = Grammar.getCharValueFromGrammarCharLiteral($c.text);
494					}
495					else
496					{
497						ttype = grammar.getTokenType($c.text);
498					}
499					IntSet notAtom = grammar.complement(ttype);
500					if ( notAtom.isNil() )
501					{
502						ErrorManager.grammarError(
503							ErrorManager.MSG_EMPTY_COMPLEMENT,
504							grammar,
505							$c.getToken(),
506							$c.text);
507					}
508					$g=factory.build_Set(notAtom,$n);
509				}
510			|	t=TOKEN_REF (ast3=ast_suffix)?
511				{
512					int ttype=0;
513					IntSet notAtom = null;
514					if ( grammar.type==Grammar.LEXER )
515					{
516						notAtom = grammar.getSetFromRule(this,$t.text);
517						if ( notAtom==null )
518						{
519							ErrorManager.grammarError(
520								ErrorManager.MSG_RULE_INVALID_SET,
521								grammar,
522								$t.getToken(),
523								$t.text);
524						}
525						else
526						{
527							notAtom = grammar.complement(notAtom);
528						}
529					}
530					else
531					{
532						ttype = grammar.getTokenType($t.text);
533						notAtom = grammar.complement(ttype);
534					}
535					if ( notAtom==null || notAtom.isNil() )
536					{
537						ErrorManager.grammarError(
538							ErrorManager.MSG_EMPTY_COMPLEMENT,
539							grammar,
540							$t.getToken(),
541							$t.text);
542					}
543					$g=factory.build_Set(notAtom,$n);
544				}
545			|	set {$g = $set.g;}
546				{
547					GrammarAST stNode = (GrammarAST)$n.getChild(0);
548					//IntSet notSet = grammar.complement(stNode.getSetValue());
549					// let code generator complement the sets
550					IntSet s = stNode.getSetValue();
551					stNode.setSetValue(s);
552					// let code gen do the complement again; here we compute
553					// for NFA construction
554					s = grammar.complement(s);
555					if ( s.isNil() )
556					{
557						ErrorManager.grammarError(
558							ErrorManager.MSG_EMPTY_COMPLEMENT,
559							grammar,
560							$n.getToken());
561					}
562					$g=factory.build_Set(s,$n);
563				}
564			)
565			{$n.followingNFAState = $g.right;}
566		)
567	;
568
569atom[String scopeName] returns [StateCluster g=null]
570	:	^( r=RULE_REF (rarg=ARG_ACTION)? (as1=ast_suffix)? )
571		{
572			NFAState start = grammar.getRuleStartState(scopeName,$r.text);
573			if ( start!=null )
574			{
575				Rule rr = grammar.getRule(scopeName,$r.text);
576				$g = factory.build_RuleRef(rr, start);
577				r.followingNFAState = $g.right;
578				r.NFAStartState = $g.left;
579				if ( $g.left.transition(0) instanceof RuleClosureTransition
580					&& grammar.type!=Grammar.LEXER )
581				{
582					addFollowTransition($r.text, $g.right);
583				}
584				// else rule ref got inlined to a set
585			}
586		}
587
588	|	^( t=TOKEN_REF  (targ=ARG_ACTION)? (as2=ast_suffix)? )
589		{
590			if ( grammar.type==Grammar.LEXER )
591			{
592				NFAState start = grammar.getRuleStartState(scopeName,$t.text);
593				if ( start!=null )
594				{
595					Rule rr = grammar.getRule(scopeName,t.getText());
596					$g = factory.build_RuleRef(rr, start);
597					t.NFAStartState = $g.left;
598					// don't add FOLLOW transitions in the lexer;
599					// only exact context should be used.
600				}
601			}
602			else
603			{
604				$g = factory.build_Atom(t);
605				t.followingNFAState = $g.right;
606			}
607		}
608
609	|	^( c=CHAR_LITERAL  (as3=ast_suffix)? )
610		{
611			if ( grammar.type==Grammar.LEXER )
612			{
613				$g = factory.build_CharLiteralAtom(c);
614			}
615			else
616			{
617				$g = factory.build_Atom(c);
618				c.followingNFAState = $g.right;
619			}
620		}
621
622	|	^( s=STRING_LITERAL  (as4=ast_suffix)? )
623		{
624			if ( grammar.type==Grammar.LEXER )
625			{
626				$g = factory.build_StringLiteralAtom(s);
627			}
628			else
629			{
630				$g = factory.build_Atom(s);
631				s.followingNFAState = $g.right;
632			}
633		}
634
635	|	^(	w=WILDCARD (as5=ast_suffix)? )
636			{
637				if ( nfa.grammar.type == Grammar.TREE_PARSER
638					&& (w.getChildIndex() > 0 || w.getParent().getChild(1).getType() == EOA) )
639				{
640					$g = factory.build_WildcardTree( $w );
641				}
642				else
643				{
644					$g = factory.build_Wildcard( $w );
645				}
646			}
647
648	|	^( DOT scope_=ID a=atom[$scope_.text] {$g = $a.g;} ) // scope override
649	;
650
651ast_suffix
652	:	ROOT
653	|	BANG
654	;
655
656set returns [StateCluster g=null]
657@init
658{
659	IntSet elements=new IntervalSet();
660	if ( state.backtracking == 0 )
661		$start.setSetValue(elements); // track set for use by code gen
662}
663	:	^( b=BLOCK
664		   (^(ALT ( ^(BACKTRACK_SEMPRED .*) )? setElement[elements] EOA))+
665		   EOB
666		 )
667		{
668		$g = factory.build_Set(elements,$b);
669		$b.followingNFAState = $g.right;
670		$b.setSetValue(elements); // track set value of this block
671		}
672		//{System.out.println("set elements="+elements.toString(grammar));}
673	;
674
675setRule returns [IntSet elements=new IntervalSet()]
676@init
677{
678	IntSet s=null;
679}
680	:	^( RULE id=ID (modifier)? ARG RET ( ^(OPTIONS .*) )? ( ruleScopeSpec )?
681			( ^(AMPERSAND .*) )*
682			^( BLOCK ( ^(OPTIONS .*) )?
683			   ( ^(ALT (BACKTRACK_SEMPRED)? setElement[elements] EOA) )+
684			   EOB
685			 )
686			(exceptionGroup)?
687			EOR
688		 )
689	;
690catch[RecognitionException re] { throw re; }
691
692setElement[IntSet elements]
693@init
694{
695	int ttype;
696	IntSet ns=null;
697}
698	:	c=CHAR_LITERAL
699		{
700			if ( grammar.type==Grammar.LEXER )
701			{
702				ttype = Grammar.getCharValueFromGrammarCharLiteral($c.text);
703			}
704			else
705			{
706				ttype = grammar.getTokenType($c.text);
707			}
708			if ( elements.member(ttype) )
709			{
710				ErrorManager.grammarError(
711					ErrorManager.MSG_DUPLICATE_SET_ENTRY,
712					grammar,
713					$c.getToken(),
714					$c.text);
715			}
716			elements.add(ttype);
717		}
718	|	t=TOKEN_REF
719		{
720			if ( grammar.type==Grammar.LEXER )
721			{
722				// recursively will invoke this rule to match elements in target rule ref
723				IntSet ruleSet = grammar.getSetFromRule(this,$t.text);
724				if ( ruleSet==null )
725				{
726					ErrorManager.grammarError(
727						ErrorManager.MSG_RULE_INVALID_SET,
728						grammar,
729						$t.getToken(),
730						$t.text);
731				}
732				else
733				{
734					elements.addAll(ruleSet);
735				}
736			}
737			else
738			{
739				ttype = grammar.getTokenType($t.text);
740				if ( elements.member(ttype) )
741				{
742					ErrorManager.grammarError(
743						ErrorManager.MSG_DUPLICATE_SET_ENTRY,
744						grammar,
745						$t.getToken(),
746						$t.text);
747				}
748				elements.add(ttype);
749			}
750		}
751
752	|	s=STRING_LITERAL
753		{
754			ttype = grammar.getTokenType($s.text);
755			if ( elements.member(ttype) )
756			{
757				ErrorManager.grammarError(
758					ErrorManager.MSG_DUPLICATE_SET_ENTRY,
759					grammar,
760					$s.getToken(),
761					$s.text);
762			}
763			elements.add(ttype);
764		}
765	|	^(CHAR_RANGE c1=CHAR_LITERAL c2=CHAR_LITERAL)
766		{
767			if ( grammar.type==Grammar.LEXER )
768			{
769				int a = Grammar.getCharValueFromGrammarCharLiteral($c1.text);
770				int b = Grammar.getCharValueFromGrammarCharLiteral($c2.text);
771				elements.addAll(IntervalSet.of(a,b));
772			}
773		}
774
775	|	gset=set
776		{
777			Transition setTrans = $gset.g.left.transition(0);
778			elements.addAll(setTrans.label.getSet());
779		}
780
781	|	^(	NOT {ns=new IntervalSet();}
782			setElement[ns]
783			{
784				IntSet not = grammar.complement(ns);
785				elements.addAll(not);
786			}
787		)
788	;
789
790/** Check to see if this block can be a set.  Can't have actions
791 *  etc...  Also can't be in a rule with a rewrite as we need
792 *  to track what's inside set for use in rewrite.
793 *
794 *  This should only be called from the helper function in TreeToNFAConverterHelper.cs
795 *  and from the rule testSetElement below.
796 */
797testBlockAsSet returns [int alts=0]
798options { backtrack = true; }
799@init
800{
801	inTest++;
802}
803	:	^(	BLOCK
804			(	^(ALT (BACKTRACK_SEMPRED)? testSetElement {{$alts += $testSetElement.alts;}} EOA)
805			)+
806			EOB
807		)
808	;
809catch[RecognitionException re] { throw re; }
810finally { inTest--; }
811
812testSetRule returns [int alts=0]
813@init
814{
815	inTest++;
816}
817	:	^(	RULE id=ID (modifier)? ARG RET ( ^(OPTIONS .*) )? ( ruleScopeSpec )?
818			( ^(AMPERSAND .*) )*
819			^(	BLOCK
820				(	^(ALT (BACKTRACK_SEMPRED)? testSetElement {{$alts += $testSetElement.alts;}} EOA)
821				)+
822				EOB
823			)
824			(exceptionGroup)?
825			EOR
826		)
827	;
828catch[RecognitionException re] { throw re; }
829finally { inTest--; }
830
831/** Match just an element; no ast suffix etc.. */
832testSetElement returns [int alts=1]
833	:	c=CHAR_LITERAL {!hasElementOptions($c)}?
834	|	t=TOKEN_REF {!hasElementOptions($t)}?
835		{{
836			if ( grammar.type==Grammar.LEXER )
837			{
838				Rule rule = grammar.getRule($t.text);
839				if ( rule==null )
840				{
841					//throw new RecognitionException("invalid rule");
842					throw new RecognitionException();
843				}
844				// recursively will invoke this rule to match elements in target rule ref
845				$alts += testSetRule(rule.tree);
846			}
847		}}
848	|   {grammar.type!=Grammar.LEXER}? => s=STRING_LITERAL
849	|	^(CHAR_RANGE c1=CHAR_LITERAL c2=CHAR_LITERAL)
850		{{ $alts = IntervalSet.of( Grammar.getCharValueFromGrammarCharLiteral($c1.text), Grammar.getCharValueFromGrammarCharLiteral($c2.text) ).size(); }}
851	|   testBlockAsSet
852		{{ $alts = $testBlockAsSet.alts; }}
853	|   ^( NOT tse=testSetElement )
854		{{ $alts = grammar.getTokenTypes().size() - $tse.alts; }}
855	;
856catch[RecognitionException re] { throw re; }
857