Skip to content

Commit 94d8596

Browse files
committed
Add ValueRequiredInspection
This inspection finds failed Let coercion accesses. Now, the failed Let coercion references carry the declaration of the member on which the coercion failed. An analogous statement holds for unbound default member accesses. In addition, this commit fixes the cache invalidation for failed let coercions and unbound default member accesses.
1 parent 68355cb commit 94d8596

19 files changed

+596
-36
lines changed
Lines changed: 106 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,106 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Inspections.Extensions;
5+
using Rubberduck.Inspections.Results;
6+
using Rubberduck.Parsing.Inspections;
7+
using Rubberduck.Parsing.Inspections.Abstract;
8+
using Rubberduck.Parsing.Symbols;
9+
using Rubberduck.Parsing.VBA;
10+
using Rubberduck.Resources.Inspections;
11+
12+
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
13+
{
14+
/// <summary>
15+
/// Locates places in which a value needs to be accessed but an object variables has been provided that does not have a suitable default member.
16+
/// </summary>
17+
/// <why>
18+
/// The VBA compiler does not check whether the necessary default member is present. Instead there is a runtime error whenever the runtime type fails to have the default member.
19+
/// </why>
20+
/// <example hasResult="true">
21+
/// <![CDATA[
22+
/// Class1:
23+
///
24+
/// Public Function Foo() As Long
25+
/// 'No default member attribute
26+
/// End Function
27+
///
28+
/// ------------------------------
29+
/// Module1:
30+
///
31+
/// Public Sub DoIt()
32+
/// Dim cls As Class1
33+
/// Dim bar As Variant
34+
///
35+
/// Set cls = New Class1
36+
/// bar = cls + 42
37+
/// End Sub
38+
/// ]]>
39+
/// </example>
40+
/// <example hasResult="false">
41+
/// <![CDATA[
42+
/// Class1:
43+
///
44+
/// Public Function Foo() As Long
45+
/// Attribute Foo.UserMemId = 0
46+
/// End Function
47+
///
48+
/// ------------------------------
49+
/// Module1:
50+
///
51+
/// Public Sub DoIt()
52+
/// Dim cls As Class1
53+
/// Dim bar As Variant
54+
///
55+
/// Set cls = New Class1
56+
/// bar = cls + 42
57+
/// End Sub
58+
/// ]]>
59+
/// </example>
60+
public class ValueRequiredInspection : InspectionBase
61+
{
62+
private readonly IDeclarationFinderProvider _declarationFinderProvider;
63+
64+
public ValueRequiredInspection(RubberduckParserState state)
65+
: base(state)
66+
{
67+
_declarationFinderProvider = state;
68+
69+
//This will most likely cause a runtime error. The exceptions are rare and should be refactored or made explicit with an @Ignore annotation.
70+
Severity = CodeInspectionSeverity.Error;
71+
}
72+
73+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
74+
{
75+
var finder = _declarationFinderProvider.DeclarationFinder;
76+
77+
//Assignments are already covered by the ObjectVariableNotSetInspection.
78+
var failedLetCoercionAccesses = finder.FailedLetCoercions()
79+
.Where(failedLetCoercion => !failedLetCoercion.IsAssignment);
80+
81+
return failedLetCoercionAccesses
82+
.Where(failedLetCoercion => !IsIgnored(failedLetCoercion))
83+
.Select(failedLetCoercion => InspectionResult(failedLetCoercion, _declarationFinderProvider));
84+
}
85+
86+
private bool IsIgnored(IdentifierReference assignment)
87+
{
88+
return assignment.IsIgnoringInspectionResultFor(AnnotationName);
89+
}
90+
91+
private IInspectionResult InspectionResult(IdentifierReference failedLetCoercion, IDeclarationFinderProvider declarationFinderProvider)
92+
{
93+
return new IdentifierReferenceInspectionResult(this,
94+
ResultDescription(failedLetCoercion),
95+
declarationFinderProvider,
96+
failedLetCoercion);
97+
}
98+
99+
private string ResultDescription(IdentifierReference failedLetCoercion)
100+
{
101+
var expression = failedLetCoercion.IdentifierName;
102+
var typeName = failedLetCoercion.Declaration?.FullAsTypeName;
103+
return string.Format(InspectionResults.ValueRequiredInspection, expression, typeName);
104+
}
105+
}
106+
}

