Skip to content

Commit 68a6e9f

Browse files
authored
Merge branch 'next' into next
2 parents 31be1b5 + 03f0f3f commit 68a6e9f

File tree

142 files changed

+3228
-9604
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

142 files changed

+3228
-9604
lines changed

.gitignore

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -115,6 +115,10 @@ csx
115115
# Windows Store app package directory
116116
AppPackages/
117117

118+
# IDE Configuration
119+
.vs/
120+
.vscode/
121+
118122
# Others
119123
sql/
120124
*.Cache

RetailCoder.VBE/Inspections/Concrete/Inspector.cs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -126,14 +126,16 @@ before moving them into the ParseTreeResults after qualifying them
126126
var emptyStringLiteralListener = IsDisabled<EmptyStringLiteralInspection>(settings) ? null : new EmptyStringLiteralInspection.EmptyStringLiteralListener();
127127
var argListWithOneByRefParamListener = IsDisabled<ProcedureCanBeWrittenAsFunctionInspection>(settings) ? null : new ProcedureCanBeWrittenAsFunctionInspection.SingleByRefParamArgListListener();
128128
var invalidAnnotationListener = IsDisabled<MissingAnnotationArgumentInspection>(settings) ? null : new MissingAnnotationArgumentInspection.InvalidAnnotationStatementListener();
129+
var optionBaseZeroListener = IsDisabled<OptionBaseZeroInspection>(settings) ? null : new OptionBaseZeroInspection.OptionBaseStatementListener();
129130

130131
var combinedListener = new CombinedParseTreeListener(new IParseTreeListener[]{
131132
obsoleteCallStatementListener,
132133
obsoleteLetStatementListener,
133134
obsoleteCommentSyntaxListener,
134135
emptyStringLiteralListener,
135136
argListWithOneByRefParamListener,
136-
invalidAnnotationListener
137+
invalidAnnotationListener,
138+
optionBaseZeroListener
137139
});
138140

