Skip to content

Commit fbf04c0

Browse files
authored
Merge pull request #206 from rubberduck-vba/next
sync with main repo
2 parents 459e7f4 + d16a86f commit fbf04c0

16 files changed

+43
-61
lines changed

RetailCoder.VBE/Inspections/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 25 additions & 45 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,10 @@
11
using System.Collections.Generic;
22
using System.Linq;
3+
using System.Security.Policy;
34
using Rubberduck.Common;
45
using Rubberduck.Parsing;
56
using Rubberduck.Parsing.Grammar;
7+
using Rubberduck.Parsing.Symbols;
68
using Rubberduck.Parsing.VBA;
79
using NLog;
810
using Rubberduck.Inspections.Abstract;
@@ -39,52 +41,30 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3941
Logger.Debug("Aborting GetInspectionResults because ParseTree results were not passed");
4042
return new InspectionResultBase[] { };
4143
}
42-
var subStmts = ParseTreeResults.OfType<QualifiedContext<VBAParser.ArgListContext>>()
43-
.Where(context => context.Context.Parent is VBAParser.SubStmtContext)
44-
.Select(context => (VBAParser.SubStmtContext)context.Context.Parent)
45-
.ToList();
4644

47-
var subStmtsNotImplementingInterfaces = subStmts
48-
.Where(c =>
49-
{
50-
var declaration =
51-
UserDeclarations.SingleOrDefault(d => d.Context == c);
52-
53-
if (UserDeclarations.FindInterfaceMembers().Contains(declaration))
54-
{
55-
return false;
56-
}
57-
58-
var interfaceImplementation = UserDeclarations.FindInterfaceImplementationMembers().SingleOrDefault(m => m.Equals(declaration));
59-
if (interfaceImplementation == null)
60-
{
61-
return true;
62-
}
63-
64-
var interfaceMember = UserDeclarations.FindInterfaceMember(interfaceImplementation);
65-
66-
return interfaceMember == null;
67-
});
68-
69-
var subStmtsNotImplementingEvents = subStmts
70-
.Where(c =>
71-
{
72-
var declaration = UserDeclarations.SingleOrDefault(d => d.Context == c);
73-
74-
if (declaration == null) { return false; } // rather be safe than sorry
75-
76-
return UserDeclarations.Where(item => item.IsWithEvents)
77-
.All(withEvents => UserDeclarations.FindEventProcedures(withEvents) == null) &&
78-
!State.AllDeclarations.FindBuiltInEventHandlers().Contains(declaration);
79-
});
80-
81-
return ParseTreeResults
82-
.Where(result => result.Context.Parent is VBAParser.SubStmtContext &&
83-
subStmtsNotImplementingInterfaces.Contains(result.Context.Parent) &&
84-
subStmtsNotImplementingEvents.Contains(result.Context.Parent)
85-
&& !IsIgnoringInspectionResultFor(result.ModuleName.Component, result.Context.Start.Line))
86-
.Select(result => new ProcedureCanBeWrittenAsFunctionInspectionResult(this, State, result,
87-
new QualifiedContext<VBAParser.SubStmtContext>(result.ModuleName, result.Context.Parent as VBAParser.SubStmtContext)));
45+
var userDeclarations = UserDeclarations.ToList();
46+
var allDeclarations = State.AllDeclarations.ToList();
47+
48+
var contextLookup = userDeclarations.Where(decl => decl.Context != null).ToDictionary(decl => decl.Context);
49+
50+
var ignored = new HashSet<Declaration>( State.DeclarationFinder.FindAllInterfaceMembers()
51+
.Concat(State.DeclarationFinder.FindAllInterfaceImplementingMembers())
52+
.Concat(allDeclarations.FindBuiltInEventHandlers())
53+
.Concat(userDeclarations.Where(item => item.IsWithEvents)));
54+
55+
return ParseTreeResults.Where(context => context.Context.Parent is VBAParser.SubStmtContext)
56+
.Select(context => contextLookup[(VBAParser.SubStmtContext)context.Context.Parent])
57+
.Where(decl => !IsIgnoringInspectionResultFor(decl, AnnotationName) &&
58+
!ignored.Contains(decl) &&
59+
userDeclarations.Where(item => item.IsWithEvents)
60+
.All(withEvents => userDeclarations.FindEventProcedures(withEvents) == null) &&
61+
!allDeclarations.FindBuiltInEventHandlers().Contains(decl))
62+
.Select(result => new ProcedureCanBeWrittenAsFunctionInspectionResult(
63+
this,
64+
State,
65+
new QualifiedContext<VBAParser.ArgListContext>(result.QualifiedName,result.Context.GetChild<VBAParser.ArgListContext>(0)),
66+
new QualifiedContext<VBAParser.SubStmtContext>(result.QualifiedName, (VBAParser.SubStmtContext)result.Context))
67+
);
8868
}
8969

