Skip to content

Commit 5985c6a

Browse files
committed
Add dedicated test class for PassParameterByReferenceQuickFix
1 parent 43f9c67 commit 5985c6a

File tree

5 files changed

+229
-186
lines changed

5 files changed

+229
-186
lines changed

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -349,7 +349,6 @@
349349
<Compile Include="Inspections\QuickFixes\AddIdentifierToWhiteListQuickFix.cs" />
350350
<Compile Include="Inspections\QuickFixes\ApplicationWorksheetFunctionQuickFix.cs" />
351351
<Compile Include="Inspections\QuickFixes\AssignedByValParameterMakeLocalCopyQuickFix.cs" />
352-
<Compile Include="Inspections\QuickFixes\AssignedByValParameterQuickFix.cs" />
353352
<Compile Include="Inspections\QuickFixes\QuickFixHelper.cs" />
354353
<Compile Include="Inspections\Resources\InspectionsUI.Designer.cs">
355354
<AutoGen>True</AutoGen>

RubberduckTests/Inspections/AssignedByValParameterInspectionTests.cs

Lines changed: 7 additions & 176 deletions
Original file line numberDiff line numberDiff line change
@@ -6,12 +6,9 @@
66
using Rubberduck.Inspections.QuickFixes;
77
using Rubberduck.Inspections.Resources;
88
using Rubberduck.Parsing.VBA;
9-
using Rubberduck.VBEditor.Events;
109
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1110
using RubberduckTests.Mocks;
1211
using System.Collections.Generic;
13-
using System;
14-
using Rubberduck.Parsing.Symbols;
1512
using Rubberduck.VBEditor.SafeComWrappers;
1613

1714
namespace RubberduckTests.Inspections
@@ -125,156 +122,6 @@ End Sub
125122
Assert.AreEqual(0, results.Count());
126123
}
127124

128-
[TestMethod]
129-
[TestCategory("Inspections")]
130-
public void AssignedByValParameter_QuickFixWorks()
131-
{
132-
133-
string inputCode =
134-
@"Public Sub Foo(Optional ByVal barByVal As String = ""XYZ"")
135-
Let barByVal = ""test""
136-
End Sub";
137-
string expectedCode =
138-
@"Public Sub Foo(Optional ByRef barByVal As String = ""XYZ"")
139-
Let barByVal = ""test""
140-
End Sub";
141-
142-
var quickFixResult = ApplyPassParameterByReferenceQuickFixToCodeFragment(inputCode);
143-
Assert.AreEqual(expectedCode, quickFixResult);
144-
145-
//check when ByVal argument is one of several parameters
146-
inputCode =
147-
@"Public Sub Foo(ByRef firstArg As Long, Optional ByVal barByVal As String = """", secondArg as Double)
148-
Let barByVal = ""test""
149-
End Sub";
150-
expectedCode =
151-
@"Public Sub Foo(ByRef firstArg As Long, Optional ByRef barByVal As String = """", secondArg as Double)
152-
Let barByVal = ""test""
153-
End Sub";
154-
155-
quickFixResult = ApplyPassParameterByReferenceQuickFixToCodeFragment(inputCode);
156-
Assert.AreEqual(expectedCode, quickFixResult);
157-
158-
inputCode =
159-
@"
160-
Private Sub Foo(Optional ByVal _
161-
bar _
162-
As _
163-
Long = 4, _
164-
ByVal _
165-
barTwo _
166-
As _
167-
Long)
168-
bar = 42
169-
End Sub
170-
"
171-
;
172-
expectedCode =
173-
@"
174-
Private Sub Foo(Optional ByRef _
175-
bar _
176-
As _
177-
Long = 4, _
178-
ByVal _
179-
barTwo _
180-
As _
181-
Long)
182-
bar = 42
183-
End Sub
184-
"
185-
;
186-
quickFixResult = ApplyPassParameterByReferenceQuickFixToCodeFragment(inputCode);
187-
Assert.AreEqual(expectedCode, quickFixResult);
188-
189-
inputCode =
190-
@"Private Sub Foo(ByVal barByVal As Long, ByVal _xByValbar As Long, ByVal _
191-
barTwo _
192-
As _
193-
Long)
194-
barTwo = 42
195-
End Sub
196-
";
197-
expectedCode =
198-
@"Private Sub Foo(ByVal barByVal As Long, ByVal _xByValbar As Long, ByRef _
199-
barTwo _
200-
As _
201-
Long)
202-
barTwo = 42
203-
End Sub
204-
";
205-
206-
quickFixResult = ApplyPassParameterByReferenceQuickFixToCodeFragment(inputCode);
207-
Assert.AreEqual(expectedCode, quickFixResult);
208-
209-
inputCode =
210-
@"Private Sub Foo(ByVal barByVal As Long, ByVal barTwoon As Long, ByVal _
211-
barTwo _
212-
As _
213-
Long)
214-
barTwo = 42
215-
End Sub
216-
";
217-
expectedCode =
218-
@"Private Sub Foo(ByVal barByVal As Long, ByVal barTwoon As Long, ByRef _
219-
barTwo _
220-
As _
221-
Long)
222-
barTwo = 42
223-
End Sub
224-
";
225-
226-
quickFixResult = ApplyPassParameterByReferenceQuickFixToCodeFragment(inputCode);
227-
Assert.AreEqual(expectedCode, quickFixResult);
228-
229-
inputCode =
230-
@"Private Sub Foo(ByVal barByVal As Long, ByVal barTwoon As Long, ByVal barTwo _
231-
As _
232-
Long)
233-
barTwo = 42
234-
End Sub
235-
";
236-
expectedCode =
237-
@"Private Sub Foo(ByVal barByVal As Long, ByVal barTwoon As Long, ByRef barTwo _
238-
As _
239-
Long)
240-
barTwo = 42
241-
End Sub
242-
";
243-
244-
quickFixResult = ApplyPassParameterByReferenceQuickFixToCodeFragment(inputCode);
245-
Assert.AreEqual(expectedCode, quickFixResult);
246-
247-
inputCode =
248-
@"Sub DoSomething(_
249-
ByVal foo As Long, _
250-
ByRef _
251-
bar, _
252-
ByRef barbecue _
253-
)
254-
foo = 4
255-
bar = barbecue * _
256-
bar + foo / barbecue
257-
End Sub
258-
";
259-
260-
expectedCode =
261-
@"Sub DoSomething(_
262-
ByRef foo As Long, _
263-
ByRef _
264-
bar, _
265-
ByRef barbecue _
266-
)
267-
foo = 4
268-
bar = barbecue * _
269-
bar + foo / barbecue
270-
End Sub
271-
";
272-
quickFixResult = ApplyPassParameterByReferenceQuickFixToCodeFragment(inputCode);
273-
Assert.AreEqual(expectedCode, quickFixResult);
274-
275-
}
276-
277-
278125
[TestMethod]
279126
[TestCategory("Inspections")]
280127
public void AssignedByValParameter_IgnoreQuickFixWorks()
@@ -312,17 +159,12 @@ public void InspectionName()
312159
}
313160

