Skip to content

Commit 507f48b

Browse files
committed
Move RegexSearchAndReplace awai from FindTarget and make it a bit more sane
This fixes the method to get the surrounding block in SearchInCurrentBlock and generally fixes how searching within a given selection works. Instead of filtering the results for the entire module, the search is performed only inside the selection. This makes a difference on the start and end line. Moreover, this commits adds fixmes for the broken handling of code modules, whose root cause is saving the modules on the results. This should never be done.
1 parent 6158b8a commit 507f48b

File tree

5 files changed

+170
-162
lines changed

5 files changed

+170
-162
lines changed

Rubberduck.Core/Navigation/RegexSearchReplace/RegexSearchReplace.cs

Lines changed: 85 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -2,10 +2,8 @@
22
using System.Collections.Generic;
33
using System.Linq;
44
using System.Text.RegularExpressions;
5-
using Antlr4.Runtime;
6-
using Rubberduck.Common;
75
using Rubberduck.Parsing;
8-
using Rubberduck.Parsing.Symbols;
6+
using Rubberduck.Parsing.Grammar;
97
using Rubberduck.Parsing.VBA;
108
using Rubberduck.VBEditor;
119
using Rubberduck.VBEditor.SafeComWrappers;
@@ -17,14 +15,12 @@ namespace Rubberduck.Navigation.RegexSearchReplace
1715
public class RegexSearchReplace : IRegexSearchReplace
1816
{
1917
private readonly IVBE _vbe;
20-
private readonly IDeclarationFinderProvider _declarationFinderProvider;
2118
private readonly ISelectionService _selectionService;
2219
private readonly ISelectedDeclarationProvider _selectedDeclarationProvider;
2320

24-
public RegexSearchReplace(IVBE vbe, IDeclarationFinderProvider declarationFinderProvider, ISelectionService selectionService, ISelectedDeclarationProvider selectedDeclarationProvider)
21+
public RegexSearchReplace(IVBE vbe, ISelectionService selectionService, ISelectedDeclarationProvider selectedDeclarationProvider)
2522
{
2623
_vbe = vbe;
27-
_declarationFinderProvider = declarationFinderProvider;
2824
_selectionService = selectionService;
2925
_selectedDeclarationProvider = selectedDeclarationProvider;
3026
_search = new Dictionary<RegexSearchReplaceScope, Func<string, IEnumerable<RegexSearchResult>>>
@@ -84,22 +80,80 @@ private IEnumerable<RegexSearchResult> GetResultsFromModule(ICodeModule module,
8480
// VBA uses 1-based indexing
8581
for (var i = 1; i <= module.CountOfLines; i++)
8682
{
87-
var matches =
88-
Regex.Matches(module.GetLines(i, 1), searchPattern)
89-
.OfType<Match>()
83+
var codeLine = module.GetLines(i, 1);
84+
var matches = LineMatches(codeLine, searchPattern)
9085
.Select(m => new RegexSearchResult(m, module, i));
9186

9287
results.AddRange(matches);
9388
}
9489
return results;
9590
}
9691

92+
private IEnumerable<Match> LineMatches(string line, string searchPattern)
93+
{
94+
return Regex.Matches(line, searchPattern)
95+
.OfType<Match>();
96+
}
97+
98+
private IEnumerable<Match> LineMatches(string line, int startColumn, int? endColumn, string searchPattern)
99+
{
100+
var shortenedLine = endColumn.HasValue
101+
? line.Substring(startColumn - 1, endColumn.Value - startColumn + 1)
102+
: line.Substring(startColumn - 1);
103+
return LineMatches(shortenedLine, searchPattern);
104+
}
105+
106+
private IEnumerable<RegexSearchResult> GetResultsFromModule(ICodeModule module, string searchPattern, Selection selection)
107+
{
108+
var startLine = selection.StartLine > 1
109+
? selection.StartLine
110+
: 1;
111+
112+
var moduleLines = module.CountOfLines;
113+
var stopLine = selection.EndLine < moduleLines
114+
? selection.EndLine
115+
: moduleLines;
116+
117+
if (startLine > stopLine)
118+
{
119+
return new List<RegexSearchResult>();
120+
}
121+
122+
if (startLine == stopLine)
123+
{
124+
return LineMatches(module.GetLines(startLine, 1), selection.StartColumn, null, searchPattern)
125+
.Select(m => new RegexSearchResult(m, module, startLine, selection.StartColumn - 1))
126+
.ToList();
127+
}
128+
129+
var results = new List<RegexSearchResult>();
130+
131+
var firstLineMatches = LineMatches(module.GetLines(startLine, 1), selection.StartColumn, selection.EndColumn, searchPattern)
132+
.Select(m => new RegexSearchResult(m, module, startLine));
133+
results.AddRange(firstLineMatches);
134+
135+
for (var lineIndex = startLine + 1; lineIndex < stopLine; lineIndex++)
136+
{
137+
var codeLine = module.GetLines(lineIndex, 1);
138+
var matches = LineMatches(codeLine, searchPattern)
139+
.Select(m => new RegexSearchResult(m, module, lineIndex));
140+
141+
results.AddRange(matches);
142+
}
143+
144+
var lastLineMatches = LineMatches(module.GetLines(stopLine, 1), 1, selection.EndColumn, searchPattern)
145+
.Select(m => new RegexSearchResult(m, module, stopLine));
146+
results.AddRange(lastLineMatches);
147+
148+
return results;
149+
}
150+
97151
private void SetSelection(RegexSearchResult item)
98152
{
99153
_selectionService.TrySetActiveSelection(item.Module.QualifiedModuleName, item.Selection);
100154
}
101155

102-
private List<RegexSearchResult> SearchSelection(string searchPattern)
156+
private IEnumerable<RegexSearchResult> SearchSelection(string searchPattern)
103157
{
104158
using (var pane = _vbe.ActiveCodePane)
105159
{
@@ -110,23 +164,30 @@ private List<RegexSearchResult> SearchSelection(string searchPattern)
110164

111165
using (var module = pane.CodeModule)
112166
{
113-
var results = GetResultsFromModule(module, searchPattern);
114-
return results.Where(r => pane.Selection.Contains(r.Selection)).ToList();
167+
return GetResultsFromModule(module, searchPattern, pane.Selection);
115168
}
116169
}
117170
}
118171

119-
private List<RegexSearchResult> SearchCurrentBlock(string searchPattern)
172+
private IEnumerable<RegexSearchResult> SearchCurrentBlock(string searchPattern)
120173
{
121-
var declarationTypes = new[]
122-
{
123-
DeclarationType.Event,
124-
DeclarationType.Function,
125-
DeclarationType.Procedure,
126-
DeclarationType.PropertyGet,
127-
DeclarationType.PropertyLet,
128-
DeclarationType.PropertySet
129-
};
174+
var activeSelection = _selectionService.ActiveSelection();
175+
if (!activeSelection.HasValue)
176+
{
177+
return new List<RegexSearchResult>();
178+
}
179+
180+
var block = _selectedDeclarationProvider
181+
.SelectedMember(activeSelection.Value)
182+
?.Context
183+
.GetSmallestDescendentContainingSelection<VBAParser.BlockContext>(activeSelection.Value.Selection);
184+
185+
if (block == null)
186+
{
187+
return new List<RegexSearchResult>();
188+
}
189+
190+
var blockSelection = block.GetSelection();
130191

131192
using (var pane = _vbe.ActiveCodePane)
132193
{
@@ -137,24 +198,8 @@ private List<RegexSearchResult> SearchCurrentBlock(string searchPattern)
137198

138199
using (var module = pane.CodeModule)
139200
{
140-
var results = GetResultsFromModule(module, searchPattern);
141-
142-
var qualifiedSelection = pane.GetQualifiedSelection();
143-
144-
if (!qualifiedSelection.HasValue)
145-
{
146-
return new List<RegexSearchResult>();
147-
}
148-
149-
var block = (ParserRuleContext)_declarationFinderProvider.DeclarationFinder
150-
.AllDeclarations
151-
.FindTarget(qualifiedSelection.Value, declarationTypes)
152-
.Context
153-
.Parent;
154-
var selection = new Selection(block.Start.Line, block.Start.Column, block.Stop.Line,
155-
block.Stop.Column);
156-
157-
return results.Where(r => selection.Contains(r.Selection)).ToList();
201+
//FIXME: This is a catastrophe waiting to happen since the module, which will get disposed, is saved on the result.
202+
return GetResultsFromModule(module, searchPattern, blockSelection);
158203
}
159204
}
160205
}

Rubberduck.Core/Navigation/RegexSearchReplace/RegexSearchResult.cs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,15 +7,17 @@ namespace Rubberduck.Navigation.RegexSearchReplace
77
public class RegexSearchResult
88
{
99
public Match Match { get; }
10+
11+
//FIXME: We should not save COM wrappers anywhere.
1012
public ICodeModule Module { get; }
1113
public Selection Selection { get; }
1214
public string DisplayString => Match.Value;
1315

14-
public RegexSearchResult(Match match, ICodeModule module, int line)
16+
public RegexSearchResult(Match match, ICodeModule module, int line, int columnOffset = 0)
1517
{
1618
Match = match;
1719
Module = module;
18-
Selection = new Selection(line, match.Index + 1, line, match.Index + match.Length + 1); // adjust columns for VBE 1-based indexing
20+
Selection = new Selection(line, match.Index + columnOffset + 1, line, match.Index + match.Length + columnOffset + 1); // adjust columns for VBE 1-based indexing
1921
}
2022
}
2123
}

Rubberduck.Parsing/ParserRuleContextExtensions.cs

Lines changed: 57 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -288,14 +288,22 @@ public static bool IsOptionCompareBinary(this ParserRuleContext context)
288288
return (optionContext is null) || !(optionContext.BINARY() is null);
289289
}
290290

