Skip to content

Commit a6c12a5

Browse files
authored
Merge pull request #4322 from comintern/bugfixes
Misc Bugfixes
2 parents ec6f285 + a3cce65 commit a6c12a5

File tree

8 files changed

+298
-42
lines changed

8 files changed

+298
-42
lines changed

Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs

Lines changed: 27 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,6 @@
99
using Rubberduck.Parsing.Inspections;
1010
using Rubberduck.Parsing.Inspections.Abstract;
1111
using Rubberduck.Parsing.VBA;
12-
using Rubberduck.Parsing.VBA.Extensions;
1312

1413
namespace Rubberduck.Inspections.QuickFixes
1514
{
@@ -32,33 +31,40 @@ public override void Fix(IInspectionResult result)
3231
var annotationText = $"'@Ignore {result.Inspection.AnnotationName}";
3332

3433
int annotationLine;
35-
string codeLine;
3634
using (var module = _state.ProjectsProvider.Component(result.QualifiedSelection.QualifiedName).CodeModule)
3735
{
3836
annotationLine = result.QualifiedSelection.Selection.StartLine;
3937
while (annotationLine != 1 && module.GetLines(annotationLine - 1, 1).EndsWith(" _"))
4038
{
4139
annotationLine--;
4240
}
43-
44-
codeLine = annotationLine == 1 ? string.Empty : module.GetLines(annotationLine - 1, 1);
4541
}
4642

4743
RuleContext treeRoot = result.Context;
4844
while (treeRoot.Parent != null)
4945
{
5046
treeRoot = treeRoot.Parent;
5147
}
52-
53-
if (codeLine.HasComment(out var commentStart) && codeLine.Substring(commentStart).StartsWith("'@Ignore "))
54-
{
55-
var listener = new AnnotationListener();
56-
ParseTreeWalker.Default.Walk(listener, treeRoot);
5748

58-
var annotationContext = listener.Contexts.Last(i => i.Start.TokenIndex <= result.Context.Start.TokenIndex);
49+
var listener = new CommentOrAnnotationListener();
50+
ParseTreeWalker.Default.Walk(listener, treeRoot);
51+
var commentContext = listener.Contexts.LastOrDefault(i => i.Stop.TokenIndex <= result.Context.Start.TokenIndex);
52+
var commented = commentContext?.Stop.Line + 1 == annotationLine;
5953

60-
var rewriter = _state.GetRewriter(result.QualifiedSelection.QualifiedName);
61-
rewriter.InsertAfter(annotationContext.annotationName().Stop.TokenIndex, $" {result.Inspection.AnnotationName},");
54+
var rewriter = _state.GetRewriter(result.QualifiedSelection.QualifiedName);
55+
56+
if (commented)
57+
{
58+
var annotation = commentContext.annotationList()?.annotation(0);
59+
if (annotation != null && annotation.GetText().StartsWith("Ignore"))
60+
{
61+
rewriter.InsertAfter(annotation.annotationName().Stop.TokenIndex, $" {result.Inspection.AnnotationName},");
62+
}
63+
else
64+
{
65+
var indent = new string(Enumerable.Repeat(' ', commentContext.Start.Column).ToArray());
66+
rewriter.InsertAfter(commentContext.Stop.TokenIndex, $"{indent}{annotationText}{Environment.NewLine}");
67+
}
6268
}
6369
else
6470
{
@@ -72,39 +78,35 @@ public override void Fix(IInspectionResult result)
7278
}
7379
else
7480
{
75-
var listener = new EOLListener();
76-
ParseTreeWalker.Default.Walk(listener, treeRoot);
81+
var eol = new EndOfLineListener();
82+
ParseTreeWalker.Default.Walk(eol, treeRoot);
7783

7884
// we subtract 2 here to get the insertion index to A) account for VBE's one-based indexing
7985
// and B) to get the newline token that introduces that line
80-
var eolContext = listener.Contexts.OrderBy(o => o.Start.TokenIndex).ElementAt(annotationLine - 2);
86+
var eolContext = eol.Contexts.OrderBy(o => o.Start.TokenIndex).ElementAt(annotationLine - 2);
8187
insertIndex = eolContext.Start.TokenIndex;
8288

8389
annotationText = Environment.NewLine + annotationText;
8490
}
8591

86-
var rewriter = _state.GetRewriter(result.QualifiedSelection.QualifiedName);
8792
rewriter.InsertBefore(insertIndex, annotationText);
8893
}
8994
}
9095

