Skip to content

Commit

Permalink
Browse files Browse the repository at this point in the history
  • Loading branch information
comintern committed Mar 11, 2017
2 parents 7b21550 + 68a6e9f commit 8c454ed
Show file tree
Hide file tree
Showing 142 changed files with 3,228 additions and 9,604 deletions.
4 changes: 4 additions & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -115,6 +115,10 @@ csx
# Windows Store app package directory
AppPackages/

# IDE Configuration
.vs/
.vscode/

# Others
sql/
*.Cache
Expand Down
8 changes: 7 additions & 1 deletion RetailCoder.VBE/Inspections/Concrete/Inspector.cs
Original file line number Diff line number Diff line change
Expand Up @@ -126,14 +126,16 @@ private IReadOnlyList<QualifiedContext> GetParseTreeResults(Configuration config
var emptyStringLiteralListener = IsDisabled<EmptyStringLiteralInspection>(settings) ? null : new EmptyStringLiteralInspection.EmptyStringLiteralListener();
var argListWithOneByRefParamListener = IsDisabled<ProcedureCanBeWrittenAsFunctionInspection>(settings) ? null : new ProcedureCanBeWrittenAsFunctionInspection.SingleByRefParamArgListListener();
var invalidAnnotationListener = IsDisabled<MissingAnnotationArgumentInspection>(settings) ? null : new MissingAnnotationArgumentInspection.InvalidAnnotationStatementListener();
var optionBaseZeroListener = IsDisabled<OptionBaseZeroInspection>(settings) ? null : new OptionBaseZeroInspection.OptionBaseStatementListener();

var combinedListener = new CombinedParseTreeListener(new IParseTreeListener[]{
obsoleteCallStatementListener,
obsoleteLetStatementListener,
obsoleteCommentSyntaxListener,
emptyStringLiteralListener,
argListWithOneByRefParamListener,
invalidAnnotationListener
invalidAnnotationListener,
optionBaseZeroListener
});

ParseTreeWalker.Default.Walk(combinedListener, componentTreePair.Value);
Expand Down Expand Up @@ -162,6 +164,10 @@ private IReadOnlyList<QualifiedContext> GetParseTreeResults(Configuration config
{
result.AddRange(invalidAnnotationListener.Contexts.Select(context => new QualifiedContext<VBAParser.AnnotationContext>(componentTreePair.Key, context)));
}
if (optionBaseZeroListener != null)
{
result.AddRange(optionBaseZeroListener.Contexts.Select(context => new QualifiedContext<VBAParser.OptionBaseStmtContext>(componentTreePair.Key, context)));
}
}
return result;
}
Expand Down
53 changes: 53 additions & 0 deletions RetailCoder.VBE/Inspections/OptionBaseZeroInspection.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,53 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Resources;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.VBA;

namespace Rubberduck.Inspections
{
public sealed class OptionBaseZeroInspection : InspectionBase, IParseTreeInspection<VBAParser.OptionBaseStmtContext>
{
private IEnumerable<QualifiedContext> _parseTreeResults;

public OptionBaseZeroInspection(RubberduckParserState state)
: base(state, CodeInspectionSeverity.Hint)
{
}

public override string Meta { get { return InspectionsUI.OptionBaseZeroInspectionMeta; } }
public override string Description { get { return InspectionsUI.OptionBaseZeroInspectionName; } }
public override CodeInspectionType InspectionType { get { return CodeInspectionType.MaintainabilityAndReadabilityIssues; } }

public IEnumerable<QualifiedContext<VBAParser.OptionBaseStmtContext>> ParseTreeResults { get { return _parseTreeResults.OfType<QualifiedContext<VBAParser.OptionBaseStmtContext>>(); } }
public void SetResults(IEnumerable<QualifiedContext> results) { _parseTreeResults = results; }

public override IEnumerable<InspectionResultBase> GetInspectionResults()
{
if (ParseTreeResults == null)
{
return new InspectionResultBase[] { };
}

return ParseTreeResults.Where(context => !IsIgnoringInspectionResultFor(context.ModuleName.Component, context.Context.Start.Line))
.Select(context => new OptionBaseZeroInspectionResult(this, new QualifiedContext<VBAParser.OptionBaseStmtContext>(context.ModuleName, context.Context)));
}

public class OptionBaseStatementListener : VBAParserBaseListener
{
private readonly IList<VBAParser.OptionBaseStmtContext> _contexts = new List<VBAParser.OptionBaseStmtContext>();
public IEnumerable<VBAParser.OptionBaseStmtContext> Contexts { get { return _contexts; } }

public override void ExitOptionBaseStmt(VBAParser.OptionBaseStmtContext context)
{
if (context.numberLiteral()?.INTEGERLITERAL().Symbol.Text == "0")
{
_contexts.Add(context);
}
}
}
}
}
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
using Antlr4.Runtime;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Resources;
using Rubberduck.VBEditor;
using System;
using System.Linq;

