Skip to content

Commit

Permalink
cleaned up
Browse files Browse the repository at this point in the history
  • Loading branch information
retailcoder committed Apr 25, 2021
1 parent 39a2ae1 commit 667f978
Show file tree
Hide file tree
Showing 8 changed files with 147 additions and 88 deletions.
Expand Up @@ -2,6 +2,7 @@
using System.Collections.Generic;
using Rubberduck.AddRemoveReferences;
using Rubberduck.Navigation.CodeExplorer;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.UI.Controls;
using Rubberduck.VBEditor.Events;
Expand Down Expand Up @@ -56,7 +57,7 @@ protected override void OnExecute(object parameter)
{
return;
}
_finder.FindAllReferences(node.Parent.Declaration, model.ToReferenceInfo());
_finder.FindAllReferences((ProjectDeclaration)node.Parent.Declaration, model.ToReferenceInfo());
return;
}

Expand Down
Expand Up @@ -85,8 +85,8 @@ private async void OnSelectionChange(object sender, DeclarationChangedEventArgs
token.ThrowIfCancellationRequested();
var argRefCount = e.Declaration is ParameterDeclaration parameter ? parameter.ArgumentReferences.Count() : 0;
var refCount = e.Declaration?.References.Count() ?? 0 + argRefCount;
var description = e.Declaration?.DescriptionString ?? string.Empty;
var refCount = (e.Declaration?.References.Count() ?? 0) + argRefCount;
var description = e.Declaration?.DescriptionString.Trim() ?? string.Empty;
token.ThrowIfCancellationRequested();
//& renders the next character as if it was an accelerator.
Expand Down
162 changes: 90 additions & 72 deletions Rubberduck.Core/UI/Controls/FindAllReferencesAction.cs
Expand Up @@ -50,75 +50,58 @@ private void _state_StateChanged(object sender, ParserStateEventArgs e)
_uiDispatcher.InvokeAsync(UpdateTab);
}

public void FindAllReferences(Declaration declaration)
public void FindAllReferences(Declaration target)
{
if (_state.Status != ParserState.Ready)
{
_logger.Info($"ParserState is {_state.Status}. This action requires a Ready state.");
return;
}

var viewModel = CreateViewModel(declaration);
if (!viewModel.SearchResults.Any())
var viewModel = CreateViewModel(target);
if (!Confirm(target.IdentifierName, viewModel.SearchResults.Count))
{
_messageBox.NotifyWarn(string.Format(RubberduckUI.AllReferences_NoneFound, declaration.IdentifierName), RubberduckUI.Rubberduck);
return;
}

if (viewModel.SearchResults.Count == 1)
{
_navigateCommand.Execute(viewModel.SearchResults.Single().GetNavigationArgs());
return;
}

_viewModel.AddTab(viewModel);
_viewModel.SelectedTab = viewModel;

try
{
var presenter = _presenterService.Presenter(_viewModel);
presenter.Show();
}
catch (Exception e)
{
_logger.Error(e);
}
ShowResults(viewModel);
}

public void FindAllReferences(Declaration declaration, ReferenceInfo reference)
public void FindAllReferences(ProjectDeclaration project, ReferenceInfo reference)
{
if (_state.Status != ParserState.Ready ||
!(declaration is ProjectDeclaration project))
if (_state.Status != ParserState.Ready)
{
_logger.Info($"ParserState is {_state.Status}. This action requires a Ready state.");
return;
}

var usages = _state.DeclarationFinder.FindAllReferenceUsesInProject(project, reference, out var referenceProject)
.Select(usage =>
new SearchResultItem(usage.ParentNonScoping,
new NavigateCodeEventArgs(usage.QualifiedModuleName, usage.Selection),
GetTrimmedModuleLine(usage.QualifiedModuleName, usage.Selection.StartLine, out var indent),
new Selection(1, usage.Selection.StartColumn - indent, 1, usage.Selection.EndColumn - indent - 1).ToZeroBased()))
.ToList();

if (!usages.Any())
var usages = _state.DeclarationFinder.FindAllReferenceUsesInProject(project, reference, out var referenceProject).ToList();
if (referenceProject == null)
{
_messageBox.NotifyWarn(string.Format(RubberduckUI.AllReferences_NoneFoundReference, referenceProject.IdentifierName), RubberduckUI.Rubberduck);
return;
}

if (usages.Count > 1000 &&
!_messageBox.ConfirmYesNo(string.Format(RubberduckUI.AllReferences_PerformanceWarning, referenceProject.IdentifierName, usages.Count),
RubberduckUI.PerformanceWarningCaption))
if (!Confirm(referenceProject.IdentifierName, usages.Count))
{
return;
}

var viewModel = CreateViewModel(project, referenceProject, usages);
_viewModel.AddTab(viewModel);
_viewModel.SelectedTab = viewModel;
var viewModel = CreateViewModel(project, referenceProject.IdentifierName, usages);
ShowResults(viewModel);
}