9196
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.IgnoreOnce;
9297

93-
private class AnnotationListener : VBAParserBaseListener
98+
private class CommentOrAnnotationListener : VBAParserBaseListener
9499
{
95-
private readonly IList<VBAParser.AnnotationContext> _contexts = new List<VBAParser.AnnotationContext>();
96-
public IEnumerable<VBAParser.AnnotationContext> Contexts => _contexts;
100+
private readonly IList<VBAParser.CommentOrAnnotationContext> _contexts = new List<VBAParser.CommentOrAnnotationContext>();
101+
public IEnumerable<VBAParser.CommentOrAnnotationContext> Contexts => _contexts;
97102

98-
public override void ExitAnnotation([NotNull] VBAParser.AnnotationContext context)
103+
public override void ExitCommentOrAnnotation([NotNull] VBAParser.CommentOrAnnotationContext context)
99104
{
100-
if (context.annotationName().GetText() == Annotations.IgnoreInspection)
101-
{
102-
_contexts.Add(context);
103-
}
105+
_contexts.Add(context);
104106
}
105107
}
106108

107-
private class EOLListener : VBAParserBaseListener
109+
private class EndOfLineListener : VBAParserBaseListener
108110
{
109111
private readonly IList<ParserRuleContext> _contexts = new List<ParserRuleContext>();
110112
public IEnumerable<ParserRuleContext> Contexts => _contexts;

Rubberduck.Core/AutoComplete/AutoCompleteService.cs

Lines changed: 18 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,11 @@ public AutoCompleteService(IGeneralConfigService configService, SelfClosingPairC
4040

4141
public void Enable()
4242
{
43-
InitializeConfig();
43+
if (!_initializing)
44+
{
45+
InitializeConfig();
46+
}
47+
4448
if (!_enabled)
4549
{
4650
VBENativeServices.KeyDown += HandleKeyDown;
@@ -49,13 +53,23 @@ public void Enable()
4953
}
5054
}
5155

56+
private bool _initializing;
5257
private void InitializeConfig()
5358
{
54-
if (!_initialized)
59+
_initializing = true;
60+
// No reason to think this would throw, but if it does, _initializing state needs to be reset.
61+
try
5562
{
56-
var config = _configService.LoadConfiguration();
57-
ApplyAutoCompleteSettings(config);
63+
if (!_initialized)
64+
{
65+
var config = _configService.LoadConfiguration();
66+
ApplyAutoCompleteSettings(config);
67+
}
5868
}
69+
finally
70+
{
71+
_initializing = false;
72+
}
5973
}
6074

6175
public void Disable()

Rubberduck.Core/UI/Settings/AutoCompleteSettingsViewModel.cs

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -14,11 +14,7 @@ public class AutoCompleteSettingsViewModel : SettingsViewModelBase, ISettingsVie
1414
{
1515
public AutoCompleteSettingsViewModel(Configuration config)
1616
{
17-
Settings = new ObservableCollection<AutoCompleteSetting>(config.UserSettings.AutoCompleteSettings.AutoCompletes);
18-
CompleteBlockOnEnter = config.UserSettings.AutoCompleteSettings.CompleteBlockOnEnter;
19-
CompleteBlockOnTab = config.UserSettings.AutoCompleteSettings.CompleteBlockOnTab;
20-
EnableSmartConcat = config.UserSettings.AutoCompleteSettings.EnableSmartConcat;
21-
17+
TransferSettingsToView(config.UserSettings.AutoCompleteSettings);
2218
ExportButtonCommand = new DelegateCommand(LogManager.GetCurrentClassLogger(), _ => ExportSettings());
2319
ImportButtonCommand = new DelegateCommand(LogManager.GetCurrentClassLogger(), _ => ImportSettings());
2420
}
@@ -44,6 +40,7 @@ public void SetToDefaults(Configuration config)
4440

4541
public void UpdateConfig(Configuration config)
4642
{
43+
config.UserSettings.AutoCompleteSettings.IsEnabled = IsEnabled;
4744
config.UserSettings.AutoCompleteSettings.CompleteBlockOnTab = CompleteBlockOnTab;
4845
config.UserSettings.AutoCompleteSettings.CompleteBlockOnEnter = CompleteBlockOnEnter;
4946
config.UserSettings.AutoCompleteSettings.EnableSmartConcat = EnableSmartConcat;
@@ -52,6 +49,7 @@ public void UpdateConfig(Configuration config)
5249

5350
private void TransferSettingsToView(Rubberduck.Settings.AutoCompleteSettings toLoad)
5451
{
52+
IsEnabled = toLoad.IsEnabled;
5553
CompleteBlockOnTab = toLoad.CompleteBlockOnTab;
5654
CompleteBlockOnEnter = toLoad.CompleteBlockOnEnter;
5755
EnableSmartConcat = toLoad.EnableSmartConcat;

Rubberduck.Core/UI/Settings/GeneralSettingsViewModel.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,8 @@ public GeneralSettingsViewModel(Configuration config, IOperatingSystem operating
3939
{
4040
new DisplayLanguageSetting("en-US"),
4141
new DisplayLanguageSetting("fr-CA"),
42-
new DisplayLanguageSetting("de-DE")
42+
new DisplayLanguageSetting("de-DE"),
43+
new DisplayLanguageSetting("cs-CZ")
4344
});
4445

4546
LogLevels = new ObservableCollection<MinimumLogLevel>(LogLevelHelper.LogLevels.Select(l => new MinimumLogLevel(l.Ordinal, l.Name)));

Rubberduck.Resources/RubberduckUI.Designer.cs

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

Rubberduck.Resources/RubberduckUI.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1300,4 +1300,7 @@ NOTE: Restart is required for the setting to take effect.</value>
13001300
<data name="IndenterSettings_IgnoreEmptyLinesInFirstBlocks" xml:space="preserve">
13011301
<value>Ignore empty lines when locating first comment and declaration blocks</value>
13021302
</data>
1303+
<data name="Language_CS" xml:space="preserve">
1304+
<value>Czech</value>
1305+
</data>
13031306
</root>

RubberduckTests/QuickFixes/IgnoreOnceQuickFixTests.cs

Lines changed: 144 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1027,8 +1027,8 @@ Dim str As String
10271027
var parser = MockParser.Create(vbe.Object);
10281028
using (var state = parser.State)
10291029
{
1030-
// FIXME reinstate and unignore tests
1031-
// refers to "UntypedFunctionUsageInspectionTests.GetBuiltInDeclarations()"
1030+
//FIXME reinstate and unignore tests
1031+
//refers to "UntypedFunctionUsageInspectionTests.GetBuiltInDeclarations()"
10321032
//GetBuiltInDeclarations().ForEach(d => state.AddDeclaration(d));
10331033

10341034
parser.Parse(new CancellationTokenSource());
@@ -1229,5 +1229,147 @@ If True Then
12291229
}
12301230
}
12311231

1232+
[Test]
1233+
[Category("QuickFixes")]
1234+
public void IgnoreQuickFixAppendsToExistingAnnotation()
1235+
{
1236+
const string inputCode =
1237+
@"Sub Foo()
1238+
'@Ignore VariableNotUsed
1239+
x = 42
1240+
End Sub";
1241+
1242+
const string expectedCode =
1243+
@"Sub Foo()
1244+
'@Ignore UndeclaredVariable, VariableNotUsed
1245+
x = 42
1246+
End Sub";
1247+
1248+
var builder = new MockVbeBuilder();
1249+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
1250+
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
1251+
.Build();
1252+
var component = project.Object.VBComponents[0];
1253+
var vbe = builder.AddProject(project).Build();
1254+
1255+
using (var state = MockParser.CreateAndParse(vbe.Object))
1256+
{
1257+
1258+
var inspection = new UndeclaredVariableInspection(state);
1259+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
1260+
1261+
new IgnoreOnceQuickFix(state, new[] { inspection }).Fix(inspectionResults.First());
1262+
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
1263+
}
1264+
}
1265+
1266+
[Test]
1267+
[Category("QuickFixes")]
1268+
public void IgnoreQuickFixAddsAnnotationAfterComment()
1269+
{
1270+
const string inputCode =
1271+
@"Sub Foo()
1272+
'comment
1273+
x = 42
1274+
End Sub";
1275+
1276+
const string expectedCode =
1277+
@"Sub Foo()
1278+
'comment
1279+
'@Ignore UndeclaredVariable
1280+
x = 42
1281+
End Sub";
1282+
1283+
var builder = new MockVbeBuilder();
1284+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
1285+
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
1286+
.Build();
1287+
var component = project.Object.VBComponents[0];
1288+
var vbe = builder.AddProject(project).Build();
1289+
1290+
using (var state = MockParser.CreateAndParse(vbe.Object))
1291+
{
1292+
1293+
var inspection = new UndeclaredVariableInspection(state);
1294+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
1295+
1296+
new IgnoreOnceQuickFix(state, new[] { inspection }).Fix(inspectionResults.First());
1297+
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
1298+
}
1299+
}
1300+
1301+
[Test]
1302+
[Category("QuickFixes")]
1303+
public void IgnoreQuickFixAddsAnnotationAfterRemComment()
1304+
{
1305+
const string inputCode =
1306+
@"Sub Foo()
1307+
Rem comment
1308+
x = 42
1309+
End Sub";
1310+
1311+
const string expectedCode =
1312+
@"Sub Foo()
1313+
Rem comment
1314+
'@Ignore UndeclaredVariable
1315+
x = 42
1316+
End Sub";
1317+
1318+
var builder = new MockVbeBuilder();
1319+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
1320+
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
1321+
.Build();
1322+
var component = project.Object.VBComponents[0];
1323+
var vbe = builder.AddProject(project).Build();
1324+
1325+
using (var state = MockParser.CreateAndParse(vbe.Object))
1326+
{
1327+
1328+
var inspection = new UndeclaredVariableInspection(state);
1329+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
1330+
1331+
new IgnoreOnceQuickFix(state, new[] { inspection }).Fix(inspectionResults.First());
1332+
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
1333+
}
1334+
}
1335+
1336+
[Test]
1337+
[Category("QuickFixes")]
1338+
public void IgnoreQuickFixAddsAnnotationAfterMultilineComment()
1339+
{
1340+
const string inputCode =
1341+
@"Sub Foo()
1342+
'multi _
1343+
line _
1344+
comment
1345+
x = 42
1346+
End Sub";
1347+
1348+
const string expectedCode =
1349+
@"Sub Foo()
1350+
'multi _
1351+
line _
1352+
comment
1353+
'@Ignore UndeclaredVariable
1354+
x = 42
1355+
End Sub";
1356+
1357+
var builder = new MockVbeBuilder();
1358+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
1359+
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
1360+
.Build();
1361+
var component = project.Object.VBComponents[0];
1362+
var vbe = builder.AddProject(project).Build();
1363+
1364+
using (var state = MockParser.CreateAndParse(vbe.Object))
1365+
{
1366+
1367+
var inspection = new UndeclaredVariableInspection(state);
1368+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
1369+
1370+
new IgnoreOnceQuickFix(state, new[] { inspection }).Fix(inspectionResults.First());
1371+
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
1372+
}
1373+
}
12321374
}
12331375
}

0 commit comments

Comments
 (0)