namespace Rubberduck.Inspections.QuickFixes
{
internal class RemoveOptionBaseStatementQuickFix : QuickFixBase
{
public RemoveOptionBaseStatementQuickFix(ParserRuleContext context, QualifiedSelection selection)
: base(context, selection, InspectionsUI.RemoveOptionBaseStatementQuickFix)
{
}

public override void Fix()
{
var module = Selection.QualifiedName.Component.CodeModule;
var lines = module.GetLines(Selection.Selection).Split(new[] { Environment.NewLine }, StringSplitOptions.None);

var newContent = Selection.Selection.LineCount != 1
? lines[0].Remove(Selection.Selection.StartColumn - 1)
: lines[0].Remove(Selection.Selection.StartColumn - 1, Selection.Selection.EndColumn - Selection.Selection.StartColumn);

if (Selection.Selection.LineCount != 1)
{
newContent += lines.Last().Remove(0, Selection.Selection.EndColumn - 1);
}

module.DeleteLines(Selection.Selection);
module.InsertLines(Selection.Selection.StartLine, newContent);
}
}
}
36 changes: 36 additions & 0 deletions RetailCoder.VBE/Inspections/Resources/InspectionsUI.Designer.cs

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

18 changes: 15 additions & 3 deletions RetailCoder.VBE/Inspections/Resources/InspectionsUI.resx
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
<?xml version="1.0" encoding="UTF-8"?>
<?xml version="1.0" encoding="utf-8"?>
<root>
<!--
Microsoft ResX Schema
Expand Down Expand Up @@ -59,7 +59,7 @@
: using a System.ComponentModel.TypeConverter
: and then encoded with base64 encoding.
-->
<xsd:schema xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata" id="root">
<xsd:schema id="root" xmlns="" xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata">
<xsd:import namespace="http://www.w3.org/XML/1998/namespace" />
<xsd:element name="root" msdata:IsDataSet="true">
<xsd:complexType>
Expand Down Expand Up @@ -650,4 +650,16 @@ If the parameter can be null, ignore this inspection result; passing a null valu
<data name="AssignedByValParameterMakeLocalCopyQuickFix" xml:space="preserve">
<value>Create and use a local copy of the parameter</value>
</data>
</root>
<data name="OptionBaseZeroInspectionMeta" xml:space="preserve">
<value>This is the default setting, it does not need to be specified.</value>
</data>
<data name="OptionBaseZeroInspectionName" xml:space="preserve">
<value>'Option Base 0' is redundant</value>
</data>
<data name="OptionBaseZeroInspectionResultFormat" xml:space="preserve">
<value>Component '{0} uses 'Option Base 0'</value>
</data>
<data name="RemoveOptionBaseStatementQuickFix" xml:space="preserve">
<value>Remove 'Option Base' statement</value>
</data>
</root>
Original file line number Diff line number Diff line change
@@ -0,0 +1,36 @@
using System.Collections.Generic;
using Rubberduck.Common;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Resources;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Inspections.QuickFixes;

