Skip to content

Commit a6e22e0

Browse files
committed
Add type resolution for ReDim declared arrays
Previously, any as type clause or type hint was ignored, leading to inspection false positives and wrong resolution of members of array elements. The solution adds a copy of the type resolution on the spot where the ReDim declared arrays are added as pseudo-undeclared variables. This requires to generate the expression parser and binding service each time and to hardcode them. This is not ideal, but it should be solved when extracting the entire logic for undeclared variables out of the declaration finder.
1 parent fb636e4 commit a6e22e0

File tree

2 files changed

+163
-7
lines changed

2 files changed

+163
-7
lines changed

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 137 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@
1111
using Rubberduck.Parsing.Grammar;
1212
using Rubberduck.Parsing.Symbols;
1313
using Rubberduck.Parsing.VBA.Extensions;
14+
using Rubberduck.Parsing.VBA.Parsing;
1415
using Rubberduck.Parsing.VBA.ReferenceManagement;
1516
using Rubberduck.VBEditor;
1617
using Rubberduck.VBEditor.SafeComWrappers;
@@ -971,12 +972,44 @@ public Declaration FindMemberEnclosingProcedure(Declaration enclosingProcedure,
971972
return null;
972973
}
973974

975+
//TODO: ove this out of the DeclarationFinder into a class only responsible for reference resolution.
974976
public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string identifierName, ParserRuleContext context)
975977
{
976978
var annotations = FindAnnotations(enclosingProcedure.QualifiedName.QualifiedModuleName, context.Start.Line,AnnotationTarget.Identifier);
977979
var isReDimVariable = IsContainedInReDimedArrayName(context);
978-
var undeclaredLocal =
979-
new Declaration(
980+
981+
Declaration undeclaredLocal;
982+
if (IsContainedInReDimedArrayName(context))
983+
{
984+
var asTypeClause = AsTypeClauseForReDimDeclaredArray(context);
985+
var typeHint = TypeHintForReDimDeclaredArray(context);
986+
var asTypeName = AsTypeNameForReDimDeclaredArray(asTypeClause, typeHint);
987+
988+
undeclaredLocal = new Declaration(
989+
new QualifiedMemberName(enclosingProcedure.QualifiedName.QualifiedModuleName, identifierName),
990+
enclosingProcedure,
991+
enclosingProcedure,
992+
asTypeName,
993+
typeHint,
994+
false,
995+
false,
996+
Accessibility.Implicit,
997+
DeclarationType.Variable,
998+
context,
999+
null,
1000+
context.GetSelection(),
1001+
true,
1002+
asTypeClause,
1003+
true,
1004+
annotations,
1005+
null,
1006+
false);
1007+
1008+
ResolveTypeForReDimDeclaredArray(undeclaredLocal);
1009+
}
1010+
else
1011+
{
1012+
undeclaredLocal = new Declaration(
9801013
new QualifiedMemberName(enclosingProcedure.QualifiedName.QualifiedModuleName, identifierName),
9811014
enclosingProcedure,
9821015
enclosingProcedure,
@@ -989,12 +1022,13 @@ public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string i
9891022
context,
9901023
null,
9911024
context.GetSelection(),
992-
isReDimVariable,
1025+
false,
9931026
null,
9941027
true,
9951028
annotations,
9961029
null,
997-
!isReDimVariable);
1030+
true);
1031+
}
9981032

9991033
var enclosingScope = (enclosingProcedure.QualifiedName, enclosingProcedure.DeclarationType);
10001034
var hasUndeclared = _newUndeclared.ContainsKey(enclosingScope);
@@ -1021,11 +1055,107 @@ public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string i
10211055

10221056
private static bool IsContainedInReDimedArrayName(ParserRuleContext context)
10231057
{
1024-
var enclosingReDimContext = context.GetAncestor<VBAParser.RedimVariableDeclarationContext>();
1025-
return enclosingReDimContext != null
1026-
&& enclosingReDimContext.expression().GetSelection().Contains(context.GetSelection());
1058+
return ContainingReDimContext(context) != null;
1059+
}
1060+
1061+
private static VBAParser.RedimVariableDeclarationContext ContainingReDimContext(ParserRuleContext context)
1062+
{
1063+
var enclosingReDimContextCandidate = context.GetAncestor<VBAParser.RedimVariableDeclarationContext>();
1064+
return enclosingReDimContextCandidate == null
1065+
|| !enclosingReDimContextCandidate.expression().GetSelection().Contains(context.GetSelection())
1066+
? null
1067+
: enclosingReDimContextCandidate;
1068+
}
1069+
1070+
private VBAParser.AsTypeClauseContext AsTypeClauseForReDimDeclaredArray(ParserRuleContext context)
1071+
{
1072+
return ContainingReDimContext(context)?.asTypeClause();
1073+
}
1074+
1075+
private string TypeHintForReDimDeclaredArray(ParserRuleContext context)
1076+
{
1077+
if (context is VBAParser.SimpleNameExprContext simpleNameContext)
1078+
{
1079+
var identifier = simpleNameContext.identifier();
1080+
return identifier != null
1081+
? Identifier.GetTypeHintValue(identifier)
1082+
: null;
1083+
}
1084+
1085+
return null;
1086+
}
1087+
1088+
private static string AsTypeNameForReDimDeclaredArray(VBAParser.AsTypeClauseContext asTypeClause, string typeHint)
1089+
{
1090+
return typeHint == null
1091+
? asTypeClause == null
1092+
? Tokens.Variant
1093+
: asTypeClause.type().GetText()
1094+
: SymbolList.TypeHintToTypeName[typeHint];
1095+
}
1096+
1097+
//note: This is copied from the TypeAnnotationPass.
1098+
//TODO: Extract common logic from TypeAnnotationPass and inject that. (Requires extracting the calling code out of the DeclarationFinder.)
1099+
private void ResolveTypeForReDimDeclaredArray(Declaration declaration)
1100+
{
1101+
if(string.IsNullOrWhiteSpace(declaration.AsTypeName)
1102+
|| declaration.AsTypeIsBaseType)
1103+
{
1104+
return;
1105+
}
1106+
1107+
string typeExpression;
1108+
if (declaration.AsTypeContext != null && declaration.AsTypeContext.type().complexType() != null)
1109+
{
1110+
var typeContext = declaration.AsTypeContext;
1111+
typeExpression = typeContext.type().complexType().GetText();
1112+
}
1113+
else if (!string.IsNullOrWhiteSpace(declaration.AsTypeNameWithoutArrayDesignator) && !SymbolList.BaseTypes.Contains(declaration.AsTypeNameWithoutArrayDesignator.ToUpperInvariant()))
1114+
{
1115+
typeExpression = declaration.AsTypeNameWithoutArrayDesignator;
1116+
}
1117+
else
1118+
{
1119+
return;
1120+
}
1121+
1122+
var module = Declaration.GetModuleParent(declaration);
1123+
if (module == null)
1124+
{
1125+
Logger.Warn("Type annotation failed for {0} because module parent is missing.", typeExpression);
1126+
return;
1127+
}
1128+
1129+
var (bindingService, expressionParser) = TypeAnnotationServices();
1130+
1131+
var expressionContext = expressionParser.Parse(typeExpression.Trim());
1132+
var boundExpression = bindingService.ResolveType(module, declaration.ParentDeclaration, expressionContext);
1133+
if (boundExpression.Classification != ExpressionClassification.ResolutionFailed)
1134+
{
1135+
declaration.AsTypeDeclaration = boundExpression.ReferencedDeclaration;
1136+
}
1137+
else
1138+
{
1139+
const string IGNORE_THIS = "DISPATCH";
1140+
if (typeExpression != IGNORE_THIS)
1141+
{
1142+
Logger.Warn("Failed to resolve type {0}", typeExpression);
1143+
}
1144+
}
10271145
}
10281146

1147+
private (BindingService bindingservice, VBAExpressionParser expressionParser) TypeAnnotationServices()
1148+
{
1149+
var typeBindingContext = new TypeBindingContext(this);
1150+
var procedurePointerBindingContext = new ProcedurePointerBindingContext(this);
1151+
var bindingService = new BindingService(
1152+
this,
1153+
new DefaultBindingContext(this, typeBindingContext, procedurePointerBindingContext),
1154+
typeBindingContext,
1155+
procedurePointerBindingContext);
1156+
var expressionParser = new VBAExpressionParser();
1157+
return (bindingService, expressionParser);
1158+
}
10291159

10301160
public void AddUnboundContext(Declaration parentDeclaration, VBAParser.LExpressionContext context, IBoundExpression withExpression)
10311161
{

RubberduckTests/Inspections/VariableTypeNotDeclaredInspectionTests.cs

Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -117,6 +117,32 @@ public void VariableTypeNotDeclared_Const_DoesNotReturnResult()
117117
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
118118
}
119119

120+
[Test]
121+
[Category("Inspections")]
122+
[TestCase("Variant")]
123+
[TestCase("Long")]
124+
public void VariableTypeNotDeclared_TypedArray_Dim_DoesNotReturnResult(string variableType)
125+
{
126+
var inputCode =
127+
$@"Sub Foo()
128+
Dim bar(0 To 1) As {variableType}
129+
End Sub";
130+
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
131+
}
132+
133+
[Test]
134+
[Category("Inspections")]
135+
[TestCase("Variant")]
136+
[TestCase("Long")]
137+
public void VariableTypeNotDeclared_TypedArray_ReDim_DoesNotReturnResult(string variableType)
138+
{
139+
var inputCode =
140+
$@"Sub Foo()
141+
ReDim bar(0 To 1) As {variableType}
142+
End Sub";
143+
Assert.AreEqual(0, InspectionResultsForStandardModule(inputCode).Count());
144+
}
145+
120146
[Test]
121147
[Category("Inspections")]
122148
public void InspectionName()

0 commit comments

Comments
 (0)