Skip to content

Commit 22c5da1

Browse files
authored
Merge branch 'next' into ReworkParseCoordinatorPart1
2 parents 878164a + 69f200e commit 22c5da1

39 files changed

+949
-190
lines changed

RetailCoder.VBE/Inspections/Abstract/InspectionResultBase.cs

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -87,18 +87,18 @@ public virtual int CompareTo(IInspectionResult other)
8787
return Inspection.CompareTo(other.Inspection);
8888
}
8989

90-
public override string ToString()
91-
{
92-
var module = QualifiedSelection.QualifiedName;
93-
return string.Format(
94-
InspectionsUI.QualifiedSelectionInspection,
95-
Inspection.Severity,
96-
Description,
97-
"(" + module.ProjectDisplayName + ")",
98-
module.ProjectName,
99-
module.ComponentName,
100-
QualifiedSelection.Selection.StartLine);
101-
}
90+
//public override string ToString()
91+
//{
92+
// var module = QualifiedSelection.QualifiedName;
93+
// return string.Format(
94+
// InspectionsUI.QualifiedSelectionInspection,
95+
// Inspection.Severity,
96+
// Description,
97+
// "(" + module.ProjectDisplayName + ")",
98+
// module.ProjectName,
99+
// module.ComponentName,
100+
// QualifiedSelection.Selection.StartLine);
101+
//}
102102

