Skip to content

Commit 6ff4a91

Browse files
committed
Resolved merge conflict
2 parents 71b4693 + bcce039 commit 6ff4a91

File tree

22 files changed

+1252
-131
lines changed

22 files changed

+1252
-131
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyMethodInspection.cs

Lines changed: 46 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -6,8 +6,11 @@
66
using System.Collections.Generic;
77
using System.Linq;
88
using Rubberduck.Parsing.Symbols;
9-
using Rubberduck.Inspections.Inspections.Extensions;
109
using Rubberduck.Common;
10+
using Rubberduck.Inspections.Inspections.Extensions;
11+
using Rubberduck.Parsing.VBA.DeclarationCaching;
12+
using Rubberduck.Parsing.VBA.Extensions;
13+
using Rubberduck.VBEditor;
1114

1215
namespace Rubberduck.Inspections.Concrete
1316
{
@@ -39,19 +42,48 @@ public EmptyMethodInspection(RubberduckParserState state)
3942

4043
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4144
{
42-
var allInterfaces = new HashSet<ClassModuleDeclaration>(State.DeclarationFinder.FindAllUserInterfaces());
43-
44-
return State.DeclarationFinder.UserDeclarations(DeclarationType.Member)
45-
.Where(member => !allInterfaces.Any(userInterface => userInterface.QualifiedModuleName == member.QualifiedModuleName)
46-
&& !((ModuleBodyElementDeclaration)member).Block.ContainsExecutableStatements())
47-
48-
.Select(result => new DeclarationInspectionResult(this,
49-
string.Format(InspectionResults.EmptyMethodInspection,
50-
Resources.RubberduckUI.ResourceManager
51-
.GetString("DeclarationType_" + result.DeclarationType)
52-
.Capitalize(),
53-
result.IdentifierName),
54-
result));
45+
var finder = State.DeclarationFinder;
46+
47+
var userInterfaces = UserInterfaces(finder);
48+
var emptyMethods = EmptyNonInterfaceMethods(finder, userInterfaces);
49+
50+
return emptyMethods.Select(Result);
51+
}
52+
53+
private static ICollection<QualifiedModuleName> UserInterfaces(DeclarationFinder finder)
54+
{
55+
return finder
56+
.FindAllUserInterfaces()
57+
.Select(decl => decl.QualifiedModuleName)
58+
.ToHashSet();
59+
}
60+
61+
private static IEnumerable<Declaration> EmptyNonInterfaceMethods(DeclarationFinder finder, ICollection<QualifiedModuleName> userInterfaces)
62+
{
63+
return finder
64+
.UserDeclarations(DeclarationType.Member)
65+
.Where(member => !userInterfaces.Contains(member.QualifiedModuleName)
66+
&& member is ModuleBodyElementDeclaration moduleBodyElement
67+
&& !moduleBodyElement.Block.ContainsExecutableStatements());
68+
}
69+
70+
private IInspectionResult Result(Declaration member)
71+
{
72+
return new DeclarationInspectionResult(
73+
this,
74+
ResultDescription(member),
75+
member);
76+
}
77+
78+
private static string ResultDescription(Declaration member)
79+
{
80+
var identifierName = member.IdentifierName;
81+
var declarationType = member.DeclarationType.ToLocalizedString();
82+
83+
return string.Format(
84+
InspectionResults.EmptyMethodInspection,
85+
declarationType,
86+
identifierName);
5587
}
5688
}
5789
}

