Skip to content

Commit 4ccf9cc

Browse files
committed
Merge branch 'ninjectMemoryLeaks' of https://github.com/Hosch250/Rubberduck
2 parents e30c994 + 458ec20 commit 4ccf9cc

File tree

8 files changed

+200
-2
lines changed

8 files changed

+200
-2
lines changed

RetailCoder.VBE/Inspections/InspectionsUI.Designer.cs

Lines changed: 11 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

RetailCoder.VBE/Inspections/InspectionsUI.resx

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -565,4 +565,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
565565
<data name="MalformedAnnotationInspectionResultFormat" xml:space="preserve">
566566
<value>Malformed '{0}' annotation.</value>
567567
</data>
568-
</root>
568+
<data name="WriteOnlyPropertyQuickFix" xml:space="preserve">
569+
<value>Add property get</value>
570+
</data>
571+
</root>

RetailCoder.VBE/Inspections/WriteOnlyPropertyInspection.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -54,6 +54,7 @@ public override IEnumerable<CodeInspectionQuickFix> QuickFixes
5454
{
5555
return new CodeInspectionQuickFix[]
5656
{
57+
new WriteOnlyPropertyQuickFix(Context, Target),
5758
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName)
5859
};
5960
}
Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,36 @@
1+
using System;
2+
using System.Linq;
3+
using Antlr4.Runtime;
4+
using Rubberduck.Parsing.Grammar;
5+
using Rubberduck.Parsing.Symbols;
6+
7+
namespace Rubberduck.Inspections
8+
{
9+
public class WriteOnlyPropertyQuickFix : CodeInspectionQuickFix
10+
{
11+
private readonly Declaration _target;
12+
13+
public WriteOnlyPropertyQuickFix(ParserRuleContext context, Declaration target)
14+
: base(context, target.QualifiedSelection, InspectionsUI.WriteOnlyPropertyQuickFix)
15+
{
16+
_target = target;
17+
}
18+
19+
public override void Fix()
20+
{
21+
var parameters = ((IDeclarationWithParameter) _target).Parameters.Cast<ParameterDeclaration>().ToList();
22+
23+
var signatureParams = parameters.Except(new[] {parameters.Last()}).Select(GetParamText);
24+
var propertyGet = "Public Property Get " + _target.IdentifierName + "(" + string.Join(", ", signatureParams) +
25+
") As " + parameters.Last().AsTypeName + Environment.NewLine + "End Property";
26+
27+
var module = _target.QualifiedName.QualifiedModuleName.Component.CodeModule;
28+
module.InsertLines(_target.Selection.StartLine, propertyGet);
29+
}
30+
31+
private string GetParamText(ParameterDeclaration param)
32+
{
33+
return (((VBAParser.ArgContext)param.Context).BYVAL() == null ? "ByRef " : "ByVal ") + param.IdentifierName + " As " + param.AsTypeName;
34+
}
35+
}
36+
}

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -373,6 +373,7 @@
373373
<Compile Include="Inspections\MalformedAnnotationInspection.cs" />
374374
<Compile Include="Inspections\ObjectVariableNotSetInspection.cs" />
375375
<Compile Include="Inspections\RemoveExplicitCallStatmentQuickFix.cs" />
376+
<Compile Include="Inspections\WriteOnlyPropertyQuickFix.cs" />
376377
<Compile Include="Navigation\CodeExplorer\ICodeExplorerDeclarationViewModel.cs" />
377378
<Compile Include="Navigation\Folders\FolderHelper.cs" />
378379
<Compile Include="Refactorings\ExtractMethod\ExtractedMethod.cs" />

RetailCoder.VBE/UI/Command/RunAllTestsCommand.cs

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,8 @@ protected override bool CanExecuteImpl(object parameter)
3737

3838
protected override void ExecuteImpl(object parameter)
3939
{
40+
EnsureRubberduckIsReferencedForEarlyBoundTests();
41+
4042
if (!_state.IsDirty())
4143
{
4244
RunTests();
@@ -48,6 +50,18 @@ protected override void ExecuteImpl(object parameter)
4850
}
4951
}
5052

