Skip to content

Commit ce34b39

Browse files
committed
review comments from PR#4145
1 parent a155193 commit ce34b39

File tree

6 files changed

+98
-53
lines changed

6 files changed

+98
-53
lines changed

Rubberduck.Parsing/Binding/Bindings/SimpleNameDefaultBinding.cs

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -156,11 +156,6 @@ function or subroutine defined at the module-level in the enclosing module.
156156
{
157157
return new SimpleNameExpression(enumMember, ExpressionClassification.Value, _context);
158158
}
159-
// Prioritize return value assignments over any other let/set property references.
160-
//if (_parent.DeclarationType == DeclarationType.PropertyGet && _declarationFinder.IsMatch(_parent.IdentifierName, _name))
161-
//{
162-
// return new SimpleNameExpression(_parent, ExpressionClassification.Property, _context);
163-
//}
164159
var property = _declarationFinder.FindMemberEnclosingModule(_module, _parent, _name, _propertySearchType);
165160
if (IsValidMatch(property, _name))
166161
{

Rubberduck.Parsing/Symbols/ConcurrentlyConstructedDeclarationFinder.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@
66

77
namespace Rubberduck.Parsing.Symbols
88
{
9-
public class ConcurrentlyConstructedDeclarationFinder : DeclarationFinder
9+
public sealed class ConcurrentlyConstructedDeclarationFinder : DeclarationFinder
1010
{
1111
private const int _maxDegreeOfConstructionParallelism = -1;
1212

@@ -16,8 +16,7 @@ public ConcurrentlyConstructedDeclarationFinder(IReadOnlyList<Declaration> decla
1616

1717
protected override void ExecuteCollectionConstructionActions(List<Action> collectionConstructionActions)
1818
{
19-
var options = new ParallelOptions();
20-
options.MaxDegreeOfParallelism = _maxDegreeOfConstructionParallelism;
19+
var options = new ParallelOptions {MaxDegreeOfParallelism = _maxDegreeOfConstructionParallelism};
2120

2221
Parallel.ForEach(
2322
collectionConstructionActions,

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 17 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System;
22
using System.Collections.Concurrent;
33
using System.Collections.Generic;
4-
using System.Collections.ObjectModel;
54
using System.Diagnostics;
65
using System.Linq;
76
using Antlr4.Runtime;
@@ -16,7 +15,7 @@
1615

1716
namespace Rubberduck.Parsing.Symbols
1817
{
19-
public class DeclarationFinder
18+
public class DeclarationFinder
2019
{
2120
private static readonly SquareBracketedNameComparer NameComparer = new SquareBracketedNameComparer();
2221
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
@@ -71,6 +70,8 @@ public DeclarationFinder(IReadOnlyList<Declaration> declarations, IEnumerable<IA
7170
_annotationService = new AnnotationService(this);
7271

7372
var collectionConstructionActions = CollectionConstructionActions(declarations, annotations, unresolvedMemberDeclarations);
73+
74+
// ReSharper disable once VirtualMemberCallInConstructor; this is under control, action collection is built right here ^^
7475
ExecuteCollectionConstructionActions(collectionConstructionActions);
7576

7677
//Temporal coupling: the initializers of the lazy collections use the regular collections filled above.
@@ -736,11 +737,6 @@ public Declaration FindMemberEnclosingProcedure(Declaration enclosingProcedure,
736737
return memberMatches.FirstOrDefault();
737738
}
738739

739-
//if (memberType == DeclarationType.Variable && NameComparer.Equals(enclosingProcedure.IdentifierName, memberName))
740-
//{
741-
// return enclosingProcedure;
742-
//}
743-
744740
return null;
745741
}
746742

@@ -763,62 +759,55 @@ public Declaration OnRedimVariable(Declaration enclosingProcedure, string identi
763759
typeHint,
764760
isSelfAssigned: false,
765761
isWithEvents: false,
766-
Accessibility.Implicit,
767-
DeclarationType.Variable,
768-
context,
769-
context.GetSelection(),
770-
isArray: true,
771-
asTypeClause,
772762
isUserDefined: true,
773-
annotations,
774-
null,
763+
isArray: true,
775764
undeclared: false,
765+
accessibility:Accessibility.Implicit,
766+
declarationType:DeclarationType.Variable,
767+
context:context,
768+
attributesPassContext:null,
769+
selection:context.GetSelection(),
770+
asTypeContext:asTypeClause,
771+
annotations:annotations,
772+
attributes:null,
776773
isRedimVariable: true);
777774
// Note: We do not add annotations again because those get added for the redim statement separately.
778775
// We have to add the newly created declaration to the lookup dictionaries because we're in the middle of the binding process
779776
// and a Redim statement after this one could reference the same variable.
780-
List<Declaration> tempDeclarations = null;
781-
if (_declarations.TryGetValue(newVariable.QualifiedName.QualifiedModuleName, out tempDeclarations))
777+
if (_declarations.TryGetValue(newVariable.QualifiedName.QualifiedModuleName, out var tempDeclarations))
782778
{
783779
tempDeclarations.Add(newVariable);
784780
}
785781
else
786782
{
787-
tempDeclarations = new List<Declaration>();
788-
tempDeclarations.Add(newVariable);
783+
tempDeclarations = new List<Declaration> {newVariable};
789784
_declarations[newVariable.QualifiedName.QualifiedModuleName] = tempDeclarations;
790785
}
791-
tempDeclarations = null;
792786
if (_declarationsByName.TryGetValue(newVariable.IdentifierName.ToLowerInvariant(), out tempDeclarations))
793787
{
794788
tempDeclarations.Add(newVariable);
795789
}
796790
else
797791
{
798-
tempDeclarations = new List<Declaration>();
799-
tempDeclarations.Add(newVariable);
792+
tempDeclarations = new List<Declaration> {newVariable};
800793
_declarationsByName[newVariable.IdentifierName.ToLowerInvariant()] = tempDeclarations;
801794
}
802-
tempDeclarations = null;
803795
if (_declarationsBySelection.TryGetValue(GetGroupingKey(newVariable), out tempDeclarations))
804796
{
805797
tempDeclarations.Add(newVariable);
806798
}
807799
else
808800
{
809-
tempDeclarations = new List<Declaration>();
810-
tempDeclarations.Add(newVariable);
801+
tempDeclarations = new List<Declaration> {newVariable};
811802
_declarationsBySelection[GetGroupingKey(newVariable)] = tempDeclarations;
812803
}
813-
tempDeclarations = null;
814804
if (_userDeclarationsByType.TryGetValue(newVariable.DeclarationType, out tempDeclarations))
815805
{
816806
tempDeclarations.Add(newVariable);
817807
}
818808
else
819809
{
820-
tempDeclarations = new List<Declaration>();
821-
tempDeclarations.Add(newVariable);
810+
tempDeclarations = new List<Declaration> {newVariable};
822811
_userDeclarationsByType[newVariable.DeclarationType] = tempDeclarations;
823812
}
824813
return newVariable;

Rubberduck.Parsing/Symbols/ResultVariableDeclaration.cs

Lines changed: 10 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,4 @@
1-
using Rubberduck.Parsing.Grammar;
2-
using System;
3-
using System.Collections.Generic;
4-
using System.Linq;
5-
using System.Text;
6-
using System.Threading.Tasks;
7-
using Rubberduck.Parsing.ComReflection;
8-
using Rubberduck.Parsing.Grammar;
9-
using Rubberduck.VBEditor;
1+
using Rubberduck.VBEditor;
102

113
namespace Rubberduck.Parsing.Symbols
124
{
@@ -24,15 +16,16 @@ public ResultVariableDeclaration(
2416
function,
2517
asTypeName,
2618
typeHint,
27-
false,
28-
false,
29-
Accessibility.Implicit,
30-
DeclarationType.ResultVariable,
31-
null,
32-
Selection.Home,
19+
isSelfAssigned:false,
20+
isWithEvents:false,
21+
accessibility:Accessibility.Implicit,
22+
declarationType:DeclarationType.ResultVariable,
23+
context:null,
24+
attributesPassContext:null,
25+
selection:Selection.Home,
3326
isArray,
34-
null,
35-
false)
27+
asTypeContext:null,
28+
isUserDefined:false)
3629
{
3730
Function = function;
3831
}

Rubberduck.Resources/Inspections/InspectionResults.Designer.cs

Lines changed: 9 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

RubberduckTests/QuickFixes/IntroduceLocalVariableQuickFixTests.cs

Lines changed: 60 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -161,6 +161,66 @@ public void IntroduceLocalVariable_QuickFixWorks_StatementSeperators()
161161
TestInsertLocalVariableQuickFix(expectedCode, inputCode);
162162
}
163163

164+
[Test]
165+
[Category("QuickFixes")]
166+
public void IntroduceLocalVariable_OnlyFixesFixesFirstOccurrenceOfReDimStatement()
167+
{
168+
var inputCode = @"
169+
Public Sub DoSomething()
170+
ReDim foo(1)
171+
ReDim foo(2)
172+
End Sub
173+
";
174+
var expectedCode = @"
175+
Public Sub DoSomething()
176+
Dim foo() As Variant
177+
ReDim foo(1)
178+
ReDim foo(2)
179+
End Sub
180+
";
181+
TestInsertLocalVariableQuickFix(expectedCode, inputCode);
182+
}
183+
184+
[Test]
185+
[Category("QuickFixes")]
186+
public void IntroduceLocalVariable_KeepsAsClauseIfConsistent()
187+
{
188+
var inputCode = @"
189+
Public Sub DoSomething()
190+
ReDim foo(1) As Long
191+
ReDim foo(2) As Long
192+
End Sub
193+
";
194+
var expectedCode = @"
195+
Public Sub DoSomething()
196+
Dim foo() As Long
197+
ReDim foo(1) As Long
198+
ReDim foo(2) As Long
199+
End Sub
200+
";
201+
TestInsertLocalVariableQuickFix(expectedCode, inputCode);
202+
}
203+
204+
[Test]
205+
[Category("QuickFixes")]
206+
public void IntroduceLocalVariable_DeclaresAsVariantIfInconsistentAsClauses()
207+
{
208+
var inputCode = @"
209+
Public Sub DoSomething()
210+
ReDim foo(1) As Long
211+
ReDim foo(2) As String
212+
End Sub
213+
";
214+
var expectedCode = @"
215+
Public Sub DoSomething()
216+
Dim foo() As Variant
217+
ReDim foo(1) As Long
218+
ReDim foo(2) As String
219+
End Sub
220+
";
221+
TestInsertLocalVariableQuickFix(expectedCode, inputCode);
222+
}
223+
164224
private void TestInsertLocalVariableQuickFix(string expectedCode, string inputCode)
165225
{
166226
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component);

0 commit comments

Comments
 (0)