Skip to content

Commit 80948b8

Browse files
authored
Merge pull request #5089 from MDoerner/ResolveParameterlessDefaultMemberAccesses
Resolve recursive and parameterless default member accesses
2 parents 4164774 + 02bda4f commit 80948b8

File tree

64 files changed

+3794
-570
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

64 files changed

+3794
-570
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignedByValParameterInspection.cs

Lines changed: 1 addition & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -48,43 +48,12 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4848
.Cast<ParameterDeclaration>()
4949
.Where(item => !item.IsByRef
5050
&& !item.IsIgnoringInspectionResultFor(AnnotationName)
51-
&& item.References.Any(IsAssignmentToDeclaration));
51+
&& item.References.Any(reference => reference.IsAssignment));
5252

5353
return parameters
5454
.Select(param => new DeclarationInspectionResult(this,
5555
string.Format(InspectionResults.AssignedByValParameterInspection, param.IdentifierName),
5656
param));
5757
}
58-
59-
private static bool IsAssignmentToDeclaration(IdentifierReference reference)
60-
{
61-
//Todo: Review whether this is still needed once parameterless default member assignments are resolved correctly.
62-
63-
if (!reference.IsAssignment)
64-
{
65-
return false;
66-
}
67-
68-
if (reference.IsSetAssignment)
69-
{
70-
return true;
71-
}
72-
73-
var declaration = reference.Declaration;
74-
if (declaration == null)
75-
{
76-
return false;
77-
}
78-
79-
if (declaration.IsObject)
80-
{
81-
//This can only be legal with a default member access.
82-
return false;
83-
}
84-
85-
//This is not perfect in case the referenced declaration is an unbound Variant.
86-
//In that case, a default member access might occur after the run-time resolution.
87-
return true;
88-
}
8958
}
9059
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAssignmentInspection.cs

Lines changed: 34 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,7 @@
11
using System.Collections.Generic;
2-
using System.Diagnostics;
32
using System.Linq;
43
using Rubberduck.Inspections.Abstract;
54
using Rubberduck.Inspections.Results;
6-
using Rubberduck.Parsing;
7-
using Rubberduck.Parsing.Grammar;
85
using Rubberduck.Parsing.Inspections.Abstract;
96
using Rubberduck.Resources.Inspections;
107
using Rubberduck.Parsing.Symbols;
@@ -40,28 +37,42 @@ public ImplicitDefaultMemberAssignmentInspection(RubberduckParserState state)
4037

4138
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4239
{
43-
var interestingDeclarations =
44-
State.AllDeclarations.Where(item =>
45-
item.AsTypeDeclaration != null
46-
&& ClassModuleDeclaration.HasDefaultMember(item.AsTypeDeclaration));
40+
var boundDefaultMemberAssignments = State.DeclarationFinder
41+
.AllIdentifierReferences()
42+
.Where(IsRelevantReference);
4743

48-
var interestingReferences = interestingDeclarations
49-
.SelectMany(declaration => declaration.References)
50-
.Where(reference =>
51-
{
52-
var letStmtContext = reference.Context.GetAncestor<VBAParser.LetStmtContext>();
53-
return reference.IsAssignment
54-
&& letStmtContext != null
55-
&& letStmtContext.LET() == null
56-
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
57-
});
44+
var boundIssues = boundDefaultMemberAssignments
45+
.Select(reference => new IdentifierReferenceInspectionResult(
46+
this,
47+
string.Format(
48+
InspectionResults.ImplicitDefaultMemberAssignmentInspection,
49+
reference.Context.GetText(),
50+
reference.Declaration.IdentifierName,
51+
reference.Declaration.QualifiedModuleName.ToString()),
52+
State,
53+
reference));
5854

59-
return interestingReferences.Select(reference => new IdentifierReferenceInspectionResult(this,
60-
string.Format(InspectionResults.ImplicitDefaultMemberAssignmentInspection,
61-
reference.Declaration.IdentifierName,
62-
reference.Declaration.AsTypeDeclaration.IdentifierName),
63-
State,
64-
reference));
55+
var unboundDefaultMemberAssignments = State.DeclarationFinder
56+
.AllUnboundDefaultMemberAccesses()
57+
.Where(IsRelevantReference);
58+
59+
var unboundIssues = unboundDefaultMemberAssignments
60+
.Select(reference => new IdentifierReferenceInspectionResult(
61+
this,
62+
string.Format(
63+
InspectionResults.ImplicitDefaultMemberAssignmentInspection_Unbound,
64+
reference.Context.GetText()),
65+
State,
66+
reference));
67+
68+
return boundIssues.Concat(unboundIssues);
69+
}
70+
71+
private bool IsRelevantReference(IdentifierReference reference)
72+
{
73+
return reference.IsAssignment
74+
&& reference.IsNonIndexedDefaultMemberAccess
75+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
6576
}
6677
}
6778
}
Lines changed: 68 additions & 65 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,9 @@
1+
using System;
12
using Rubberduck.Parsing;
23
using Rubberduck.Parsing.Symbols;
34
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
45
using Rubberduck.Resources;
6+
using Rubberduck.VBEditor;
57