53+
private void EnsureRubberduckIsReferencedForEarlyBoundTests()
54+
{
55+
foreach (var member in _state.AllUserDeclarations)
56+
{
57+
if (member.AsTypeName == "Rubberduck.PermissiveAssertClass" ||
58+
member.AsTypeName == "Rubberduck.AssertClass")
59+
{
60+
member.Project.EnsureReferenceToAddInLibrary();
61+
}
62+
}
63+
}
64+
5165
private void TestsRefreshed(object sender, EventArgs e)
5266
{
5367
RunTests();

RetailCoder.VBE/UI/UnitTesting/TestExplorerViewModel.cs

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -228,8 +228,22 @@ private bool CanExecuteRefreshCommand(object parameter)
228228
return !Model.IsBusy && _state.IsDirty();
229229
}
230230

231+
private void EnsureRubberduckIsReferencedForEarlyBoundTests()
232+
{
233+
foreach (var member in _state.AllUserDeclarations)
234+
{
235+
if (member.AsTypeName == "Rubberduck.PermissiveAssertClass" ||
236+
member.AsTypeName == "Rubberduck.AssertClass")
237+
{
238+
member.Project.EnsureReferenceToAddInLibrary();
239+
}
240+
}
241+
}
242+
231243
private void ExecuteRepeatLastRunCommand(object parameter)
232244
{
245+
EnsureRubberduckIsReferencedForEarlyBoundTests();
246+
233247
var tests = _model.LastRun.ToList();
234248
_model.ClearLastRun();
235249

@@ -246,6 +260,8 @@ private void ExecuteRepeatLastRunCommand(object parameter)
246260

247261
private void ExecuteRunNotExecutedTestsCommand(object parameter)
248262
{
263+
EnsureRubberduckIsReferencedForEarlyBoundTests();
264+
249265
_model.ClearLastRun();
250266

251267
var stopwatch = new Stopwatch();
@@ -261,6 +277,8 @@ private void ExecuteRunNotExecutedTestsCommand(object parameter)
261277

262278
private void ExecuteRunFailedTestsCommand(object parameter)
263279
{
280+
EnsureRubberduckIsReferencedForEarlyBoundTests();
281+
264282
_model.ClearLastRun();
265283

266284
var stopwatch = new Stopwatch();
@@ -276,6 +294,8 @@ private void ExecuteRunFailedTestsCommand(object parameter)
276294

277295
private void ExecuteRunPassedTestsCommand(object parameter)
278296
{
297+
EnsureRubberduckIsReferencedForEarlyBoundTests();
298+
279299
_model.ClearLastRun();
280300

281301
var stopwatch = new Stopwatch();
@@ -301,6 +321,8 @@ private void ExecuteSelectedTestCommand(object obj)
301321
return;
302322
}
303323

324+
EnsureRubberduckIsReferencedForEarlyBoundTests();
325+
304326
_model.ClearLastRun();
305327

306328
var stopwatch = new Stopwatch();

RubberduckTests/Inspections/WriteOnlyPropertyInspectionTests.cs

Lines changed: 111 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -193,6 +193,117 @@ Property Let Foo(value)
193193
Assert.IsFalse(inspectionResults.Any());
194194
}
195195

196+
[TestMethod]
197+
[TestCategory("Inspections")]
198+
public void WriteOnlyProperty_AddPropertyGetQuickFixWorks_ImplicitTypesAndAccessibility()
199+
{
200+
const string inputCode =
201+
@"Property Let Foo(value)
202+
End Property";
203+
204+
const string expectedCode =
205+
@"Public Property Get Foo() As Variant
206+
End Property
207+
Property Let Foo(value)
208+
End Property";
209+
210+
//Arrange
211+
var builder = new MockVbeBuilder();
212+
var project = builder.ProjectBuilder("VBAProject", vbext_ProjectProtection.vbext_pp_none)
213+
.AddComponent("MyClass", vbext_ComponentType.vbext_ct_ClassModule, inputCode)
214+
.Build();
215+
var module = project.Object.VBComponents.Item(0).CodeModule;
216+
var vbe = builder.AddProject(project).Build();
217+
218+
var mockHost = new Mock<IHostApplication>();
219+
mockHost.SetupAllProperties();
220+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
221+
222+
parser.Parse(new CancellationTokenSource());
223+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
224+
225+
var inspection = new WriteOnlyPropertyInspection(parser.State);
226+
var inspectionResults = inspection.GetInspectionResults();
227+
228+
inspectionResults.First().QuickFixes.Single(s => s is WriteOnlyPropertyQuickFix).Fix();
229+
230+
Assert.AreEqual(expectedCode, module.Lines());
231+
}
232+
233+
[TestMethod]
234+
[TestCategory("Inspections")]
235+
public void WriteOnlyProperty_AddPropertyGetQuickFixWorks_ExlicitTypesAndAccessibility()
236+
{
237+
const string inputCode =
238+
@"Public Property Let Foo(ByVal value As Integer)
239+
End Property";
240+
241+
const string expectedCode =
242+
@"Public Property Get Foo() As Integer
243+
End Property
244+
Public Property Let Foo(ByVal value As Integer)
245+
End Property";
246+
247+
//Arrange
248+
var builder = new MockVbeBuilder();
249+
var project = builder.ProjectBuilder("VBAProject", vbext_ProjectProtection.vbext_pp_none)
250+
.AddComponent("MyClass", vbext_ComponentType.vbext_ct_ClassModule, inputCode)
251+
.Build();
252+
var module = project.Object.VBComponents.Item(0).CodeModule;
253+
var vbe = builder.AddProject(project).Build();
254+
255+
var mockHost = new Mock<IHostApplication>();
256+
mockHost.SetupAllProperties();
257+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
258+
259+
parser.Parse(new CancellationTokenSource());
260+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
261+
262+
var inspection = new WriteOnlyPropertyInspection(parser.State);
263+
var inspectionResults = inspection.GetInspectionResults();
264+
265+
inspectionResults.First().QuickFixes.Single(s => s is WriteOnlyPropertyQuickFix).Fix();
266+
267+
Assert.AreEqual(expectedCode, module.Lines());
268+
}
269+
270+
[TestMethod]
271+
[TestCategory("Inspections")]
272+
public void WriteOnlyProperty_AddPropertyGetQuickFixWorks_MultipleParams()
273+
{
274+
const string inputCode =
275+
@"Public Property Let Foo(value1, ByVal value2 As Integer, ByRef value3 As Long, value4 As Date, ByVal value5, value6 As String)
276+
End Property";
277+
278+
const string expectedCode =
279+
@"Public Property Get Foo(ByRef value1 As Variant, ByVal value2 As Integer, ByRef value3 As Long, ByRef value4 As Date, ByVal value5 As Variant) As String
280+
End Property
281+
Public Property Let Foo(value1, ByVal value2 As Integer, ByRef value3 As Long, value4 As Date, ByVal value5, value6 As String)
282+
End Property";
283+
284+
//Arrange
285+
var builder = new MockVbeBuilder();
286+
var project = builder.ProjectBuilder("VBAProject", vbext_ProjectProtection.vbext_pp_none)
287+
.AddComponent("MyClass", vbext_ComponentType.vbext_ct_ClassModule, inputCode)
288+
.Build();
289+
var module = project.Object.VBComponents.Item(0).CodeModule;
290+
var vbe = builder.AddProject(project).Build();
291+
292+
var mockHost = new Mock<IHostApplication>();
293+
mockHost.SetupAllProperties();
294+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));
295+
296+
parser.Parse(new CancellationTokenSource());
297+
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
298+
299+
var inspection = new WriteOnlyPropertyInspection(parser.State);
300+
var inspectionResults = inspection.GetInspectionResults();
301+
302+
inspectionResults.First().QuickFixes.Single(s => s is WriteOnlyPropertyQuickFix).Fix();
303+
304+
Assert.AreEqual(expectedCode, module.Lines());
305+
}
306+
196307
[TestMethod]
197308
[TestCategory("Inspections")]
198309
public void WriteOnlyProperty_IgnoreQuickFixWorks()

0 commit comments

Comments
 (0)