314161

315-
private string ApplyPassParameterByReferenceQuickFixToCodeFragment(string inputCode)
162+
private void AssertVbaFragmentYieldsExpectedInspectionResultCount(string inputCode, int expectedCount)
316163
{
317-
var vbe = BuildMockVBEStandardModuleForVBAFragment(inputCode);
318-
var inspectionResults = GetInspectionResults(vbe);
319-
320-
inspectionResults.First().QuickFixes.Single(s => s is PassParameterByReferenceQuickFix).Fix();
321-
322-
return GetModuleContent(vbe);
164+
var inspectionResults = GetInspectionResults(inputCode);
165+
Assert.AreEqual(expectedCount, inspectionResults.Count());
323166
}
324167

325-
326168
private string ApplyIgnoreOnceQuickFixToCodeFragment(string inputCode)
327169
{
328170
var vbe = BuildMockVBEStandardModuleForVBAFragment(inputCode);
@@ -348,31 +190,20 @@ private string GetModuleContent(Mock<IVBE> vbe)
348190

349191
private IEnumerable<Rubberduck.Inspections.Abstract.InspectionResultBase> GetInspectionResults(Mock<IVBE> vbe)
350192
{
351-
var parser = GetMockParseCoordinator(vbe);
193+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
194+
parser.Parse(new CancellationTokenSource());
195+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
196+
352197
var inspection = new AssignedByValParameterInspection(parser.State);
353198
return inspection.GetInspectionResults();
354199
}
355200

356-
private void AssertVbaFragmentYieldsExpectedInspectionResultCount(string inputCode, int expectedCount)
357-
{
358-
var inspectionResults = GetInspectionResults(inputCode);
359-
Assert.AreEqual(expectedCount, inspectionResults.Count());
360-
}
361-
362201
private Mock<IVBE> BuildMockVBEStandardModuleForVBAFragment(string inputCode)
363202
{
364203
var builder = new MockVbeBuilder();
365204
IVBComponent component;
366205
return builder.BuildFromSingleStandardModule(inputCode, out component);
367206

368207
}
369-
private ParseCoordinator GetMockParseCoordinator(Mock<IVBE> vbe)
370-
{
371-
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
372-
373-
parser.Parse(new CancellationTokenSource());
374-
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
375-
return parser;
376-
}
377208
}
378209
}

RubberduckTests/Inspections/AssignedByValParameterMakeLocalCopyQuickFixTests.cs

Lines changed: 4 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -468,7 +468,10 @@ private string GetModuleContent(Mock<IVBE> vbe)
468468
}
469469
private IEnumerable<Rubberduck.Inspections.Abstract.InspectionResultBase> GetInspectionResults(Mock<IVBE> vbe)
470470
{
471-
var parser = GetMockParseCoordinator(vbe);
471+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
472+
parser.Parse(new CancellationTokenSource());
473+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
474+
472475
var inspection = new AssignedByValParameterInspection(parser.State);
473476
return inspection.GetInspectionResults();
474477
}
@@ -478,13 +481,5 @@ private Mock<IVBE> BuildMockVBEStandardModuleForVBAFragment(string inputCode)
478481
IVBComponent component;
479482
return builder.BuildFromSingleStandardModule(inputCode, out component);
480483
}
481-
private ParseCoordinator GetMockParseCoordinator(Mock<IVBE> vbe)
482-
{
483-
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
484-
485-
parser.Parse(new CancellationTokenSource());
486-
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
487-
return parser;
488-
}
489484
}
490485
}

0 commit comments

Comments
 (0)