Skip to content

Commit c84e8bc

Browse files
committed
implemented ObjectVariableNotSetInspection; closes #383
1 parent e4ebaca commit c84e8bc

File tree

7 files changed

+394
-144
lines changed

7 files changed

+394
-144
lines changed

RetailCoder.VBE/Inspections/InspectionsUI.Designer.cs

Lines changed: 178 additions & 142 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

RetailCoder.VBE/Inspections/InspectionsUI.resx

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -509,4 +509,17 @@
509509
<data name="QualifiedSelectionInspection" xml:space="preserve">
510510
<value>{0}: {1} - {2}.{3}, line {4}</value>
511511
</data>
512+
<data name="ObjectVariableNotSetInspectionMeta" xml:space="preserve">
513+
<value>As far as Rubberduck can tell, this variable is an object variable, assigned without the 'Set' keyword. This causes run-time error 91 'Object or With block variable not set'.</value>
514+
</data>
515+
<data name="ObjectVariableNotSetInspectionResultFormat" xml:space="preserve">
516+
<value>Object variable '{0}' is assigned without the 'Set' keyword</value>
517+
<comment>{0} Variable name</comment>
518+
</data>
519+
<data name="SetObjectVariableQuickFix" xml:space="preserve">
520+
<value>Use 'Set' keyword</value>
521+
</data>
522+
<data name="ObjectVariableNotSetInspectionName" xml:space="preserve">
523+
<value>Object variable assignment requires 'Set' keyword</value>
524+
</data>
512525
</root>
Lines changed: 106 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,106 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Antlr4.Runtime;
4+
using Rubberduck.Parsing;
5+
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.Parsing.Nodes;
7+
using Rubberduck.Parsing.Symbols;
8+
using Rubberduck.Parsing.VBA;
9+
using Rubberduck.VBEditor;
10+
11+
namespace Rubberduck.Inspections
12+
{
13+
public sealed class ObjectVariableNotSetInspectionResult : InspectionResultBase
14+
{
15+
private readonly IdentifierReference _reference;
16+
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
17+
18+
public ObjectVariableNotSetInspectionResult(IInspection inspection, IdentifierReference reference)
19+
:base(inspection, reference.QualifiedModuleName, reference.Context)
20+
{
21+
_reference = reference;
22+
_quickFixes = new CodeInspectionQuickFix[]
23+
{
24+
new SetObjectVariableQuickFix(_reference),
25+
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName),
26+
};
27+
}
28+
29+
public override IEnumerable<CodeInspectionQuickFix> QuickFixes { get { return _quickFixes; } }
30+
31+
public override string Description
32+
{
33+
get { return string.Format(InspectionsUI.ObjectVariableNotSetInspectionResultFormat, _reference.Declaration.IdentifierName); }
34+
}
35+
}
36+
37+
public sealed class SetObjectVariableQuickFix : CodeInspectionQuickFix
38+
{
39+
public SetObjectVariableQuickFix(IdentifierReference reference)
40+
: base(context: reference.Context.Parent.Parent as ParserRuleContext, // ImplicitCallStmt_InStmtContext
41+
selection: new QualifiedSelection(reference.QualifiedModuleName, reference.Selection),
42+
description: InspectionsUI.SetObjectVariableQuickFix)
43+
{
44+
}
45+
46+
public override bool CanFixInModule { get { return true; } }
47+
public override bool CanFixInProject { get { return true; } }
48+
49+
public override void Fix()
50+
{
51+
var codeModule = Selection.QualifiedName.Component.CodeModule;
52+
var codeLine = codeModule.get_Lines(Selection.Selection.StartLine, 1);
53+
54+
var letStatementLeftSide = Context.GetText();
55+
var setStatementLeftSide = Tokens.Set + ' ' + letStatementLeftSide;
56+
57+
var correctLine = codeLine.Replace(letStatementLeftSide, setStatementLeftSide);
58+
codeModule.ReplaceLine(Selection.Selection.StartLine, correctLine);
59+
}
60+
}
61+
62+
public sealed class ObjectVariableNotSetInspection : InspectionBase
63+
{
64+
public ObjectVariableNotSetInspection(RubberduckParserState state)
65+
: base(state, CodeInspectionSeverity.Error)
66+
{
67+
}
68+
69+
public override string Meta { get { return InspectionsUI.ObjectVariableNotSetInspectionMeta; } }
70+
public override string Description { get { return InspectionsUI.ObjectVariableNotSetInspectionResultFormat; } }
71+
public override CodeInspectionType InspectionType { get { return CodeInspectionType.CodeQualityIssues; } }
72+
73+
private static readonly IReadOnlyList<string> ValueTypes = new[]
74+
{
75+
Tokens.Boolean,
76+
Tokens.Byte,
77+
Tokens.Currency,
78+
Tokens.Date,
79+
Tokens.Decimal,
80+
Tokens.Double,
81+
Tokens.Integer,
82+
Tokens.Long,
83+
Tokens.LongLong,
84+
Tokens.Single,
85+
Tokens.String
86+
};
87+
88+
public override IEnumerable<InspectionResultBase> GetInspectionResults()
89+
{
90+
return State.AllUserDeclarations
91+
.Where(item => !ValueTypes.Contains(item.AsTypeName)
92+
&& !item.IsSelfAssigned
93+
&& (item.DeclarationType == DeclarationType.Variable
94+
|| item.DeclarationType == DeclarationType.Parameter))
95+
.SelectMany(declaration =>
96+
declaration.References.Where(reference =>
97+
{
98+
var setStmtContext = reference.Context.Parent.Parent.Parent as VBAParser.LetStmtContext;
99+
return setStmtContext != null && setStmtContext.LET() == null;
100+
}))
101+
.Select(reference => new ObjectVariableNotSetInspectionResult(this, reference));
102+
103+
104+
}
105+
}
106+
}