Rubberduck.CodeAnalysis/Inspections/Concrete/EncapsulatePublicFieldInspection.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -40,8 +40,9 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4040
{
4141
// we're creating a public field for every control on a form, needs to be ignored.
4242
var fields = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
43-
.Where(item => item.Accessibility == Accessibility.Public
44-
&& (item.DeclarationType != DeclarationType.Control))
43+
.Where(item => item.DeclarationType != DeclarationType.Control
44+
&& (item.Accessibility == Accessibility.Public ||
45+
item.Accessibility == Accessibility.Global))
4546
.ToList();
4647

4748
return fields

Rubberduck.CodeAnalysis/Inspections/Concrete/UntypedFunctionUsageInspection.cs

Lines changed: 42 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,8 @@
66
using Rubberduck.Parsing.Inspections.Abstract;
77
using Rubberduck.Resources.Inspections;
88
using Rubberduck.Parsing.VBA;
9-
using Rubberduck.Inspections.Inspections.Extensions;
9+
using Rubberduck.Parsing.Symbols;
10+
using Rubberduck.Parsing.VBA.DeclarationCaching;
1011

1112
namespace Rubberduck.Inspections.Concrete
1213
{
@@ -36,7 +37,7 @@ public sealed class UntypedFunctionUsageInspection : InspectionBase
3637
public UntypedFunctionUsageInspection(RubberduckParserState state)
3738
: base(state) { }
3839

39-
private readonly string[] _tokens = {
40+
private readonly HashSet<string> _tokens = new HashSet<string>{
4041
Tokens.Error,
4142
Tokens.Hex,
4243
Tokens.Oct,
@@ -64,17 +65,46 @@ public UntypedFunctionUsageInspection(RubberduckParserState state)
6465

6566
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6667
{
67-
var declarations = BuiltInDeclarations
68-
.Where(item =>
69-
_tokens.Any(token => item.IdentifierName == token || item.IdentifierName == "_B_var_" + token) &&
70-
item.Scope.StartsWith("VBE7.DLL;"));
68+
var finder = State.DeclarationFinder;
7169

72-
return declarations.SelectMany(declaration => declaration.References
73-
.Where(item => _tokens.Contains(item.IdentifierName))
74-
.Select(item => new IdentifierReferenceInspectionResult(this,
75-
string.Format(InspectionResults.UntypedFunctionUsageInspection, item.Declaration.IdentifierName),
76-
State,
77-
item)));
70+
var declarationsToConsider = BuiltInVariantStringFunctionsWithStringTypedVersion(finder);
71+
72+
return declarationsToConsider
73+
.SelectMany(NonStringHintedReferences)
74+
.Select(Result);
75+
}
76+
77+
private IEnumerable<Declaration> BuiltInVariantStringFunctionsWithStringTypedVersion(DeclarationFinder finder)
78+
{
79+
return finder
80+
.BuiltInDeclarations(DeclarationType.Member)
81+
.Where(item => (_tokens.Contains(item.IdentifierName)
82+
|| item.IdentifierName.StartsWith("_B_var_")
83+
&& _tokens.Contains(item.IdentifierName.Substring("_B_var_".Length)))
84+
&& item.Scope.StartsWith("VBE7.DLL;"));
85+
}
86+
87+
private IEnumerable<IdentifierReference> NonStringHintedReferences(Declaration declaration)
88+
{
89+
return declaration.References
90+
.Where(item => _tokens.Contains(item.IdentifierName));
91+
}
92+
93+
private IInspectionResult Result(IdentifierReference reference)
94+
{
95+
return new IdentifierReferenceInspectionResult(
96+
this,
97+
ResultDescription(reference),
98+
State,
99+
reference);
100+
}
101+
102+
private static string ResultDescription(IdentifierReference reference)
103+
{
104+
var declarationName = reference.Declaration.IdentifierName;
105+
return string.Format(
106+
InspectionResults.UntypedFunctionUsageInspection,
107+
declarationName);
78108
}
79109
}
80110
}

Rubberduck.Core/UI/Notifiers/MemberAttributeRecoveryFailureNotifier.cs

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,9 @@
11
using System;
22
using System.Collections.Generic;
3+
using System.Linq;
34
using Rubberduck.Interaction;
45
using Rubberduck.Parsing.Rewriter;
6+
using Rubberduck.Parsing.Symbols;
57
using Rubberduck.VBEditor;
68

79
namespace Rubberduck.UI.Notifiers
@@ -44,18 +46,19 @@ private static string RewriteFailureReasonMessage(RewriteSessionState sessionSta
4446
}
4547
}
4648

47-
public void NotifyMembersForRecoveryNotFound(IEnumerable<QualifiedMemberName> membersNotFound)
49+
public void NotifyMembersForRecoveryNotFound(IEnumerable<(QualifiedMemberName memberName, DeclarationType memberType)> membersNotFound)
4850
{
4951
var message = MembersNotFoundMessage(membersNotFound);
5052
var caption = Resources.RubberduckUI.MemberAttributeRecoveryFailureCaption;
5153

5254
_messageBox.NotifyWarn(message, caption);
5355
}
5456

55-
private string MembersNotFoundMessage(IEnumerable<QualifiedMemberName> membersNotFound)
57+
private string MembersNotFoundMessage(IEnumerable<(QualifiedMemberName memberName, DeclarationType memberType)> membersNotFound)
5658
{
57-
var missingMemberList = $"{Environment.NewLine}{string.Join(Environment.NewLine, membersNotFound)}";
58-
return string.Format(Resources.RubberduckUI.MemberAttributeRecoveryMembersNotFoundMessage, missingMemberList); ;
59+
var missingMemberTexts = membersNotFound.Select(tpl => $"{tpl.memberName} ({tpl.memberType})");
60+
var missingMemberList = $"{Environment.NewLine}{string.Join(Environment.NewLine, missingMemberTexts)}";
61+
return string.Format(Resources.RubberduckUI.MemberAttributeRecoveryMembersNotFoundMessage, missingMemberList);
5962
}
6063
}
6164
}