private void ShowResults(SearchResultsViewModel viewModel)
{
if (viewModel.SearchResults.Count == 1)
{
viewModel.NavigateCommand.Execute(viewModel.SearchResults[0].GetNavigationArgs());
return;
}

try
{
_viewModel.AddTab(viewModel);
_viewModel.SelectedTab = viewModel;

var presenter = _presenterService.Presenter(_viewModel);
presenter.Show();
}
Expand All @@ -128,55 +111,90 @@ public void FindAllReferences(Declaration declaration, ReferenceInfo reference)
}
}

private string GetTrimmedModuleLine(QualifiedModuleName module, int line, out int indent)
private bool Confirm(string identifier, int referencesFound)
{
var component = _state.ProjectsProvider.Component(module);
using (var codeModule = component.CodeModule)
const int threshold = 1000;
if (referencesFound == 0)
{
var code = codeModule.GetLines(line, 1);
indent = code.TakeWhile(c => c.Equals(' ')).Count();
return code.Trim();
_messageBox.NotifyWarn(
string.Format(RubberduckUI.AllReferences_NoneFoundReference, identifier),
RubberduckUI.Rubberduck);
return false;
}
}

private SearchResultsViewModel CreateViewModel(ProjectDeclaration project, ProjectDeclaration reference, IEnumerable<SearchResultItem> results)
{
var viewModel = new SearchResultsViewModel(_navigateCommand,
string.Format(RubberduckUI.SearchResults_AllReferencesTabFormat, reference.IdentifierName), project, results);
if (referencesFound > threshold)
{
return _messageBox.ConfirmYesNo(
string.Format(RubberduckUI.AllReferences_PerformanceWarning, identifier, referencesFound),
RubberduckUI.PerformanceWarningCaption);
}

return viewModel;
return true;
}

private SearchResultsViewModel CreateViewModel(Declaration declaration)