139141
ParseTreeWalker.Default.Walk(combinedListener, componentTreePair.Value);
@@ -162,6 +164,10 @@ before moving them into the ParseTreeResults after qualifying them
162164
{
163165
result.AddRange(invalidAnnotationListener.Contexts.Select(context => new QualifiedContext<VBAParser.AnnotationContext>(componentTreePair.Key, context)));
164166
}
167+
if (optionBaseZeroListener != null)
168+
{
169+
result.AddRange(optionBaseZeroListener.Contexts.Select(context => new QualifiedContext<VBAParser.OptionBaseStmtContext>(componentTreePair.Key, context)));
170+
}
165171
}
166172
return result;
167173
}
Lines changed: 53 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,53 @@
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;
7+
using Rubberduck.Parsing.Grammar;
8+
using Rubberduck.Parsing.VBA;
9+
10+
namespace Rubberduck.Inspections
11+
{
12+
public sealed class OptionBaseZeroInspection : InspectionBase, IParseTreeInspection<VBAParser.OptionBaseStmtContext>
13+
{
14+
private IEnumerable<QualifiedContext> _parseTreeResults;
15+
16+
public OptionBaseZeroInspection(RubberduckParserState state)
17+
: base(state, CodeInspectionSeverity.Hint)
18+
{
19+
}
20+
21+
public override string Meta { get { return InspectionsUI.OptionBaseZeroInspectionMeta; } }
22+
public override string Description { get { return InspectionsUI.OptionBaseZeroInspectionName; } }
23+
public override CodeInspectionType InspectionType { get { return CodeInspectionType.MaintainabilityAndReadabilityIssues; } }
24+
25+
public IEnumerable<QualifiedContext<VBAParser.OptionBaseStmtContext>> ParseTreeResults { get { return _parseTreeResults.OfType<QualifiedContext<VBAParser.OptionBaseStmtContext>>(); } }
26+
public void SetResults(IEnumerable<QualifiedContext> results) { _parseTreeResults = results; }
27+
28+
public override IEnumerable<InspectionResultBase> GetInspectionResults()
29+
{
30+
if (ParseTreeResults == null)
31+
{
32+
return new InspectionResultBase[] { };
33+
}
34+
35+
return ParseTreeResults.Where(context => !IsIgnoringInspectionResultFor(context.ModuleName.Component, context.Context.Start.Line))
36+
.Select(context => new OptionBaseZeroInspectionResult(this, new QualifiedContext<VBAParser.OptionBaseStmtContext>(context.ModuleName, context.Context)));
37+
}
38+
39+
public class OptionBaseStatementListener : VBAParserBaseListener
40+
{
41+
private readonly IList<VBAParser.OptionBaseStmtContext> _contexts = new List<VBAParser.OptionBaseStmtContext>();
42+
public IEnumerable<VBAParser.OptionBaseStmtContext> Contexts { get { return _contexts; } }
43+
44+
public override void ExitOptionBaseStmt(VBAParser.OptionBaseStmtContext context)
45+
{
46+
if (context.numberLiteral()?.INTEGERLITERAL().Symbol.Text == "0")
47+
{
48+
_contexts.Add(context);
49+
}
50+
}
51+
}
52+
}
53+
}
Lines changed: 35 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,35 @@
1+
using Antlr4.Runtime;
2+
using Rubberduck.Inspections.Abstract;
3+
using Rubberduck.Inspections.Resources;
4+
using Rubberduck.VBEditor;
5+
using System;
6+
using System.Linq;
7+
8+
namespace Rubberduck.Inspections.QuickFixes
9+
{
10+
internal class RemoveOptionBaseStatementQuickFix : QuickFixBase
11+
{
12+
public RemoveOptionBaseStatementQuickFix(ParserRuleContext context, QualifiedSelection selection)
13+
: base(context, selection, InspectionsUI.RemoveOptionBaseStatementQuickFix)
14+
{
15+
}
16+
17+
public override void Fix()
18+
{
19+
var module = Selection.QualifiedName.Component.CodeModule;
20+
var lines = module.GetLines(Selection.Selection).Split(new[] { Environment.NewLine }, StringSplitOptions.None);
21+
22+
var newContent = Selection.Selection.LineCount != 1
23+
? lines[0].Remove(Selection.Selection.StartColumn - 1)
24+
: lines[0].Remove(Selection.Selection.StartColumn - 1, Selection.Selection.EndColumn - Selection.Selection.StartColumn);
25+
26+
if (Selection.Selection.LineCount != 1)
27+
{
28+
newContent += lines.Last().Remove(0, Selection.Selection.EndColumn - 1);
29+
}
30+
31+
module.DeleteLines(Selection.Selection);
32+
module.InsertLines(Selection.Selection.StartLine, newContent);
33+
}
34+
}
35+
}

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: 15 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
<?xml version="1.0" encoding="UTF-8"?>
1+
<?xml version="1.0" encoding="utf-8"?>
22
<root>
33
<!--
44
Microsoft ResX Schema
@@ -59,7 +59,7 @@
5959
: using a System.ComponentModel.TypeConverter
6060
: and then encoded with base64 encoding.
6161
-->
62-
<xsd:schema xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata" id="root">
62+
<xsd:schema id="root" xmlns="" xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata">
6363
<xsd:import namespace="http://www.w3.org/XML/1998/namespace" />
6464
<xsd:element name="root" msdata:IsDataSet="true">
6565
<xsd:complexType>
@@ -650,4 +650,16 @@ If the parameter can be null, ignore this inspection result; passing a null valu
650650
<data name="AssignedByValParameterMakeLocalCopyQuickFix" xml:space="preserve">
651651
<value>Create and use a local copy of the parameter</value>
652652
</data>
653-
</root>
653+
<data name="OptionBaseZeroInspectionMeta" xml:space="preserve">
654+
<value>This is the default setting, it does not need to be specified.</value>
655+
</data>
656+
<data name="OptionBaseZeroInspectionName" xml:space="preserve">
657+
<value>'Option Base 0' is redundant</value>
658+
</data>
659+
<data name="OptionBaseZeroInspectionResultFormat" xml:space="preserve">
660+
<value>Component '{0} uses 'Option Base 0'</value>
661+
</data>
662+
<data name="RemoveOptionBaseStatementQuickFix" xml:space="preserve">
663+
<value>Remove 'Option Base' statement</value>
664+
</data>
665+
</root>
Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,36 @@
1+
using System.Collections.Generic;
2+
using Rubberduck.Common;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Resources;
5+
using Rubberduck.Parsing;
6+
using Rubberduck.Parsing.Grammar;
7+
using Rubberduck.Inspections.QuickFixes;
8+
9+
namespace Rubberduck.Inspections.Results
10+
{
11+
public class OptionBaseZeroInspectionResult : InspectionResultBase
12+
{
13+
private IEnumerable<QuickFixBase> _quickFixes;
14+
15+
public OptionBaseZeroInspectionResult(IInspection inspection, QualifiedContext<VBAParser.OptionBaseStmtContext> qualifiedContext)
16+
: base(inspection, qualifiedContext.ModuleName, qualifiedContext.Context)
17+
{ }
18+
19+
public override IEnumerable<QuickFixBase> QuickFixes
20+
{
21+
get
22+
{
23+
return _quickFixes ?? (_quickFixes = new QuickFixBase[]
24+
{
25+
new RemoveOptionBaseStatementQuickFix(Context, QualifiedSelection),
26+
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
27+
});
28+
}
29+
}
30+
31+
public override string Description
32+
{
33+
get { return string.Format(InspectionsUI.OptionBaseZeroInspectionResultFormat.Captialize(), QualifiedName.ComponentName); }
34+
}
35+
}
36+
}

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -346,6 +346,7 @@
346346
<Compile Include="Inspections\HungarianNotationInspection.cs" />
347347
<Compile Include="Inspections\ImplicitDefaultMemberAssignmentInspection.cs" />
348348
<Compile Include="Inspections\MemberNotOnInterfaceInspection.cs" />
349+
<Compile Include="Inspections\OptionBaseZeroInspection.cs" />
349350
<Compile Include="Inspections\QuickFixes\AddIdentifierToWhiteListQuickFix.cs" />
350351
<Compile Include="Inspections\QuickFixes\ApplicationWorksheetFunctionQuickFix.cs" />
351352
<Compile Include="Inspections\QuickFixes\AssignedByValParameterMakeLocalCopyQuickFix.cs" />
@@ -404,6 +405,8 @@
404405
<Compile Include="Inspections\QuickFixes\SplitMultipleDeclarationsQuickFix.cs" />
405406
<Compile Include="Inspections\QuickFixes\RemoveUnusedDeclarationQuickFix.cs" />
406407
<Compile Include="Inspections\QuickFixes\PassParameterByReferenceQuickFix.cs" />
408+
<Compile Include="Inspections\Results\OptionBaseZeroInspectionResult.cs" />
409+
<Compile Include="Inspections\QuickFixes\RemoveOptionBaseStatementQuickFix.cs" />
407410
<Compile Include="Inspections\UndeclaredVariableInspection.cs" />
408411
<Compile Include="Inspections\Results\UndeclaredVariableInspectionResult.cs" />
409412
<Compile Include="Inspections\QuickFixes\UntypedFunctionUsageQuickFix.cs" />

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 76 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@
1010
using Antlr4.Runtime;
1111
using Rubberduck.Parsing.Grammar;
1212
using Rubberduck.VBEditor.Application;
13+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1314

