Skip to content

Commit 5747a05

Browse files
authored
Merge pull request #5249 from MDoerner/FixRefactoringExtensionsForRedimArrays
Remove DeclarationExtensions and improve selected declaration detection
2 parents f59e0fa + 14e20a1 commit 5747a05

File tree

78 files changed

+2048
-1723
lines changed

Some content is hidden

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

78 files changed

+2048
-1723
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ObsoleteGlobalInspection.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
using System.Linq;
33
using Rubberduck.Common;
44
using Rubberduck.Inspections.Abstract;
5+
using Rubberduck.Inspections.Inspections.Extensions;
56
using Rubberduck.Inspections.Results;
67
using Rubberduck.Parsing.Inspections.Abstract;
78
using Rubberduck.Resources.Inspections;

Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs

Lines changed: 3 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
using System.Collections.Generic;
33
using System.Diagnostics;
44
using System.Linq;
5-
using Rubberduck.Common;
65
using Rubberduck.Inspections.Abstract;
76
using Rubberduck.Inspections.Results;
87
using Rubberduck.Parsing;
@@ -12,7 +11,6 @@
1211
using Rubberduck.Parsing.Symbols;
1312
using Rubberduck.Parsing.VBA;
1413
using Rubberduck.Parsing.VBA.Extensions;
15-
using Rubberduck.Inspections.Inspections.Extensions;
1614