291-
/// Returns the context's first descendent of the generic type containing the token with the specified token index.
291+
/// Returns the context's widest descendent of the generic type containing the token with the specified token index.
292292
/// </summary>
293-
public static TContext GetDescendentContainingTokenIndex<TContext>(this ParserRuleContext context, int tokenIndex) where TContext : ParserRuleContext
293+
public static TContext GetWidestDescendentContainingTokenIndex<TContext>(this ParserRuleContext context, int tokenIndex) where TContext : ParserRuleContext
294294
{
295295
var descendents = GetDescendentsContainingTokenIndex<TContext>(context, tokenIndex);
296296
return descendents.FirstOrDefault();
297297
}
298298

299+
/// Returns the context's smallest descendent of the generic type containing the token with the specified token index.
300+
/// </summary>
301+
public static TContext GetSmallestDescendentContainingTokenIndex<TContext>(this ParserRuleContext context, int tokenIndex) where TContext : ParserRuleContext
302+
{
303+
var descendents = GetDescendentsContainingTokenIndex<TContext>(context, tokenIndex);
304+
return descendents.LastOrDefault();
305+
}
306+
299307
/// <summary>
300308
/// Returns all the context's descendents of the generic type containing the token with the specified token index.
301309
/// If there are multiple matches, they are ordered from outermost to innermost context.
@@ -325,6 +333,51 @@ public static IEnumerable<TContext> GetDescendentsContainingTokenIndex<TContext>
325333
return matches;
326334
}
327335