1415
namespace Rubberduck.Parsing.Symbols
1516
{
@@ -48,6 +49,8 @@ public class DeclarationFinder
4849
private readonly ConcurrentDictionary<QualifiedModuleName, ConcurrentBag<IAnnotation>> _annotations;
4950
private readonly ConcurrentDictionary<Declaration, ConcurrentBag<Declaration>> _parametersByParent;
5051
private readonly ConcurrentDictionary<DeclarationType, ConcurrentBag<Declaration>> _userDeclarationsByType;
52+
private readonly IDictionary<QualifiedSelection, IEnumerable<Declaration>> _declarationsBySelection;
53+
private readonly IDictionary<QualifiedSelection, IEnumerable<IdentifierReference>> _referencesBySelection;
5154

5255
private readonly Lazy<ConcurrentDictionary<Declaration, Declaration[]>> _handlersByWithEventsField;
5356
private readonly Lazy<ConcurrentDictionary<VBAParser.ImplementsStmtContext, Declaration[]>> _membersByImplementsContext;
@@ -58,12 +61,29 @@ public class DeclarationFinder
5861

5962
private readonly object threadLock = new object();
6063

64+
private static QualifiedSelection GetGroupingKey(Declaration declaration)
65+
{
66+
// we want the procedures' whole body, not just their identifier:
67+
return declaration.DeclarationType.HasFlag(DeclarationType.Member)
68+
? new QualifiedSelection(
69+
declaration.QualifiedName.QualifiedModuleName,
70+
declaration.Context.GetSelection())
71+
: declaration.QualifiedSelection;
72+
}
73+
6174
public DeclarationFinder(IReadOnlyList<Declaration> declarations, IEnumerable<IAnnotation> annotations, IReadOnlyList<UnboundMemberDeclaration> unresolvedMemberDeclarations, IHostApplication hostApp = null)
6275
{
6376
_hostApp = hostApp;
6477
_annotations = annotations.GroupBy(node => node.QualifiedSelection.QualifiedName).ToConcurrentDictionary();
6578
_declarations = declarations.GroupBy(item => item.QualifiedName.QualifiedModuleName).ToConcurrentDictionary();
6679
_declarationsByName = declarations.GroupBy(declaration => declaration.IdentifierName.ToLowerInvariant()).ToConcurrentDictionary();
80+
_declarationsBySelection = declarations.Where(declaration => !declaration.IsBuiltIn)
81+
.GroupBy(GetGroupingKey)
82+
.ToDictionary(group => group.Key, group => group.AsEnumerable());
83+
_referencesBySelection = declarations
84+
.SelectMany(declaration => declaration.References)
85+
.GroupBy(reference => new QualifiedSelection(reference.QualifiedModuleName, reference.Selection))
86+
.ToDictionary(group => group.Key, group => group.AsEnumerable());
6787
_parametersByParent = declarations.Where(declaration => declaration.DeclarationType == DeclarationType.Parameter)
6888
.GroupBy(declaration => declaration.ParentDeclaration).ToConcurrentDictionary();
6989
_userDeclarationsByType = declarations.Where(declaration => !declaration.IsBuiltIn).GroupBy(declaration => declaration.DeclarationType).ToConcurrentDictionary();
@@ -148,6 +168,62 @@ public DeclarationFinder(IReadOnlyList<Declaration> declarations, IEnumerable<IA
148168
,true);
149169
}
150170

171+
public Declaration FindSelectedDeclaration(ICodePane activeCodePane)
172+
{
173+
if (activeCodePane == null || activeCodePane.IsWrappingNullReference)
174+
{
175+
return null;
176+
}
177+
178+
var qualifiedSelection = activeCodePane.GetQualifiedSelection();
179+
if (!qualifiedSelection.HasValue || qualifiedSelection.Value.Equals(default(QualifiedSelection)))
180+
{
181+
return null;
182+
}
183+
184+
var selection = qualifiedSelection.Value.Selection;
185+
186+
// statistically we'll be on an IdentifierReference more often than on a Declaration:
187+
var matches = _referencesBySelection
188+
.Where(kvp => kvp.Key.QualifiedName.Equals(qualifiedSelection.Value.QualifiedName)
189+
&& kvp.Key.Selection.ContainsFirstCharacter(qualifiedSelection.Value.Selection))
190+
.SelectMany(kvp => kvp.Value)
191+
.OrderByDescending(reference => reference.Declaration.DeclarationType)
192+
.Select(reference => reference.Declaration)
193+
.Distinct()
194+
.ToArray();
195+
196+
if (!matches.Any())
197+
{
198+
matches = _declarationsBySelection
199+
.Where(kvp => kvp.Key.QualifiedName.Equals(qualifiedSelection.Value.QualifiedName)
200+
&& kvp.Key.Selection.ContainsFirstCharacter(selection))
201+
.SelectMany(kvp => kvp.Value)
202+
.OrderByDescending(declaration => declaration.DeclarationType)
203+
.Distinct()
204+
.ToArray();
205+
}
206+
207+
switch (matches.Length)
208+
{
209+
case 0:
210+
ConcurrentBag<Declaration> modules;
211+
return _declarations.TryGetValue(qualifiedSelection.Value.QualifiedName, out modules)
212+
? modules.SingleOrDefault(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Module))
213+
: null;
214+
215+
case 1:
216+
var match = matches.Single();
217+
return match.DeclarationType == DeclarationType.ModuleOption
218+
? match.ParentScopeDeclaration
219+
: match;
220+
221+
default:
222+
// they're sorted by type, so a local comes before the procedure it's in
223+
return matches.FirstOrDefault();
224+
}
225+
}
226+
151227
public IEnumerable<Declaration> FreshUndeclared
152228
{
153229
get { return _newUndeclared.AllValues(); }

Rubberduck.Parsing/Symbols/DeclarationType.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,9 +16,9 @@ public enum DeclarationType
1616
[DebuggerDisplay("ClassModule")]
1717
ClassModule = 1 << 3 | Module,
1818
[DebuggerDisplay("UserForm")]
19-
UserForm = 1 << 4,
19+
UserForm = 1 << 4 | ClassModule,
2020
[DebuggerDisplay("Document")]
21-
Document = 1 << 5,
21+
Document = 1 << 5 | ClassModule,
2222
[DebuggerDisplay("ModuleOption")]
2323
ModuleOption = 1 << 6,
2424
[DebuggerDisplay("Member")]

0 commit comments

Comments
 (0)