Rubberduck.Core/UI/Refactorings/EncapsulateField/EncapsulateFieldView.xaml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -118,7 +118,8 @@
118118
FontFamily="Courier New "
119119
ShowLineNumbers="False"
120120
HorizontalScrollBarVisibility="Auto"
121-
VerticalScrollBarVisibility="Disabled"
121+
VerticalScrollBarVisibility="Auto"
122+
MinHeight="200"
122123
IsReadOnly="True"
123124
Text="{Binding PropertyPreview,Mode=OneWay}"/>
124125
</Expander>

Rubberduck.Main/ComClientLibrary/UnitTesting/AssertClass.cs

Lines changed: 3 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -305,19 +305,12 @@ protected void TestArraySequenceEquity(Array expected, Array actual, string mess
305305

306306
var flattenedExpected = expected.Cast<object>().ToList();
307307
var flattenedActual = actual.Cast<object>().ToList();
308-
if (!flattenedActual.SequenceEqual(flattenedExpected, comparer))
309-
{
310-
if (equals)
311-
{
312-
AssertHandler.OnAssertFailed(message, methodName);
313-
}
314-
AssertHandler.OnAssertSucceeded();
315-
}
316-
317-
if (!equals)
308+
if (equals ^ flattenedActual.SequenceEqual(flattenedExpected, comparer))
318309
{
319310
AssertHandler.OnAssertFailed(message, methodName);
311+
return;
320312
}
313+
321314
AssertHandler.OnAssertSucceeded();
322315
}
323316