336+
/// Returns the context's widest descendent of the generic type containing the specified selection.
337+
/// </summary>
338+
public static TContext GetWidestDescendentContainingSelection<TContext>(this ParserRuleContext context, Selection selection) where TContext : ParserRuleContext
339+
{
340+
var descendents = GetDescendentsContainingSelection<TContext>(context, selection);
341+
return descendents.FirstOrDefault();
342+
}
343+
344+
/// Returns the context's smallest descendent of the generic type containing the specified selection.
345+
/// </summary>
346+
public static TContext GetSmallestDescendentContainingSelection<TContext>(this ParserRuleContext context, Selection selection) where TContext : ParserRuleContext
347+
{
348+
var descendents = GetDescendentsContainingSelection<TContext>(context, selection);
349+
return descendents.LastOrDefault();
350+
}
351+
352+
/// <summary>
353+
/// Returns all the context's descendents of the generic type containing the specified selection.
354+
/// If there are multiple matches, they are ordered from outermost to innermost context.
355+
/// </summary>
356+
public static IEnumerable<TContext> GetDescendentsContainingSelection<TContext>(this ParserRuleContext context, Selection selection) where TContext : ParserRuleContext
357+
{
358+
if (context == null || !context.GetSelection().Contains(selection))
359+
{
360+
return new List<TContext>();
361+
}
362+
363+
var matches = new List<TContext>();
364+
if (context is TContext match)
365+
{
366+
matches.Add(match);
367+
}
368+
369+
foreach (var child in context.children)
370+
{
371+
if (child is ParserRuleContext childContext && childContext.GetSelection().Contains(selection))
372+
{
373+
matches.AddRange(childContext.GetDescendentsContainingSelection<TContext>(selection));
374+
break; //Only one child can contain the selection.
375+
}
376+
}
377+
378+
return matches;
379+
}
380+
328381
/// <summary>
329382
/// Returns the context containing the token preceding the context provided it is of the specified generic type.
330383
/// </summary>
@@ -344,7 +397,7 @@ public static bool TryGetPrecedingContext<TContext>(this ParserRuleContext conte
344397
return false;
345398
}
346399

347-
precedingContext = ancestorContainingPrecedingIndex.GetDescendentContainingTokenIndex<TContext>(precedingTokenIndex);
400+
precedingContext = ancestorContainingPrecedingIndex.GetWidestDescendentContainingTokenIndex<TContext>(precedingTokenIndex);
348401
return precedingContext != null;
349402
}
350403

@@ -367,7 +420,7 @@ public static bool TryGetFollowingContext<TContext>(this ParserRuleContext conte
367420
return false;
368421
}
369422

370-
followingContext = ancestorContainingFollowingIndex.GetDescendentContainingTokenIndex<TContext>(followingTokenIndex);
423+
followingContext = ancestorContainingFollowingIndex.GetWidestDescendentContainingTokenIndex<TContext>(followingTokenIndex);
371424
return followingContext != null;
372425
}
373426

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,24 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
4+
namespace Rubberduck.Parsing.Symbols
5+
{
6+
public static class DeclarationEnumerableExtensions
7+
{
8+
/// <summary>
9+
/// Gets all declarations of the specified <see cref="DeclarationType"/>.
10+
/// </summary>
11+
public static IEnumerable<Declaration> OfType(this IEnumerable<Declaration> declarations, DeclarationType declarationType)
12+
{
13+
return declarations.Where(declaration => declaration.DeclarationType.HasFlag(declarationType));
14+
}
15+
16+
/// <summary>
17+
/// Gets the declaration for all identifiers declared in or below the specified scope.
18+
/// </summary>
19+
public static IEnumerable<Declaration> InScope(this IEnumerable<Declaration> declarations, Declaration parent)
20+
{
21+
return declarations.Where(declaration => declaration.ParentScope == parent.Scope);
22+
}
23+
}
24+
}

0 commit comments

Comments
 (0)