Skip to content

Commit 8a33837

Browse files
authored
Merge pull request #3114 from rkapka/next
Made RemoveTypeHintsQuickFix work correctly for constant declarations
2 parents 69a93e9 + fc82886 commit 8a33837

File tree

5 files changed

+70
-13
lines changed

5 files changed

+70
-13
lines changed

RetailCoder.VBE/UI/RubberduckUI.Designer.cs

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

RetailCoder.VBE/UI/RubberduckUI.resx

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1470,7 +1470,7 @@ All our stargazers, likers & followers, for the warm fuzzies
14701470
<value>By marker</value>
14711471
</data>
14721472
<data name="DeclarationType_LibraryProcedure" xml:space="preserve">
1473-
<value>Library procedure</value>
1473+
<value>library procedure</value>
14741474
</data>
14751475
<data name="CodeExplorer_ShowSignaturesToolTip" xml:space="preserve">
14761476
<value>Toggle signatures</value>

Rubberduck.Inspections/QuickFixes/RemoveTypeHintsQuickFix.cs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,10 @@ public void Fix(IInspectionResult result)
4242
var variableContext = (VBAParser.VariableSubStmtContext) result.Target.Context;
4343
rewriter.InsertAfter(variableContext.identifier().Stop.TokenIndex, asTypeClause);
4444
break;
45+
case DeclarationType.Constant:
46+
var constantContext = (VBAParser.ConstSubStmtContext) result.Target.Context;
47+
rewriter.InsertAfter(constantContext.identifier().Stop.TokenIndex, asTypeClause);
48+
break;
4549
case DeclarationType.Parameter:
4650
var parameterContext = (VBAParser.ArgContext)result.Target.Context;
4751
rewriter.InsertAfter(parameterContext.unrestrictedIdentifier().Stop.TokenIndex, asTypeClause);

Rubberduck.Parsing/Symbols/DeclarationSymbolsListener.cs

Lines changed: 12 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -431,12 +431,13 @@ public override void EnterFunctionStmt(VBAParser.FunctionStmtContext context)
431431
return;
432432
}
433433
var name = Identifier.GetName(identifier);
434-
435-
var asTypeClause = context.asTypeClause();
436-
var asTypeName = asTypeClause == null
437-
? Tokens.Variant
438-
: asTypeClause.type().GetText();
439434
var typeHint = Identifier.GetTypeHintValue(identifier);
435+
var asTypeClause = context.asTypeClause();
436+
var asTypeName = typeHint == null
437+
? asTypeClause == null
438+
? Tokens.Variant
439+
: asTypeClause.type().GetText()
440+
: SymbolList.TypeHintToTypeName[typeHint];
440441
var isArray = asTypeName.EndsWith("()");
441442
var declaration = CreateDeclaration(
442443
name,
@@ -462,11 +463,13 @@ public override void EnterPropertyGetStmt(VBAParser.PropertyGetStmtContext conte
462463
var accessibility = GetProcedureAccessibility(context.visibility());
463464
var identifier = context.functionName().identifier();
464465
var name = Identifier.GetName(identifier);
465-
var asTypeClause = context.asTypeClause();
466-
var asTypeName = asTypeClause == null
467-
? Tokens.Variant
468-
: asTypeClause.type().GetText();
469466
var typeHint = Identifier.GetTypeHintValue(identifier);
467+
var asTypeClause = context.asTypeClause();
468+
var asTypeName = typeHint == null
469+
? asTypeClause == null
470+
? Tokens.Variant
471+
: asTypeClause.type().GetText()
472+
: SymbolList.TypeHintToTypeName[typeHint];
470473
var isArray = asTypeClause != null && asTypeClause.type().LPAREN() != null;
471474
var declaration = CreateDeclaration(
472475
name,

RubberduckTests/Inspections/ObsoleteTypeHintInspectionTests.cs

Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -187,6 +187,26 @@ Dim buzz$
187187
Assert.AreEqual(1, inspectionResults.Count());
188188
}
189189

190+
[TestMethod]
191+
[TestCategory("Inspections")]
192+
public void ObsoleteTypeHint_ConstantReturnsResult()
193+
{
194+
const string inputCode =
195+
@"Public Function Foo() As Boolean
196+
Const buzz$ = 0
197+
Foo = True
198+
End Function";
199+
200+
IVBComponent component;
201+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out component);
202+
var state = MockParser.CreateAndParse(vbe.Object);
203+
204+
var inspection = new ObsoleteTypeHintInspection(state);
205+
var inspectionResults = inspection.GetInspectionResults();
206+
207+
Assert.AreEqual(1, inspectionResults.Count());
208+
}
209+
190210
[TestMethod]
191211
[TestCategory("Inspections")]
192212
public void ObsoleteTypeHint_StringValueDoesNotReturnsResult()
@@ -520,6 +540,36 @@ Dim buzz As String
520540
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
521541
}
522542

543+
[TestMethod]
544+
[TestCategory("Inspections")]
545+
public void ObsoleteTypeHint_QuickFixWorks_Constant_StringTypeHint()
546+
{
547+
const string inputCode =
548+
@"Public Sub Foo()
549+
Const buzz$ = """"
550+
End Sub";
551+
552+
const string expectedCode =
553+
@"Public Sub Foo()
554+
Const buzz As String = """"
555+
End Sub";
556+
557+
IVBComponent component;
558+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out component);
559+
var state = MockParser.CreateAndParse(vbe.Object);
560+
561+
var inspection = new ObsoleteTypeHintInspection(state);
562+
var inspectionResults = inspection.GetInspectionResults();
563+
564+
var fix = new RemoveTypeHintsQuickFix(state);
565+
foreach (var result in inspectionResults)
566+
{
567+
fix.Fix(result);
568+
}
569+
570+
Assert.AreEqual(expectedCode, state.GetRewriter(component).GetText());
571+
}
572+
523573
[TestMethod]
524574
[TestCategory("Inspections")]
525575
public void ObsoleteTypeHint_IgnoreQuickFixWorks()

0 commit comments

Comments
 (0)