Rubberduck.Parsing/Binding/Bindings/LetCoercionDefaultBinding.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -85,9 +85,8 @@ private static IBoundExpression Resolve(IBoundExpression wrappedExpression, Pars
8585

8686
private static IBoundExpression ExpressionForResolutionFailure(IBoundExpression wrappedExpression, ParserRuleContext expression)
8787
{
88-
var contextTExt = expression.GetText();
8988
//We return a LetCoercionExpression classified as failed to enable us to save this failed coercion.
90-
return new LetCoercionDefaultMemberAccessExpression(null, ExpressionClassification.ResolutionFailed, expression, wrappedExpression, 1, null);
89+
return new LetCoercionDefaultMemberAccessExpression(wrappedExpression.ReferencedDeclaration, ExpressionClassification.ResolutionFailed, expression, wrappedExpression, 1, null);
9190
}
9291

9392
private static IBoundExpression ResolveViaDefaultMember(IBoundExpression wrappedExpression, string asTypeName, Declaration asTypeDeclaration, ParserRuleContext expression, bool isAssignment, int recursionDepth = 1, RecursiveDefaultMemberAccessExpression containedExpression = null)
@@ -96,7 +95,7 @@ private static IBoundExpression ResolveViaDefaultMember(IBoundExpression wrapped
9695
|| Tokens.Object.Equals(asTypeName, StringComparison.InvariantCultureIgnoreCase))
9796
{
9897
// We cannot know the the default member in this case, so return an unbound member call.
99-
return new LetCoercionDefaultMemberAccessExpression(null, ExpressionClassification.Unbound, expression, wrappedExpression, recursionDepth, containedExpression);
98+
return new LetCoercionDefaultMemberAccessExpression(wrappedExpression.ReferencedDeclaration, ExpressionClassification.Unbound, expression, wrappedExpression, recursionDepth, containedExpression);
10099
}
101100

102101
var defaultMember = (asTypeDeclaration as ClassModuleDeclaration)?.DefaultMember;

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1563,7 +1563,7 @@ public IReadOnlyCollection<IdentifierReference> FailedLetCoercions(QualifiedModu
15631563
public IEnumerable<IdentifierReference> FailedLetCoercions()
15641564
{
15651565
return _failedLetCoercions.Values
1566-
.SelectMany(defaultMemberAccess => defaultMemberAccess);
1566+
.SelectMany(coercion => coercion);
15671567
}
15681568
}
15691569
}

Rubberduck.Parsing/VBA/ModuleState.cs

Lines changed: 15 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System;
22
using System.Collections.Concurrent;
33
using System.Collections.Generic;
4+
using System.Linq;
45
using Antlr4.Runtime;
56
using Antlr4.Runtime.Tree;
67
using Rubberduck.Parsing.Annotations;
@@ -25,8 +26,8 @@ public class ModuleState
2526
public SyntaxErrorException ModuleException { get; private set; }
2627
public IDictionary<(string scopeIdentifier, DeclarationType scopeType), Attributes> ModuleAttributes { get; private set; }
2728
public IDictionary<(string scopeIdentifier, DeclarationType scopeType), ParserRuleContext> MembersAllowingAttributes { get; private set; }
28-
public IReadOnlyCollection<IdentifierReference> UnboundDefaultMemberAccesses => _unboundDefaultMemberAccesses;
29-
public IReadOnlyCollection<IdentifierReference> FailedLetCoercions => _failedLetCoercions;
29+
public IReadOnlyCollection<IdentifierReference> UnboundDefaultMemberAccesses => _unboundDefaultMemberAccesses.ToList();
30+
public IReadOnlyCollection<IdentifierReference> FailedLetCoercions => _failedLetCoercions.ToList();
3031