68
namespace Rubberduck.UI.Command.MenuItems.CommandBars
79
{
@@ -46,96 +48,97 @@ public string Format(Declaration declaration, bool multipleControls)
4648

4749
private string FormatDeclaration(Declaration declaration, bool multipleControls = false)
4850
{
49-
var formattedDeclaration = string.Empty;
5051
var moduleName = declaration.QualifiedName.QualifiedModuleName;
51-
var typeName = declaration.HasTypeHint
52-
? SymbolList.TypeHintToTypeName[declaration.TypeHint]
53-
: declaration.AsTypeName;
5452
var declarationType = RubberduckUI.ResourceManager.GetString("DeclarationType_" + declaration.DeclarationType, Settings.Settings.Culture);
5553

56-
if (multipleControls)
57-
{
58-
typeName = RubberduckUI.ContextMultipleControlsSelection;
59-
}
60-
else if (declaration is ValuedDeclaration)
61-
{
62-
var valued = (ValuedDeclaration)declaration;
63-
typeName = "(" + declarationType + (string.IsNullOrEmpty(typeName) ? string.Empty : ":" + typeName) +
64-
(string.IsNullOrEmpty(valued.Expression) ? string.Empty : $" = {valued.Expression}") + ")";
54+
var typeName = TypeName(declaration, multipleControls, declarationType);
55+
var formattedDeclaration = FormattedDeclaration(declaration, typeName, moduleName, declarationType);
56+
return formattedDeclaration.Trim();
57+
}
6558

66-
}
67-
else if (declaration is ParameterDeclaration)
68-
{
69-
var parameter = (ParameterDeclaration)declaration;
70-
typeName = "(" + declarationType + (string.IsNullOrEmpty(typeName) ? string.Empty : ":" + typeName) +
71-
(string.IsNullOrEmpty(parameter.DefaultValue) ? string.Empty : $" = {parameter.DefaultValue}") + ")";
72-
}
73-
else
59+
private static string FormattedDeclaration(
60+
Declaration declaration,
61+
string typeName,
62+
QualifiedModuleName moduleName,
63+
string declarationType)
64+
{
65+
if (declaration.ParentDeclaration != null)
7466
{
75-
typeName = "(" + declarationType + (string.IsNullOrEmpty(typeName) ? string.Empty : ":" + typeName) + ")";
76-
}
67+
if (declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Member))
68+
{
69+
// locals, parameters
70+
return $"{declaration.ParentDeclaration.QualifiedName}:{declaration.IdentifierName} {typeName}";
71+
}
72+
73+
if (declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
74+
{
75+
// fields
76+
var withEvents = declaration.IsWithEvents ? "(WithEvents) " : string.Empty;
77+
return $"{withEvents}{moduleName}.{declaration.IdentifierName} {typeName}";
78+
}
79+
}
7780

78-
if (declaration.DeclarationType.HasFlag(DeclarationType.Project) || declaration.DeclarationType == DeclarationType.BracketedExpression)
79-
{
80-
var filename = System.IO.Path.GetFileName(declaration.QualifiedName.QualifiedModuleName.ProjectPath);
81-
formattedDeclaration = string.Format("{0}{1}{2} ({3})", filename, string.IsNullOrEmpty(filename) ? string.Empty : ";", declaration.IdentifierName, declarationType);
82-
}
83-
else if (declaration.DeclarationType.HasFlag(DeclarationType.Module))
84-
{
85-
formattedDeclaration = moduleName + " (" + declarationType + ")";
86-
}
87-
8881
if (declaration.DeclarationType.HasFlag(DeclarationType.Member))
8982
{
90-
formattedDeclaration = declaration.QualifiedName.ToString();
83+
var formattedDeclaration = declaration.QualifiedName.ToString();
9184
if (declaration.DeclarationType == DeclarationType.Function
9285
|| declaration.DeclarationType == DeclarationType.PropertyGet)
9386
{
9487
formattedDeclaration += typeName;
9588
}
89+
90+
return formattedDeclaration;
9691
}
9792

98-
if (declaration.DeclarationType == DeclarationType.Enumeration
99-
|| declaration.DeclarationType == DeclarationType.UserDefinedType)
100-
{
101-
formattedDeclaration = !declaration.IsUserDefined
102-
// built-in enums & UDT's don't have a module
103-
? System.IO.Path.GetFileName(moduleName.ProjectPath) + ";" + moduleName.ProjectName + "." + declaration.IdentifierName
104-
: moduleName.ToString();
105-
}
106-
else if (declaration.DeclarationType == DeclarationType.EnumerationMember
107-
|| declaration.DeclarationType == DeclarationType.UserDefinedTypeMember)
93+
if (declaration.DeclarationType.HasFlag(DeclarationType.Module))
10894
{
109-
formattedDeclaration = string.Format("{0}.{1}.{2} {3}",
110-
!declaration.IsUserDefined
111-
? System.IO.Path.GetFileName(moduleName.ProjectPath) + ";" + moduleName.ProjectName
112-
: moduleName.ToString(),
113-
declaration.ParentDeclaration.IdentifierName,
114-
declaration.IdentifierName,
115-
typeName);
95+
return $"{moduleName} ({declarationType})";
11696
}
117-
else if (declaration.DeclarationType == DeclarationType.ComAlias)
97+
98+
switch (declaration.DeclarationType)
11899
{
119-
formattedDeclaration = string.Format("{0};{1}.{2} (alias:{3})",
120-
System.IO.Path.GetFileName(moduleName.ProjectPath), moduleName.ProjectName,
121-
declaration.IdentifierName, declaration.AsTypeName);
100+
case DeclarationType.Project:
101+
case DeclarationType.BracketedExpression:
102+
var filename = System.IO.Path.GetFileName(declaration.QualifiedName.QualifiedModuleName.ProjectPath);
103+
return $"{filename}{(string.IsNullOrEmpty(filename) ? string.Empty : ";")}{declaration.IdentifierName} ({declarationType})";
104+
case DeclarationType.Enumeration:
105+
case DeclarationType.UserDefinedType:
106+
return !declaration.IsUserDefined
107+
// built-in enums & UDT's don't have a module
108+
? $"{System.IO.Path.GetFileName(moduleName.ProjectPath)};{moduleName.ProjectName}.{declaration.IdentifierName}"
109+
: moduleName.ToString();
110+
case DeclarationType.EnumerationMember:
111+
case DeclarationType.UserDefinedTypeMember:
112+
return declaration.IsUserDefined
113+
? $"{moduleName}.{declaration.ParentDeclaration.IdentifierName}.{declaration.IdentifierName} {typeName}"
114+
: $"{System.IO.Path.GetFileName(moduleName.ProjectPath)};{moduleName.ProjectName}.{declaration.ParentDeclaration.IdentifierName}.{declaration.IdentifierName} {typeName}";
115+
case DeclarationType.ComAlias:
116+
return $"{System.IO.Path.GetFileName(moduleName.ProjectPath)};{moduleName.ProjectName}.{declaration.IdentifierName} (alias:{declaration.AsTypeName})";
122117
}
123118

124-
var subscripts = declaration.IsArray ? "()" : string.Empty;
125-
if (declaration.ParentDeclaration != null && declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Member))
119+
return string.Empty;
120+
}
121+
122+
private static string TypeName(Declaration declaration, bool multipleControls, string declarationType)
123+
{
124+
if (multipleControls)
126125
{
127-
// locals, parameters
128-
formattedDeclaration = string.Format("{0}:{1}{2} {3}", declaration.ParentDeclaration.QualifiedName, declaration.IdentifierName, subscripts, typeName);
126+
return RubberduckUI.ContextMultipleControlsSelection;
129127
}
130128

131-
if (declaration.ParentDeclaration != null && declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
129+
var typeName = declaration.IsArray
130+
? $"{declaration.AsTypeName}()"
131+
: declaration.AsTypeName;
132+
133+
switch (declaration)
132134
{
133-
// fields
134-
var withEvents = declaration.IsWithEvents ? "(WithEvents) " : string.Empty;
135-
formattedDeclaration = string.Format("{0}{1}.{2} {3}", withEvents, moduleName, declaration.IdentifierName, typeName);
135+
case ValuedDeclaration valued:
136+
return $"({declarationType}{(string.IsNullOrEmpty(typeName) ? string.Empty : ":" + typeName)}{(string.IsNullOrEmpty(valued.Expression) ? string.Empty : $" = {valued.Expression}")})";
137+
case ParameterDeclaration parameter:
138+
return $"({declarationType}{(string.IsNullOrEmpty(typeName) ? string.Empty : ":" + typeName)}{(string.IsNullOrEmpty(parameter.DefaultValue) ? string.Empty : $" = {parameter.DefaultValue}")})";
139+
default:
140+
return $"({declarationType}{(string.IsNullOrEmpty(typeName) ? string.Empty : ":" + typeName)})";
136141
}
137-
138-
return formattedDeclaration.Trim();
139142
}
140143
}
141144
}
Lines changed: 46 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -1,59 +1,81 @@
11
using Rubberduck.Parsing.Symbols;
22
using System;
3+
using System.Linq;
4+
using Antlr4.Runtime;
5+
using Rubberduck.Parsing.Grammar;
36