Rubberduck.Parsing/Binding/Bindings/MemberAccessDefaultBinding.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ public MemberAccessDefaultBinding(
3434
parent,
3535
expression,
3636
null,
37-
Identifier.GetName(expression.unrestrictedIdentifier()),
37+
expression.unrestrictedIdentifier().GetText(),
3838
statementContext,
3939
unrestrictedNameContext)
4040
{
Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,12 @@
11
using System.Collections.Generic;
2+
using Rubberduck.Parsing.Symbols;
23
using Rubberduck.VBEditor;
34

45
namespace Rubberduck.Parsing.Rewriter
56
{
67
public interface IMemberAttributeRecoveryFailureNotifier
78
{
89
void NotifyRewriteFailed(RewriteSessionState rewriteSessionState);
9-
void NotifyMembersForRecoveryNotFound(IEnumerable<QualifiedMemberName> membersNotFound);
10+
void NotifyMembersForRecoveryNotFound(IEnumerable<(QualifiedMemberName memberName, DeclarationType memberType)> membersNotFound);
1011
}
1112
}

Rubberduck.Parsing/Rewriter/MemberAttributeRecoverer.cs

Lines changed: 19 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
using System;
22
using System.Collections.Generic;
3+
using System.Diagnostics;
34
using System.Linq;
45
using System.Threading;
56
using System.Threading.Tasks;
@@ -19,15 +20,17 @@ public sealed class MemberAttributeRecoverer : IMemberAttributeRecovererWithSett
1920
private IRewritingManager _rewritingManager;
2021
private readonly IMemberAttributeRecoveryFailureNotifier _failureNotifier;
2122

22-
private readonly
23-
IDictionary<QualifiedModuleName, IDictionary<string, HashSet<AttributeNode>>> _attributesToRecover
24-
= new Dictionary<QualifiedModuleName, IDictionary<string, HashSet<AttributeNode>>>();
25-
private readonly HashSet<QualifiedMemberName> _missingMembers = new HashSet<QualifiedMemberName>();
23+
private readonly IDictionary<QualifiedModuleName, IDictionary<(string memberName, DeclarationType memberType), HashSet<AttributeNode>>> _attributesToRecover
24+
= new Dictionary<QualifiedModuleName, IDictionary<(string memberName, DeclarationType memberType), HashSet<AttributeNode>>>();
25+
private readonly HashSet<(QualifiedMemberName memberName, DeclarationType memberType)> _missingMembers = new HashSet<(QualifiedMemberName memberName, DeclarationType memberType)>();
2626

2727
private readonly Logger _logger = LogManager.GetCurrentClassLogger();
2828

29-
public MemberAttributeRecoverer(IDeclarationFinderProvider declarationFinderProvider,
30-
IParseManager parseManager, IAttributesUpdater attributesUpdater, IMemberAttributeRecoveryFailureNotifier failureNotifier)
29+
public MemberAttributeRecoverer(
30+
IDeclarationFinderProvider declarationFinderProvider,
31+
IParseManager parseManager,
32+
IAttributesUpdater attributesUpdater,
33+
IMemberAttributeRecoveryFailureNotifier failureNotifier)
3134
{
3235
_declarationFinderProvider = declarationFinderProvider;
3336
_parseManager = parseManager;
@@ -83,7 +86,7 @@ private void SaveAttributesToRecover(IDictionary<QualifiedModuleName, IEnumerabl
8386
var attributesByMember = declarationsByModule[module]
8487
.Where(decl => decl.Attributes.Any())
8588
.ToDictionary(
86-
decl => decl.IdentifierName,
89+
decl => (decl.IdentifierName, decl.DeclarationType),
8790
decl => (HashSet<AttributeNode>)decl.Attributes);
8891
_attributesToRecover.Add(module, attributesByMember);
8992
}
@@ -154,41 +157,41 @@ private void CancelTheCurrentParse()
154157
_parseManager.OnParseCancellationRequested(this);
155158
}
156159

157-
private void RecoverAttributes(IRewriteSession rewriteSession, QualifiedModuleName module, IDictionary<string, HashSet<AttributeNode>> attributesByMember)
160+
private void RecoverAttributes(IRewriteSession rewriteSession, QualifiedModuleName module, IDictionary<(string memberName, DeclarationType memberType), HashSet<AttributeNode>> attributesByMember)
158161
{
159162
var membersWithAttributesToRecover = attributesByMember.Keys.ToHashSet();
160163
var declarationFinder = _declarationFinderProvider.DeclarationFinder;
161164
var declarationsWithAttributesToRecover = declarationFinder.Members(module)
162-
.Where(decl => membersWithAttributesToRecover.Contains(decl.IdentifierName)
165+
.Where(decl => membersWithAttributesToRecover.Contains((decl.IdentifierName, decl.DeclarationType))
163166
&& decl.ParentScopeDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
164167
.ToList();
165168

166169
if (membersWithAttributesToRecover.Count != declarationsWithAttributesToRecover.Count)
167170
{
168171
var membersWithoutDeclarations = MembersWithoutDeclarations(membersWithAttributesToRecover, declarationsWithAttributesToRecover);
169172
LogFailureToRecoverAllAttributes(module, membersWithoutDeclarations);
170-
_missingMembers.UnionWith(membersWithoutDeclarations.Select(memberName => new QualifiedMemberName(module, memberName)));
173+
_missingMembers.UnionWith(membersWithoutDeclarations.Select(tpl => (new QualifiedMemberName(module, tpl.memberName), tpl.memberType)));
171174
}
172175

173176
foreach (var declaration in declarationsWithAttributesToRecover)
174177
{
175-
RecoverAttributes(rewriteSession, declaration, attributesByMember[declaration.IdentifierName]);
178+
RecoverAttributes(rewriteSession, declaration, attributesByMember[(declaration.IdentifierName, declaration.DeclarationType)]);
176179
}
177180
}
178181

179-
private static ICollection<string> MembersWithoutDeclarations(HashSet<string> membersWithAttributesToRecover, IEnumerable<Declaration> declarationsWithAttributesToRecover)
182+
private static ICollection<(string memberName, DeclarationType memberType)> MembersWithoutDeclarations(HashSet<(string memberName, DeclarationType memberType)> membersWithAttributesToRecover, IEnumerable<Declaration> declarationsWithAttributesToRecover)
180183
{
181184
var membersWithoutDeclarations = membersWithAttributesToRecover.ToHashSet();
182-
membersWithoutDeclarations.ExceptWith(declarationsWithAttributesToRecover.Select(decl => decl.IdentifierName));
185+
membersWithoutDeclarations.ExceptWith(declarationsWithAttributesToRecover.Select(decl => (decl.IdentifierName, decl.DeclarationType)));
183186
return membersWithoutDeclarations;
184187
}
185188

186-
private void LogFailureToRecoverAllAttributes(QualifiedModuleName module, IEnumerable<string> membersWithoutDeclarations)
189+
private void LogFailureToRecoverAllAttributes(QualifiedModuleName module, IEnumerable<(string memberName, DeclarationType memberType)> membersWithoutDeclarations)
187190
{
188191
_logger.Warn("Could not recover the attributes for all members because one or more members could no longer be found.");
189-
foreach (var member in membersWithoutDeclarations)
192+
foreach (var (memberName, memberType) in membersWithoutDeclarations)
190193
{
191-
_logger.Trace($"Could not recover the attributes for member {member} in module {module} because a member of that name exists no longer.");
194+
_logger.Trace($"Could not recover the attributes for member {memberName} of type {memberType} in module {module} because a member of that name and type exists no longer.");
192195
}
193196
}
194197

Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -829,7 +829,7 @@ public override void ExitEnumerationStmt(VBAParser.EnumerationStmtContext contex
829829
public override void EnterEnumerationStmt_Constant(VBAParser.EnumerationStmt_ConstantContext context)
830830
{
831831
AddDeclaration(CreateDeclaration(
832-
context.identifier().GetText(),
832+
WithBracketsRemoved(context.identifier().GetText()),
833833
"Long",
834834
Accessibility.Implicit,
835835
DeclarationType.EnumerationMember,
@@ -840,6 +840,16 @@ public override void EnterEnumerationStmt_Constant(VBAParser.EnumerationStmt_Con
840840
null));
841841
}
842842

843+
private static string WithBracketsRemoved(string enumElementName)
844+
{
845+
if (enumElementName.StartsWith("[") && enumElementName.EndsWith("]"))
846+
{
847+
return enumElementName.Substring(1, enumElementName.Length - 2);
848+
}
849+
850+
return enumElementName;
851+
}
852+
843853
public override void EnterOptionPrivateModuleStmt(VBAParser.OptionPrivateModuleStmtContext context)
844854
{
845855
((ProceduralModuleDeclaration)_moduleDeclaration).IsPrivateModule = true;

0 commit comments

Comments
 (0)