Skip to content

Commit 7e17257

Browse files
authored
Merge pull request #4619 from rubberduck-vba/next
Hotfix release for 2.3.0
2 parents d1840ac + 7af60a3 commit 7e17257

File tree

167 files changed

+3141
-1299
lines changed

Some content is hidden

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

167 files changed

+3141
-1299
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

Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs

Lines changed: 2 additions & 67 deletions
Original file line numberDiff line numberDiff line change
@@ -20,18 +20,12 @@ public IllegalAnnotationInspection(RubberduckParserState state)
2020

2121
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2222
{
23-
var illegalAnnotations = new List<IAnnotation>();
24-
2523
var userDeclarations = State.DeclarationFinder.AllUserDeclarations.ToList();
2624
var identifierReferences = State.DeclarationFinder.AllIdentifierReferences().ToList();
2725
var annotations = State.AllAnnotations;
2826

29-
illegalAnnotations.AddRange(UnboundAnnotations(annotations, userDeclarations, identifierReferences));
30-
illegalAnnotations.AddRange(NonIdentifierAnnotationsOnIdentifiers(identifierReferences));
31-
illegalAnnotations.AddRange(NonModuleAnnotationsOnModules(userDeclarations));
32-
illegalAnnotations.AddRange(NonMemberAnnotationsOnMembers(userDeclarations));
33-
illegalAnnotations.AddRange(NonVariableAnnotationsOnVariables(userDeclarations));
34-
illegalAnnotations.AddRange(NonGeneralAnnotationsWhereOnlyGeneralAnnotationsBelong(userDeclarations));
27+
var illegalAnnotations = UnboundAnnotations(annotations, userDeclarations, identifierReferences)
28+
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation));
3529

3630
return illegalAnnotations.Select(annotation =>
3731
new QualifiedContextInspectionResult(
@@ -50,64 +44,5 @@ private static ICollection<IAnnotation> UnboundAnnotations(IEnumerable<IAnnotati
5044

5145
return annotations.Where(annotation => !boundAnnotationsSelections.Contains(annotation.QualifiedSelection)).ToList();
5246
}
53-
54-
private static ICollection<IAnnotation> NonIdentifierAnnotationsOnIdentifiers(IEnumerable<IdentifierReference> identifierReferences)
55-
{
56-
return identifierReferences
57-
.SelectMany(reference => reference.Annotations)
58-
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation))
59-
.ToList();
60-
}
61-
62-
private static ICollection<IAnnotation> NonModuleAnnotationsOnModules(IEnumerable<Declaration> userDeclarations)
63-
{
64-
return userDeclarations
65-
.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Module))
66-
.SelectMany(moduleDeclaration => moduleDeclaration.Annotations)
67-
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.ModuleAnnotation))
68-
.ToList();
69-
}
70-
71-
private static ICollection<IAnnotation> NonMemberAnnotationsOnMembers(IEnumerable<Declaration> userDeclarations)
72-
{
73-
return userDeclarations
74-
.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Member))
75-
.SelectMany(member => member.Annotations)
76-
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.MemberAnnotation))
77-
.ToList();
78-
}
79-
80-
private static ICollection<IAnnotation> NonVariableAnnotationsOnVariables(IEnumerable<Declaration> userDeclarations)
81-
{
82-
return userDeclarations
83-
.Where(declaration => VariableAnnotationDeclarationTypes.Contains(declaration.DeclarationType))
84-
.SelectMany(declaration => declaration.Annotations)
85-
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.VariableAnnotation))
86-
.ToList();
87-
}
88-
89-
private static readonly HashSet<DeclarationType> VariableAnnotationDeclarationTypes = new HashSet<DeclarationType>()
90-
{
91-
DeclarationType.Variable,
92-
DeclarationType.Control,
93-
DeclarationType.Constant,
94-
DeclarationType.Enumeration,
95-
DeclarationType.EnumerationMember,
96-
DeclarationType.UserDefinedType,
97-
DeclarationType.UserDefinedType,
98-
DeclarationType.UserDefinedTypeMember
99-
};
100-
101-
private static ICollection<IAnnotation> NonGeneralAnnotationsWhereOnlyGeneralAnnotationsBelong(IEnumerable<Declaration> userDeclarations)
102-
{
103-
return userDeclarations
104-
.Where(declaration => !declaration.DeclarationType.HasFlag(DeclarationType.Module)
105-
&& !declaration.DeclarationType.HasFlag(DeclarationType.Member)
106-
&& !VariableAnnotationDeclarationTypes.Contains(declaration.DeclarationType)
107-
&& declaration.DeclarationType != DeclarationType.Project)
108-
.SelectMany(member => member.Annotations)
109-
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation))
110-
.ToList();
111-
}
11247
}
11348
}

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8,10 +8,10 @@
88
using Rubberduck.Parsing.Grammar;
99
using Rubberduck.Parsing.Inspections;
1010
using Rubberduck.Parsing.Inspections.Abstract;
11-
using Rubberduck.Resources.Inspections;
1211
using Rubberduck.Parsing.Symbols;
1312
using Rubberduck.Parsing.VBA;
1413
using Rubberduck.Parsing.VBA.Parsing;
14+
using Rubberduck.Resources.Inspections;
1515

1616
namespace Rubberduck.Inspections.Concrete
1717
{
@@ -33,7 +33,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3333
return Listener.Contexts.Select(context =>
3434
{
3535
var name = string.Format(InspectionResults.MissingAttributeInspection, context.MemberName.MemberName,
36-
((VBAParser.AnnotationContext) context.Context).annotationName().GetText());
36+
((VBAParser.AnnotationContext)context.Context).annotationName().GetText());
3737
return new QualifiedContextInspectionResult(this, name, context);
3838
});
3939
}

Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -96,7 +96,7 @@ private IVBComponent GetVBComponentMatchingSheetName(IdentifierReferenceInspecti
9696

9797
var sheetArgumentContext = indexExprContext.argumentList().argument(0);
9898
var sheetName = FormatSheetName(sheetArgumentContext.GetText());
99-
var project = State.Projects.First(p => p.ProjectId == reference.QualifiedName.ProjectId);
99+
var project = State.ProjectsProvider.Project(reference.QualifiedName.ProjectId);
100100

101101
using (var components = project.VBComponents)
102102
{

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
}

Rubberduck.CodeAnalysis/Inspections/Inspector.cs

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -250,12 +250,25 @@ private bool IsDisabled(CodeInspectionSettings config, IInspection inspection)
250250

251251
public void Dispose()
252252
{
253+
Dispose(true);
254+
GC.SuppressFinalize(this);
255+
}
256+
257+
private bool _isDisposed;
258+
protected virtual void Dispose(bool disposing)
259+
{
260+
if (_isDisposed || !disposing)
261+
{
262+
return;
263+
}
264+
253265
if (_configService != null)
254266
{
255267
_configService.SettingsChanged -= ConfigServiceSettingsChanged;
256268
}
257269

258-
_inspections.Clear();
270+
_inspections.Clear();
271+
_isDisposed = true;
259272
}
260273
}
261274
}

0 commit comments

Comments
 (0)