1715
namespace Rubberduck.Inspections.Concrete
1816
{
@@ -61,8 +59,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6159
parametersThatCanBeChangedToBePassedByVal.AddRange(InterFaceMembersThatCanBeChangedToBePassedByVal(interfaceDeclarationMembers));
6260

6361
var eventMembers = State.DeclarationFinder.UserDeclarations(DeclarationType.Event).ToList();
64-
var formEventHandlerScopeDeclarations = State.FindFormEventHandlers();
65-
var eventHandlerScopeDeclarations = State.DeclarationFinder.FindEventHandlers().Concat(parameters.FindUserEventHandlers());
62+
var formEventHandlerScopeDeclarations = State.DeclarationFinder.FindFormEventHandlers();
63+
var eventHandlerScopeDeclarations = State.DeclarationFinder.FindEventHandlers();
6664
var eventScopeDeclarations = eventMembers
6765
.Concat(formEventHandlerScopeDeclarations)
6866
.Concat(eventHandlerScopeDeclarations)
@@ -157,11 +155,8 @@ private IEnumerable<ParameterDeclaration> EventMembersThatCanBeChangedToBePassed
157155

158156
var parameterCanBeChangedToBeByVal = eventParameters.Select(parameter => parameter.IsByRef).ToList();
159157

160-
//todo: Find a better way to find the handlers.
161158
var eventHandlers = State.DeclarationFinder
162-
.AllUserDeclarations
163-
.FindHandlersForEvent(memberDeclaration)
164-
.Select(s => s.Item2)
159+
.FindEventHandlers(memberDeclaration)
165160
.ToList();
166161

167162
foreach (var eventHandler in eventHandlers.OfType<IParameterizedDeclaration>())

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 4 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System.Collections.Generic;
22
using System.Linq;
33
using Antlr4.Runtime;
4-
using Rubberduck.Common;
54
using Rubberduck.Inspections.Abstract;
65
using Rubberduck.Inspections.Results;
76
using Rubberduck.Parsing;
@@ -11,7 +10,6 @@
1110
using Rubberduck.Parsing.Symbols;
1211
using Rubberduck.Parsing.VBA;
1312
using Rubberduck.VBEditor;
14-
using Rubberduck.Inspections.Inspections.Extensions;
1513

1614
namespace Rubberduck.Inspections.Concrete
1715
{
@@ -71,21 +69,20 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
7169
return Listener.Contexts
7270
.Where(context => context.Context.Parent is VBAParser.SubStmtContext
7371
&& HasArgumentReferencesWithIsAssignmentFlagged(context))
74-
.Select(context => GetSubStmtParentDeclaration(context))
72+
.Select(GetSubStmtParentDeclaration)
7573
.Where(decl => decl != null &&
7674
!ignored.Contains(decl) &&
7775
userDeclarations.Where(item => item.IsWithEvents)
78-
.All(withEvents => userDeclarations.FindEventProcedures(withEvents) == null) &&
76+
.All(withEvents => !State.DeclarationFinder.FindHandlersForWithEventsField(withEvents).Any()) &&
7977
!builtinHandlers.Contains(decl))
8078
.Select(result => new DeclarationInspectionResult(this,
8179
string.Format(InspectionResults.ProcedureCanBeWrittenAsFunctionInspection, result.IdentifierName),
8280
result));
8381

8482
bool HasArgumentReferencesWithIsAssignmentFlagged(QualifiedContext<ParserRuleContext> context)
8583
{
86-
return contextLookup.TryGetValue(context.Context.GetChild<VBAParser.ArgContext>(), out Declaration decl)
87-
? decl.References.Any(rf => rf.IsAssignment)
88-
: false;
84+
return contextLookup.TryGetValue(context.Context.GetChild<VBAParser.ArgContext>(), out Declaration decl)
85+
&& decl.References.Any(rf => rf.IsAssignment);
8986
}
9087

9188
Declaration GetSubStmtParentDeclaration(QualifiedContext<ParserRuleContext> context)

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureNotUsedInspection.cs

Lines changed: 7 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -2,11 +2,13 @@
22
using System.Linq;
33
using Rubberduck.Common;
44
using Rubberduck.Inspections.Abstract;
5+
using Rubberduck.Inspections.Inspections.Extensions;
56
using Rubberduck.Inspections.Results;
67
using Rubberduck.Parsing.Inspections.Abstract;
78
using Rubberduck.Resources.Inspections;
89
using Rubberduck.Parsing.Symbols;
910
using Rubberduck.Parsing.VBA;
11+
using Rubberduck.Parsing.VBA.Extensions;
1012
using Rubberduck.VBEditor.SafeComWrappers;
1113

1214
namespace Rubberduck.Inspections.Concrete
@@ -58,40 +60,19 @@ public ProcedureNotUsedInspection(RubberduckParserState state) : base(state) { }
5860

5961
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6062
{
61-
var declarations = UserDeclarations.ToList();
62-
6363
var classes = State.DeclarationFinder.UserDeclarations(DeclarationType.ClassModule)
6464
.Concat(State.DeclarationFinder.UserDeclarations(DeclarationType.Document))
6565
.ToList();
6666
var modules = State.DeclarationFinder.UserDeclarations(DeclarationType.ProceduralModule).ToList();
6767

68-
var handlers = State.DeclarationFinder.UserDeclarations(DeclarationType.Control)
69-
.SelectMany(control => declarations.FindEventHandlers(control)).ToList();
68+
var handlers = State.DeclarationFinder.FindEventHandlers().ToHashSet();
7069

71-
var builtInHandlers = State.DeclarationFinder.FindEventHandlers();
72-
handlers.AddRange(builtInHandlers);
70+
var interfaceMembers = State.DeclarationFinder.FindAllInterfaceMembers().ToHashSet();
71+
var implementingMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers().ToHashSet();
7372

74-
var withEventFields = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable).Where(item => item.IsWithEvents).ToList();
75-
var withHanders = withEventFields
76-
.SelectMany(field => State.DeclarationFinder.FindHandlersForWithEventsField(field))
73+
var items = State.AllUserDeclarations
74+
.Where(item => !IsIgnoredDeclaration(item, interfaceMembers, implementingMembers, handlers, classes, modules))
7775
.ToList();
78-
79-
handlers.AddRange(withHanders);
80-
81-
var forms = State.DeclarationFinder.UserDeclarations(DeclarationType.ClassModule)
82-
.Where(item => item.QualifiedName.QualifiedModuleName.ComponentType == ComponentType.UserForm)
83-
.ToList();
84-
85-
if (forms.Any())
86-
{
87-
handlers.AddRange(forms.SelectMany(form => State.FindFormEventHandlers(form)));
88-
}
89-
90-
var interfaceMembers = State.DeclarationFinder.FindAllInterfaceMembers().ToList();
91-
var implementingMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers().ToList();
92-
93-
var items = declarations
94-
.Where(item => !IsIgnoredDeclaration(item, interfaceMembers, implementingMembers, handlers, classes, modules)).ToList();
9576
var issues = items.Select(issue => new DeclarationInspectionResult(this,
9677
string.Format(InspectionResults.IdentifierNotUsedInspection, issue.DeclarationType.ToLocalizedString(), issue.IdentifierName),
9778
issue));
Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,14 @@
1+
using System.Globalization;
2+
using Rubberduck.Parsing.Symbols;
3+
using Rubberduck.Resources;
4+
5+
namespace Rubberduck.Inspections.Inspections.Extensions
6+
{
7+
public static class DeclarationTypeExtensions
8+
{
9+
public static string ToLocalizedString(this DeclarationType type)
10+
{
11+
return RubberduckUI.ResourceManager.GetString("DeclarationType_" + type, CultureInfo.CurrentUICulture);
12+
}
13+
}
14+
}

Rubberduck.CodeAnalysis/QuickFixes/PassParameterByValueQuickFix.cs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
using System.Linq;
2-
using Rubberduck.Common;
32
using Rubberduck.Inspections.Abstract;
43
using Rubberduck.Inspections.Concrete;
54
using Rubberduck.Parsing.Grammar;
@@ -52,12 +51,14 @@ private void FixMethods(Declaration target, IRewriteSession rewriteSession)
5251
return; // should only happen if the parse results are stale; prevents a crash in that case
5352
}
5453

55-
//FIXME: Make this use the DeclarationFinder.
5654
var members = target.ParentDeclaration.DeclarationType == DeclarationType.Event
57-
? _state.AllUserDeclarations.FindHandlersForEvent(target.ParentDeclaration)
58-
.Select(s => s.Item2)
55+
? _state.DeclarationFinder
56+
.FindEventHandlers(target.ParentDeclaration)
5957
.ToList()
60-
: _state.DeclarationFinder.FindInterfaceImplementationMembers(target.ParentDeclaration).Cast<Declaration>().ToList();
58+
: _state.DeclarationFinder
59+
.FindInterfaceImplementationMembers(target.ParentDeclaration)
60+
.Cast<Declaration>()
61+
.ToList();
6162

6263
foreach (var member in members)
6364
{

Rubberduck.Core/Navigation/RegexSearchReplace/RegexSearchReplace.cs

Lines changed: 89 additions & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -2,10 +2,9 @@
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;
7+
using Rubberduck.Parsing.VBA;
98
using Rubberduck.VBEditor;
109
using Rubberduck.VBEditor.SafeComWrappers;
1110
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
@@ -16,14 +15,14 @@ namespace Rubberduck.Navigation.RegexSearchReplace
1615
public class RegexSearchReplace : IRegexSearchReplace
1716
{
1817
private readonly IVBE _vbe;
19-
private readonly IParseCoordinator _parser;
2018
private readonly ISelectionService _selectionService;
19+
private readonly ISelectedDeclarationProvider _selectedDeclarationProvider;
2120

22-
public RegexSearchReplace(IVBE vbe, IParseCoordinator parser, ISelectionService selectionService)
21+
public RegexSearchReplace(IVBE vbe, ISelectionService selectionService, ISelectedDeclarationProvider selectedDeclarationProvider)
2322
{
2423
_vbe = vbe;
25-
_parser = parser;
2624
_selectionService = selectionService;
25+
_selectedDeclarationProvider = selectedDeclarationProvider;
2726
_search = new Dictionary<RegexSearchReplaceScope, Func<string, IEnumerable<RegexSearchResult>>>
2827
{
2928
{ RegexSearchReplaceScope.Selection, SearchSelection},
@@ -81,22 +80,80 @@ private IEnumerable<RegexSearchResult> GetResultsFromModule(ICodeModule module,
8180
// VBA uses 1-based indexing
8281
for (var i = 1; i <= module.CountOfLines; i++)
8382
{
84-
var matches =
85-
Regex.Matches(module.GetLines(i, 1), searchPattern)
86-
.OfType<Match>()
83+
var codeLine = module.GetLines(i, 1);
84+
var matches = LineMatches(codeLine, searchPattern)
8785
.Select(m => new RegexSearchResult(m, module, i));
8886

8987
results.AddRange(matches);
9088
}
9189
return results;
9290
}
9391

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+
94151
private void SetSelection(RegexSearchResult item)
95152
{
96153
_selectionService.TrySetActiveSelection(item.Module.QualifiedModuleName, item.Selection);
97154
}
98155

99-
private List<RegexSearchResult> SearchSelection(string searchPattern)
156+
private IEnumerable<RegexSearchResult> SearchSelection(string searchPattern)
100157
{
101158
using (var pane = _vbe.ActiveCodePane)
102159
{
@@ -107,25 +164,31 @@ private List<RegexSearchResult> SearchSelection(string searchPattern)
107164

108165
using (var module = pane.CodeModule)
109166
{
110-
var results = GetResultsFromModule(module, searchPattern);
111-
return results.Where(r => pane.Selection.Contains(r.Selection)).ToList();
167+
return GetResultsFromModule(module, searchPattern, pane.Selection);
112168
}
113169
}
114170
}
115171

116-
private List<RegexSearchResult> SearchCurrentBlock(string searchPattern)
172+
private IEnumerable<RegexSearchResult> SearchCurrentBlock(string searchPattern)
117173
{
118-
var declarationTypes = new[]
119-
{
120-
DeclarationType.Event,
121-
DeclarationType.Function,
122-
DeclarationType.Procedure,
123-
DeclarationType.PropertyGet,
124-
DeclarationType.PropertyLet,
125-
DeclarationType.PropertySet
126-
};
127-
128-
var state = _parser.State;
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();
191+
129192
using (var pane = _vbe.ActiveCodePane)
130193
{
131194
if (pane == null || pane.IsWrappingNullReference)
@@ -135,23 +198,8 @@ private List<RegexSearchResult> SearchCurrentBlock(string searchPattern)
135198

136199
using (var module = pane.CodeModule)
137200
{
138-
var results = GetResultsFromModule(module, searchPattern);
139-
140-
var qualifiedSelection = pane.GetQualifiedSelection();
141-
142-
if (!qualifiedSelection.HasValue)
143-
{
144-
return new List<RegexSearchResult>();
145-
}
146-
147-
var block = (ParserRuleContext)state.AllDeclarations
148-
.FindTarget(qualifiedSelection.Value, declarationTypes)
149-
.Context
150-
.Parent;
151-
var selection = new Selection(block.Start.Line, block.Start.Column, block.Stop.Line,
152-
block.Stop.Column);
153-
154-
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);
155203
}
156204
}
157205
}

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
}

0 commit comments

Comments
 (0)