private SearchResultsViewModel CreateViewModel(Declaration declaration, string identifier = null, IEnumerable<IdentifierReference> references = null)
{
var results = declaration.References
var nameRefs = (references ?? declaration.References)
.Where(reference => !reference.IsArrayAccess)
.Distinct()
.Select(reference =>
new SearchResultItem(
reference.ParentNonScoping,
new NavigateCodeEventArgs(reference.QualifiedModuleName, reference.Selection),
GetTrimmedModuleLine(reference.QualifiedModuleName, reference.Selection.StartLine, out var indent),
new Selection(1, reference.Selection.StartColumn - indent, 1, reference.Selection.EndColumn - indent - 1).ToZeroBased()))
.Concat((declaration is ParameterDeclaration parameter)
? parameter.ArgumentReferences.Select(argument =>
new SearchResultItem(
argument.ParentNonScoping,
new NavigateCodeEventArgs(argument.QualifiedModuleName, argument.Selection),
GetTrimmedModuleLine(argument.QualifiedModuleName, argument.Selection.StartLine, out var indent),
new Selection(1, argument.Selection.StartColumn - indent, 1, argument.Selection.EndColumn - indent - 1).ToZeroBased()))
: Enumerable.Empty<SearchResultItem>());
.GroupBy(reference => reference.QualifiedModuleName)
.ToDictionary(group => group.Key);

var argRefs = (declaration is ParameterDeclaration parameter
? parameter.ArgumentReferences
: Enumerable.Empty<ArgumentReference>())
.Distinct()
.GroupBy(argRef => argRef.QualifiedModuleName)
.ToDictionary(group => group.Key);

var results = new List<SearchResultItem>();
var modules = nameRefs.Keys.Concat(argRefs.Keys).Distinct();
foreach (var qualifiedModuleName in modules)
{
var component = _state.ProjectsProvider.Component(qualifiedModuleName);
var module = component.CodeModule;

if (nameRefs.TryGetValue(qualifiedModuleName, out var identifierReferences))
{
foreach (var identifierReference in identifierReferences)
{
var (context, selection) = identifierReference.HighligthSelection(module);
var result = new SearchResultItem(
identifierReference.ParentNonScoping,
new NavigateCodeEventArgs(qualifiedModuleName, identifierReference.Selection),
context, selection);
results.Add(result);
}
}

if (argRefs.TryGetValue(qualifiedModuleName, out var argReferences))
{
foreach (var argumentReference in argReferences)
{
var (context, selection) = argumentReference.HighligthSelection(module);
var result = new SearchResultItem(
argumentReference.ParentNonScoping,
new NavigateCodeEventArgs(qualifiedModuleName, argumentReference.Selection),
context, selection);
results.Add(result);
}
}
}

var accessor = declaration.DeclarationType.HasFlag(DeclarationType.PropertyGet) ? "(get)"
: declaration.DeclarationType.HasFlag(DeclarationType.PropertyLet) ? "(let)"
: declaration.DeclarationType.HasFlag(DeclarationType.PropertySet) ? "(set)"
: string.Empty;

var tabCaption = $"{declaration.IdentifierName} {accessor}".Trim();
var tabCaption = $"{identifier ?? declaration.IdentifierName} {accessor}".Trim();


var viewModel = new SearchResultsViewModel(_navigateCommand,
string.Format(RubberduckUI.SearchResults_AllReferencesTabFormat, tabCaption), declaration, results);
string.Format(RubberduckUI.SearchResults_AllReferencesTabFormat, tabCaption), declaration,
results.OrderBy(item => item.ParentScope.QualifiedModuleName.ToString())
.ThenBy(item => item.Selection)
.ToList());

return viewModel;
}
Expand Down
29 changes: 20 additions & 9 deletions Rubberduck.Core/UI/Converters/SearchResultToXamlConverter.cs
Expand Up @@ -26,40 +26,51 @@ class SearchResultToXamlConverter : IValueConverter