47
namespace Rubberduck.Parsing.Binding
58
{
69
public sealed class ArgumentListArgument
710
{
811
private readonly IExpressionBinding _binding;
9-
private IBoundExpression _expression;
10-
private IBoundExpression _namedArgumentExpression;
11-
private readonly ArgumentListArgumentType _argumentType;
12+
private readonly ParserRuleContext _context;
1213
private readonly Func<Declaration, IBoundExpression> _namedArgumentExpressionCreator;
14+
private readonly bool _isAddressOfArgument;
1315

14-
public ArgumentListArgument(IExpressionBinding binding, ArgumentListArgumentType argumentType)
15-
: this (binding, argumentType, calledProcedure => null)
16+
public ArgumentListArgument(IExpressionBinding binding, ParserRuleContext context, ArgumentListArgumentType argumentType, bool isAddressOfArgument = false)
17+
: this (binding, context, argumentType, calledProcedure => null, isAddressOfArgument)
1618
{
1719
}
1820

19-
public ArgumentListArgument(IExpressionBinding binding, ArgumentListArgumentType argumentType, Func<Declaration, IBoundExpression> namedArgumentExpressionCreator)
21+
public ArgumentListArgument(IExpressionBinding binding, ParserRuleContext context, ArgumentListArgumentType argumentType, Func<Declaration, IBoundExpression> namedArgumentExpressionCreator, bool isAddressOfArgument = false)
2022
{
2123
_binding = binding;
22-
_argumentType = argumentType;
24+
_context = context;
25+
ArgumentType = argumentType;
2326
_namedArgumentExpressionCreator = namedArgumentExpressionCreator;
27+
_isAddressOfArgument = isAddressOfArgument;
2428
}
2529

26-
public ArgumentListArgumentType ArgumentType
30+
public ArgumentListArgumentType ArgumentType { get; }
31+
public IBoundExpression NamedArgumentExpression { get; private set; }
32+
public IBoundExpression Expression { get; private set; }
33+
34+
public void Resolve(Declaration calledProcedure, int parameterIndex)
2735
{
28-
get
36+
var binding = _binding;
37+
if (calledProcedure != null)
2938
{
30-
return _argumentType;
39+
NamedArgumentExpression = _namedArgumentExpressionCreator(calledProcedure);
40+
41+
if (!_isAddressOfArgument && !CanBeObject(calledProcedure, parameterIndex))
42+
{
43+
binding = new LetCoercionDefaultBinding(_context, binding);
44+
}
3145
}
46+
47+
Expression = binding.Resolve();
3248
}
3349

34-
public IBoundExpression NamedArgumentExpression
50+
private bool CanBeObject(Declaration calledProcedure, int parameterIndex)
3551
{
36-
get
52+
if (NamedArgumentExpression != null)
3753
{
38-
return _namedArgumentExpression;
54+
var correspondingParameter = NamedArgumentExpression.ReferencedDeclaration as ParameterDeclaration;
55+
return CanBeObject(correspondingParameter);
3956
}
40-
}
4157

42-
public IBoundExpression Expression
43-
{
44-
get
58+
if (parameterIndex >= 0 && calledProcedure is IParameterizedDeclaration parameterizedDeclaration)
4559
{
46-
return _expression;
60+
var parameters = parameterizedDeclaration.Parameters.ToList();
61+
if (parameterIndex >= parameters.Count)
62+
{
63+
return parameters.Any(param => param.IsParamArray);
64+
}
65+
66+
var correspondingParameter = parameters[parameterIndex];
67+
return CanBeObject(correspondingParameter);
68+
4769
}
70+
71+
return true;
4872
}
4973

50-
public void Resolve(Declaration calledProcedure)
74+
private bool CanBeObject(ParameterDeclaration parameter)
5175
{
52-
_expression = _binding.Resolve();
53-
if (calledProcedure != null)
54-
{
55-
_namedArgumentExpression = _namedArgumentExpressionCreator(calledProcedure);
56-
}
76+
return parameter.IsObject
77+
|| Tokens.Variant.Equals(parameter.AsTypeName, StringComparison.InvariantCultureIgnoreCase)
78+
&& (!parameter.IsArray || parameter.IsParamArray);
5779
}
5880
}
5981
}

0 commit comments

Comments
 (0)