Skip to content

Commit cf9b589

Browse files
committed
added failing test for SynchronizeAttributesQuickFix: Missing PredeclaredId attribute fix (changes "= False" to "= True")
1 parent 931f9d8 commit cf9b589

File tree

3 files changed

+94
-1
lines changed

3 files changed

+94
-1
lines changed

Rubberduck.Inspections/QuickFixes/SynchronizeAttributesQuickFix.cs

Lines changed: 25 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,21 @@ public void Fix(IInspectionResult result)
5757
}
5858
else
5959
{
60-
Debug.Assert(false, "bug: inspection result has a null membername");
60+
var moduleName = result.QualifiedSelection.QualifiedName;
61+
62+
var attributeContext = context as VBAParser.AttributeStmtContext;
63+
if(attributeContext != null)
64+
{
65+
Fix(moduleName, attributeContext);
66+
return;
67+
}
68+
69+
var annotationContext = context as VBAParser.AnnotationContext;
70+
if(annotationContext != null)
71+
{
72+
Fix(moduleName, annotationContext);
73+
return;
74+
}
6175
}
6276
}
6377

@@ -71,6 +85,16 @@ private void Fix(QualifiedMemberName memberName, VBAParser.AttributeStmtContext
7185

7286
}
7387

88+
private void Fix(QualifiedModuleName moduleName, VBAParser.AttributeStmtContext context)
89+
{
90+
91+
}
92+
93+
private void Fix(QualifiedModuleName moduleName, VBAParser.AnnotationContext context)
94+
{
95+
96+
}
97+
7498
/// <summary>
7599
/// Adds an attribute to match given annotation.
76100
/// </summary>
Lines changed: 68 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,68 @@
1+
using System.Linq;
2+
using System.Threading;
3+
using Microsoft.VisualStudio.TestTools.UnitTesting;
4+
using Rubberduck.Inspections.Concrete;
5+
using Rubberduck.Inspections.QuickFixes;
6+
using Rubberduck.Parsing.Grammar;
7+
using Rubberduck.VBEditor.SafeComWrappers;
8+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
9+
using RubberduckTests.Mocks;
10+
11+
namespace RubberduckTests.Inspections
12+
{
13+
[TestClass]
14+
public class SynchronizeAttributesQuickFixTests
15+
{
16+
[TestMethod]
17+
public void AddsMissingPredeclaredIdAttribute()
18+
{
19+
const string testModuleName = "Test";
20+
const string inputCode = @"
21+
VERSION 1.0 CLASS
22+
BEGIN
23+
MultiUse = -1 'True
24+
END
25+
Attribute VB_Name = """ + testModuleName + @"""
26+
Attribute VB_GlobalNameSpace = False
27+
Attribute VB_Creatable = False
28+
Attribute VB_PredeclaredId = False
29+
Attribute VB_Exposed = False
30+
Option Explicit
31+
'@PredeclaredId
32+
";
33+
const string expectedCode = @"
34+
VERSION 1.0 CLASS
35+
BEGIN
36+
MultiUse = -1 'True
37+
END
38+
Attribute VB_Name = """ + testModuleName + @"""
39+
Attribute VB_GlobalNameSpace = False
40+
Attribute VB_Creatable = False
41+
Attribute VB_PredeclaredId = True
42+
Attribute VB_Exposed = False
43+
Option Explicit
44+
'@PredeclaredId
45+
";
46+
47+
IVBComponent component;
48+
var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, testModuleName, ComponentType.ClassModule, out component);
49+
50+
var state = MockParser.CreateAndParse(vbe.Object);
51+
var inspection = new MissingAttributeInspection(state);
52+
var inspector = InspectionsHelper.GetInspector(inspection);
53+
var result = inspector.FindIssuesAsync(state, CancellationToken.None).Result?.SingleOrDefault();
54+
if(result?.Context.GetType() != typeof(VBAParser.AnnotationContext))
55+
{
56+
Assert.Inconclusive("Inspection failed to return a result.");
57+
}
58+
59+
var fix = new SynchronizeAttributesQuickFix(state);
60+
fix.Fix(result);
61+
62+
var rewriter = state.GetAttributeRewriter(result.QualifiedSelection.QualifiedName);
63+
var actual = rewriter.GetText();
64+
65+
Assert.AreEqual(expectedCode, actual);
66+
}
67+
}
68+
}

RubberduckTests/RubberduckTests.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -107,6 +107,7 @@
107107
<Compile Include="Inspections\OptionBaseZeroInspectionTests.cs" />
108108
<Compile Include="Inspections\PassParameterByReferenceQuickFixTests.cs" />
109109
<Compile Include="Inspections\QuickFixProviderTests.cs" />
110+
<Compile Include="Inspections\SynchronizeAttributesQuickFixTests.cs" />
110111
<Compile Include="Inspections\UndeclaredVariableInspectionTests.cs" />
111112
<Compile Include="Mocks\TestAttributeParser.cs" />
112113
<Compile Include="Parsing\Coordination\IModuleToModuleReferenceManagerTestBase.cs" />

0 commit comments

Comments
 (0)