22using Rubberduck . Parsing . Grammar ;
33using Rubberduck . Parsing . Symbols ;
44using Rubberduck . Parsing . VBA ;
5- using System . Collections . Generic ;
65using System . Diagnostics ;
76using System . Linq ;
87
98namespace Rubberduck . Inspections
109{
1110 public static class VariableRequiresSetAssignmentEvaluator
1211 {
13- public static IEnumerable < Declaration > GetDeclarationsPotentiallyRequiringSetAssignment ( IEnumerable < Declaration > declarations )
14- {
15- //Reduce most of the declaration list with the easy ones
16- var relevantDeclarations = declarations . Where ( dec => dec . AsTypeName == Tokens . Variant
17- || ! SymbolList . ValueTypes . Contains ( dec . AsTypeName )
18- && ( MayRequireAssignmentUsingSet ( dec ) || RequiresAssignmentUsingSet ( dec ) ) ) ;
19-
20- return relevantDeclarations ;
21- }
22-
23- /// <summary>
24- /// Determines whether the 'Set' keyword needs to be added in the context of the specified identifier reference.
25- /// </summary>
26- /// <param name="reference">The identifier reference to analyze</param>
27- /// <param name="state">The parser state</param>
28- public static bool NeedsSetKeywordAdded ( IdentifierReference reference , RubberduckParserState state )
29- {
30- var setStmtContext = reference . Context . GetAncestor < VBAParser . SetStmtContext > ( ) ;
31- return setStmtContext == null && RequiresSetAssignment ( reference , state ) ;
32- }
33-
3412 /// <summary>
3513 /// Determines whether the 'Set' keyword is required (whether it's present or not) for the specified identifier reference.
3614 /// </summary>
@@ -44,20 +22,12 @@ public static bool RequiresSetAssignment(IdentifierReference reference, Rubberdu
4422 return false ;
4523 }
4624
47- var setStmtContext = reference . Context . GetAncestor < VBAParser . SetStmtContext > ( ) ;
48- if ( setStmtContext != null )
25+ if ( reference . IsSetAssignment )
4926 {
5027 // don't assume Set keyword is legit...
5128 return reference . Declaration . IsObject ;
5229 }
5330
54- var letStmtContext = reference . Context . GetAncestor < VBAParser . LetStmtContext > ( ) ;
55- if ( letStmtContext == null )
56- {
57- // not an assignment
58- return false ;
59- }
60-
6131 var declaration = reference . Declaration ;
6232 if ( declaration . IsArray )
6333 {
@@ -66,8 +36,7 @@ public static bool RequiresSetAssignment(IdentifierReference reference, Rubberdu
6636 }
6737
6838 var isObjectVariable = declaration . IsObject ;
69- var isVariant = declaration . IsUndeclared || declaration . AsTypeName == Tokens . Variant ;
70- if ( ! isObjectVariable && ! isVariant )
39+ if ( ! isObjectVariable && ! ( declaration . IsUndeclared || Tokens . Variant . Equals ( declaration . AsTypeName ) ) )
7140 {
7241 return false ;
7342 }
@@ -76,23 +45,24 @@ public static bool RequiresSetAssignment(IdentifierReference reference, Rubberdu
7645 {
7746 // get the members of the returning type, a default member could make us lie otherwise
7847 var classModule = declaration . AsTypeDeclaration as ClassModuleDeclaration ;
79- if ( classModule ? . DefaultMember ! = null )
48+ if ( classModule ? . DefaultMember = = null )
8049 {
81- var parameters = ( classModule . DefaultMember as IParameterizedDeclaration ) ? . Parameters . ToArray ( ) ?? Enumerable . Empty < ParameterDeclaration > ( ) . ToArray ( ) ;
82- if ( ! parameters . Any ( ) || parameters . All ( p => p . IsOptional ) )
83- {
84- // assigned declaration has a default parameterless member, which is legally being assigned here.
85- // might be a good idea to flag that default member assignment though...
86- return false ;
87- }
50+ return true ;
8851 }
89-
52+ var parameters = ( classModule . DefaultMember as IParameterizedDeclaration ) ? . Parameters ;
9053 // assign declaration is an object without a default parameterless (or with all parameters optional) member - LHS needs a 'Set' keyword.
91- return true ;
54+ return parameters != null && parameters . All ( p => p . IsOptional ) ;
9255 }
9356
9457 // assigned declaration is a variant. we need to know about the RHS of the assignment.
9558
59+ var letStmtContext = reference . Context . GetAncestor < VBAParser . LetStmtContext > ( ) ;
60+ if ( letStmtContext == null )
61+ {
62+ // not an assignment
63+ return false ;
64+ }
65+
9666 var expression = letStmtContext . expression ( ) ;
9767 if ( expression == null )
9868 {
@@ -126,69 +96,12 @@ public static bool RequiresSetAssignment(IdentifierReference reference, Rubberdu
12696 return true ;
12797 }
12898
129- var accessibleDeclarations = state . DeclarationFinder . GetAccessibleDeclarations ( reference . ParentScoping ) ;
130- foreach ( var accessibleDeclaration in accessibleDeclarations . Where ( d => d . IdentifierName == expression . GetText ( ) ) )
131- {
132- if ( accessibleDeclaration . DeclarationType . HasFlag ( DeclarationType . ClassModule ) || accessibleDeclaration . AsTypeName == Tokens . Object )
133- {
134- return true ;
135- }
136- }
137-
138- return false ;
139- }
140-
141- private static bool MayRequireAssignmentUsingSet ( Declaration declaration )
142- {
143- if ( declaration . AsTypeName == Tokens . Variant )
144- {
145- return true ;
146- }
147-
148- if ( declaration . IsArray )
149- {
150- return false ;
151- }
152-
153- if ( declaration . AsTypeDeclaration != null )
154- {
155- if ( ( ClassModuleDeclaration . HasDefaultMember ( declaration . AsTypeDeclaration )
156- || declaration . AsTypeDeclaration . DeclarationType == DeclarationType . Enumeration ) )
157- {
158- return false ;
159- }
160- }
161-
162- if ( SymbolList . ValueTypes . Contains ( declaration . AsTypeName ) )
163- {
164- return false ;
165- }
166- return true ;
167- }
168-
169- private static bool RequiresAssignmentUsingSet ( Declaration declaration )
170- {
171- if ( declaration . AsTypeDeclaration != null )
172- {
173- return declaration . AsTypeDeclaration . DeclarationType == DeclarationType . ClassModule
174- && ( ( ( IsVariableOrParameter ( declaration )
175- && ! declaration . IsSelfAssigned )
176- || ( IsMemberWithReturnType ( declaration )
177- && declaration . IsTypeSpecified ) ) ) ;
178- }
179- return false ;
180- }
181-
182- private static bool IsMemberWithReturnType ( Declaration item )
183- {
184- return ( item . DeclarationType == DeclarationType . Function
185- || item . DeclarationType == DeclarationType . PropertyGet ) ;
186- }
187-
188- private static bool IsVariableOrParameter ( Declaration item )
189- {
190- return item . DeclarationType == DeclarationType . Variable
191- || item . DeclarationType == DeclarationType . Parameter ;
99+ // is the reference referring to something else in scope that's a object?
100+ var project = Declaration . GetProjectParent ( reference . ParentScoping ) ;
101+ var module = Declaration . GetModuleParent ( reference . ParentScoping ) ;
102+ return state . DeclarationFinder . MatchName ( expression . GetText ( ) . ToLowerInvariant ( ) )
103+ . Any ( decl => ( decl . DeclarationType . HasFlag ( DeclarationType . ClassModule ) || Tokens . Object . Equals ( decl . AsTypeName ) )
104+ && AccessibilityCheck . IsAccessible ( project , module , reference . ParentScoping , decl ) ) ;
192105 }
193106 }
194107}
0 commit comments