Skip to content

Commit d90726e

Browse files
committed
Fix ObjectVariableNotSet around default members
1 parent 295ecd6 commit d90726e

File tree

1 file changed

+51
-13
lines changed

1 file changed

+51
-13
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableRequiresSetAssignmentEvaluator.cs

Lines changed: 51 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -53,13 +53,7 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
5353
{
5454
// get the members of the returning type, a default member could make us lie otherwise
5555
var classModule = declaration.AsTypeDeclaration as ClassModuleDeclaration;
56-
if (classModule?.DefaultMember == null)
57-
{
58-
return true;
59-
}
60-
var parameters = (classModule.DefaultMember as IParameterizedDeclaration)?.Parameters;
61-
// assign declaration is an object without a default parameterless (or with all parameters optional) member - LHS needs a 'Set' keyword.
62-
return parameters != null && parameters.Any(p => !p.IsOptional);
56+
return !HasPotentiallyNonObjectParameterlessDefaultMember(classModule);
6357
}
6458

6559
// assigned declaration is a variant. we need to know about the RHS of the assignment.
@@ -76,9 +70,30 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
7670
return false;
7771
}
7872

79-
if (expression is VBAParser.NewExprContext)
73+
74+
var module = Declaration.GetModuleParent(reference.ParentScoping);
75+
76+
if (expression is VBAParser.NewExprContext newExpr)
8077
{
81-
// RHS expression is newing up an object reference - LHS needs a 'Set' keyword:
78+
var newTypeExpression = newExpr.expression();
79+
80+
// todo resolve expression type
81+
82+
//Covers the case of a single type on the RHS of the assignment.
83+
var simpleTypeName = newTypeExpression.GetDescendent<VBAParser.SimpleNameExprContext>();
84+
if (simpleTypeName != null && simpleTypeName.GetText() == newTypeExpression.GetText())
85+
{
86+
var qualifiedIdentifierSelection = new QualifiedSelection(module.QualifiedModuleName,
87+
simpleTypeName.identifier().GetSelection());
88+
var identifierText = simpleTypeName.identifier().GetText();
89+
return declarationFinderProvider.DeclarationFinder.IdentifierReferences(qualifiedIdentifierSelection)
90+
.Select(identifierReference => identifierReference.Declaration)
91+
.Where(decl => identifierText == decl.IdentifierName)
92+
.OfType<ClassModuleDeclaration>()
93+
.Any(typeDecl => !HasPotentiallyNonObjectParameterlessDefaultMember(typeDecl));
94+
}
95+
//Here, we err on the side of false-positives, but that seems more appropriate than not to treat qualified type expressions incorrectly.
96+
//Whether there is a legitimate use here for default members is questionable anyway.
8297
return true;
8398
}
8499

@@ -94,8 +109,6 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
94109
}
95110

96111
// todo resolve expression return type
97-
var project = Declaration.GetProjectParent(reference.ParentScoping);
98-
var module = Declaration.GetModuleParent(reference.ParentScoping);
99112

100113
//Covers the case of a single variable on the RHS of the assignment.
101114
var simpleName = expression.GetDescendent<VBAParser.SimpleNameExprContext>();
@@ -104,15 +117,40 @@ public static bool RequiresSetAssignment(IdentifierReference reference, IDeclara
104117
var qualifiedIdentifierSelection = new QualifiedSelection(module.QualifiedModuleName,
105118
simpleName.identifier().GetSelection());
106119
return declarationFinderProvider.DeclarationFinder.IdentifierReferences(qualifiedIdentifierSelection)
107-
.Any(identifierReference => identifierReference.Declaration.IsObject
108-
&& simpleName.identifier().GetText() == identifierReference.Declaration.IdentifierName);
120+
.Select(identifierReference => identifierReference.Declaration)
121+
.Where(decl => decl.IsObject
122+
&& simpleName.identifier().GetText() == decl.IdentifierName)
123+
.Select(typeDeclaration => typeDeclaration.AsTypeDeclaration as ClassModuleDeclaration)
124+
.Any(typeDecl => !HasPotentiallyNonObjectParameterlessDefaultMember(typeDecl));
109125
}
110126

127+
var project = Declaration.GetProjectParent(reference.ParentScoping);
128+
111129
//todo: Use code path analysis to ensure that we are really picking up the last assignment to the RHS.
112130
// is the reference referring to something else in scope that's a object?
113131
return declarationFinderProvider.DeclarationFinder.MatchName(expression.GetText())
114132
.Any(decl => (decl.DeclarationType.HasFlag(DeclarationType.ClassModule) || Tokens.Object.Equals(decl.AsTypeName))
115133
&& AccessibilityCheck.IsAccessible(project, module, reference.ParentScoping, decl));
116134
}
135+
136+
private static bool HasPotentiallyNonObjectParameterlessDefaultMember(ClassModuleDeclaration classModule)
137+
{
138+
var defaultMember = classModule?.DefaultMember;
139+
140+
if (defaultMember == null)
141+
{
142+
return false;
143+
}
144+
145+
var parameters = (defaultMember as IParameterizedDeclaration)?.Parameters;
146+
// assign declaration is an object without a default parameterless (or with all parameters optional) member - LHS needs a 'Set' keyword.
147+
if (parameters != null && parameters.Any(p => !p.IsOptional))
148+
{
149+
return false;
150+
}
151+
152+
var defaultMemberType = defaultMember.AsTypeDeclaration as ClassModuleDeclaration;
153+
return defaultMemberType == null || HasPotentiallyNonObjectParameterlessDefaultMember(defaultMemberType);
154+
}
117155
}
118156
}

0 commit comments

Comments
 (0)