103103
public virtual NavigateCodeEventArgs GetNavigationArgs()
104104
{
Lines changed: 43 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,43 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Resources;
5+
using Rubberduck.Inspections.Results;
6+
using Rubberduck.Parsing.Symbols;
7+
using Rubberduck.Parsing.VBA;
8+
using Rubberduck.VBEditor;
9+
10+
namespace Rubberduck.Inspections
11+
{
12+
public class ApplicationWorksheetFunctionInspection : InspectionBase
13+
{
14+
public ApplicationWorksheetFunctionInspection(RubberduckParserState state)
15+
: base(state, CodeInspectionSeverity.Suggestion)
16+
{ }
17+
18+
public override string Meta { get { return InspectionsUI.ApplicationWorksheetFunctionInspectionMeta; } }
19+
public override string Description { get { return InspectionsUI.ApplicationWorksheetFunctionInspectionName; } }
20+
public override CodeInspectionType InspectionType { get { return CodeInspectionType.CodeQualityIssues; } }
21+
22+
public override IEnumerable<InspectionResultBase> GetInspectionResults()
23+
{
24+
var excel = State.DeclarationFinder.Projects.SingleOrDefault(item => item.IsBuiltIn && item.IdentifierName == "Excel");
25+
if (excel == null) { return Enumerable.Empty<InspectionResultBase>(); }
26+
27+
var members = new HashSet<string>(BuiltInDeclarations.Where(decl => decl.DeclarationType == DeclarationType.Function &&
28+
decl.ParentDeclaration != null &&
29+
decl.ParentDeclaration.ComponentName.Equals("WorksheetFunction"))
30+
.Select(decl => decl.IdentifierName));
31+
32+
var usages = BuiltInDeclarations.Where(decl => decl.References.Any() &&
33+
decl.ProjectName.Equals("Excel") &&
34+
decl.ComponentName.Equals("Application") &&
35+
members.Contains(decl.IdentifierName));
36+
37+
return (from usage in usages
38+
from reference in usage.References.Where(use => !IsIgnoringInspectionResultFor(use, AnnotationName))
39+
let qualifiedSelection = new QualifiedSelection(reference.QualifiedModuleName, reference.Selection)
40+
select new ApplicationWorksheetFunctionInspectionResult(this, qualifiedSelection, usage.IdentifierName));
41+
}
42+
}
43+
}
Lines changed: 12 additions & 54 deletions
Original file line numberDiff line numberDiff line change
@@ -1,26 +1,15 @@
1-
using System;
2-
using System.Collections.Generic;
1+
using System.Collections.Generic;
32
using System.Linq;
4-
using Antlr4.Runtime;
53
using Rubberduck.Inspections.Abstract;
64
using Rubberduck.Inspections.Resources;
75
using Rubberduck.Inspections.Results;
8-
using Rubberduck.Parsing;
9-
using Rubberduck.Parsing.Grammar;
106
using Rubberduck.Parsing.Symbols;
117
using Rubberduck.Parsing.VBA;
12-
using Rubberduck.VBEditor;
138

149
namespace Rubberduck.Inspections
1510
{
1611
public sealed class MemberNotOnInterfaceInspection : InspectionBase
1712
{
18-
private static readonly List<Type> InterestingTypes = new List<Type>
19-
{
20-
typeof(VBAParser.MemberAccessExprContext),
21-
typeof(VBAParser.WithMemberAccessExprContext)
22-
};
23-
2413
public MemberNotOnInterfaceInspection(RubberduckParserState state, CodeInspectionSeverity defaultSeverity = CodeInspectionSeverity.Warning)
2514
: base(state, defaultSeverity)
2615
{
@@ -32,51 +21,20 @@ public MemberNotOnInterfaceInspection(RubberduckParserState state, CodeInspectio
3221

3322
public override IEnumerable<InspectionResultBase> GetInspectionResults()
3423
{
24+
var unresolved = State.DeclarationFinder.UnresolvedMemberDeclarations().Where(decl => !IsIgnoringInspectionResultFor(decl, AnnotationName)).ToList();
25+
3526
var targets = Declarations.Where(decl => decl.AsTypeDeclaration != null &&
36-
decl.ParentDeclaration.DeclarationType != DeclarationType.Project &&
27+
decl.AsTypeDeclaration.IsBuiltIn &&
3728
decl.AsTypeDeclaration.DeclarationType == DeclarationType.ClassModule &&
38-
((ClassModuleDeclaration)decl.AsTypeDeclaration).IsExtensible &&
39-
decl.References.Any(usage => InterestingTypes.Contains(usage.Context.Parent.GetType())))
40-
.ToList();
29+
((ClassModuleDeclaration)decl.AsTypeDeclaration).IsExtensible)
30+
.SelectMany(decl => decl.References).ToList();
4131

42-
//Unfortunately finding implemented members is fairly expensive, so group by the return type.
43-
return (from access in targets.GroupBy(t => t.AsTypeDeclaration)
44-
let typeDeclaration = access.Key
45-
let typeMembers = new HashSet<string>(BuiltInDeclarations.Where(d => d.ParentDeclaration != null && d.ParentDeclaration.Equals(typeDeclaration))
46-
.Select(d => d.IdentifierName)
47-
.Distinct())
48-
from references in access.Select(usage => usage.References.Where(r => InterestingTypes.Contains(r.Context.Parent.GetType())))
49-
from reference in references.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
50-
let identifier = reference.Context.Parent.GetChild(reference.Context.Parent.ChildCount - 1)
51-
where !typeMembers.Contains(identifier.GetText())
52-
let pseudoDeclaration = CreatePseudoDeclaration((ParserRuleContext) identifier, reference)
53-
where !pseudoDeclaration.Annotations.Any()
54-
select new MemberNotOnInterfaceInspectionResult(this, pseudoDeclaration, (ParserRuleContext) identifier, typeDeclaration))
55-
.Cast<InspectionResultBase>().ToList();
56-
}
57-
58-
//Builds a throw-away Declaration for the indentifiers found by the inspection. These aren't (and shouldn't be) created by the parser.
59-
//Used to pass to the InspectionResult to make it selectable.
60-
private static Declaration CreatePseudoDeclaration(ParserRuleContext context, IdentifierReference reference)
61-
{
62-
return new Declaration(
63-
new QualifiedMemberName(reference.QualifiedModuleName, context.GetText()),
64-
null,
65-
null,
66-
string.Empty,
67-
string.Empty,
68-
false,
69-
false,
70-
Accessibility.Implicit,
71-
DeclarationType.Variable,
72-
context,
73-
context.GetSelection(),
74-
false,
75-
null,
76-
true,
77-
null,
78-
null,
79-
true);
32+
return (from access in unresolved
33+
let callingContext = targets.FirstOrDefault(usage => usage.Context.Equals(access.CallingContext))
34+
where callingContext != null
35+
select
36+
new MemberNotOnInterfaceInspectionResult(this, access, callingContext.Declaration.AsTypeDeclaration))
37+
.ToList();
8038
}
8139
}
8240
}
Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,38 @@
1+
using Rubberduck.Inspections.Abstract;
2+
using Rubberduck.Inspections.Resources;
3+
using Rubberduck.VBEditor;
4+
5+
namespace Rubberduck.Inspections.QuickFixes
6+
{
7+
public class ApplicationWorksheetFunctionQuickFix : QuickFixBase
8+
{
9+
private readonly string _memberName;
10+
11+
public ApplicationWorksheetFunctionQuickFix(QualifiedSelection selection, string memberName)
12+
: base(null, selection, InspectionsUI.ApplicationWorksheetFunctionQuickFix)
13+
{
14+
_memberName = memberName;
15+
}
16+
17+
public override bool CanFixInModule { get { return true; } }
18+
public override bool CanFixInProject { get { return true; } }
19+
20+
public override void Fix()
21+
{
22+
var module = Selection.QualifiedName.Component.CodeModule;
23+
24+
var oldContent = module.GetLines(Selection.Selection);
25+
var newCall = string.Format("WorksheetFunction.{0}", _memberName);
26+
var start = Selection.Selection.StartColumn - 1;
27+
//The member being called will always be a single token, so this will always be safe (it will be a single line).
28+
var end = Selection.Selection.EndColumn - 1;
29+
var newContent = oldContent.Substring(0, start) + newCall +
30+
(oldContent.Length > end
31+
? oldContent.Substring(end, oldContent.Length - end)
32+
: string.Empty);
33+
34+
module.DeleteLines(Selection.Selection);
35+
module.InsertLines(Selection.Selection.StartLine, newContent);
36+
}
37+
}
38+
}

RetailCoder.VBE/Inspections/Resources/InspectionsUI.Designer.cs

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

RetailCoder.VBE/Inspections/Resources/InspectionsUI.resx

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -634,4 +634,17 @@ If the parameter can be null, ignore this inspection result; passing a null valu
634634
<data name="HostSpecificExpressionInspectionResultFormat" xml:space="preserve">
635635
<value>Expression '{0}' cannot be validated at compile-time.</value>
636636
</data>
637+
<data name="ApplicationWorksheetFunctionInspectionMeta" xml:space="preserve">
638+
<value>The Excel Application object does not implement the WorksheetFunction interface directly. All calls made to WorksheetFunction members are handled as late bound and errors in the called member will be returned wrapped in a Variant of VbVarType.vbError. This makes errors un-trappable with error handlers and adds a performance penalty in comparison to early bound calls. Consider calling Application.WorksheetFunction explicitly. Note: If this call generated errors in the past, those errors were ignored. If applying the quick fix, proper error handling should be in place.</value>
639+
</data>
640+
<data name="ApplicationWorksheetFunctionInspectionName" xml:space="preserve">
641+
<value>Late bound WorksheetFunction call.</value>
642+
</data>
643+
<data name="ApplicationWorksheetFunctionInspectionResultFormat" xml:space="preserve">
644+
<value>Use of late bound Application.{0} member.</value>
645+
<comment>{0} Member name</comment>
646+
</data>
647+
<data name="ApplicationWorksheetFunctionQuickFix" xml:space="preserve">
648+
<value>Use Application.WorksheetFunction explicitly.</value>
649+
</data>
637650
</root>
Lines changed: 45 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,45 @@
1+
using System.Collections.Generic;
2+
using Rubberduck.Common;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.QuickFixes;
5+
using Rubberduck.Inspections.Resources;
6+
using Rubberduck.VBEditor;
7+
8+
namespace Rubberduck.Inspections.Results
9+
{
10+
public class ApplicationWorksheetFunctionInspectionResult : InspectionResultBase
11+
{
12+
private readonly QualifiedSelection _qualifiedSelection;
13+
private readonly string _memberName;
14+
private IEnumerable<QuickFixBase> _quickFixes;
15+
16+
public ApplicationWorksheetFunctionInspectionResult(IInspection inspection, QualifiedSelection qualifiedSelection, string memberName)
17+
: base(inspection, qualifiedSelection.QualifiedName)
18+
{
19+
_memberName = memberName;
20+
_qualifiedSelection = qualifiedSelection;
21+
}
22+
23+
public override QualifiedSelection QualifiedSelection
24+
{
25+
get { return _qualifiedSelection; }
26+
}
27+
28+
public override IEnumerable<QuickFixBase> QuickFixes
29+
{
30+
get
31+
{
32+
return _quickFixes ?? (_quickFixes = new QuickFixBase[]
33+
{
34+
new IgnoreOnceQuickFix(null, _qualifiedSelection, Inspection.AnnotationName),
35+
new ApplicationWorksheetFunctionQuickFix(_qualifiedSelection, _memberName)
36+
});
37+
}
38+
}
39+
40+
public override string Description
41+
{
42+
get { return string.Format(InspectionsUI.ApplicationWorksheetFunctionInspectionResultFormat, _memberName).Captialize(); }
43+
}
44+
}
45+
}

RetailCoder.VBE/Inspections/Results/MemberNotOnInterfaceInspectionResult.cs

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -9,14 +9,12 @@ namespace Rubberduck.Inspections.Results
99
{
1010
public class MemberNotOnInterfaceInspectionResult : InspectionResultBase
1111
{
12-
private readonly ParserRuleContext _member;
1312
private readonly Declaration _asTypeDeclaration;
1413
private IEnumerable<QuickFixBase> _quickFixes;
1514

16-
public MemberNotOnInterfaceInspectionResult(IInspection inspection, Declaration target, ParserRuleContext member, Declaration asTypeDeclaration)
15+
public MemberNotOnInterfaceInspectionResult(IInspection inspection, Declaration target, Declaration asTypeDeclaration)
1716
: base(inspection, target)
1817
{
19-
_member = member;
2018
_asTypeDeclaration = asTypeDeclaration;
2119
}
2220

@@ -26,14 +24,14 @@ public override IEnumerable<QuickFixBase> QuickFixes
2624
{
2725
return _quickFixes ?? (_quickFixes = new QuickFixBase[]
2826
{
29-
new IgnoreOnceQuickFix(_member, QualifiedSelection, Inspection.AnnotationName)
27+
new IgnoreOnceQuickFix(Target.Context, QualifiedSelection, Inspection.AnnotationName)
3028
});
3129
}
3230
}
3331

3432
public override string Description
3533
{
36-
get { return string.Format(InspectionsUI.MemberNotOnInterfaceInspectionResultFormat, _member.GetText(), _asTypeDeclaration.IdentifierName); }
34+
get { return string.Format(InspectionsUI.MemberNotOnInterfaceInspectionResultFormat, Target.IdentifierName, _asTypeDeclaration.IdentifierName); }
3735
}
3836
}
3937
}

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -365,17 +365,20 @@
365365
<Compile Include="Common\WinAPI\WM.cs" />
366366
<Compile Include="Common\WindowsOperatingSystem.cs" />
367367
<Compile Include="Common\UndocumentedAttribute.cs" />
368+
<Compile Include="Inspections\ApplicationWorksheetFunctionInspection.cs" />
368369
<Compile Include="Inspections\HostSpecificExpressionInspection.cs" />
369370
<Compile Include="Inspections\HungarianNotationInspection.cs" />
370371
<Compile Include="Inspections\ImplicitDefaultMemberAssignmentInspection.cs" />
371372
<Compile Include="Inspections\MemberNotOnInterfaceInspection.cs" />
372373
<Compile Include="Inspections\QuickFixes\AddIdentifierToWhiteListQuickFix.cs" />
374+
<Compile Include="Inspections\QuickFixes\ApplicationWorksheetFunctionQuickFix.cs" />
373375
<Compile Include="Inspections\Resources\InspectionsUI.Designer.cs">
374376
<AutoGen>True</AutoGen>
375377
<DesignTime>True</DesignTime>
376378
<DependentUpon>InspectionsUI.resx</DependentUpon>
377379
</Compile>
378380
<Compile Include="Inspections\Results\AggregateInspectionResult.cs" />
381+
<Compile Include="Inspections\Results\ApplicationWorksheetFunctionInspectionResult.cs" />
379382
<Compile Include="Inspections\Results\HostSpecificExpressionInspectionResult.cs" />
380383
<Compile Include="Inspections\Results\ImplicitDefaultMemberAssignmentInspectionResult.cs" />
381384
<Compile Include="Inspections\QuickFixes\IntroduceLocalVariableQuickFix.cs" />

RetailCoder.VBE/UnitTesting/TestEngine.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -3,11 +3,10 @@
33
using System.Diagnostics;
44
using System.Linq;
55
using Rubberduck.Parsing.Annotations;
6+
using Rubberduck.Parsing.Symbols;
67
using Rubberduck.Parsing.VBA;
78
using Rubberduck.UI.UnitTesting;
8-
using Rubberduck.VBEditor;
99
using Rubberduck.VBEditor.Application;
10-
using Rubberduck.VBEditor.Extensions;
1110
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1211

1312
namespace Rubberduck.UnitTesting
@@ -99,7 +98,7 @@ public void Run(IEnumerable<TestMethod> tests)
9998
}
10099
}
101100

102-
private void Run(IEnumerable<QualifiedMemberName> members)
101+
private void Run(IEnumerable<Declaration> members)
103102
{
104103
if (_hostApplication == null)
105104
{

0 commit comments

Comments
 (0)