Skip to content

Commit e653531

Browse files
committed
Merge with next
2 parents 5b624a4 + 4213a8a commit e653531

File tree

65 files changed

+3728
-892
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

65 files changed

+3728
-892
lines changed

README.md

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,8 +15,8 @@ If you like this project and would like to thank its contributors, you are welco
1515

1616
[nextBuildStatus]:https://ci.appveyor.com/api/projects/status/we3pdnkeebo4nlck/branch/next?svg=true
1717
[masterBuildStatus]:https://ci.appveyor.com/api/projects/status/we3pdnkeebo4nlck/branch/master?svg=true
18-
19-
[![Average time to resolve an issue](http://isitmaintained.com/badge/resolution/rubberduck-vba/Rubberduck.svg)](http://isitmaintained.com/project/rubberduck-vba/Rubberduck "Average time to resolve an issue") [![Percentage of issues still open](http://isitmaintained.com/badge/open/rubberduck-vba/Rubberduck.svg)](http://isitmaintained.com/project/rubberduck-vba/Rubberduck "Percentage of issues still open")
18+
[![Average time to resolve an issue](http://isitmaintained.com/badge/resolution/Rubberduck-vba/rubberduck.svg)](http://isitmaintained.com/project/Rubberduck-vba/rubberduck "Average time to resolve an issue")
19+
[![Percentage of issues still open](http://isitmaintained.com/badge/open/Rubberduck-vba/rubberduck.svg)](http://isitmaintained.com/project/Rubberduck-vba/rubberduck "Percentage of issues still open")
2020

2121
> **[rubberduckvba.com](http://rubberduckvba.com)** [Wiki](https://github.com/rubberduck-vba/Rubberduck/wiki) [Rubberduck News](https://rubberduckvba.wordpress.com/)
2222
> devs@rubberduckvba.com
Lines changed: 71 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,71 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing;
6+
using Rubberduck.Parsing.Annotations;
7+
using Rubberduck.Parsing.Inspections;
8+
using Rubberduck.Parsing.Inspections.Abstract;
9+
using Rubberduck.Parsing.Symbols;
10+
using Rubberduck.Parsing.VBA;
11+
using Rubberduck.Resources.Inspections;
12+
13+
namespace Rubberduck.Inspections.Concrete
14+
{
15+
[CannotAnnotate]
16+
public sealed class AttributeValueOutOfSyncInspection : InspectionBase
17+
{
18+
public AttributeValueOutOfSyncInspection(RubberduckParserState state)
19+
:base(state)
20+
{
21+
}
22+
23+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
24+
{
25+
var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations
26+
.Where(declaration => declaration.Annotations.Any(annotation => annotation.AnnotationType.HasFlag(AnnotationType.Attribute)));
27+
var results = new List<DeclarationInspectionResult>();
28+
foreach (var declaration in declarationsWithAttributeAnnotations)
29+
{
30+
foreach (var annotation in declaration.Annotations.OfType<IAttributeAnnotation>())
31+
{
32+
if (HasDifferingAttributeValues(declaration, annotation, out var attributeValues))
33+
{
34+
var description = string.Format(InspectionResults.AttributeValueOutOfSyncInspection,
35+
annotation.Attribute,
36+
string.Join(", ", attributeValues),
37+
annotation.AnnotationType);
38+
39+
var result = new DeclarationInspectionResult(this, description, declaration,
40+
new QualifiedContext(declaration.QualifiedModuleName, annotation.Context));
41+
result.Properties.Annotation = annotation;
42+
result.Properties.AttributeValues = attributeValues;
43+
44+
results.Add(result);
45+
}
46+
}
47+
}
48+
49+
return results;
50+
}
51+
52+
private static bool HasDifferingAttributeValues(Declaration declaration, IAttributeAnnotation annotation, out IReadOnlyList<string> attributeValues)
53+
{
54+
var attributeNodes = declaration.DeclarationType.HasFlag(DeclarationType.Module)
55+
? declaration.Attributes.AttributeNodesFor(annotation)
56+
: declaration.Attributes.AttributeNodesFor(annotation, declaration.IdentifierName);
57+
58+
foreach (var attributeNode in attributeNodes)
59+
{
60+
var values = attributeNode.Values;
61+
if (!annotation.AttributeValues.SequenceEqual(values))
62+
{
63+
attributeValues = values;
64+
return true;
65+
}
66+
}
67+
attributeValues = new List<string>();
68+
return false;
69+
}
70+
}
71+
}
Lines changed: 28 additions & 56 deletions
Original file line numberDiff line numberDiff line change
@@ -1,87 +1,59 @@
11
using System.Collections.Generic;
22
using System.Linq;
3-
using Antlr4.Runtime;
43
using Rubberduck.Inspections.Abstract;
54
using Rubberduck.Inspections.Results;
65
using Rubberduck.Parsing;
76
using Rubberduck.Parsing.Annotations;
8-
using Rubberduck.Parsing.Grammar;
97
using Rubberduck.Parsing.Inspections;
108
using Rubberduck.Parsing.Inspections.Abstract;
11-
using Rubberduck.Resources.Inspections;
129
using Rubberduck.Parsing.Symbols;
1310
using Rubberduck.Parsing.VBA;
14-
using Rubberduck.Parsing.VBA.Parsing;
11+
using Rubberduck.Resources.Inspections;
1512

1613
namespace Rubberduck.Inspections.Concrete
1714
{
1815
[CannotAnnotate]
19-
public sealed class MissingAttributeInspection : ParseTreeInspectionBase
16+
public sealed class MissingAttributeInspection : InspectionBase
2017
{
2118
public MissingAttributeInspection(RubberduckParserState state)
2219
: base(state)
23-
{
24-
Listener = new MissingMemberAttributeListener(state);
25-
}
26-
27-
public override CodeKind TargetKindOfCode => CodeKind.AttributesCode;
28-
29-
public override IInspectionListener Listener { get; }
20+
{}
3021

3122
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3223
{
33-
return Listener.Contexts.Select(context =>
24+
var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations
25+
.Where(declaration => declaration.Annotations.Any(annotation => annotation.AnnotationType.HasFlag(AnnotationType.Attribute)));
26+
var results = new List<DeclarationInspectionResult>();
27+
foreach (var declaration in declarationsWithAttributeAnnotations)
3428
{
35-
var name = string.Format(InspectionResults.MissingAttributeInspection, context.MemberName.MemberName,
36-
((VBAParser.AnnotationContext) context.Context).annotationName().GetText());
37-
return new QualifiedContextInspectionResult(this, name, context);
38-
});
39-
}
40-
41-
public class MissingMemberAttributeListener : ParseTreeListeners.AttributeAnnotationListener
42-
{
43-
public MissingMemberAttributeListener(RubberduckParserState state) : base(state) { }
44-
45-
public override void ExitAnnotation(VBAParser.AnnotationContext context)
46-
{
47-
var annotationType = context.AnnotationType;
48-
49-
if (!annotationType.HasFlag(AnnotationType.Attribute))
29+
foreach(var annotation in declaration.Annotations.OfType<IAttributeAnnotation>())
5030
{
51-
return;
52-
}
31+
if (MissesCorrespondingAttribute(declaration, annotation))
32+
{
33+
var description = string.Format(InspectionResults.MissingAttributeInspection, declaration.IdentifierName,
34+
annotation.AnnotationType.ToString());
5335

54-
var isMemberAnnotation = annotationType.HasFlag(AnnotationType.MemberAnnotation);
55-
var isModuleScope = CurrentScopeDeclaration.DeclarationType.HasFlag(DeclarationType.Module);
36+
var result = new DeclarationInspectionResult(this, description, declaration,
37+
new QualifiedContext(declaration.QualifiedModuleName, annotation.Context));
38+
result.Properties.Annotation = annotation;
5639

57-
if (isModuleScope && !isMemberAnnotation)
58-
{
59-
// module-level annotation
60-
var module = State.DeclarationFinder.UserDeclarations(DeclarationType.Module).Single(m => m.QualifiedName.QualifiedModuleName.Equals(CurrentModuleName));
61-
if (!module.Attributes.HasAttributeFor(context.AnnotationType))
62-
{
63-
AddContext(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context));
40+
results.Add(result);
6441
}
6542
}
66-
else if (isMemberAnnotation)
67-
{
68-
// member-level annotation is above the context for the first member in the module..
69-
if (isModuleScope)
70-
{
71-
CurrentScopeDeclaration = FirstMember;
72-
}
43+
}
7344

74-
var member = Members.Value.Single(m => m.Key.Equals(CurrentScopeDeclaration.QualifiedName.MemberName));
75-
if (!member.Value.Attributes.HasAttributeFor(context.AnnotationType, member.Key))
76-
{
77-
AddContext(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context));
78-
}
79-
}
80-
else
81-
{
82-
// annotation is illegal. ignore.
83-
}
45+
return results;
46+
}
47+
48+
private static bool MissesCorrespondingAttribute(Declaration declaration, IAttributeAnnotation annotation)
49+
{
50+
if (string.IsNullOrEmpty(annotation.Attribute))
51+
{
52+
return false;
8453
}
54+
return declaration.DeclarationType.HasFlag(DeclarationType.Module)
55+
? !declaration.Attributes.HasAttributeFor(annotation)
56+
: !declaration.Attributes.HasAttributeFor(annotation, declaration.IdentifierName);
8557
}
8658
}
8759
}

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableRequiresSetAssignmentEvaluator.cs

Lines changed: 58 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Rubberduck.Parsing.VBA;
55
using System.Diagnostics;
66
using System.Linq;
7+
using Rubberduck.VBEditor;
78

89
namespace Rubberduck.Inspections
910
{
@@ -52,13 +53,7 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
5253
{
5354
// get the members of the returning type, a default member could make us lie otherwise
5455
var classModule = declaration.AsTypeDeclaration as ClassModuleDeclaration;
55-
if (classModule?.DefaultMember == null)
56-
{
57-
return true;
58-
}
59-
var parameters = (classModule.DefaultMember as IParameterizedDeclaration)?.Parameters;
60-
// assign declaration is an object without a default parameterless (or with all parameters optional) member - LHS needs a 'Set' keyword.
61-
return parameters != null && parameters.All(p => p.IsOptional);
56+
return !HasPotentiallyNonObjectParameterlessDefaultMember(classModule);
6257
}
6358

6459
// assigned declaration is a variant. we need to know about the RHS of the assignment.
@@ -75,9 +70,30 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
7570
return false;
7671
}
7772

78-
if (expression is VBAParser.NewExprContext)
73+
74+
var module = Declaration.GetModuleParent(reference.ParentScoping);
75+
76+
if (expression is VBAParser.NewExprContext newExpr)
7977
{
80-
// RHS expression is newing up an object reference - LHS needs a 'Set' keyword:
78+
var newTypeExpression = newExpr.expression();
79+
80+
// todo resolve expression type
81+
82+
//Covers the case of a single type on the RHS of the assignment.
83+
var simpleTypeName = newTypeExpression.GetDescendent<VBAParser.SimpleNameExprContext>();
84+
if (simpleTypeName != null && simpleTypeName.GetText() == newTypeExpression.GetText())
85+
{
86+
var qualifiedIdentifierSelection = new QualifiedSelection(module.QualifiedModuleName,
87+
simpleTypeName.identifier().GetSelection());
88+
var identifierText = simpleTypeName.identifier().GetText();
89+
return declarationFinderProvider.DeclarationFinder.IdentifierReferences(qualifiedIdentifierSelection)
90+
.Select(identifierReference => identifierReference.Declaration)
91+
.Where(decl => identifierText == decl.IdentifierName)
92+
.OfType<ClassModuleDeclaration>()
93+
.Any(typeDecl => !HasPotentiallyNonObjectParameterlessDefaultMember(typeDecl));
94+
}
95+
//Here, we err on the side of false-positives, but that seems more appropriate than not to treat qualified type expressions incorrectly.
96+
//Whether there is a legitimate use here for default members is questionable anyway.
8197
return true;
8298
}
8399

@@ -93,20 +109,48 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
93109
}
94110

95111
// todo resolve expression return type
96-
var project = Declaration.GetProjectParent(reference.ParentScoping);
97-
var module = Declaration.GetModuleParent(reference.ParentScoping);
98112

113+
//Covers the case of a single variable on the RHS of the assignment.
99114
var simpleName = expression.GetDescendent<VBAParser.SimpleNameExprContext>();
100-
if (simpleName != null)
115+
if (simpleName != null && simpleName.GetText() == expression.GetText())
101116
{
102-
return declarationFinderProvider.DeclarationFinder.MatchName(simpleName.identifier().GetText())
103-
.Any(d => AccessibilityCheck.IsAccessible(project, module, reference.ParentScoping, d) && d.IsObject);
117+
var qualifiedIdentifierSelection = new QualifiedSelection(module.QualifiedModuleName,
118+
simpleName.identifier().GetSelection());
119+
return declarationFinderProvider.DeclarationFinder.IdentifierReferences(qualifiedIdentifierSelection)
120+
.Select(identifierReference => identifierReference.Declaration)
121+
.Where(decl => decl.IsObject
122+
&& simpleName.identifier().GetText() == decl.IdentifierName)
123+
.Select(typeDeclaration => typeDeclaration.AsTypeDeclaration as ClassModuleDeclaration)
124+
.Any(typeDecl => !HasPotentiallyNonObjectParameterlessDefaultMember(typeDecl));
104125
}
105126

127+
var project = Declaration.GetProjectParent(reference.ParentScoping);
128+
129+
//todo: Use code path analysis to ensure that we are really picking up the last assignment to the RHS.
106130
// is the reference referring to something else in scope that's a object?
107131
return declarationFinderProvider.DeclarationFinder.MatchName(expression.GetText())
108132
.Any(decl => (decl.DeclarationType.HasFlag(DeclarationType.ClassModule) || Tokens.Object.Equals(decl.AsTypeName))
109133
&& AccessibilityCheck.IsAccessible(project, module, reference.ParentScoping, decl));
110134
}
135+
136+
private static bool HasPotentiallyNonObjectParameterlessDefaultMember(ClassModuleDeclaration classModule)
137+
{
138+
var defaultMember = classModule?.DefaultMember;
139+
140+
if (defaultMember == null)
141+
{
142+
return false;
143+
}
144+
145+
var parameters = (defaultMember as IParameterizedDeclaration)?.Parameters;
146+
// assign declaration is an object without a default parameterless (or with all parameters optional) member - LHS needs a 'Set' keyword.
147+
if (parameters != null && parameters.Any(p => !p.IsOptional))
148+
{
149+
return false;
150+
}
151+
152+
var defaultMemberType = defaultMember.AsTypeDeclaration as ClassModuleDeclaration;
153+
return defaultMemberType == null || HasPotentiallyNonObjectParameterlessDefaultMember(defaultMemberType);
154+
}
111155
}
112156
}
Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,42 @@
1+
using Rubberduck.Inspections.Abstract;
2+
using Rubberduck.Inspections.Concrete;
3+
using Rubberduck.Parsing.Annotations;
4+
using Rubberduck.Parsing.Inspections.Abstract;
5+
using Rubberduck.Parsing.Rewriter;
6+
using Rubberduck.Parsing.Symbols;
7+
using Rubberduck.Parsing.VBA;
8+
using Rubberduck.Parsing.VBA.Parsing;
9+
10+
namespace Rubberduck.Inspections.QuickFixes
11+
{
12+
public sealed class AddMissingAttributeQuickFix : QuickFixBase
13+
{
14+
private readonly IAttributesUpdater _attributesUpdater;
15+
16+
public AddMissingAttributeQuickFix(IAttributesUpdater attributesUpdater)
17+
: base(typeof(MissingAttributeInspection))
18+
{
19+
_attributesUpdater = attributesUpdater;
20+
}
21+
22+
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
23+
{
24+
var declaration = result.Target;
25+
IAttributeAnnotation annotation = result.Properties.Annotation;
26+
27+
var attributeName = declaration.DeclarationType.HasFlag(DeclarationType.Module)
28+
? annotation.Attribute
29+
: $"{declaration.IdentifierName}.{annotation.Attribute}";
30+
31+
_attributesUpdater.AddAttribute(rewriteSession, declaration, attributeName, annotation.AttributeValues);
32+
}
33+
34+
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.AddMissingAttributeQuickFix;
35+
36+
public override CodeKind TargetCodeKind => CodeKind.AttributesCode;
37+
38+
public override bool CanFixInProcedure => true;
39+
public override bool CanFixInModule => true;
40+
public override bool CanFixInProject => true;
41+
}
42+
}

0 commit comments

Comments
 (0)