RetailCoder.VBE/Inspections/SelfAssignedDeclarationInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ public SelfAssignedDeclarationInspection(RubberduckParserState state)
1717
public override string Description { get { return InspectionsUI.SelfAssignedDeclarationInspectionResultFormat; } }
1818
public override CodeInspectionType InspectionType { get { return CodeInspectionType.CodeQualityIssues; } }
1919

20-
private static readonly IEnumerable<string> ValueTypes = new[]
20+
private static readonly IReadOnlyList<string> ValueTypes = new[]
2121
{
2222
Tokens.Boolean,
2323
Tokens.Byte,

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -347,6 +347,7 @@
347347
<DesignTime>True</DesignTime>
348348
</Compile>
349349
<Compile Include="Inspections\MakeSingleLineParameterQuickFix.cs" />
350+
<Compile Include="Inspections\ObjectVariableNotSetInspection.cs" />
350351
<Compile Include="Inspections\RemoveExplicitCallStatmentQuickFix.cs" />
351352
<Compile Include="Settings\RubberduckHotkey.cs" />
352353
<Compile Include="UI\About\AboutControl.xaml.cs">

RetailCoder.VBE/UI/CodeInspections/InspectionResultsControl.xaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -424,7 +424,7 @@
424424
<StackPanel Margin="4" Orientation="Horizontal" HorizontalAlignment="Stretch">
425425
<Image Style="{StaticResource IconStyle}" VerticalAlignment="Center"
426426
Source="{Binding SelectedItem.Inspection.Severity, Converter={StaticResource SeverityIconConverter}}"/>
427-
<TextBlock Margin="4" Text="{Binding SelectedItem.Inspection.Description}" FontWeight="Bold" TextWrapping="WrapWithOverflow"/>
427+
<TextBlock Margin="4" Text="{Binding SelectedItem.Description}" FontWeight="Bold" TextWrapping="WrapWithOverflow"/>
428428
</StackPanel>
429429

430430
<TextBlock Margin="4" Text="{Binding SelectedItem.Inspection.Meta}" FontSize="10" TextWrapping="WrapWithOverflow"/>

RubberduckTests/Inspections/ConstantNotUsedInspectionTests.cs

Lines changed: 94 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,100 @@
1010

1111
namespace RubberduckTests.Inspections
1212
{
13+
[TestClass]
14+
public class ObjectVariableNotSetInspectionTests
15+
{
16+
[TestMethod]
17+
public void ObjectVariableNotSet_GivenStringVariable_ReturnsNoResult()
18+
{
19+
const string inputCode = @"
20+
Private Sub Workbook_Open()
21+
22+
Dim target As String
23+
target = Range(""A1"")
24+
25+
target.Value = ""all good""
26+
27+
End Sub";
28+
29+
//Arrange
30+
var builder = new MockVbeBuilder();
31+
VBComponent component;
32+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
33+
var mockHost = new Mock<IHostApplication>();
34+
mockHost.SetupAllProperties();
35+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState());
36+
37+
parser.Parse();
38+
if (parser.State.Status == ParserState.Error) { Assert.Inconclusive("Parser Error"); }
39+
40+
var inspection = new ObjectVariableNotSetInspection(parser.State);
41+
var inspectionResults = inspection.GetInspectionResults();
42+
43+
Assert.AreEqual(0, inspectionResults.Count());
44+
}
45+
46+
[TestMethod]
47+
public void ObjectVariableNotSet_GivenObjectVariableNotSet_ReturnsResult()
48+
{
49+
const string inputCode = @"
50+
Private Sub Workbook_Open()
51+
52+
Dim target As Range
53+
target = Range(""A1"")
54+
55+
target.Value = ""forgot something?""
56+
57+
End Sub";
58+
59+
//Arrange
60+
var builder = new MockVbeBuilder();
61+
VBComponent component;
62+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
63+
var mockHost = new Mock<IHostApplication>();
64+
mockHost.SetupAllProperties();
65+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState());
66+
67+
parser.Parse();
68+
if (parser.State.Status == ParserState.Error) { Assert.Inconclusive("Parser Error"); }
69+
70+
var inspection = new ObjectVariableNotSetInspection(parser.State);
71+
var inspectionResults = inspection.GetInspectionResults();
72+
73+
Assert.AreEqual(1, inspectionResults.Count());
74+
}
75+
76+
[TestMethod]
77+
public void ObjectVariableNotSet_GivenSetObjectVariable_ReturnsNoResult()
78+
{
79+
const string inputCode = @"
80+
Private Sub Workbook_Open()
81+
82+
Dim target As Range
83+
Set target = Range(""A1"")
84+
85+
target.Value = ""All good""
86+
87+
End Sub";
88+
89+
//Arrange
90+
var builder = new MockVbeBuilder();
91+
VBComponent component;
92+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
93+
var mockHost = new Mock<IHostApplication>();
94+
mockHost.SetupAllProperties();
95+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState());
96+
97+
parser.Parse();
98+
if (parser.State.Status == ParserState.Error) { Assert.Inconclusive("Parser Error"); }
99+
100+
var inspection = new ObjectVariableNotSetInspection(parser.State);
101+
var inspectionResults = inspection.GetInspectionResults();
102+
103+
Assert.AreEqual(0, inspectionResults.Count());
104+
}
105+
}
106+
13107
[TestClass]
14108
public class ConstantNotUsedInspectionTests
15109
{

0 commit comments

Comments
 (0)