Skip to content

Commit 5c40f06

Browse files
committed
extracted parameter finder logic to DeclarationFinder
1 parent 08fc6fe commit 5c40f06

File tree

2 files changed

+53
-52
lines changed

2 files changed

+53
-52
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs

Lines changed: 1 addition & 52 deletions
Original file line numberDiff line numberDiff line change
@@ -51,58 +51,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5151
private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierReference reference)
5252
{
5353
var argExpression = reference.Context.GetAncestor<VBAParser.ArgumentExpressionContext>();
54-
if (argExpression?.GetDescendent<VBAParser.ParenthesizedExprContext>() != null || argExpression?.BYVAL() != null)
55-
{
56-
// not an argument, or argument is parenthesized and thus passed ByVal
57-
return false;
58-
}
59-
60-
var callStmt = argExpression?.GetAncestor<VBAParser.CallStmtContext>();
61-
var procedureName = callStmt?.GetDescendent<VBAParser.LExpressionContext>()
62-
.GetDescendents<VBAParser.IdentifierContext>()
63-
.LastOrDefault()?.GetText();
64-
if (procedureName == null)
65-
{
66-
// if we don't know what we're calling, we can't dig any further
67-
return false;
68-
}
69-
70-
var procedure = State.DeclarationFinder.MatchName(procedureName)
71-
.Where(p => AccessibilityCheck.IsAccessible(enclosingProcedure, p))
72-
.SingleOrDefault(p => !p.DeclarationType.HasFlag(DeclarationType.Property) || p.DeclarationType.HasFlag(DeclarationType.PropertyGet));
73-
if (procedure?.ParentScopeDeclaration is ClassModuleDeclaration)
74-
{
75-
// we can't know that the member is on the class' default interface
76-
return false;
77-
}
78-
79-
var parameters = State.DeclarationFinder.Parameters(procedure);
80-
81-
ParameterDeclaration parameter;
82-
var namedArg = argExpression.GetAncestor<VBAParser.NamedArgumentContext>();
83-
if (namedArg != null)
84-
{
85-
// argument is named: we're lucky
86-
var parameterName = namedArg.unrestrictedIdentifier().GetText();
87-
parameter = parameters.SingleOrDefault(p => p.IdentifierName == parameterName);
88-
}
89-
else
90-
{
91-
// argument is positional: work out its index
92-
var argList = callStmt.GetDescendent<VBAParser.ArgumentListContext>();
93-
var args = argList.GetDescendents<VBAParser.PositionalArgumentContext>().ToArray();
94-
var parameterIndex = args.Select((a, i) =>
95-
a.GetDescendent<VBAParser.ArgumentExpressionContext>() == argExpression ? (a, i) : (null, -1))
96-
.SingleOrDefault(item => item.a != null).i;
97-
parameter = parameters.OrderBy(p => p.Selection).Select((p, i) => (p, i))
98-
.SingleOrDefault(item => item.i == parameterIndex).p;
99-
}
100-
101-
if (parameter == null)
102-
{
103-
// couldn't locate parameter
104-
return false;
105-
}
54+
var parameter = State.DeclarationFinder.FindParameterFromArgument(argExpression, enclosingProcedure);
10655

10756
// note: not recursive, by design.
10857
return (parameter.IsImplicitByRef || parameter.IsByRef)

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 52 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -531,6 +531,58 @@ public IEnumerable<Declaration> MatchName(string name)
531531
: Enumerable.Empty<Declaration>();
532532
}
533533

534+
public ParameterDeclaration FindParameterFromArgument(VBAParser.ArgumentExpressionContext argExpression, Declaration enclosingProcedure)
535+
{
536+
if (argExpression?.GetDescendent<VBAParser.ParenthesizedExprContext>() != null || argExpression?.BYVAL() != null)
537+
{
538+
// not an argument, or argument is parenthesized and thus passed ByVal
539+
return null;
540+
}
541+
542+
var callStmt = argExpression?.GetAncestor<VBAParser.CallStmtContext>();
543+
var procedureName = callStmt?.GetDescendent<VBAParser.LExpressionContext>()
544+
.GetDescendents<VBAParser.IdentifierContext>()
545+
.LastOrDefault()?.GetText();
546+
if (procedureName == null)
547+
{
548+
// if we don't know what we're calling, we can't dig any further
549+
return null;
550+
}
551+
552+
var procedure = MatchName(procedureName)
553+
.Where(p => AccessibilityCheck.IsAccessible(enclosingProcedure, p))
554+
.SingleOrDefault(p => !p.DeclarationType.HasFlag(DeclarationType.Property) || p.DeclarationType.HasFlag(DeclarationType.PropertyGet));
555+
if (procedure?.ParentScopeDeclaration is ClassModuleDeclaration)
556+
{
557+
// we can't know that the member is on the class' default interface
558+
return null;
559+
}
560+
561+
var parameters = Parameters(procedure);
562+
563+
ParameterDeclaration parameter;
564+
var namedArg = argExpression.GetAncestor<VBAParser.NamedArgumentContext>();
565+
if (namedArg != null)
566+
{
567+
// argument is named: we're lucky
568+
var parameterName = namedArg.unrestrictedIdentifier().GetText();
569+
parameter = parameters.SingleOrDefault(p => p.IdentifierName == parameterName);
570+
}
571+
else
572+
{
573+
// argument is positional: work out its index
574+
var argList = callStmt.GetDescendent<VBAParser.ArgumentListContext>();
575+
var args = argList.GetDescendents<VBAParser.PositionalArgumentContext>().ToArray();
576+
var parameterIndex = args.Select((a, i) =>
577+
a.GetDescendent<VBAParser.ArgumentExpressionContext>() == argExpression ? (a, i) : (null, -1))
578+
.SingleOrDefault(item => item.a != null).i;
579+
parameter = parameters.OrderBy(p => p.Selection).Select((p, i) => (p, i))
580+
.SingleOrDefault(item => item.i == parameterIndex).p;
581+
}
582+
583+
return parameter;
584+
}
585+
534586
private string ToNormalizedName(string name)
535587
{
536588
var lower = name.ToLowerInvariant();

0 commit comments

Comments
 (0)