Skip to content

Commit 1911f6c

Browse files
authored
Merge pull request #4389 from comintern/bugfixes
Various bug fixes.
2 parents 6df939d + 3a5e485 commit 1911f6c

File tree

8 files changed

+138
-13
lines changed

8 files changed

+138
-13
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAssignmentInspection.cs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
using System.Collections.Generic;
2+
using System.Diagnostics;
23
using System.Linq;
34
using Rubberduck.Inspections.Abstract;
45
using Rubberduck.Inspections.Results;
@@ -28,7 +29,10 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2829
.Where(reference =>
2930
{
3031
var letStmtContext = reference.Context.GetAncestor<VBAParser.LetStmtContext>();
31-
return reference.IsAssignment && letStmtContext != null && letStmtContext.LET() == null;
32+
return reference.IsAssignment
33+
&& letStmtContext != null
34+
&& letStmtContext.LET() == null
35+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
3236
});
3337

3438
return interestingReferences.Select(reference => new IdentifierReferenceInspectionResult(this,

Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -21,20 +21,22 @@ public UnassignedVariableUsageInspection(RubberduckParserState state)
2121
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2222
{
2323
var declarations = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
24-
.Where(result => !IsIgnoringInspectionResultFor(result, AnnotationName))
25-
.Where(declaration =>
26-
State.DeclarationFinder.MatchName(declaration.AsTypeName).All(d => d.DeclarationType != DeclarationType.UserDefinedType)
24+
.Where(declaration =>
25+
State.DeclarationFinder.MatchName(declaration.AsTypeName)
26+
.All(d => d.DeclarationType != DeclarationType.UserDefinedType)
2727
&& !declaration.IsSelfAssigned
28-
&& !declaration.References.Any(reference => reference.IsAssignment && !IsIgnoringInspectionResultFor(reference, AnnotationName)));
28+
&& !declaration.References.Any(reference => reference.IsAssignment));
2929

30-
//The parameter scoping was apparently incorrect before - need to filter for the actual function.
30+
//See https://github.com/rubberduck-vba/Rubberduck/issues/2010 for why these are being excluded.
31+
//TODO: These need to be modified to correctly work in VB6.
3132
var lenFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.Len"));
32-
var lenbFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.Len"));
33+
var lenbFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.LenB"));
3334

3435
return declarations.Where(d => d.References.Any() &&
3536
!DeclarationReferencesContainsReference(lenFunction, d) &&
3637
!DeclarationReferencesContainsReference(lenbFunction, d))
3738
.SelectMany(d => d.References)
39+
.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
3840
.Select(r => new IdentifierReferenceInspectionResult(this,
3941
string.Format(InspectionResults.UnassignedVariableUsageInspection, r.IdentifierName),
4042
State,

Rubberduck.Core/AutoComplete/AutoCompleteService.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,7 @@ public AutoCompleteService(IGeneralConfigService configService, SelfClosingPairC
3535
{
3636
_selfClosingPairCompletion = selfClosingPairCompletion;
3737
_configService = configService;
38+
InitializeConfig();
3839
_configService.SettingsChanged += ConfigServiceSettingsChanged;
3940
}
4041

Rubberduck.Core/Common/RubberduckHooks.cs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,6 @@ public void HookHotkeys()
3232
_hooks.Clear();
3333

3434
var config = _config.LoadConfiguration();
35-
AutoComplete.ApplyAutoCompleteSettings(config);
3635
var settings = config.UserSettings.HotkeySettings;
3736

3837
foreach (var hotkeySetting in settings.Settings.Where(hotkeySetting => hotkeySetting.IsEnabled))
@@ -73,7 +72,6 @@ public void Attach()
7372

7473
try
7574
{
76-
AutoComplete.Enable();
7775
foreach (var hook in Hooks)
7876
{
7977
hook.Attach();
@@ -96,7 +94,6 @@ public void Detach()
9694

9795
try
9896
{
99-
AutoComplete.Disable();
10097
foreach (var hook in Hooks)
10198
{
10299
hook.MessageReceived -= hook_MessageReceived;

Rubberduck.Core/Settings/ConfigurationLoader.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -99,7 +99,8 @@ public void SaveConfiguration(Configuration toSerialize)
9999
var inspectOnReparse = toSerialize.UserSettings.CodeInspectionSettings.RunInspectionsOnSuccessfulParse;
100100
var oldAutoCompleteSettings = _autoCompleteProvider.Create().AutoCompletes.Select(s => Tuple.Create(s.Key, s.IsEnabled));
101101
var newAutoCompleteSettings = toSerialize.UserSettings.AutoCompleteSettings.AutoCompletes.Select(s => Tuple.Create(s.Key, s.IsEnabled));
102-
var autoCompletesChanged = !oldAutoCompleteSettings.SequenceEqual(newAutoCompleteSettings);
102+
var autoCompletesChanged = !oldAutoCompleteSettings.SequenceEqual(newAutoCompleteSettings) ||
103+
toSerialize.UserSettings.AutoCompleteSettings.IsEnabled != _autoCompleteProvider.Create().IsEnabled;
103104

104105
_generalProvider.Save(toSerialize.UserSettings.GeneralSettings);
105106
_hotkeyProvider.Save(toSerialize.UserSettings.HotkeySettings);
Lines changed: 119 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,119 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using System.Text;
5+
using System.Threading;
6+
using System.Threading.Tasks;
7+
using NUnit.Framework;
8+
using Rubberduck.Inspections.Concrete;
9+
using Rubberduck.Parsing.VBA;
10+
using Rubberduck.VBEditor.SafeComWrappers;
11+
using RubberduckTests.Mocks;
12+
13+
namespace RubberduckTests.Inspections
14+
{
15+
[TestFixture]
16+
public class ImplicitDefaultMemberAssignmentInspectionTests
17+
{
18+
[Test]
19+
[Ignore("Ignored pending #4390")]
20+
[Category("Inspections")]
21+
public void ImplicitDefaultMemberAssignment_ReturnsResult()
22+
{
23+
const string inputCode =
24+
@"Public Sub Foo(bar As Range)
25+
With bar
26+
.Cells(1, 1) = 42
27+
End With
28+
End Sub
29+
";
30+
31+
var builder = new MockVbeBuilder();
32+
var project = builder.ProjectBuilder("TestProject1", "TestProject1", ProjectProtection.Unprotected)
33+
.AddComponent("Module1", ComponentType.StandardModule, inputCode)
34+
.AddReference("Excel", MockVbeBuilder.LibraryPathMsExcel, 1, 8, true)
35+
.Build();
36+
var vbe = builder.AddProject(project).Build();
37+
38+
var parser = MockParser.Create(vbe.Object);
39+
using (var state = parser.State)
40+
{
41+
parser.Parse(new CancellationTokenSource());
42+
if (state.Status >= ParserState.Error)
43+
{
44+
Assert.Inconclusive("Parser Error");
45+
}
46+
47+
var inspection = new ImplicitDefaultMemberAssignmentInspection(state);
48+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
49+
50+
Assert.AreEqual(1, inspectionResults.Count());
51+
}
52+
}
53+
54+
[Test]
55+
[Category("Inspections")]
56+
public void ImplicitDefaultMemberAssignment_IgnoredDoesNotReturnResult()
57+
{
58+
const string inputCode =
59+
@"Public Sub Foo(bar As Range)
60+
With bar
61+
'@Ignore ImplicitDefaultMemberAssignment
62+
.Cells(1, 1) = 42
63+
End With
64+
End Sub
65+
";
66+
var builder = new MockVbeBuilder();
67+
var project = builder.ProjectBuilder("TestProject1", "TestProject1", ProjectProtection.Unprotected)
68+
.AddComponent("Module1", ComponentType.StandardModule, inputCode)
69+
.AddReference("Excel", MockVbeBuilder.LibraryPathMsExcel, 1, 8, true)
70+
.Build();
71+
var vbe = builder.AddProject(project).Build();
72+
73+
using (var state = MockParser.CreateAndParse(vbe.Object))
74+
{
75+
var inspection = new ImplicitDefaultMemberAssignmentInspection(state);
76+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
77+
78+
Assert.AreEqual(0, inspectionResults.Count());
79+
}
80+
}
81+
82+
[Test]
83+
[Category("Inspections")]
84+
public void ImplicitDefaultMemberAssignment_ExplicitCallDoesNotReturnResult()
85+
{
86+
const string inputCode =
87+
@"Public Sub Foo(bar As Range)
88+
With bar
89+
.Cells(1, 1).Value = 42
90+
End With
91+
End Sub
92+
";
93+
var builder = new MockVbeBuilder();
94+
var project = builder.ProjectBuilder("TestProject1", "TestProject1", ProjectProtection.Unprotected)
95+
.AddComponent("Module1", ComponentType.StandardModule, inputCode)
96+
.AddReference("Excel", MockVbeBuilder.LibraryPathMsExcel, 1, 8, true)
97+
.Build();
98+
var vbe = builder.AddProject(project).Build();
99+
100+
using (var state = MockParser.CreateAndParse(vbe.Object))
101+
{
102+
var inspection = new ImplicitDefaultMemberAssignmentInspection(state);
103+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
104+
105+
Assert.AreEqual(0, inspectionResults.Count());
106+
}
107+
}
108+
109+
[Test]
110+
[Category("Inspections")]
111+
public void InspectionName()
112+
{
113+
const string inspectionName = "ImplicitDefaultMemberAssignmentInspection";
114+
var inspection = new ImplicitDefaultMemberAssignmentInspection(null);
115+
116+
Assert.AreEqual(inspectionName, inspection.Name);
117+
}
118+
}
119+
}

RubberduckTests/Inspections/UnassignedVariableUsageInspectionTests.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -93,11 +93,11 @@ Dim bb As Boolean
9393
public void UnassignedVariableUsage_Ignored_DoesNotReturnResult()
9494
{
9595
const string inputCode =
96-
@"Sub Foo()
97-
'@Ignore UnassignedVariableUsage
96+
@"Sub Foo()
9897
Dim b As Boolean
9998
Dim bb As Boolean
10099
100+
'@Ignore UnassignedVariableUsage
101101
bb = b
102102
End Sub";
103103

RubberduckTests/RubberduckTests.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -108,6 +108,7 @@
108108
<Compile Include="CodeAnalysis\CodeMetrics\CyclomaticComplexityTests.cs" />
109109
<Compile Include="CodeAnalysis\CodeMetrics\LineCountTests.cs" />
110110
<Compile Include="CodeExplorer\CodeExplorerTests.cs" />
111+
<Compile Include="Inspections\ImplicitDefaultMemberAssignmentInspectionTests.cs" />
111112
<Compile Include="Inspections\UnreachableCase\ExpressionFilterUnitTests.cs" />
112113
<Compile Include="Inspections\UnreachableCase\ParseTreeExpressionEvaluatorUnitTests.cs" />
113114
<Compile Include="Inspections\UnreachableCase\ParseTreeValueUnitTests.cs" />

0 commit comments

Comments
 (0)