Skip to content

Commit 77fa481

Browse files
authored
Merge pull request #4581 from comintern/next
Various quick bug fixes for 2.3 patch release
2 parents 14547be + b8b0b7d commit 77fa481

File tree

10 files changed

+175
-45
lines changed

10 files changed

+175
-45
lines changed

Rubberduck.Core/App.cs

Lines changed: 33 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@
99
using System;
1010
using System.Diagnostics;
1111
using System.Globalization;
12+
using System.Linq;
1213
using Rubberduck.Parsing.UIContext;
1314
using Rubberduck.Resources;
1415
using Rubberduck.UI.Command;
@@ -182,24 +183,22 @@ private void ApplyCultureConfig()
182183

183184
private static void LocalizeResources(CultureInfo culture)
184185
{
185-
//TODO: this method needs something better - maybe use reflection to discover all resourcees
186-
// to set culture for all resources files?
187-
Resources.RubberduckUI.Culture = culture;
188-
Resources.About.AboutUI.Culture = culture;
189-
Resources.Inspections.InspectionInfo.Culture = culture;
190-
Resources.Inspections.InspectionNames.Culture = culture;
191-
Resources.Inspections.InspectionResults.Culture = culture;
192-
Resources.Inspections.InspectionsUI.Culture = culture;
193-
Resources.Inspections.QuickFixes.Culture = culture;
194-
Resources.Menus.RubberduckMenus.Culture = culture;
195-
Resources.RegexAssistant.RegexAssistantUI.Culture = culture;
196-
Resources.Settings.SettingsUI.Culture = culture;
197-
Resources.Settings.ToDoExplorerPage.Culture = culture;
198-
Resources.Settings.UnitTestingPage.Culture = culture;
199-
Resources.ToDoExplorer.ToDoExplorerUI.Culture = culture;
200-
Resources.UnitTesting.AssertMessages.Culture = culture;
201-
Resources.UnitTesting.TestExplorer.Culture = culture;
202-
Resources.Templates.Culture = culture;
186+
var localizers = AppDomain.CurrentDomain.GetAssemblies()
187+
.SingleOrDefault(assembly => assembly.GetName().Name == "Rubberduck.Resources")
188+
?.DefinedTypes.SelectMany(type => type.DeclaredProperties.Where(prop =>
189+
prop.CanWrite && prop.Name.Equals("Culture") && prop.PropertyType == typeof(CultureInfo) &&
190+
(prop.SetMethod?.IsStatic ?? false)));
191+
192+
if (localizers == null)
193+
{
194+
return;
195+
}
196+
197+
var args = new object[] { culture };
198+
foreach (var localizer in localizers)
199+
{
200+
localizer.SetMethod.Invoke(null, args);
201+
}
203202
}
204203

205204
private void CheckForLegacyIndenterSettings()
@@ -230,14 +229,26 @@ public void LogRubberduckStart()
230229
{
231230
var version = _version.CurrentVersion;
232231
GlobalDiagnosticsContext.Set("RubberduckVersion", version.ToString());
232+
233233
var headers = new List<string>
234234
{
235235
$"\r\n\tRubberduck version {version} loading:",
236-
$"\tOperating System: {Environment.OSVersion.VersionString} {(Environment.Is64BitOperatingSystem ? "x64" : "x86")}",
237-
$"\tHost Product: {Application.ProductName} {(Environment.Is64BitProcess ? "x64" : "x86")}",
238-
$"\tHost Version: {Application.ProductVersion}",
239-
$"\tHost Executable: {Path.GetFileName(Application.ExecutablePath).ToUpper()}", // .ToUpper() used to convert ExceL.EXE -> EXCEL.EXE
236+
$"\tOperating System: {Environment.OSVersion.VersionString} {(Environment.Is64BitOperatingSystem ? "x64" : "x86")}"
240237
};
238+
try
239+
{
240+
headers.AddRange(new []
241+
{
242+
$"\tHost Product: {Application.ProductName} {(Environment.Is64BitProcess ? "x64" : "x86")}",
243+
$"\tHost Version: {Application.ProductVersion}",
244+
$"\tHost Executable: {Path.GetFileName(Application.ExecutablePath).ToUpper()}", // .ToUpper() used to convert ExceL.EXE -> EXCEL.EXE
245+
});
246+
}
247+
catch
248+
{
249+
headers.Add("\tHost could not be determined.");
250+
}
251+
241252
LogLevelHelper.SetDebugInfo(string.Join(Environment.NewLine, headers));
242253
}
243254