namespace Rubberduck.Inspections.Results
{
public class OptionBaseZeroInspectionResult : InspectionResultBase
{
private IEnumerable<QuickFixBase> _quickFixes;

public OptionBaseZeroInspectionResult(IInspection inspection, QualifiedContext<VBAParser.OptionBaseStmtContext> qualifiedContext)
: base(inspection, qualifiedContext.ModuleName, qualifiedContext.Context)
{ }

public override IEnumerable<QuickFixBase> QuickFixes
{
get
{
return _quickFixes ?? (_quickFixes = new QuickFixBase[]
{
new RemoveOptionBaseStatementQuickFix(Context, QualifiedSelection),
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
});
}
}

public override string Description
{
get { return string.Format(InspectionsUI.OptionBaseZeroInspectionResultFormat.Captialize(), QualifiedName.ComponentName); }
}
}
}
3 changes: 3 additions & 0 deletions RetailCoder.VBE/Rubberduck.csproj
Original file line number Diff line number Diff line change
Expand Up @@ -346,6 +346,7 @@
<Compile Include="Inspections\HungarianNotationInspection.cs" />
<Compile Include="Inspections\ImplicitDefaultMemberAssignmentInspection.cs" />
<Compile Include="Inspections\MemberNotOnInterfaceInspection.cs" />
<Compile Include="Inspections\OptionBaseZeroInspection.cs" />
<Compile Include="Inspections\QuickFixes\AddIdentifierToWhiteListQuickFix.cs" />
<Compile Include="Inspections\QuickFixes\ApplicationWorksheetFunctionQuickFix.cs" />
<Compile Include="Inspections\QuickFixes\AssignedByValParameterMakeLocalCopyQuickFix.cs" />
Expand Down Expand Up @@ -404,6 +405,8 @@
<Compile Include="Inspections\QuickFixes\SplitMultipleDeclarationsQuickFix.cs" />
<Compile Include="Inspections\QuickFixes\RemoveUnusedDeclarationQuickFix.cs" />
<Compile Include="Inspections\QuickFixes\PassParameterByReferenceQuickFix.cs" />
<Compile Include="Inspections\Results\OptionBaseZeroInspectionResult.cs" />
<Compile Include="Inspections\QuickFixes\RemoveOptionBaseStatementQuickFix.cs" />
<Compile Include="Inspections\UndeclaredVariableInspection.cs" />
<Compile Include="Inspections\Results\UndeclaredVariableInspectionResult.cs" />
<Compile Include="Inspections\QuickFixes\UntypedFunctionUsageQuickFix.cs" />
Expand Down
76 changes: 76 additions & 0 deletions Rubberduck.Parsing/Symbols/DeclarationFinder.cs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@
using Antlr4.Runtime;
using Rubberduck.Parsing.Grammar;
using Rubberduck.VBEditor.Application;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;

