Skip to content

Commit d49b82b

Browse files
committed
merge with next
2 parents b40a96e + 77fa481 commit d49b82b

File tree

131 files changed

+3254
-1418
lines changed

Some content is hidden

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

131 files changed

+3254
-1418
lines changed

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/NonReturningFunctionInspection.cs

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
using System.Linq;
33
using Rubberduck.Inspections.Abstract;
44
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing;
56
using Rubberduck.Parsing.Grammar;
67
using Rubberduck.Parsing.Inspections.Abstract;
78
using Rubberduck.Resources.Inspections;
@@ -34,7 +35,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3435
var unassigned = (from function in functions
3536
let isUdt = IsReturningUserDefinedType(function)
3637
let inScopeRefs = function.References.Where(r => r.ParentScoping.Equals(function))
37-
where (!isUdt && (!inScopeRefs.Any(r => r.IsAssignment)))
38+
where (!isUdt && (!inScopeRefs.Any(r => r.IsAssignment) &&
39+
!inScopeRefs.Any(reference => IsAssignedByRefArgument(function, reference))))
3840
|| (isUdt && !IsUserDefinedTypeAssigned(function))
3941
select function)
4042
.ToList();
@@ -46,6 +48,17 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4648
issue));
4749
}
4850

51+
private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierReference reference)
52+
{
53+
var argExpression = reference.Context.GetAncestor<VBAParser.ArgumentExpressionContext>();
54+
var parameter = State.DeclarationFinder.FindParameterFromArgument(argExpression, enclosingProcedure);
55+
56+
// note: not recursive, by design.
57+
return parameter != null
58+
&& (parameter.IsImplicitByRef || parameter.IsByRef)
59+
&& parameter.References.Any(r => r.IsAssignment);
60+
}
61+
4962
private bool IsReturningUserDefinedType(Declaration member)
5063
{
5164
return member.AsTypeDeclaration != null &&

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/UnassignedVariableUsageInspection.cs

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4141

4242
return declarations
4343
.Where(d => d.References.Any() && !excludedDeclarations.Any(excl => DeclarationReferencesContainsReference(excl, d)))
44-
.SelectMany(d => d.References)
44+
.SelectMany(d => d.References.Where(r => !IsAssignedByRefArgument(r.ParentScoping, r)))
4545
.Distinct()
4646
.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
4747
.Where(r => !r.Context.TryGetAncestor<VBAParser.RedimStmtContext>(out _) && !IsArraySubscriptAssignment(r))
@@ -51,6 +51,17 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5151
r)).ToList();
5252
}
5353

54+
private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierReference reference)
55+
{
56+
var argExpression = reference.Context.GetAncestor<VBAParser.ArgumentExpressionContext>();
57+
var parameter = State.DeclarationFinder.FindParameterFromArgument(argExpression, enclosingProcedure);
58+
59+
// note: not recursive, by design.
60+
return parameter != null
61+
&& (parameter.IsImplicitByRef || parameter.IsByRef)
62+
&& parameter.References.Any(r => r.IsAssignment);
63+
}
64+
5465
private static bool IsArraySubscriptAssignment(IdentifierReference reference)
5566
{
5667
var isLetAssignment = reference.Context.TryGetAncestor<VBAParser.LetStmtContext>(out var letStmt);

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableNotAssignedInspection.cs

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,8 @@
22
using System.Linq;
33
using Rubberduck.Inspections.Abstract;
44
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing;
6+
using Rubberduck.Parsing.Grammar;
57
using Rubberduck.Parsing.Inspections.Abstract;
68
using Rubberduck.Resources.Inspections;
79
using Rubberduck.Parsing.Symbols;
@@ -25,11 +27,22 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2527
!declaration.IsWithEvents
2628
&& State.DeclarationFinder.MatchName(declaration.AsTypeName).All(item => item.DeclarationType != DeclarationType.UserDefinedType) // UDT variables don't need to be assigned
2729
&& !declaration.IsSelfAssigned
28-
&& !declaration.References.Any(reference => reference.IsAssignment))
30+
&& !declaration.References.Any(reference => reference.IsAssignment || IsAssignedByRefArgument(reference.ParentScoping, reference)))
2931
.Where(result => !IsIgnoringInspectionResultFor(result, AnnotationName));
3032

3133
return declarations.Select(issue =>
3234
new DeclarationInspectionResult(this, string.Format(InspectionResults.VariableNotAssignedInspection, issue.IdentifierName), issue));
3335
}
36+
37+
private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierReference reference)
38+
{
39+
var argExpression = reference.Context.GetAncestor<VBAParser.ArgumentExpressionContext>();
40+
var parameter = State.DeclarationFinder.FindParameterFromArgument(argExpression, enclosingProcedure);
41+
42+
// note: not recursive, by design.
43+
return parameter != null
44+
&& (parameter.IsImplicitByRef || parameter.IsByRef)
45+
&& parameter.References.Any(r => r.IsAssignment);
46+
}
3447
}
3548
}

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableRequiresSetAssignmentEvaluator.cs

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -72,6 +72,7 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
7272
if (expression == null)
7373
{
7474
Debug.Assert(false, "RHS expression is empty? What's going on here?");
75+
return false;
7576
}
7677

7778
if (expression is VBAParser.NewExprContext)
@@ -86,25 +87,24 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
8687
// RHS is a 'Nothing' token - LHS needs a 'Set' keyword:
8788
return true;
8889
}
90+
if (literalExpression != null)
91+
{
92+
return false; // any other literal expression definitely isn't an object.
93+
}
8994

9095
// todo resolve expression return type
96+
var project = Declaration.GetProjectParent(reference.ParentScoping);
97+
var module = Declaration.GetModuleParent(reference.ParentScoping);
9198

92-
var memberRefs = declarationFinderProvider.DeclarationFinder.IdentifierReferences(reference.ParentScoping.QualifiedName);
93-
var lastRef = memberRefs.LastOrDefault(r => !Equals(r, reference) && r.Context.GetAncestor<VBAParser.LetStmtContext>() == letStmtContext);
94-
if (lastRef?.Declaration.AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.ClassModule) ?? false)
99+
var simpleName = expression.GetDescendent<VBAParser.SimpleNameExprContext>();
100+
if (simpleName != null)
95101
{
96-
// the last reference in the expression is referring to an object type
97-
return true;
98-
}
99-
if (lastRef?.Declaration.AsTypeName == Tokens.Object)
100-
{
101-
return true;
102+
return declarationFinderProvider.DeclarationFinder.MatchName(simpleName.identifier().GetText())
103+
.Any(d => AccessibilityCheck.IsAccessible(project, module, reference.ParentScoping, d) && d.IsObject);
102104
}
103105

104106
// is the reference referring to something else in scope that's a object?
105-
var project = Declaration.GetProjectParent(reference.ParentScoping);
106-
var module = Declaration.GetModuleParent(reference.ParentScoping);
107-
return declarationFinderProvider.DeclarationFinder.MatchName(expression.GetText().ToLowerInvariant())
107+
return declarationFinderProvider.DeclarationFinder.MatchName(expression.GetText())
108108
.Any(decl => (decl.DeclarationType.HasFlag(DeclarationType.ClassModule) || Tokens.Object.Equals(decl.AsTypeName))
109109
&& AccessibilityCheck.IsAccessible(project, module, reference.ParentScoping, decl));
110110
}

0 commit comments

Comments
 (0)