Rubberduck.Core/CodeAnalysis/CodeMetrics/CodeMetricsViewModel.cs

Lines changed: 3 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -65,13 +65,9 @@ private void UpdateData()
6565
.GroupBy(declaration => declaration.ProjectId)
6666
.ToList();
6767

68-
if (userDeclarations.Any(
69-
grouping => grouping.All(declaration => declaration.DeclarationType != DeclarationType.Project)))
70-
{
71-
return;
72-
}
73-
74-
var newProjects = userDeclarations.Select(grouping =>
68+
var newProjects = userDeclarations
69+
.Where(grouping => grouping.Any(declaration => declaration.DeclarationType == DeclarationType.Project))
70+
.Select(grouping =>
7571
new CodeExplorerProjectViewModel(_folderHelper,
7672
grouping.SingleOrDefault(declaration => declaration.DeclarationType == DeclarationType.Project),
7773
grouping,

Rubberduck.Core/Navigation/CodeExplorer/CodeExplorerViewModel.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -546,7 +546,7 @@ public double FontSize
546546
public AddTestModuleCommand AddTestModuleCommand { get; set; }
547547
public AddTestModuleWithStubsCommand AddTestModuleWithStubsCommand { get; set; }
548548
public AddTemplateCommand AddTemplateCommand { get; set; }
549-
public CommandBase OpenDesignerCommand { get; set; }
549+
public OpenDesignerCommand OpenDesignerCommand { get; set; }
550550
public CommandBase OpenProjectPropertiesCommand { get; set; }
551551
public SetAsStartupProjectCommand SetAsStartupProjectCommand { get; set; }
552552
public RenameCommand RenameCommand { get; set; }

Rubberduck.Core/UI/Refactorings/EncapsulateField/EncapsulateFieldPresenter.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -38,9 +38,9 @@ public EncapsulateFieldModel Show()
3838
}
3939

4040
_model.PropertyName = _view.ViewModel.PropertyName;
41-
_model.ImplementLetSetterType = _view.ViewModel.CanHaveLet;
42-
_model.ImplementSetSetterType = _view.ViewModel.CanHaveSet;
43-
_model.CanImplementLet = _view.ViewModel.CanHaveSet && !_view.ViewModel.CanHaveSet;
41+
_model.ImplementLetSetterType = _view.ViewModel.IsLetSelected;
42+
_model.ImplementSetSetterType = _view.ViewModel.IsSetSelected;
43+
_model.CanImplementLet = _view.ViewModel.CanHaveLet;
4444

4545
_model.ParameterName = _view.ViewModel.ParameterName;
4646
return _model;

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -549,9 +549,9 @@ upperBound : constantExpression;
549549

550550
constantExpression : expression;
551551

552-
variableStmt : (DIM | STATIC | visibility) whiteSpace (WITHEVENTS whiteSpace)? variableListStmt;
552+
variableStmt : (DIM | STATIC | visibility) whiteSpace variableListStmt;
553553
variableListStmt : variableSubStmt (whiteSpace? COMMA whiteSpace? variableSubStmt)*;
554-
variableSubStmt : identifier (whiteSpace? LPAREN whiteSpace? (subscripts whiteSpace?)? RPAREN)? (whiteSpace asTypeClause)?;
554+
variableSubStmt : (WITHEVENTS whiteSpace)? identifier (whiteSpace? LPAREN whiteSpace? (subscripts whiteSpace?)? RPAREN)? (whiteSpace asTypeClause)?;
555555

556556
whileWendStmt :
557557
WHILE whiteSpace expression endOfStatement

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 19 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -503,7 +503,10 @@ public bool IsMatch(string declarationName, string potentialMatchName)
503503

504504
private IEnumerable<Declaration> FindEvents(Declaration module)
505505
{
506-
Debug.Assert(module != null);
506+
if (module is null)
507+
{
508+
return Enumerable.Empty<Declaration>();
509+
}
507510

508511
var members = Members(module.QualifiedName.QualifiedModuleName);
509512
return members == null
@@ -541,19 +544,26 @@ public ParameterDeclaration FindParameterFromArgument(VBAParser.ArgumentExpressi
541544
return null;
542545
}
543546

544-
var callStmt = argExpression?.GetAncestor<VBAParser.CallStmtContext>();
545-
var procedureName = callStmt?.GetDescendent<VBAParser.LExpressionContext>()
546-
.GetDescendents<VBAParser.IdentifierContext>()
547-
.LastOrDefault()?.GetText();
548-
if (procedureName == null)
547+
var callStmt = argExpression.GetAncestor<VBAParser.CallStmtContext>();
548+
549+
var identifier = callStmt?
550+
.GetDescendent<VBAParser.LExpressionContext>()
551+
.GetDescendents<VBAParser.IdentifierContext>()
552+
.LastOrDefault();
553+
554+
if (identifier == null)
549555
{
550556
// if we don't know what we're calling, we can't dig any further
551557
return null;
552558
}
553559

554-
var procedure = MatchName(procedureName)
555-
.Where(p => AccessibilityCheck.IsAccessible(enclosingProcedure, p))
556-
.SingleOrDefault(p => !p.DeclarationType.HasFlag(DeclarationType.Property) || p.DeclarationType.HasFlag(DeclarationType.PropertyGet));
560+
var selection = new QualifiedSelection(enclosingProcedure.QualifiedModuleName, identifier.GetSelection());
561+
if (!_referencesBySelection.TryGetValue(selection, out var matches))
562+
{
563+
return null;
564+
}
565+
566+
var procedure = matches.SingleOrDefault()?.Declaration;
557567
if (procedure?.ParentScopeDeclaration is ClassModuleDeclaration)
558568
{
559569
// we can't know that the member is on the class' default interface

Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -685,7 +685,7 @@ public override void EnterVariableSubStmt(VBAParser.VariableSubStmtContext conte
685685
? Tokens.Variant
686686
: asTypeClause.type().GetText()
687687
: SymbolList.TypeHintToTypeName[typeHint];
688-
var withEvents = parent.WITHEVENTS() != null;
688+
var withEvents = context.WITHEVENTS() != null;
689689
var isAutoObject = asTypeClause != null && asTypeClause.NEW() != null;
690690
bool isArray = context.LPAREN() != null;
691691
AddDeclaration(

RubberduckTests/Grammar/VBAParserTests.cs

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3517,6 +3517,20 @@ End Type
35173517
AssertTree(parseResult.Item1, parseResult.Item2, "//unrestrictedIdentifier", matches => matches.Count == 1);
35183518
}
35193519

3520+
3521+
[Test]
3522+
[Category("Parser")]
3523+
[TestCase("Private WithEvents foo As EventSource, WithEvents bar As EventSource", 2)]
3524+
[TestCase("Private WithEvents foo As EventSource, bar As EventSource", 2)]
3525+
[TestCase("Private foo As EventSource, WithEvents bar As EventSource", 2)]
3526+
[TestCase("Private foo As EventSource, bar As EventSource", 2)]
3527+
[TestCase("Private WithEvents foo As EventSource", 1)]
3528+
public void WithEventsInVariableList(string code, int count)
3529+
{
3530+
var parseResult = Parse(code);
3531+
AssertTree(parseResult.Item1, parseResult.Item2, "//variableSubStmt", matches => matches.Count == count);
3532+
}
3533+
35203534
private Tuple<VBAParser, ParserRuleContext> Parse(string code, PredictionMode predictionMode = null)
35213535
{
35223536
var stream = new AntlrInputStream(code);

RubberduckTests/Symbols/DeclarationFinderTests.cs

Lines changed: 40 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,8 @@
1010
using Rubberduck.VBEditor;
1111
using Antlr4.Runtime;
1212
using Rubberduck.Common;
13+
using Rubberduck.Parsing;
14+
using Rubberduck.Parsing.Grammar;
1315

1416
namespace RubberduckTests.Symbols
1517
{
@@ -1212,6 +1214,44 @@ Dim sht As WorkSheet
12121214
}
12131215
}
12141216

1217+
[Test]
1218+
[Category("Resolver")]
1219+
public void FindParameterFromArgument_WorksWithMultipleScopes()
1220+
{
1221+
var module1 =
1222+
@"Public Sub Foo(arg As Variant)
1223+
End Sub";
1224+
1225+
var module2 =
1226+
@"Private Sub Foo(expected As Variant)
1227+
End Sub
1228+
1229+
Public Sub Bar()
1230+
Dim fooBar As Variant
1231+
Foo fooBar
1232+
End Sub
1233+
";
1234+
var vbe = new MockVbeBuilder()
1235+
.ProjectBuilder("UnderTest", ProjectProtection.Unprotected)
1236+
.AddComponent("Module1", ComponentType.StandardModule, module1, new Selection(1, 1))
1237+
.AddComponent("Module2", ComponentType.StandardModule, module2, new Selection(1, 1))
1238+
.AddProjectToVbeBuilder()
1239+
.Build();
1240+
1241+
using (var state = MockParser.CreateAndParse(vbe.Object))
1242+
{
1243+
var declarations = state.DeclarationFinder.AllDeclarations.ToList();
1244+
var expected = declarations.FirstOrDefault(decl => decl.IdentifierName.Equals("expected"));
1245+
1246+
var enclosing = declarations.FirstOrDefault(decl => decl.IdentifierName.Equals("Bar"));
1247+
var context = enclosing?.Context.GetDescendent<VBAParser.ArgumentExpressionContext>();
1248+
var actual = state.DeclarationFinder.FindParameterFromArgument(context, enclosing);
1249+
1250+
Assert.AreEqual(expected, actual);
1251+
}
1252+
}
1253+
1254+
12151255
[Category("Resolver")]
12161256
[Category("Interfaces")]
12171257
[Test]
Lines changed: 59 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,59 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using System.Runtime.ExceptionServices;
4+
using System.Threading;
5+
using NUnit.Framework;
6+
using Rubberduck.Parsing.Symbols;
7+
using Rubberduck.VBEditor;
8+
using Rubberduck.VBEditor.SafeComWrappers;
9+
using RubberduckTests.Mocks;
10+
11+
namespace RubberduckTests.Symbols
12+
{
13+
[TestFixture]
14+
public class VariableDeclarationTests
15+
{
16+
[Test]
17+
[TestCase("Private WithEvents foo As EventSource", true)]
18+
[TestCase("Private foo As EventSource", false)]
19+
[Category("Resolver")]
20+
public void WithEventsIsResolvedCorrectly(string declaration, bool withEvents)
21+
{
22+
var variables = ArrangeAndGetVariableDeclarations(ComponentType.ClassModule, declaration);
23+
var foo = variables.Single();
24+
Assert.AreEqual(withEvents, foo.IsWithEvents);
25+
}
26+
27+
[Test]
28+
[TestCase("Private WithEvents {0} As EventSource, WithEvents {1} As EventSource", "foo", "bar", true, true)]
29+
[TestCase("Private {0} As EventSource, WithEvents {1} As EventSource", "foo", "bar", false, true)]
30+
[TestCase("Private WithEvents {0} As EventSource, {1} As EventSource", "foo", "bar", true, false)]
31+
[TestCase("Private {0} As EventSource, {1} As EventSource", "foo", "bar", false, false)]
32+
[Category("Resolver")]
33+
public void WithEventsIsResolvedCorrectlyVariableList(string template, string first, string second, bool firstEvents, bool secondEvents)
34+
{
35+
var variables = ArrangeAndGetVariableDeclarations(ComponentType.ClassModule, string.Format(template, first, second));
36+
Assert.AreEqual(2, variables.Count);
37+
Assert.AreEqual(firstEvents, variables.Single(variable => variable.IdentifierName.Equals(first)).IsWithEvents);
38+
Assert.AreEqual(secondEvents, variables.Single(variable => variable.IdentifierName.Equals(second)).IsWithEvents);
39+
}
40+
41+
private List<VariableDeclaration> ArrangeAndGetVariableDeclarations(ComponentType moduleType, string code)
42+
{
43+
var vbe = new MockVbeBuilder()
44+
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
45+
.AddComponent("UnderTest", moduleType, code, new Selection(1, 1))
46+
.AddProjectToVbeBuilder()
47+
.Build();
48+
49+
using (var parser = MockParser.Create(vbe.Object))
50+
{
51+
parser.Parse(new CancellationTokenSource());
52+
53+
return parser.State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
54+
.Cast<VariableDeclaration>()
55+
.ToList();
56+
}
57+
}
58+
}
59+
}

0 commit comments

Comments
 (0)