namespace Rubberduck.Parsing.Symbols
{
Expand Down Expand Up @@ -48,6 +49,8 @@ public class DeclarationFinder
private readonly ConcurrentDictionary<QualifiedModuleName, ConcurrentBag<IAnnotation>> _annotations;
private readonly ConcurrentDictionary<Declaration, ConcurrentBag<Declaration>> _parametersByParent;
private readonly ConcurrentDictionary<DeclarationType, ConcurrentBag<Declaration>> _userDeclarationsByType;
private readonly IDictionary<QualifiedSelection, IEnumerable<Declaration>> _declarationsBySelection;
private readonly IDictionary<QualifiedSelection, IEnumerable<IdentifierReference>> _referencesBySelection;

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

private readonly object threadLock = new object();

private static QualifiedSelection GetGroupingKey(Declaration declaration)
{
// we want the procedures' whole body, not just their identifier:
return declaration.DeclarationType.HasFlag(DeclarationType.Member)
? new QualifiedSelection(
declaration.QualifiedName.QualifiedModuleName,
declaration.Context.GetSelection())
: declaration.QualifiedSelection;
}

public DeclarationFinder(IReadOnlyList<Declaration> declarations, IEnumerable<IAnnotation> annotations, IReadOnlyList<UnboundMemberDeclaration> unresolvedMemberDeclarations, IHostApplication hostApp = null)
{
_hostApp = hostApp;
_annotations = annotations.GroupBy(node => node.QualifiedSelection.QualifiedName).ToConcurrentDictionary();
_declarations = declarations.GroupBy(item => item.QualifiedName.QualifiedModuleName).ToConcurrentDictionary();
_declarationsByName = declarations.GroupBy(declaration => declaration.IdentifierName.ToLowerInvariant()).ToConcurrentDictionary();
_declarationsBySelection = declarations.Where(declaration => !declaration.IsBuiltIn)
.GroupBy(GetGroupingKey)
.ToDictionary(group => group.Key, group => group.AsEnumerable());
_referencesBySelection = declarations
.SelectMany(declaration => declaration.References)
.GroupBy(reference => new QualifiedSelection(reference.QualifiedModuleName, reference.Selection))
.ToDictionary(group => group.Key, group => group.AsEnumerable());
_parametersByParent = declarations.Where(declaration => declaration.DeclarationType == DeclarationType.Parameter)
.GroupBy(declaration => declaration.ParentDeclaration).ToConcurrentDictionary();
_userDeclarationsByType = declarations.Where(declaration => !declaration.IsBuiltIn).GroupBy(declaration => declaration.DeclarationType).ToConcurrentDictionary();
Expand Down Expand Up @@ -148,6 +168,62 @@ public DeclarationFinder(IReadOnlyList<Declaration> declarations, IEnumerable<IA
,true);
}

public Declaration FindSelectedDeclaration(ICodePane activeCodePane)
{
if (activeCodePane == null || activeCodePane.IsWrappingNullReference)
{
return null;
}

var qualifiedSelection = activeCodePane.GetQualifiedSelection();
if (!qualifiedSelection.HasValue || qualifiedSelection.Value.Equals(default(QualifiedSelection)))
{
return null;
}

var selection = qualifiedSelection.Value.Selection;

// statistically we'll be on an IdentifierReference more often than on a Declaration:
var matches = _referencesBySelection
.Where(kvp => kvp.Key.QualifiedName.Equals(qualifiedSelection.Value.QualifiedName)
&& kvp.Key.Selection.ContainsFirstCharacter(qualifiedSelection.Value.Selection))
.SelectMany(kvp => kvp.Value)
.OrderByDescending(reference => reference.Declaration.DeclarationType)
.Select(reference => reference.Declaration)
.Distinct()
.ToArray();

if (!matches.Any())
{
matches = _declarationsBySelection
.Where(kvp => kvp.Key.QualifiedName.Equals(qualifiedSelection.Value.QualifiedName)
&& kvp.Key.Selection.ContainsFirstCharacter(selection))
.SelectMany(kvp => kvp.Value)
.OrderByDescending(declaration => declaration.DeclarationType)
.Distinct()
.ToArray();
}

switch (matches.Length)
{
case 0:
ConcurrentBag<Declaration> modules;
return _declarations.TryGetValue(qualifiedSelection.Value.QualifiedName, out modules)
? modules.SingleOrDefault(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Module))
: null;

case 1:
var match = matches.Single();
return match.DeclarationType == DeclarationType.ModuleOption
? match.ParentScopeDeclaration
: match;

default:
// they're sorted by type, so a local comes before the procedure it's in
return matches.FirstOrDefault();
}
}

public IEnumerable<Declaration> FreshUndeclared
{
get { return _newUndeclared.AllValues(); }
Expand Down
4 changes: 2 additions & 2 deletions Rubberduck.Parsing/Symbols/DeclarationType.cs
Original file line number Diff line number Diff line change
Expand Up @@ -16,9 +16,9 @@ public enum DeclarationType
[DebuggerDisplay("ClassModule")]
ClassModule = 1 << 3 | Module,
[DebuggerDisplay("UserForm")]
UserForm = 1 << 4,
UserForm = 1 << 4 | ClassModule,
[DebuggerDisplay("Document")]
Document = 1 << 5,
Document = 1 << 5 | ClassModule,
[DebuggerDisplay("ModuleOption")]
ModuleOption = 1 << 6,
[DebuggerDisplay("Member")]
Expand Down

0 comments on commit 8c454ed

Please sign in to comment.