Skip to content

Commit d374ba7

Browse files
authored
Merge pull request #5175 from MDoerner/HacktoberGrammarFixes
Hacktoberfest parser fixes
2 parents 3ebc6e4 + a63403b commit d374ba7

33 files changed

+1171
-506
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,12 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5656
|| annotation.AnnotatedLine == null);
5757
var attributeAnnotationsInDocuments = AttributeAnnotationsInDocuments(userDeclarations);
5858

59-
var illegalAnnotations = unboundAnnotations.Concat(attributeAnnotationsInDocuments).ToHashSet();
59+
var attributeAnnotationsOnDeclarationsNotAllowingAttributes = AttributeAnnotationsOnDeclarationsNotAllowingAttributes(userDeclarations);
60+
61+
var illegalAnnotations = unboundAnnotations
62+
.Concat(attributeAnnotationsInDocuments)
63+
.Concat(attributeAnnotationsOnDeclarationsNotAllowingAttributes)
64+
.ToHashSet();
6065

6166
return illegalAnnotations.Select(annotation =>
6267
new QualifiedContextInspectionResult(
@@ -82,5 +87,14 @@ private static IEnumerable<IParseTreeAnnotation> AttributeAnnotationsInDocuments
8287
.Where(declaration => declaration.QualifiedModuleName.ComponentType == ComponentType.Document);
8388
return declarationsInDocuments.SelectMany(doc => doc.Annotations).Where(pta => pta.Annotation is IAttributeAnnotation);
8489
}
90+
91+
private static IEnumerable<IParseTreeAnnotation> AttributeAnnotationsOnDeclarationsNotAllowingAttributes(IEnumerable<Declaration> userDeclarations)
92+
{
93+
return userDeclarations
94+
.Where(declaration => declaration.AttributesPassContext == null
95+
&& !declaration.DeclarationType.HasFlag(DeclarationType.Module))
96+
.SelectMany(declaration => declaration.Annotations)
97+
.Where(parseTreeAnnotation => parseTreeAnnotation.Annotation is IAttributeAnnotation);
98+
}
8599
}
86100
}

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,9 @@ public MissingAttributeInspection(RubberduckParserState state)
4848
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4949
{
5050
var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations
51-
.Where(declaration => declaration.Annotations.Any(pta => pta.Annotation is IAttributeAnnotation));
51+
.Where(declaration => declaration.Annotations.Any(pta => pta.Annotation is IAttributeAnnotation)
52+
&& (declaration.DeclarationType.HasFlag(DeclarationType.Module)
53+
|| declaration.AttributesPassContext != null));
5254
var results = new List<DeclarationInspectionResult>();
5355
foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document
5456
&& !decl.IsIgnoringInspectionResultFor(AnnotationName)))

Rubberduck.CodeAnalysis/Inspections/Concrete/ShadowedDeclarationInspection.cs

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
using System.Collections.Generic;
1+
using System;
2+
using System.Collections.Generic;
23
using System.Globalization;
34
using System.Linq;
45
using Rubberduck.Inspections.Abstract;
@@ -200,6 +201,12 @@ private static bool DeclarationInReferencedProjectCanBeShadowed(Declaration orig
200201
return false;
201202
}
202203

204+
// We insert Debug.Assert as a member access on an artificial Debug standard module. Thus, Assert will also be seen as shadowing Debug.Assert, which is not true.
205+
if (originalDeclaration.IdentifierName.Equals("Assert", StringComparison.InvariantCultureIgnoreCase) && originalDeclaration.QualifiedModuleName.ComponentName.Equals("Debug", StringComparison.InvariantCultureIgnoreCase))
206+
{
207+
return false;
208+
}
209+
203210
return DeclarationAccessibilityCanBeShadowed(originalDeclaration);
204211
}
205212

Rubberduck.Parsing/Binding/Bindings/MemberAccessDefaultBinding.cs

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,29 @@ public MemberAccessDefaultBinding(
4141
_lExpressionBinding = lExpressionBinding;
4242
}
4343

