Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 3 additions & 3 deletions RetailCoder.VBE/Inspections/Abstract/InspectionResultBase.cs
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ protected InspectionResultBase(IInspection inspection, QualifiedModuleName quali
/// <summary>
/// Gets the information needed to select the target instruction in the VBE.
/// </summary>
public QualifiedSelection QualifiedSelection
public virtual QualifiedSelection QualifiedSelection
{
get
{
Expand All @@ -85,13 +85,13 @@ public QualifiedSelection QualifiedSelection
/// <summary>
/// Gets all available "quick fixes" for a code inspection result.
/// </summary>
public virtual IEnumerable<QuickFixBase> QuickFixes { get { return new QuickFixBase[] {}; } }
public virtual IEnumerable<QuickFixBase> QuickFixes { get { return Enumerable.Empty<QuickFixBase>(); } }

public bool HasQuickFixes { get { return QuickFixes.Any(); } }

public virtual QuickFixBase DefaultQuickFix { get { return QuickFixes.FirstOrDefault(); } }

public int CompareTo(IInspectionResult other)
public virtual int CompareTo(IInspectionResult other)
{
return Inspection.CompareTo(other.Inspection);
}
Expand Down
11 changes: 10 additions & 1 deletion RetailCoder.VBE/Inspections/Concrete/Inspector.cs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Settings;
using Rubberduck.UI;
using Rubberduck.Inspections.Results;

namespace Rubberduck.Inspections.Concrete
{
Expand All @@ -22,6 +23,7 @@ public class Inspector : IInspector
{
private readonly IGeneralConfigService _configService;
private readonly List<IInspection> _inspections;
private readonly int AGGREGATION_THRESHOLD = 128;

public Inspector(IGeneralConfigService configService, IEnumerable<IInspection> inspections)
{
Expand Down Expand Up @@ -94,7 +96,14 @@ public async Task<IEnumerable<IInspectionResult>> FindIssuesAsync(RubberduckPars
LogManager.GetCurrentClassLogger().Error(e);
}
state.OnStatusMessageUpdate(RubberduckUI.ResourceManager.GetString("ParserState_" + state.Status, UI.Settings.Settings.Culture)); // should be "Ready"
return allIssues;

var issuesByType = allIssues.GroupBy(issue => issue.GetType())
.ToDictionary(grouping => grouping.Key, grouping => grouping.ToList());
return issuesByType.Where(kv => kv.Value.Count <= AGGREGATION_THRESHOLD)
.SelectMany(kv => kv.Value)
.Union(issuesByType.Where(kv => kv.Value.Count > AGGREGATION_THRESHOLD)
.Select(kv => new AggregateInspectionResult(kv.Value.OrderBy(i => i.QualifiedSelection).ToList())));
//return allIssues;
}

private IReadOnlyList<QualifiedContext> GetParseTreeResults(Configuration config, RubberduckParserState state)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
using System;
using System.Linq;
using Antlr4.Runtime;
using Rubberduck.Inspections.Abstract;
Expand Down Expand Up @@ -25,7 +26,7 @@ public override void Fix()

// DeclareExplicitVariant() overloads return empty string if context is null
Selection selection;
var fix = DeclareExplicitVariant(Context as VBAParser.VariableSubStmtContext, out originalInstruction, out selection);
var fix = DeclareExplicitVariant(Context as VBAParser.VariableSubStmtContext, contextLines, out originalInstruction, out selection);
if (!string.IsNullOrEmpty(fix))
{
// maintain original indentation for a variable declaration
Expand All @@ -34,7 +35,7 @@ public override void Fix()

if (string.IsNullOrEmpty(originalInstruction))
{
fix = DeclareExplicitVariant(Context as VBAParser.ConstSubStmtContext, out originalInstruction, out selection);
fix = DeclareExplicitVariant(Context as VBAParser.ConstSubStmtContext, contextLines, out originalInstruction, out selection);
}

if (string.IsNullOrEmpty(originalInstruction))
Expand Down Expand Up @@ -100,7 +101,7 @@ private string DeclareExplicitVariant(VBAParser.ArgContext context, out string i
return fix;
}

private string DeclareExplicitVariant(VBAParser.VariableSubStmtContext context, out string instruction, out Selection selection)
private string DeclareExplicitVariant(VBAParser.VariableSubStmtContext context, string contextLines, out string instruction, out Selection selection)
{
if (context == null)
{
Expand All @@ -110,17 +111,19 @@ private string DeclareExplicitVariant(VBAParser.VariableSubStmtContext context,
}

var parent = (ParserRuleContext)context.Parent.Parent;
instruction = parent.GetText();
selection = parent.GetSelection();
instruction = contextLines.Substring(selection.StartColumn - 1);

var variable = context.GetText();
var replacement = context.identifier().GetText() + ' ' + Tokens.As + ' ' + Tokens.Variant;

var result = instruction.Replace(variable, replacement);
var insertIndex = instruction.IndexOf(variable, StringComparison.Ordinal);
var result = instruction.Substring(0, insertIndex)
+ replacement + instruction.Substring(insertIndex + variable.Length);
return result;
}

private string DeclareExplicitVariant(VBAParser.ConstSubStmtContext context, out string instruction, out Selection selection)
private string DeclareExplicitVariant(VBAParser.ConstSubStmtContext context, string contextLines, out string instruction, out Selection selection)
{
if (context == null)
{
Expand All @@ -130,16 +133,18 @@ private string DeclareExplicitVariant(VBAParser.ConstSubStmtContext context, out
}

var parent = (ParserRuleContext)context.Parent;
instruction = parent.GetText();
selection = parent.GetSelection();
selection = parent.GetSelection();
instruction = contextLines.Substring(selection.StartColumn - 1);

var constant = context.GetText();
var replacement = context.identifier().GetText() + ' '
+ Tokens.As + ' ' + Tokens.Variant + ' '
+ context.EQ().GetText() + ' '
+ context.expression().GetText();

var result = instruction.Replace(constant, replacement);
var insertIndex = instruction.IndexOf(constant, StringComparison.Ordinal);
var result = instruction.Substring(0, insertIndex)
+ replacement + instruction.Substring(insertIndex + constant.Length);
return result;
}
}
Expand Down

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

9 changes: 6 additions & 3 deletions RetailCoder.VBE/Inspections/Resources/InspectionsUI.de.resx
Original file line number Diff line number Diff line change
Expand Up @@ -568,7 +568,7 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
<value>Code, der undeklarierte Variablen verwendet, kompiliert nicht wenn 'Option Explicit' spezifiziert wird. Undeklarierte Variablen sind immer vom Typ 'Variant', was unnötige Zusatzkosten in Ausführungszeit und Speicherverbauch verursacht.</value>
</data>
<data name="WriteOnlyPropertyQuickFix" xml:space="preserve">
<value>Add property get</value>
<value>Addieren 'Property Get'</value>
</data>
<data name="ModuleScopeDimKeywordInspectionMeta" xml:space="preserve">
<value>Das Schlüsselwort 'Public' kann nur auf Modulebene verwendet werden; Sein Konterpart 'Private' kann auch nur auf Modulebene verwendet werden. 'Dim' jedoch kann verwendet werden, um sowohl modulweite als auch prozedurweite Variablen zu deklarieren. Um der Konsistenz Willen ist es besser, 'Dim' nur für lokale Variablen zu verwenden, also 'Private' statt 'Dim' auf Modulebene zu verwenden.</value>
Expand All @@ -588,7 +588,10 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
<data name="ModuleScopeDimKeywordInspectionResultFormat" xml:space="preserve">
<value>Die Modulvariable '{0}' ist mit dem 'Dim'-Schlüsselwort deklariert.</value>
</data>
<data name="FunctionReturnValueNotUsedInspectionMeta">
<data name="FunctionReturnValueNotUsedInspectionMeta" xml:space="preserve">
<value>Ein Member ist als Funktion geschrieben, aber wird wie eine Prozedur verwendet. Falls die Funktion nicht rekursiv ist, sollten Sie in Erwägung ziehen, die 'Function' in ein 'Sub' zu konvertieren. Falls die Funktion rekursiv ist, verwendet keiner der externen Aufrufer den Rückgabewert.</value>
</data>
</root>
<data name="AggregateInspectionResultFormat" xml:space="preserve">
<value>{0} ({1} Ergebnisse)</value>
</data>
</root>
3 changes: 3 additions & 0 deletions RetailCoder.VBE/Inspections/Resources/InspectionsUI.fr.resx
Original file line number Diff line number Diff line change
Expand Up @@ -601,4 +601,7 @@ Si le paramètre peut être nul, ignorer ce résultat; passer une valeur nulle
<data name="ImplicitDefaultMemberAssignmentInspectionResultFormat" xml:space="preserve">
<value>Assignation de '{0}' réfère implicitement au membre par défaut de la classe '{1}'</value>
</data>
<data name="AggregateInspectionResultFormat" xml:space="preserve">
<value>{0} ({1} résultats)</value>
</data>
</root>
4 changes: 4 additions & 0 deletions RetailCoder.VBE/Inspections/Resources/InspectionsUI.resx
Original file line number Diff line number Diff line change
Expand Up @@ -602,4 +602,8 @@ If the parameter can be null, ignore this inspection result; passing a null valu
<data name="ImplicitDefaultMemberAssignmentInspectionResultFormat" xml:space="preserve">
<value>Assignment to '{0}' implicitly assigns default member of class '{1}'</value>
</data>
<data name="AggregateInspectionResultFormat" xml:space="preserve">
<value>{0} ({1} results)</value>
<comment>{0} inpection description, {1} result count</comment>
</data>
</root>
71 changes: 71 additions & 0 deletions RetailCoder.VBE/Inspections/Results/AggregateInspectionResult.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,71 @@
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Resources;
using Rubberduck.VBEditor;
using System.Collections.Generic;
using System.Linq;
using Antlr4.Runtime;

namespace Rubberduck.Inspections.Results
{
class AggregateInspectionResult: InspectionResultBase
{
private readonly List<IInspectionResult> _results;
private readonly IInspectionResult _result;

public AggregateInspectionResult(List<IInspectionResult> results)
: base(results[0].Inspection, results[0].QualifiedSelection.QualifiedName, ParserRuleContext.EmptyContext)
{
_results = results;
_result = results[0];
}

public IReadOnlyList<IInspectionResult> IndividualResults { get { return _results; } }

public override string Description
{
get
{
return string.Format(InspectionsUI.AggregateInspectionResultFormat, _result.Inspection.Description, _results.Count);
}
}

public override QualifiedSelection QualifiedSelection
{
get
{
return _result.QualifiedSelection;
}
}

public override IEnumerable<QuickFixBase> QuickFixes
{
get { return _result.QuickFixes == null ? base.QuickFixes : new[] { _result.QuickFixes.FirstOrDefault() }; }
}

public override QuickFixBase DefaultQuickFix { get { return _result.QuickFixes == null ? null : _result.QuickFixes.FirstOrDefault(); } }

public override int CompareTo(IInspectionResult other)
{
if (other == this)
{
return 0;
}
var aggregated = other as AggregateInspectionResult;
if (aggregated == null)
{
return -1;
}
if (_results.Count != aggregated._results.Count) {
return _results.Count - aggregated._results.Count;
}
for (var i = 0; i < _results.Count; i++)
{
if (_results[i].CompareTo(aggregated._results[i]) != 0)
{
return _results[i].CompareTo(aggregated._results[i]);
}
}
return 0;
}
}
}
13 changes: 7 additions & 6 deletions RetailCoder.VBE/Rubberduck.csproj
Original file line number Diff line number Diff line change
Expand Up @@ -366,6 +366,12 @@
<Compile Include="Common\WindowsOperatingSystem.cs" />
<Compile Include="Common\UndocumentedAttribute.cs" />
<Compile Include="Inspections\ImplicitDefaultMemberAssignmentInspection.cs" />
<Compile Include="Inspections\Resources\InspectionsUI.Designer.cs">
<AutoGen>True</AutoGen>
<DesignTime>True</DesignTime>
<DependentUpon>InspectionsUI.resx</DependentUpon>
</Compile>
<Compile Include="Inspections\Results\AggregateInspectionResult.cs" />
<Compile Include="Inspections\Results\ImplicitDefaultMemberAssignmentInspectionResult.cs" />
<Compile Include="Inspections\QuickFixes\IntroduceLocalVariableQuickFix.cs" />
<Compile Include="Inspections\QuickFixes\OptionExplicitQuickFix.cs" />
Expand Down Expand Up @@ -519,11 +525,6 @@
<Compile Include="Inspections\Results\FunctionReturnValueNotUsedInspectionResult.cs" />
<Compile Include="Inspections\Abstract\IInspection.cs" />
<Compile Include="Inspections\Abstract\IInspectionModel.cs" />
<Compile Include="Inspections\Resources\InspectionsUI.Designer.cs">
<AutoGen>True</AutoGen>
<DesignTime>True</DesignTime>
<DependentUpon>InspectionsUI.resx</DependentUpon>
</Compile>
<Compile Include="Inspections\SelfAssignedDeclarationInspection.cs" />
<Compile Include="Inspections\QuickFixes\SelfAssignedDeclarationInspectionResult.cs" />
<Compile Include="Inspections\MoveFieldCloserToUsageInspection.cs" />
Expand Down Expand Up @@ -1038,8 +1039,8 @@
<ItemGroup>
<EmbeddedResource Include="Inspections\Resources\InspectionsUI.resx">
<Generator>PublicResXFileCodeGenerator</Generator>
<LastGenOutput>InspectionsUI.Designer.cs</LastGenOutput>
<SubType>Designer</SubType>
<LastGenOutput>InspectionsUI.Designer.cs</LastGenOutput>
</EmbeddedResource>
<EmbeddedResource Include="Inspections\Resources\InspectionsUI.de.resx">
<Generator>ResXFileCodeGenerator</Generator>
Expand Down
15 changes: 10 additions & 5 deletions RetailCoder.VBE/UI/Inspections/InspectionResultsViewModel.cs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@
using Rubberduck.Common;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Resources;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.VBA;
using Rubberduck.Settings;
using Rubberduck.UI.Command;
Expand Down Expand Up @@ -353,12 +354,16 @@ private void ExecuteQuickFixInModuleCommand(object parameter)
return;
}

var items = _results.Where(result => result.Inspection == SelectedInspection
&& result.QualifiedSelection.QualifiedName == selectedResult.QualifiedSelection.QualifiedName)
.Select(item => item.QuickFixes.Single(fix => fix.GetType() == _defaultFix.GetType()))
.OrderByDescending(item => item.Selection.Selection.EndLine)
.ThenByDescending(item => item.Selection.Selection.EndColumn);
var filteredResults = _results
.Where(result => result.Inspection == SelectedInspection
&& result.QualifiedSelection.QualifiedName == selectedResult.QualifiedSelection.QualifiedName)
.ToList();

var items = filteredResults.Where(result => !(result is AggregateInspectionResult))
.Select(item => item.QuickFixes.Single(fix => fix.GetType() == _defaultFix.GetType()))
.Union(filteredResults.OfType<AggregateInspectionResult>()
.SelectMany(aggregate => aggregate.IndividualResults.Select(result => result.QuickFixes.Single(fix => fix.GetType() == _defaultFix.GetType()))))
.OrderByDescending(fix => fix.Selection);
ExecuteQuickFixes(items);
}

Expand Down
28 changes: 22 additions & 6 deletions Rubberduck.Parsing/VBA/RubberduckParserState.cs
Original file line number Diff line number Diff line change
Expand Up @@ -239,9 +239,12 @@ public void RefreshProjects(IVBE vbe)

private void RemoveProject(string projectId, bool notifyStateChanged = false)
{
if (_projects.ContainsKey(projectId))
lock (_projects)
{
_projects.Remove(projectId);
if (_projects.ContainsKey(projectId))
{
_projects.Remove(projectId);
}
}

ClearStateCache(projectId, notifyStateChanged);
Expand All @@ -251,7 +254,10 @@ public List<IVBProject> Projects
{
get
{
return new List<IVBProject>(_projects.Values);
lock(_projects)
{
return new List<IVBProject>(_projects.Values);
}
}
}

Expand Down Expand Up @@ -303,11 +309,20 @@ public void SetModuleState(IVBComponent component, ParserState state, SyntaxErro
var projectId = component.Collection.Parent.HelpFile;

IVBProject project = null;
foreach (var item in _projects)
lock (_projects)
{
if (item.Value.HelpFile == projectId)
foreach (var item in _projects)
{
project = project != null ? null : item.Value;
if (item.Value.HelpFile == projectId)
{
if (project != null)
{
// ghost component detected, abort project iteration
project = null;
break;
}
project = item.Value;
}
}
}

Expand Down Expand Up @@ -1077,6 +1092,7 @@ public void Dispose()

_moduleStates.Clear();
_declarationSelections.Clear();
// no lock because nobody should try to update anything here
_projects.Clear();

_isDisposed = true;
Expand Down
Loading