Skip to content

Commit b62455a

Browse files
committed
Merge pull request #1344 from retailcoder/next
ObjectVariableNotSetInspection
2 parents 61e0fb6 + d7da07d commit b62455a

File tree

11 files changed

+428
-155
lines changed

11 files changed

+428
-155
lines changed

RetailCoder.VBE/App.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,6 @@
1717
using Rubberduck.UI.Command.MenuItems;
1818
using Infralution.Localization.Wpf;
1919
using Rubberduck.Common.Dispatch;
20-
using Rubberduck.Common.Hotkeys;
21-
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodePane;
2220

2321
namespace Rubberduck
2422
{

RetailCoder.VBE/Common/MouseHook.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -71,6 +71,7 @@ public void Attach()
7171
_hookId = User32.SetWindowsHookEx(WindowsHook.MOUSE_LL, _callback, handle, 0);
7272
if (_hookId == IntPtr.Zero)
7373
{
74+
IsAttached = false;
7475
throw new Win32Exception();
7576
}
7677

@@ -86,7 +87,7 @@ public void Detach()
8687
}
8788

8889
IsAttached = false;
89-
if (!User32.UnhookWindowsHookEx(_hookId))
90+
if (_hookId != IntPtr.Zero && !User32.UnhookWindowsHookEx(_hookId))
9091
{
9192
_hookId = IntPtr.Zero;
9293
throw new Win32Exception();

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: 20 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
using System.Collections.Generic;
22
using System.Linq;
3+
using Rubberduck.Parsing.Grammar;
34
using Rubberduck.Parsing.VBA;
45
using Rubberduck.Parsing.Symbols;
56

@@ -16,14 +17,30 @@ public SelfAssignedDeclarationInspection(RubberduckParserState state)
1617
public override string Description { get { return InspectionsUI.SelfAssignedDeclarationInspectionResultFormat; } }
1718
public override CodeInspectionType InspectionType { get { return CodeInspectionType.CodeQualityIssues; } }
1819

20+
private static readonly IReadOnlyList<string> ValueTypes = new[]
21+
{
22+
Tokens.Boolean,
23+
Tokens.Byte,
24+
Tokens.Currency,
25+
Tokens.Date,
26+
Tokens.Decimal,
27+
Tokens.Double,
28+
Tokens.Integer,
29+
Tokens.Long,
30+
Tokens.LongLong,
31+
Tokens.Single,
32+
Tokens.String
33+
};
34+
1935
public override IEnumerable<InspectionResultBase> GetInspectionResults()
2036
{
2137
return UserDeclarations
2238
.Where(declaration => declaration.IsSelfAssigned
39+
&& declaration.IsTypeSpecified()
40+
&& !ValueTypes.Contains(declaration.AsTypeName)
2341
&& declaration.DeclarationType == DeclarationType.Variable
24-
&& declaration.ParentScope == declaration.QualifiedName.QualifiedModuleName.ToString()
25-
&& declaration.ParentDeclaration != null
26-
&& declaration.ParentDeclaration.DeclarationType == DeclarationType.Class)
42+
&& declaration.ParentScopeDeclaration != null
43+
&& declaration.ParentScopeDeclaration.DeclarationType.HasFlag(DeclarationType.Member))
2744
.Select(issue => new SelfAssignedDeclarationInspectionResult(this, issue));
2845
}
2946
}

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"/>

RetailCoder.VBE/UI/Command/Refactorings/CodePaneRefactorRenameCommand.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -47,8 +47,7 @@ public override void Execute(object parameter)
4747
}
4848
else
4949
{
50-
var selection = Vbe.ActiveCodePane.GetSelection();
51-
target = _state.AllUserDeclarations.FindTarget(selection);
50+
target = _state.FindSelectedDeclaration(Vbe.ActiveCodePane);
5251
}
5352

5453
if (target == null)

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 12 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -102,7 +102,7 @@ public void Parse()
102102
var components = projects.SelectMany(p => p.VBComponents.Cast<VBComponent>()).ToList();
103103
_state.SetModuleState(ParserState.LoadingReference);
104104

105-
LoadComReferences(projects);
105+
SyncComReferences(projects);
106106

107107
foreach (var component in components)
108108
{
@@ -138,7 +138,7 @@ private void ParseAll()
138138
var unchanged = components.Where(c => !_state.IsModified(c)).ToList();
139139

140140
_state.SetModuleState(ParserState.LoadingReference); // todo: change that to a simple statusbar text update
141-
LoadComReferences(projects);
141+
SyncComReferences(projects);
142142

143143
if (!modified.Any())
144144
{
@@ -168,7 +168,7 @@ private void ParseAll()
168168

169169
private readonly HashSet<ReferencePriorityMap> _references = new HashSet<ReferencePriorityMap>();
170170

171-
private void LoadComReferences(IEnumerable<VBProject> projects)
171+
private void SyncComReferences(IReadOnlyList<VBProject> projects)
172172
{
173173
foreach (var vbProject in projects)
174174
{
@@ -200,9 +200,17 @@ private void LoadComReferences(IEnumerable<VBProject> projects)
200200
}
201201
}
202202
}
203+
204+
var mappedIds = _references.Select(map => map.ReferenceId);
205+
var unmapped = projects.SelectMany(project => project.References.Cast<Reference>())
206+
.Where(reference => !mappedIds.Contains(reference.ReferenceId()));
207+
foreach (var reference in unmapped)
208+
{
209+
UnloadComReference(reference);
210+
}
203211
}
204212

205-
public void UnloadComReference(Reference reference)
213+
private void UnloadComReference(Reference reference)
206214
{
207215
var referenceId = reference.ReferenceId();
208216
var map = _references.SingleOrDefault(r => r.ReferenceId == referenceId);

0 commit comments

Comments
 (0)