public object Convert(object value, Type targetType, object parameter, CultureInfo culture)
{
const char nonBreakingSpace = '\u00A0';
if (value is SearchResultItem item)
{
var textBlock = new TextBlock();
textBlock.TextWrapping = TextWrapping.Wrap;

var input = item.ResultText;
string escapedXml = input;// SecurityElement.Escape(input);

var input = item.ResultText.Replace(' ', nonBreakingSpace);
if (item.HighlightIndex.HasValue)
{
var highlight = item.HighlightIndex.Value;
if (highlight.StartColumn > 0)
{
var preRun = new Run(escapedXml.Substring(0, highlight.StartColumn));
var preRun = new Run(input.Substring(0, highlight.StartColumn))
{
Foreground = Brushes.DimGray,
FontFamily = new FontFamily("Consolas")
};
textBlock.Inlines.Add(preRun);
}

var highlightRun = new Run(escapedXml.Substring(highlight.StartColumn, highlight.EndColumn - highlight.StartColumn + 1))
var highlightRun = new Run(input.Substring(highlight.StartColumn,
highlight.EndLine == highlight.StartLine
? highlight.EndColumn - highlight.StartColumn
: highlight.StartColumn + highlight.EndColumn - 1))
{
Background = Brushes.Yellow,
Foreground = Brushes.Black,
FontWeight = FontWeights.SemiBold
Foreground = Brushes.DimGray,
FontWeight = FontWeights.Bold,
FontFamily = new FontFamily("Consolas")
};
textBlock.Inlines.Add(highlightRun);

if (highlight.EndColumn < item.ResultText.Length - 1)
{
var postRun = new Run(escapedXml.Substring(highlight.EndColumn + 1));
var postRun = new Run(input.Substring(highlight.EndColumn))
{
Foreground = Brushes.DimGray,
FontFamily = new FontFamily("Consolas")
};
textBlock.Inlines.Add(postRun);
}
}
else
{
textBlock.Inlines.Add(new Run(escapedXml));
textBlock.Inlines.Add(new Run(input));
}

return textBlock;
Expand Down
16 changes: 15 additions & 1 deletion Rubberduck.Parsing/Symbols/ArgumentReference.cs
@@ -1,9 +1,13 @@
using System.Collections.Generic;
using System;
using System.Collections.Generic;
using System.Linq;
using Antlr4.Runtime;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Binding;
using Rubberduck.Parsing.Grammar;
using Rubberduck.VBEditor;
using Rubberduck.VBEditor.ComManagement;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;

namespace Rubberduck.Parsing.Symbols
{
Expand Down Expand Up @@ -45,5 +49,15 @@ public class ArgumentReference : IdentifierReference
public int NumberOfArguments { get; }
public VBAParser.ArgumentListContext ArgumentListContext { get; }
public Selection ArgumentListSelection { get; }

public override (string context, Selection highlight) HighligthSelection(ICodeModule module)
{
var lines = module.GetLines(Selection.StartLine, Selection.LineCount).Split('\n');

var line = lines[0]; // TODO think of something that makes sense for multiline
var indent = line.TakeWhile((c, i) => c.Equals(' ') && i < Selection.StartColumn).Count();
return (line.Trim(), new Selection(1, Math.Max(Selection.StartColumn - indent - 1, 1), 1, Math.Max(Selection.EndColumn - indent,1)).ToZeroBased());
}

}
}
10 changes: 10 additions & 0 deletions Rubberduck.Parsing/Symbols/IdentifierReference.cs
Expand Up @@ -6,6 +6,7 @@
using System.Linq;
using System.Diagnostics;
using System;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;

namespace Rubberduck.Parsing.Symbols
{
Expand Down Expand Up @@ -132,6 +133,15 @@ public bool IsSelected(QualifiedSelection selection)
Selection.ContainsFirstCharacter(selection.Selection);
}

public virtual (string context, Selection highlight) HighligthSelection(ICodeModule module)
{
var lines = module.GetLines(Selection.StartLine, Selection.LineCount).Split('\n');

var line = lines[0]; // TODO think of something that makes sense for multiline
var indent = line.TakeWhile(c => c.Equals(' ')).Count();
return (line.Trim(), new Selection(1, Math.Max(Selection.StartColumn - indent,1), 1, Math.Max(Selection.EndColumn - indent,1)).ToZeroBased());
}

public bool Equals(IdentifierReference other)
{
return other != null
Expand Down
Expand Up @@ -628,9 +628,8 @@ public ParameterDeclaration FindParameterOfNonDefaultMemberFromSimpleArgumentNot
}

var parameters = Parameters(callingNonDefaultMember);
var hasNamedArgs = argumentExpression?.GetAncestor<VBAParser.ArgListContext>()?.TryGetChildContext<VBAParser.NamedArgumentContext>(out _) ?? false;

ParameterDeclaration parameter;

var namedArg = argumentExpression.GetAncestor<VBAParser.NamedArgumentContext>();
if (namedArg != null)
{
Expand Down Expand Up @@ -1591,6 +1590,11 @@ public bool IsReferenceUsedInProject(ProjectDeclaration project, ReferenceInfo r
}

referenceProject = GetProjectDeclarationForReference(reference);
if (referenceProject == null)
{
Logger.Warn($"Could not get the project declaration for reference '{reference.Name}'.");
return output;
}
if (!_referencesByProjectId.TryGetValue(referenceProject.ProjectId, out var directReferences))
{
return output;
Expand Down
3 changes: 2 additions & 1 deletion Rubberduck.VBEEditor/Selection.cs
Expand Up @@ -82,7 +82,8 @@ public bool Contains(Selection selection)
return false;
}

public bool IsSingleCharacter => StartLine == EndLine && StartColumn == EndColumn;
public bool IsSingleLine => StartLine == EndLine;
public bool IsSingleCharacter => IsSingleLine && StartColumn == EndColumn;

public Selection PreviousLine => StartLine == 1 ? Home : new Selection(StartLine - 1, 1);
public Selection NextLine => new Selection(StartLine + 1, 1);
Expand Down

0 comments on commit 667f978

Please sign in to comment.