Skip to content

Commit b151934

Browse files
committed
Addressed PR initial comments except Dialog dependency removal
1 parent 5985c6a commit b151934

9 files changed

+32
-8
lines changed

RetailCoder.VBE/Common/ICodeModuleExtensions.cs renamed to RetailCoder.VBE/Common/CodeModuleExtensions.cs

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,20 +4,31 @@
44

55
namespace Rubberduck.Common
66
{
7-
public static class ICodeModuleExtensions
7+
public static class CodeModuleExtensions
88
{
99
public static void ReplaceToken(this ICodeModule module, IToken token, string replacement)
1010
{
1111
var original = module.GetLines(token.Line, 1);
1212
var result = ReplaceStringAtIndex(original, token.Text, replacement, token.Column);
1313
module.ReplaceLine(token.Line, result);
1414
}
15+
1516
public static void ReplaceIdentifierReferenceName(this ICodeModule module, IdentifierReference identifierReference, string replacement)
1617
{
1718
var original = module.GetLines(identifierReference.Selection.StartLine, 1);
1819
var result = ReplaceStringAtIndex(original, identifierReference.IdentifierName, replacement, identifierReference.Context.Start.Column);
1920
module.ReplaceLine(identifierReference.Selection.StartLine, result);
2021
}
22+
23+
public static void InsertLines(this ICodeModule module, int startLine, string[] lines)
24+
{
25+
int lineNumber = startLine;
26+
for ( int idx = 0; idx < lines.Length; idx++ )
27+
{
28+
module.InsertLines(lineNumber, lines[idx]);
29+
lineNumber++;
30+
}
31+
}
2132
private static string ReplaceStringAtIndex(string original, string toReplace, string replacement, int startIndex)
2233
{
2334
var stopIndex = startIndex + toReplace.Length - 1;

RetailCoder.VBE/Inspections/QuickFixes/AssignedByValParameterMakeLocalCopyQuickFix.cs

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -94,15 +94,17 @@ private void ReplaceAssignedByValParameterReferences()
9494
module.ReplaceIdentifierReferenceName(identifierReference, _localCopyVariableName);
9595
}
9696
}
97+
9798
private void InsertLocalVariableDeclarationAndAssignment()
9899
{
99100
var blocks = QuickFixHelper.GetBlockStmtContextsForContext(_target.Context.Parent.Parent);
100101
var firstBlockLineNumber = blocks.FirstOrDefault().Start.Line;
101102

102103
var module = Selection.QualifiedName.Component.CodeModule;
103-
module.InsertLines(firstBlockLineNumber++, BuildLocalCopyDeclaration());
104-
module.InsertLines(firstBlockLineNumber, BuildLocalCopyAssignment());
104+
string[] lines = { BuildLocalCopyDeclaration(), BuildLocalCopyAssignment() };
105+
module.InsertLines(firstBlockLineNumber, lines);
105106
}
107+
106108
private string BuildLocalCopyDeclaration()
107109
{
108110
return Tokens.Dim + " " + _localCopyVariableName + " " + Tokens.As
@@ -113,14 +115,14 @@ private string BuildLocalCopyAssignment()
113115
return (SymbolList.ValueTypes.Contains(_target.AsTypeName) ? string.Empty : Tokens.Set + " ")
114116
+ _localCopyVariableName + " = " + _target.IdentifierName;
115117
}
118+
116119
private string[] GetVariableNamesAccessibleToProcedureContext(RuleContext ruleContext)
117120
{
118121
var allIdentifiers = new HashSet<string>();
119122

120123
var blocks = QuickFixHelper.GetBlockStmtContextsForContext(ruleContext);
121124

122125
var blockStmtIdentifiers = GetIdentifierNames(blocks);
123-
124126
allIdentifiers.UnionWith(blockStmtIdentifiers);
125127

126128
var args = QuickFixHelper.GetArgContextsForContext(ruleContext);
@@ -132,6 +134,7 @@ private string[] GetVariableNamesAccessibleToProcedureContext(RuleContext ruleCo
132134

133135
return allIdentifiers.ToArray();
134136
}
137+
135138
private HashSet<string> GetIdentifierNames(IReadOnlyList<RuleContext> ruleContexts)
136139
{
137140
var identifiers = new HashSet<string>();
@@ -142,6 +145,7 @@ private HashSet<string> GetIdentifierNames(IReadOnlyList<RuleContext> ruleContex
142145
}
143146
return identifiers;
144147
}
148+
145149
private HashSet<string> GetIdentifierNames(RuleContext ruleContext)
146150
{
147151
//Recursively work through the tree to get all IdentifierContexts
@@ -169,6 +173,7 @@ private HashSet<string> GetIdentifierNames(RuleContext ruleContext)
169173
}
170174
return results;
171175
}
176+
172177
private static List<IParseTree> GetChildren(RuleContext ruleCtx)
173178
{
174179
var result = new List<IParseTree>();

RetailCoder.VBE/Inspections/QuickFixes/PassParameterByReferenceQuickFix.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,6 @@ public override void Fix()
3131
.Equals(_target.IdentifierName));
3232

3333
module.ReplaceToken(argContext.BYVAL().Symbol,Tokens.ByRef);
34-
3534
}
3635
}
3736
}