9070
public class SingleByRefParamArgListListener : VBAParserBaseListener

Rubberduck.Parsing/ComReflection/ComModule.cs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,11 @@ public ComMember DefaultMember
2424
get { return null; }
2525
}
2626

27+
public bool IsExtensible
28+
{
29+
get { return false; }
30+
}
31+
2732
private readonly List<ComField> _fields = new List<ComField>();
2833
public IEnumerable<ComField> Fields
2934
{

Rubberduck.Parsing/ComReflection/ComType.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,13 +9,14 @@ public interface IComType : IComBase
99
bool IsAppObject { get; }
1010
bool IsPreDeclared { get; }
1111
bool IsHidden { get; }
12-
bool IsRestricted { get; }
12+
bool IsRestricted { get; }
1313
}
1414

1515
public interface IComTypeWithMembers : IComType
1616
{
1717
IEnumerable<ComMember> Members { get; }
1818
ComMember DefaultMember { get; }
19+
bool IsExtensible { get; }
1920
}
2021

2122
public interface IComTypeWithFields : IComType

Rubberduck.Parsing/ComReflection/ReferencedDeclarationsCollector.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -205,7 +205,7 @@ private static Attributes GetModuleAttributes(IComType module)
205205
{
206206
attributes.AddGlobalClassAttribute();
207207
}
208-
if (module as ComInterface != null && ((ComInterface)module).IsExtensible)
208+
if (module as IComTypeWithMembers != null && ((IComTypeWithMembers)module).IsExtensible)
209209
{
210210
attributes.AddExtensibledClassAttribute();
211211
}

RubberduckTests/Inspections/MemberNotOnInterfaceInspectionTests.cs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,6 @@ private static ParseCoordinator ArrangeParser(string inputCode)
3838
[TestCategory("Inspections")]
3939
public void MemberNotOnInterface_ReturnsResult_UnDeclaredMember()
4040
{
41-
Assert.Inconclusive("Pending post-merge fix.");
4241
const string inputCode =
4342
@"Sub Foo()
4443
Dim dict As Dictionary
@@ -63,7 +62,6 @@ Dim dict As Dictionary
6362
[TestCategory("Inspections")]
6463
public void MemberNotOnInterface_ReturnsResult_UnDeclaredInterfaceMember()
6564
{
66-
Assert.Inconclusive("Pending post-merge fix.");
6765
const string inputCode =
6866
@"Sub Foo()
6967
Dim dict As Dictionary
@@ -88,7 +86,6 @@ Dim dict As Dictionary
8886
[TestCategory("Inspections")]
8987
public void MemberNotOnInterface_ReturnsResult_UnDeclaredMemberOnParameter()
9088
{
91-
Assert.Inconclusive("Pending post-merge fix.");
9289
const string inputCode =
9390
@"Sub Foo(dict As Dictionary)
9491
dict.NonMember

RubberduckTests/Inspections/ObjectVariableNotSetInpsectionTests.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -178,7 +178,6 @@ Dim target As Range
178178
[TestCategory("Inspections")]
179179
public void ObjectVariableNotSet_FunctionReturnsArrayOfType_ReturnsNoResult()
180180
{
181-
Assert.Inconclusive("Pending reserialization.");
182181
const string inputCode = @"
183182
Private Function GetSomeDictionaries() As Dictionary()
184183
Dim temp(0 To 1) As Worksheet

RubberduckTests/Testfiles/Resolver/ADODB.6.1.xml

Lines changed: 1 addition & 1 deletion
Large diffs are not rendered by default.

RubberduckTests/Testfiles/Resolver/Excel.1.8.xml

Lines changed: 1 addition & 1 deletion
Large diffs are not rendered by default.

RubberduckTests/Testfiles/Resolver/MSForms.2.0.xml

Lines changed: 1 addition & 1 deletion
Large diffs are not rendered by default.

RubberduckTests/Testfiles/Resolver/MSXML2.6.0.xml

Lines changed: 1 addition & 1 deletion
Large diffs are not rendered by default.

0 commit comments

Comments
 (0)