44+
public MemberAccessDefaultBinding(
45+
DeclarationFinder declarationFinder,
46+
Declaration project,
47+
Declaration module,
48+
Declaration parent,
49+
VBAParser.ObjectPrintExprContext expression,
50+
IExpressionBinding lExpressionBinding,
51+
StatementResolutionContext statementContext,
52+
ParserRuleContext unrestrictedNameContext)
53+
: this(
54+
declarationFinder,
55+
project,
56+
module,
57+
parent,
58+
expression,
59+
null,
60+
Tokens.Print,
61+
statementContext,
62+
unrestrictedNameContext)
63+
{
64+
_lExpressionBinding = lExpressionBinding;
65+
}
66+
4467
public MemberAccessDefaultBinding(
4568
DeclarationFinder declarationFinder,
4669
Declaration project,
Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,28 @@
1+
using Antlr4.Runtime;
2+
3+
namespace Rubberduck.Parsing.Binding
4+
{
5+
public sealed class ObjectPrintDefaultBinding : IExpressionBinding
6+
{
7+
private readonly ParserRuleContext _context;
8+
private readonly IExpressionBinding _printMethodBinding;
9+
private readonly IExpressionBinding _outputListBinding;
10+
11+
public ObjectPrintDefaultBinding(
12+
ParserRuleContext context,
13+
IExpressionBinding printMethodBinding,
14+
IExpressionBinding outputListBinding)
15+
{
16+
_context = context;
17+
_printMethodBinding = printMethodBinding;
18+
_outputListBinding = outputListBinding;
19+
}
20+
21+
public IBoundExpression Resolve()
22+
{
23+
var printMethodExpression = _printMethodBinding.Resolve();
24+
var outputListExpression = _outputListBinding?.Resolve();
25+
return new ObjectPrintExpression(_context, printMethodExpression, outputListExpression);
26+
}
27+
}
28+
}
Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
1+
using System.Collections.Generic;
2+
using Antlr4.Runtime;
3+
4+
namespace Rubberduck.Parsing.Binding
5+
{
6+
public sealed class OutputListDefaultBinding : IExpressionBinding
7+
{
8+
private readonly ParserRuleContext _context;
9+
private readonly List<IExpressionBinding> _itemBindings;
10+
11+
public OutputListDefaultBinding(
12+
ParserRuleContext context,
13+
List<IExpressionBinding> itemBindings)
14+
{
15+
_context = context;
16+
_itemBindings = itemBindings;
17+
}
18+
19+
public IBoundExpression Resolve()
20+
{
21+
var itemExpressions = new List<IBoundExpression>();
22+
foreach (var itemBinding in _itemBindings)
23+
{
24+
itemExpressions.Add(itemBinding.Resolve());
25+
};
26+
return new OutputListExpression(_context, itemExpressions);
27+
}
28+
}
29+
}

Rubberduck.Parsing/Binding/DefaultBindingContext.cs

Lines changed: 125 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
using Rubberduck.Parsing.Grammar;
33
using Rubberduck.Parsing.Symbols;
44
using System;
5+
using System.Collections.Generic;
56
using Antlr4.Runtime.Tree;
67
using Rubberduck.Parsing.VBA.DeclarationCaching;
78

@@ -29,7 +30,26 @@ public IBoundExpression Resolve(Declaration module, Declaration parent, IParseTr
2930
return bindingTree?.Resolve();
3031
}
3132

32-
public IExpressionBinding BuildTree(Declaration module, Declaration parent, IParseTree expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext, bool requiresLetCoercion = false, bool isLetAssignment = false)
33+
public IExpressionBinding BuildTree(
34+
Declaration module,
35+
Declaration parent,
36+
IParseTree expression,
37+
IBoundExpression withBlockVariable,
38+
StatementResolutionContext statementContext,
39+
bool requiresLetCoercion = false,
40+
bool isLetAssignment = false)
41+
{
42+
return Visit(
43+
module,
44+
parent,
45+
expression,
46+
withBlockVariable,
47+
statementContext,
48+
requiresLetCoercion,
49+
isLetAssignment);
50+
}
51+
52+
public IExpressionBinding Visit(Declaration module, Declaration parent, IParseTree expression, IBoundExpression withBlockVariable, StatementResolutionContext statementContext, bool requiresLetCoercion = false, bool isLetAssignment = false)
3353
{
3454
if (requiresLetCoercion && expression is ParserRuleContext context)
3555
{
@@ -51,6 +71,10 @@ public IExpressionBinding BuildTree(Declaration module, Declaration parent, IPar
5171
return Visit(module, parent, booleanExpressionContext, withBlockVariable);
5272
case VBAParser.IntegerExpressionContext integerExpressionContext:
5373
return Visit(module, parent, integerExpressionContext, withBlockVariable);
74+
case VBAParser.OutputListContext outputListContext:
75+
return Visit(module, parent, outputListContext, withBlockVariable);
76+
case VBAParser.UnqualifiedObjectPrintStmtContext unqualifiedObjectPrintStmtContext:
77+
return Visit(module, parent, unqualifiedObjectPrintStmtContext, withBlockVariable);
5478
default:
5579
throw new NotSupportedException($"Unexpected context type {expression.GetType()}");
5680
}
@@ -160,6 +184,8 @@ private IExpressionBinding Visit(Declaration module, Declaration parent, VBAPars
160184
return Visit(module, parent, dictionaryAccessExprContext, withBlockVariable);
161185
case VBAParser.WithDictionaryAccessExprContext withDictionaryAccessExprContext:
162186
return Visit(module, parent, withDictionaryAccessExprContext, withBlockVariable);
187+
case VBAParser.ObjectPrintExprContext objectPrintExprContext:
188+
return Visit(module, parent, objectPrintExprContext, withBlockVariable);
163189
default:
164190
throw new NotSupportedException($"Unexpected lExpression type {expression.GetType()}");
165191
}
@@ -208,7 +234,61 @@ private IExpressionBinding Visit(Declaration module, Declaration parent, VBAPars
208234
{
209235
var lExpression = expression.lExpression();
210236
var lExpressionBinding = Visit(module, parent, lExpression, withBlockVariable, StatementResolutionContext.Undefined);
211-
return new MemberAccessDefaultBinding(_declarationFinder, Declaration.GetProjectParent(parent), module, parent, expression, lExpressionBinding, statementContext, expression.unrestrictedIdentifier());
237+
return new MemberAccessDefaultBinding(
238+
_declarationFinder,
239+
Declaration.GetProjectParent(parent),
240+
module,
241+
parent,
242+
expression,
243+
lExpressionBinding,
244+
statementContext,
245+
expression.unrestrictedIdentifier());
246+
}
247+
248+
private IExpressionBinding Visit(Declaration module, Declaration parent, VBAParser.ObjectPrintExprContext expression, IBoundExpression withBlockVariable)
249+
{
250+
var lExpression = expression.lExpression();
251+
var lExpressionBinding = Visit(module, parent, lExpression, withBlockVariable, StatementResolutionContext.Undefined);
252+
var memberAccessBinding = new MemberAccessDefaultBinding(
253+
_declarationFinder,
254+
Declaration.GetProjectParent(parent),
255+
module,
256+
parent,
257+
expression,
258+
lExpressionBinding,
259+
StatementResolutionContext.Undefined,
260+
expression.printMethod());
261+
var outputListContext = expression.outputList();
262+
var outputListBinding = outputListContext != null
263+
? Visit(
264+
module,
265+
parent,
266+
outputListContext,
267+
withBlockVariable)
268+
: null;
269+
return new ObjectPrintDefaultBinding(expression, memberAccessBinding, outputListBinding);
270+
}
271+
272+
private IExpressionBinding Visit(Declaration module, Declaration parent, VBAParser.UnqualifiedObjectPrintStmtContext expression, IBoundExpression withBlockVariable)
273+
{
274+
var printMethodContext = expression.printMethod();
275+
var simpleNameBinding = new SimpleNameDefaultBinding(
276+
_declarationFinder,
277+
Declaration.GetProjectParent(parent),
278+
module,
279+
parent,
280+
printMethodContext,
281+
printMethodContext.GetText(),
282+
StatementResolutionContext.Undefined);
283+
var outputListContext = expression.outputList();
284+
var outputListBinding = outputListContext != null
285+
? Visit(
286+
module,
287+
parent,
288+
outputListContext,
289+
withBlockVariable)
290+
: null;
291+
return new ObjectPrintDefaultBinding(expression, simpleNameBinding, outputListBinding);
212292
}
213293

214294
private IExpressionBinding Visit(Declaration module, Declaration parent, VBAParser.IndexExprContext expression, IBoundExpression withBlockVariable)
@@ -416,6 +496,49 @@ private IExpressionBinding Visit(Declaration module, Declaration parent, VBAPars
416496
return new LetCoercionDefaultBinding(expression, innerExpression);
417497
}
418498

499+
private IExpressionBinding Visit(Declaration module, Declaration parent, VBAParser.OutputListContext outputListContext, IBoundExpression withBlockVariable)
500+
{
501+
var itemBindings = new List<IExpressionBinding>();
502+
foreach (var outputItem in outputListContext.outputItem())
503+
{
504+
if (outputItem.outputClause() != null)
505+
{
506+
if (outputItem.outputClause().spcClause() != null)
507+
{
508+
itemBindings.Add(Visit(
509+
module,
510+
parent,
511+
outputItem.outputClause().spcClause().spcNumber().expression(),
512+
withBlockVariable,
513+
StatementResolutionContext.Undefined,
514+
requiresLetCoercion: true));
515+
}
516+
if (outputItem.outputClause().tabClause() != null && outputItem.outputClause().tabClause().tabNumberClause() != null)
517+
{
518+
itemBindings.Add(Visit(
519+
module,
520+
parent,
521+
outputItem.outputClause().tabClause().tabNumberClause().tabNumber().expression(),
522+
withBlockVariable,
523+
StatementResolutionContext.Undefined,
524+
requiresLetCoercion: true));
525+
}
526+
if (outputItem.outputClause().outputExpression() != null)
527+
{
528+
itemBindings.Add(Visit(
529+
module,
530+
parent,
531+
outputItem.outputClause().outputExpression().expression(),
532+
withBlockVariable,
533+
StatementResolutionContext.Undefined,
534+
requiresLetCoercion: true));
535+
}
536+
}
537+
}
538+
539+
return new OutputListDefaultBinding(outputListContext, itemBindings);
540+
}
541+
419542
private static IExpressionBinding Visit(Declaration module, VBAParser.InstanceExprContext expression)
420543
{
421544
return new InstanceDefaultBinding(expression, module);
Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
using Antlr4.Runtime;
2+
3+
namespace Rubberduck.Parsing.Binding
4+
{
5+
public sealed class ObjectPrintExpression : BoundExpression
6+
{
7+
public ObjectPrintExpression(
8+
ParserRuleContext context,
9+
IBoundExpression printMethodExpression,
10+
IBoundExpression outputListBoundExpression)
11+
: base(null, ExpressionClassification.Subroutine, context)
12+
{
13+
PrintMethodExpressions = printMethodExpression;
14+
OutputListExpression = outputListBoundExpression;
15+
}
16+
17+
public IBoundExpression PrintMethodExpressions { get; }
18+
public IBoundExpression OutputListExpression { get; }
19+
}
20+
}
Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
using System.Collections.Generic;
2+
using Antlr4.Runtime;
3+
4+
namespace Rubberduck.Parsing.Binding
5+
{
6+
public sealed class OutputListExpression : BoundExpression
7+
{
8+
public OutputListExpression(
9+
ParserRuleContext context,
10+
IReadOnlyCollection<IBoundExpression> itemExpressions)
11+
: base(null, ExpressionClassification.Value, context)
12+
{
13+
ItemExpressions = itemExpressions;
14+
}
15+
16+
public IReadOnlyCollection<IBoundExpression> ItemExpressions { get; }
17+
}
18+
}

0 commit comments

Comments
 (0)