RetailCoder.VBE/Inspections/Resources/InspectionsUI.de.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -594,4 +594,7 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
594594
<data name="AggregateInspectionResultFormat" xml:space="preserve">
595595
<value>{0} ({1} Ergebnisse)</value>
596596
</data>
597+
<data name="AssignedByValParameterMakeLocalCopyQuickFix" xml:space="preserve">
598+
<value>Create and use a local copy of the parameter</value>
599+
</data>
597600
</root>

RetailCoder.VBE/Inspections/Resources/InspectionsUI.fr.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -604,4 +604,7 @@ Si le paramètre peut être nul, ignorer ce résultat; passer une valeur nulle
604604
<data name="AggregateInspectionResultFormat" xml:space="preserve">
605605
<value>{0} ({1} résultats)</value>
606606
</data>
607+
<data name="AssignedByValParameterMakeLocalCopyQuickFix" xml:space="preserve">
608+
<value>Create and use a local copy of the parameter</value>
609+
</data>
607610
</root>

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -325,7 +325,7 @@
325325
<Compile Include="Common\Hotkeys\Hotkey.cs" />
326326
<Compile Include="Common\IAttachable.cs" />
327327
<Compile Include="Common\Hotkeys\IHotkey.cs" />
328-
<Compile Include="Common\ICodeModuleExtensions.cs" />
328+
<Compile Include="Common\CodeModuleExtensions.cs" />
329329
<Compile Include="Common\IOperatingSystem.cs" />
330330
<Compile Include="Common\IRubberduckHooks.cs" />
331331
<Compile Include="Common\LogLevelHelper.cs" />

RubberduckTests/Inspections/AssignedByValParameterInspectionTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -140,6 +140,7 @@ Public Sub Foo(ByVal arg1 As String)
140140
var quickFixResult = ApplyIgnoreOnceQuickFixToCodeFragment(inputCode);
141141
Assert.AreEqual(expectedCode, quickFixResult);
142142
}
143+
143144
[TestMethod]
144145
[TestCategory("Inspections")]
145146
public void InspectionType()
@@ -158,7 +159,6 @@ public void InspectionName()
158159
Assert.AreEqual(inspectionName, inspection.Name);
159160
}
160161

161-
162162
private void AssertVbaFragmentYieldsExpectedInspectionResultCount(string inputCode, int expectedCount)
163163
{
164164
var inspectionResults = GetInspectionResults(inputCode);

RubberduckTests/Inspections/AssignedByValParameterMakeLocalCopyQuickFixTests.cs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -466,6 +466,7 @@ private string GetModuleContent(Mock<IVBE> vbe)
466466
var module = project.VBComponents[0].CodeModule;
467467
return module.Content();
468468
}
469+
469470
private IEnumerable<Rubberduck.Inspections.Abstract.InspectionResultBase> GetInspectionResults(Mock<IVBE> vbe)
470471
{
471472
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
@@ -475,6 +476,7 @@ private string GetModuleContent(Mock<IVBE> vbe)
475476
var inspection = new AssignedByValParameterInspection(parser.State);
476477
return inspection.GetInspectionResults();
477478
}
479+
478480
private Mock<IVBE> BuildMockVBEStandardModuleForVBAFragment(string inputCode)
479481
{
480482
var builder = new MockVbeBuilder();

RubberduckTests/Inspections/PassParameterByReferenceQuickFixTests.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -161,7 +161,6 @@ End Sub
161161
";
162162
quickFixResult = ApplyPassParameterByReferenceQuickFixToVBAFragment(inputCode);
163163
Assert.AreEqual(expectedCode, quickFixResult);
164-
165164
}
166165
[TestMethod]
167166
[TestCategory("Inspections")]
@@ -197,6 +196,7 @@ private string GetModuleContent(Mock<IVBE> vbe)
197196
var module = project.VBComponents[0].CodeModule;
198197
return module.Content();
199198
}
199+
200200
private IEnumerable<Rubberduck.Inspections.Abstract.InspectionResultBase> GetInspectionResults(Mock<IVBE> vbe)
201201
{
202202
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
@@ -206,6 +206,7 @@ private string GetModuleContent(Mock<IVBE> vbe)
206206
var inspection = new AssignedByValParameterInspection(parser.State);
207207
return inspection.GetInspectionResults();
208208
}
209+
209210
private Mock<IVBE> BuildMockVBEStandardModuleForVBAFragment(string inputCode)
210211
{
211212
var builder = new MockVbeBuilder();

0 commit comments

Comments
 (0)