Skip to content

Commit 5edd560

Browse files
committed
Split up evaluating whether 'Set' is required and evaluating whether 'Set' needs to be added. Reduced scope of inspection.
1 parent a788811 commit 5edd560

File tree

7 files changed

+53
-54
lines changed

7 files changed

+53
-54
lines changed

Rubberduck.Inspections/Concrete/ObjectVariableNotSetInspection.cs

Lines changed: 6 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,7 @@
1-
using System;
2-
using System.Collections.Generic;
3-
using System.Diagnostics;
1+
using System.Collections.Generic;
42
using System.Linq;
53
using Rubberduck.Inspections.Abstract;
64
using Rubberduck.Inspections.Results;
7-
using Rubberduck.Parsing;
8-
using Rubberduck.Parsing.Grammar;
95
using Rubberduck.Parsing.Inspections.Abstract;
106
using Rubberduck.Parsing.Inspections.Resources;
117
using Rubberduck.Parsing.Symbols;
@@ -33,19 +29,19 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3329
private IEnumerable<IdentifierReference> InterestingReferences()
3430
{
3531
var result = new List<IdentifierReference>();
36-
foreach (var qmn in State.DeclarationFinder.AllModules.Where(m => m.ComponentType != ComponentType.Undefined && m.ComponentType != ComponentType.ComComponent))
32+
foreach (var moduleReferences in State.DeclarationFinder.IdentifierReferences())
3733
{
38-
var module = State.DeclarationFinder.ModuleDeclaration(qmn);
34+
var module = State.DeclarationFinder.ModuleDeclaration(moduleReferences.Key);
3935
if (module == null || !module.IsUserDefined || IsIgnoringInspectionResultFor(module, AnnotationName))
4036
{
41-
// module isn't user code, or this inspection is ignored at module-level
37+
// module isn't user code (?), or this inspection is ignored at module-level
4238
continue;
4339
}
4440

45-
foreach (var reference in State.DeclarationFinder.IdentifierReferences(qmn))
41+
foreach (var reference in moduleReferences.Value)
4642
{
4743
if (!IsIgnoringInspectionResultFor(reference, AnnotationName)
48-
&& VariableRequiresSetAssignmentEvaluator.RequiresSetAssignment(reference, State))
44+
&& VariableRequiresSetAssignmentEvaluator.NeedsSetKeywordAdded(reference, State))
4945
{
5046
result.Add(reference);
5147
}

Rubberduck.Inspections/QuickFixes/AssignedByValParameterMakeLocalCopyQuickFix.cs

Lines changed: 5 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -116,21 +116,17 @@ private void InsertLocalVariableDeclarationAndAssignment(IModuleRewriter rewrite
116116
var requiresAssignmentUsingSet =
117117
target.References.Any(refItem => VariableRequiresSetAssignmentEvaluator.RequiresSetAssignment(refItem, _parserState));
118118

119-
var localVariableAssignment = string.Format("{0}{1}",
120-
requiresAssignmentUsingSet ? $"{Tokens.Set} " : string.Empty,
121-
$"{localIdentifier} = {target.IdentifierName}");
119+
var localVariableAssignment =
120+
$"{(requiresAssignmentUsingSet ? $"{Tokens.Set} " : string.Empty)}{localIdentifier} = {target.IdentifierName}";
122121

123122
var endOfStmtCtxt = ((ParserRuleContext)target.Context.Parent.Parent).GetChild<VBAParser.EndOfStatementContext>();
124123
var eosContent = endOfStmtCtxt.GetText();
125-
var idxLastNewLine = eosContent.LastIndexOf(Environment.NewLine);
124+
var idxLastNewLine = eosContent.LastIndexOf(Environment.NewLine, StringComparison.InvariantCultureIgnoreCase);
126125
var endOfStmtCtxtComment = eosContent.Substring(0, idxLastNewLine);
127126
var endOfStmtCtxtEndFormat = eosContent.Substring(idxLastNewLine);
128127

129-
var insertCtxt = (ParserRuleContext)((ParserRuleContext)target.Context.Parent.Parent).GetChild<VBAParser.AsTypeClauseContext>();
130-
if (insertCtxt == null)
131-
{
132-
insertCtxt = (ParserRuleContext)target.Context.Parent;
133-
}
128+
var insertCtxt = ((ParserRuleContext) target.Context.Parent.Parent).GetChild<VBAParser.AsTypeClauseContext>()
129+
?? (ParserRuleContext) target.Context.Parent;
134130

135131
rewriter.Remove(endOfStmtCtxt);
136132
rewriter.InsertAfter(insertCtxt.Stop.TokenIndex, $"{endOfStmtCtxtComment}{endOfStmtCtxtEndFormat}{localVariableDeclaration}" + $"{endOfStmtCtxtEndFormat}{localVariableAssignment}{endOfStmtCtxtEndFormat}");

Rubberduck.Inspections/VariableRequiresSetAssignmentEvaluator.cs

Lines changed: 19 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,22 @@ public static IEnumerable<Declaration> GetDeclarationsPotentiallyRequiringSetAss
2020
return relevantDeclarations;
2121
}
2222

23+
/// <summary>
24+
/// Determines whether the 'Set' keyword needs to be added in the context of the specified identifier reference.
25+
/// </summary>
26+
/// <param name="reference">The identifier reference to analyze</param>
27+
/// <param name="state">The parser state</param>
28+
public static bool NeedsSetKeywordAdded(IdentifierReference reference, RubberduckParserState state)
29+
{
30+
var setStmtContext = reference.Context.GetAncestor<VBAParser.SetStmtContext>();
31+
return RequiresSetAssignment(reference, state) && setStmtContext == null;
32+
}
33+
34+
/// <summary>
35+
/// Determines whether the 'Set' keyword is required (whether it's present or not) for the specified identifier reference.
36+
/// </summary>
37+
/// <param name="reference">The identifier reference to analyze</param>
38+
/// <param name="state">The parser state</param>
2339
public static bool RequiresSetAssignment(IdentifierReference reference, RubberduckParserState state)
2440
{
2541
if (!reference.IsAssignment)
@@ -31,21 +47,14 @@ public static bool RequiresSetAssignment(IdentifierReference reference, Rubberdu
3147
var setStmtContext = reference.Context.GetAncestor<VBAParser.SetStmtContext>();
3248
if (setStmtContext != null)
3349
{
34-
// assignment already has a Set keyword
35-
return true;
36-
// (but is it misplaced? ...hmmm... beyond the scope of *this* inspection though)
37-
// if we're only ever assigning to 'Nothing', might as well flag it though
38-
if (reference.Declaration.References.Where(r => r.IsAssignment).All(r =>
39-
r.Context.GetAncestor<VBAParser.SetStmtContext>().expression().GetText() == Tokens.Nothing))
40-
{
41-
return true;
42-
}
50+
// don't assume Set keyword is legit...
51+
return reference.Declaration.IsObject;
4352
}
4453

4554
var letStmtContext = reference.Context.GetAncestor<VBAParser.LetStmtContext>();
4655
if (letStmtContext == null)
4756
{
48-
// we're probably in a For Each loop
57+
// not an assignment
4958
return false;
5059
}
5160

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -339,13 +339,13 @@ private static string CorrectlyFormatedDescription(string literalDescription)
339339
/// </summary>
340340
public bool IsEnumeratorMember => _attributes.Any(a => a.Name.EndsWith("VB_UserMemId") && a.Values.Contains("-4"));
341341

342-
public virtual bool IsObject =>
343-
AsTypeName == Tokens.Object
344-
|| (AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.ClassModule) ?? false)
345-
&& !AsTypeIsBaseType
346-
&& !IsArray
347-
&& !DeclarationType.HasFlag(DeclarationType.UserDefinedType)
348-
&& !DeclarationType.HasFlag(DeclarationType.Enumeration);
342+
public virtual bool IsObject =>
343+
AsTypeName == Tokens.Object || (
344+
AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.ClassModule) ??
345+
!AsTypeIsBaseType
346+
&& !IsArray
347+
&& !DeclarationType.HasFlag(DeclarationType.UserDefinedType)
348+
&& !DeclarationType.HasFlag(DeclarationType.Enumeration));
349349

350350
public void AddReference(
351351
QualifiedModuleName module,

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
using System;
66
using System.Collections.Concurrent;
77
using System.Collections.Generic;
8+
using System.Collections.ObjectModel;
89
using System.Diagnostics;
910
using System.Linq;
1011
using Antlr4.Runtime;
@@ -1059,13 +1060,28 @@ private static bool IsSubroutineOrProperty(Declaration declaration)
10591060
|| declaration.DeclarationType == DeclarationType.Procedure;
10601061
}
10611062

1063+
/// <summary>
1064+
/// Creates a dictionary of identifier references, keyed by module.
1065+
/// </summary>
1066+
public IReadOnlyDictionary<QualifiedModuleName,IEnumerable<IdentifierReference>> IdentifierReferences()
1067+
{
1068+
return new ReadOnlyDictionary<QualifiedModuleName, IEnumerable<IdentifierReference>>(
1069+
_referencesByModule.ToDictionary(kvp => kvp.Key, kvp => kvp.Value.AsEnumerable()));
1070+
}
1071+
1072+
/// <summary>
1073+
/// Gets all identifier references in the specified module.
1074+
/// </summary>
10621075
public IEnumerable<IdentifierReference> IdentifierReferences(QualifiedModuleName module)
10631076
{
10641077
return _referencesByModule.TryGetValue(module, out List<IdentifierReference> value)
10651078
? value
10661079
: Enumerable.Empty<IdentifierReference>();
10671080
}
10681081

1082+
/// <summary>
1083+
/// Gets all identifier references in the specified member.
1084+
/// </summary>
10691085
public IEnumerable<IdentifierReference> IdentifierReferences(QualifiedMemberName member)
10701086
{
10711087
return _referencesByMember.TryGetValue(member, out List<IdentifierReference> value)

RubberduckTests/Inspections/ObjectVariableNotSetInspectionTests.cs

Lines changed: 0 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
using System.Threading;
33
using NUnit.Framework;
44
using Rubberduck.Inspections.Concrete;
5-
using Rubberduck.Parsing.VBA;
65
using Rubberduck.VBEditor.SafeComWrappers;
76
using RubberduckTests.Common;
87
using RubberduckTests.Mocks;
@@ -13,22 +12,6 @@ namespace RubberduckTests.Inspections
1312
[DeploymentItem(@"TestFiles\")]
1413
public class ObjectVariableNotSetInspectionTests
1514
{
16-
[Test]
17-
[Category("Inspections")]
18-
public void ObjectVariableNotSet_OnlyAssignedToNothing_ReturnsResult()
19-
{
20-
var expectResultCount = 1;
21-
var input =
22-
@"
23-
Private Sub DoSomething()
24-
Dim target As Object
25-
target.DoSomething ' error 91
26-
Set target = Nothing
27-
End Sub
28-
";
29-
AssertInputCodeYieldsExpectedInspectionResultCount(input, expectResultCount);
30-
}
31-
3215
[Test]
3316
[Category("Inspections")]
3417
public void ObjectVariableNotSet_AlsoAssignedToNothing_ReturnsNoResult()

RubberduckTests/QuickFixes/AssignedByValParameterMakeLocalCopyQuickFixTests.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -360,7 +360,6 @@ private string ApplyLocalVariableQuickFixToCodeFragment(string inputCode, string
360360

361361
using (var state = MockParser.CreateAndParse(vbe.Object))
362362
{
363-
364363
var inspection = new AssignedByValParameterInspection(state);
365364
var inspectionResults = inspection.GetInspectionResults();
366365
var result = inspectionResults.FirstOrDefault();

0 commit comments

Comments
 (0)