3132
public bool IsNew { get; private set; }
3233
public bool IsMarkedAsModified { get; private set; }
@@ -158,7 +159,6 @@ public ModuleState SetAttributesTokenStream(ITokenStream attributesTokenStream)
158159
public ModuleState AddUnboundDefaultMemberAccess(IdentifierReference defaultMemberAccess)
159160
{
160161
if (defaultMemberAccess.IsDefaultMemberAccess
161-
&& defaultMemberAccess.Declaration == null
162162
&& !_unboundDefaultMemberAccesses.Contains(defaultMemberAccess))
163163
{
164164
_unboundDefaultMemberAccesses.Add(defaultMemberAccess);
@@ -167,10 +167,14 @@ public ModuleState AddUnboundDefaultMemberAccess(IdentifierReference defaultMemb
167167
return this;
168168
}
169169

170+
public void ClearUnboundDefaultMemberAccesses()
171+
{
172+
_unboundDefaultMemberAccesses.Clear();
173+
}
174+
170175
public ModuleState AddFailedLetCoercion(IdentifierReference failedLetCoercion)
171176
{
172177
if (failedLetCoercion.IsDefaultMemberAccess
173-
&& failedLetCoercion.Declaration == null
174178
&& !_failedLetCoercions.Contains(failedLetCoercion))
175179
{
176180
_failedLetCoercions.Add(failedLetCoercion);
@@ -179,6 +183,11 @@ public ModuleState AddFailedLetCoercion(IdentifierReference failedLetCoercion)
179183
return this;
180184
}
181185

186+
public void ClearFailedLetCoercions()
187+
{
188+
_failedLetCoercions.Clear();
189+
}
190+
182191
public void MarkAsModified()
183192
{
184193
IsMarkedAsModified = true;
@@ -197,6 +206,8 @@ public void Dispose()
197206
Comments?.Clear();
198207
Annotations?.Clear();
199208
ModuleAttributes?.Clear();
209+
_unboundDefaultMemberAccesses?.Clear();
210+
_failedLetCoercions?.Clear();
200211

201212
_isDisposed = true;
202213
}

Rubberduck.Parsing/VBA/ReferenceManagement/BoundExpressionVisitor.cs

Lines changed: 14 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -499,18 +499,21 @@ private void Visit(
499499

500500
Visit(expression.WrappedExpression, module, scope, parent);
501501

502-
if (expression.Classification != ExpressionClassification.Unbound
503-
&& expression.ReferencedDeclaration != null)
504-
{
505-
AddDefaultMemberReference(expression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement);
506-
}
507-
else if (expression.Classification == ExpressionClassification.ResolutionFailed)
508-
{
509-
AddFailedLetCoercionReference(expression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement);
510-
}
511-
else
502+
switch (expression.Classification)
512503
{
513-
AddUnboundDefaultMemberReference(expression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement);
504+
case ExpressionClassification.ResolutionFailed:
505+
AddFailedLetCoercionReference(expression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement);
506+
break;
507+
case ExpressionClassification.Unbound:
508+
AddUnboundDefaultMemberReference(expression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement);
509+
break;
510+
default:
511+
if (expression.ReferencedDeclaration != null)
512+
{
513+
AddDefaultMemberReference(expression, module, scope, parent, isAssignmentTarget, hasExplicitLetStatement);
514+
}
515+
516+
break;
514517
}
515518
}
516519

Rubberduck.Parsing/VBA/ReferenceManagement/ReferenceResolveRunnerBase.cs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -125,6 +125,11 @@ private void PerformPreResolveCleanup(IReadOnlyCollection<QualifiedModuleName> t
125125
_referenceRemover.RemoveReferencesBy(toResolve, token);
126126
_moduleToModuleReferenceManager.ClearModuleToModuleReferencesFromModule(toResolve);
127127
_moduleToModuleReferenceManager.ClearModuleToModuleReferencesToModule(toResolve);
128+
foreach (var module in toResolve)
129+
{
130+
_state.ClearUnboundDefaultMemberAccesses(module);
131+
_state.ClearFailedLetCoercions(module);
132+
}
128133
}
129134

130135
private void ExecuteCompilationPasses(IReadOnlyCollection<QualifiedModuleName> modules, CancellationToken token)

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 18 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -193,7 +193,7 @@ private void RefreshFinder(IHostApplication host)
193193
DeclarationFinder = _declarationFinderFactory.Create(
194194
AllDeclarationsFromModuleStates,
195195
AllAnnotations,
196-
AllUnresolvedMemberDeclarationsFromModulestates,
196+
AllUnresolvedMemberDeclarationsFromModuleStates,
197197
AllUnboundDefaultMemberAccessesFromModuleStates,
198198
AllFailedLetCoercionsFromModuleStates,
199199
host);
@@ -739,7 +739,7 @@ private bool ThereAreDeclarations()
739739
/// <summary>
740740
/// Gets a copy of the unresolved member declarations directly from the module states. (Used for refreshing the DeclarationFinder.)
741741
/// </summary>
742-
private IReadOnlyList<UnboundMemberDeclaration> AllUnresolvedMemberDeclarationsFromModulestates
742+
private IReadOnlyList<UnboundMemberDeclaration> AllUnresolvedMemberDeclarationsFromModuleStates
743743
{
744744
get
745745
{
@@ -874,6 +874,14 @@ public void AddUnboundDefaultMemberAccesses(QualifiedModuleName module, IEnumera
874874
}
875875
}
876876

877+
public void ClearUnboundDefaultMemberAccesses(QualifiedModuleName module)
878+
{
879+
if (_moduleStates.TryGetValue(module, out var moduleState))
880+
{
881+
moduleState.ClearUnboundDefaultMemberAccesses();
882+
}
883+
}
884+
877885
public void AddFailedLetCoercions(QualifiedModuleName module, IEnumerable<IdentifierReference> failedLetCoercions)
878886
{
879887
var moduleState = _moduleStates.GetOrAdd(module, new ModuleState(new ConcurrentDictionary<Declaration, byte>()));
@@ -883,6 +891,14 @@ public void AddFailedLetCoercions(QualifiedModuleName module, IEnumerable<Identi
883891
}
884892
}
885893

894+
public void ClearFailedLetCoercions(QualifiedModuleName module)
895+
{
896+
if (_moduleStates.TryGetValue(module, out var moduleState))
897+
{
898+
moduleState.ClearFailedLetCoercions();
899+
}
900+
}
901+
886902
public void ClearStateCache(string projectId)
887903
{
888904
try

Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs

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

Rubberduck.Resources/Inspections/InspectionInfo.de.resx

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -386,12 +386,15 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
386386
<value>Der VBA-Compiler gibt keinen Fehler aus, wenn ein Objekt einer Variables Set-zugewiesen wird mit einem inkompatiblen Objekttype, d.h. deren Typ weder identisch, ein Subtyp noch ein Supertyp ist. In fast allen Fällen führt dies zu einem Laufzeitfehler, der schwerer zu entdecken ist und auf einen Programmierfehler hinweist. In allen anderen Fällen kann der Quallcode so geändert werden, dass er ausschließlich Zuweisungen zwischen kompatiblen deklarierten Typen verwendet.</value>
387387
</data>
388388
<data name="ArgumentWithIncompatibleObjectTypeInspection" xml:space="preserve">
389-
<value>Der VBA-Compiler gibt keinen Fehler aus, wenn ein Objekt als Argument für einen Parameter übergeben wird mit einem inkompatiblen Objekttype, d.h. dessen Typ weder identisch, ein Subtyp noch ein Supertyp ist. In fast allen Fällen führt dies zu einem Laufzeitfehler, der schwerer zu entdecken ist und auf einen Programmierfehler hinweist. In allen anderen Fällen kann der Quallcode so geändert werden, dass er ausschließlich Zuweisungen zwischen kompatiblen deklarierten Typen verwendet.</value>
389+
<value>Der VBA-Compiler gibt keinen Fehler aus, wenn ein Objekt als Argument für einen Parameter übergeben wird mit einem inkompatiblen Objekttype, d.h. dessen Typ weder identisch, ein Subtyp noch ein Supertyp ist. In fast allen Fällen führt dies zu einem Laufzeitfehler, der schwerer zu entdecken ist und auf einen Programmierfehler hinweist. In allen anderen Fällen kann der Quallcode so geändert werden, dass ausschließlich Argumente mit kompatiblen deklarierten Typen verwendet werden.</value>
390390
</data>
391391
<data name="EmptyMethodInspection" xml:space="preserve">
392392
<value>Methoden ohne ausführbare Anweisungen können den Eindruck erwecken, dass sie etwas tun, was sie eigentlich nicht tun. Dies kann zu unerwartetem Verhalten führen.</value>
393393
</data>
394394
<data name="ImplementedInterfaceMemberInspection" xml:space="preserve">
395395
<value>Eine Klasse, die dafür gedacht ist von anderen Klassen als Interface genutzt zu werden, sollte gewöhnlicher Weise keine Implementierungen enthalten. Falls die Intention ist diese Klasse direkt als konkrete Klasse zu verwenden, kann dieses Inspektionsresultat ignoriert werden.</value>
396396
</data>
397+
<data name="ValueRequiredInspection" xml:space="preserve">
398+
<value>Der VBA-Compiler gibt keinen Fehler aus, wenn ein Objekt an einer Stelle verwendet wird, die einen Wert verlangt, und der deklarierte Type des Objekts keinen passenden Standardmember hat. In fast allen Fällen führt dies zu einem Laufzeitfehler, der schwerer zu entdecken ist und auf einen Programmierfehler hinweist.</value>
399+
</data>
397400
</root>

0 commit comments

Comments
 (0)