Skip to content

Commit 2f1dfb4

Browse files
committed
fixes #4545
1 parent 15a4137 commit 2f1dfb4

File tree

3 files changed

+164
-6
lines changed

3 files changed

+164
-6
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs

Lines changed: 58 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
using System.Linq;
33
using Rubberduck.Inspections.Abstract;
44
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing;
56
using Rubberduck.Parsing.Grammar;
67
using Rubberduck.Parsing.Inspections.Abstract;
78
using Rubberduck.Resources.Inspections;
@@ -34,7 +35,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3435
var unassigned = (from function in functions
3536
let isUdt = IsReturningUserDefinedType(function)
3637
let inScopeRefs = function.References.Where(r => r.ParentScoping.Equals(function))
37-
where (!isUdt && (!inScopeRefs.Any(r => r.IsAssignment)))
38+
where (!isUdt && (!inScopeRefs.Any(r => r.IsAssignment) &&
39+
!inScopeRefs.Any(reference => IsAssignedByRefArgument(function, reference))))
3840
|| (isUdt && !IsUserDefinedTypeAssigned(function))
3941
select function)
4042
.ToList();
@@ -46,6 +48,61 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4648
issue));
4749
}
4850

51+
private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierReference reference)
52+
{
53+
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+
var parameters = State.DeclarationFinder.Parameters(procedure);
74+
75+
ParameterDeclaration parameter;
76+
var namedArg = argExpression.GetAncestor<VBAParser.NamedArgumentContext>();
77+
if (namedArg != null)
78+
{
79+
// argument is named: we're lucky
80+
var parameterName = namedArg.unrestrictedIdentifier().GetText();
81+
parameter = parameters.SingleOrDefault(p => p.IdentifierName == parameterName);
82+
}
83+
else
84+
{
85+
// argument is positional: work out its index
86+
var argList = callStmt.GetDescendent<VBAParser.ArgumentListContext>();
87+
var args = argList.GetDescendents<VBAParser.PositionalArgumentContext>().ToArray();
88+
var parameterIndex = args.Select((a, i) =>
89+
a.GetDescendent<VBAParser.ArgumentExpressionContext>() == argExpression ? (a, i) : (null, -1))
90+
.SingleOrDefault(item => item.a != null).i;
91+
parameter = parameters.OrderBy(p => p.Selection).Select((p, i) => (p, i))
92+
.SingleOrDefault(item => item.i == parameterIndex).p;
93+
}
94+
95+
if (parameter == null)
96+
{
97+
// couldn't locate parameter
98+
return false;
99+
}
100+
101+
// note: not recursive, by design.
102+
return (parameter.IsImplicitByRef || parameter.IsByRef)
103+
&& parameter.References.Any(r => r.IsAssignment);
104+
}
105+
49106
private bool IsReturningUserDefinedType(Declaration member)
50107
{
51108
return member.AsTypeDeclaration != null &&

Rubberduck.Parsing/VBA/AccessibilityCheck.cs

Lines changed: 11 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -5,14 +5,20 @@ namespace Rubberduck.Parsing.VBA
55
{
66
public static class AccessibilityCheck
77
{
8-
public static bool IsAccessible(Declaration callingProject, Declaration callingModule, Declaration callingParent, Declaration callee)
8+
public static bool IsAccessible(Declaration callingParent, Declaration callee)
99
{
10-
return callee != null
11-
&& (callee.DeclarationType.HasFlag(DeclarationType.Project)
12-
|| (callee.DeclarationType.HasFlag(DeclarationType.Module) && IsModuleAccessible(callingProject, callingModule, callee))
13-
|| (!callee.DeclarationType.HasFlag(DeclarationType.Module) && IsMemberAccessible(callingProject, callingModule, callingParent, callee)));
10+
var callingModule = callingParent.ParentScopeDeclaration;
11+
var callingProject = callingModule.ParentDeclaration;
12+
return IsAccessible(callingProject, callingModule, callingParent, callee);
1413
}
1514

15+
public static bool IsAccessible(Declaration callingProject, Declaration callingModule, Declaration callingParent, Declaration callee)
16+
{
17+
return callee != null
18+
&& (callee.DeclarationType.HasFlag(DeclarationType.Project)
19+
|| (callee.DeclarationType.HasFlag(DeclarationType.Module) && IsModuleAccessible(callingProject, callingModule, callee))
20+
|| (!callee.DeclarationType.HasFlag(DeclarationType.Module) && IsMemberAccessible(callingProject, callingModule, callingParent, callee)));
21+
}
1622

1723
public static bool IsModuleAccessible(Declaration callingProject, Declaration callingModule, Declaration calleeModule)
1824
{

RubberduckTests/Inspections/NonReturningFunctionInspectionTests.cs

Lines changed: 95 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -146,6 +146,101 @@ Function Goo() As String
146146
}
147147
}
148148

149+
[Test]
150+
[Category("Inspections")]
151+
public void NonReturningFunction_ReturnsResult_GivenParenthesizedByRefAssignment()
152+
{
153+
const string inputCode = @"
154+
Public Function Foo() As Boolean
155+
ByRefAssign (Foo)
156+
End Function
157+
158+
Public Sub ByRefAssign(ByRef a As Boolean)
159+
End Sub
160+
";
161+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
162+
using (var state = MockParser.CreateAndParse(vbe.Object))
163+
{
164+
165+
var inspection = new NonReturningFunctionInspection(state);
166+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
167+
168+
Assert.AreEqual(1, inspectionResults.Count());
169+
}
170+
}
171+
172+
[Test]
173+
[Category("Inspections")]
174+
public void NonReturningFunction_NoResult_GivenByRefAssignment_WithMemberAccess()
175+
{
176+
const string inputCode = @"
177+
Public Function Foo() As Boolean
178+
TestModule1.ByRefAssign False, Foo
179+
End Function
180+
181+
Public Sub ByRefAssign(ByVal v As Boolean, ByRef a As Boolean)
182+
a = v
183+
End Sub
184+
";
185+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
186+
using (var state = MockParser.CreateAndParse(vbe.Object))
187+
{
188+
189+
var inspection = new NonReturningFunctionInspection(state);
190+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
191+
192+
Assert.AreEqual(0, inspectionResults.Count());
193+
}
194+
}
195+
196+
[Test]
197+
[Category("Inspections")]
198+
public void NonReturningFunction_ReturnsResult_GivenUnassignedByRefAssignment_WithMemberAccess()
199+
{
200+
const string inputCode = @"
201+
Public Function Foo() As Boolean
202+
TestModule1.ByRefAssign False, Foo
203+
End Function
204+
205+
Public Sub ByRefAssign(ByVal v As Boolean, ByRef a As Boolean)
206+
'nope, not assigned
207+
End Sub
208+
";
209+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
210+
using (var state = MockParser.CreateAndParse(vbe.Object))
211+
{
212+
213+
var inspection = new NonReturningFunctionInspection(state);
214+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
215+
216+
Assert.AreEqual(1, inspectionResults.Count());
217+
}
218+
}
219+
220+
[Test]
221+
[Category("Inspections")]
222+
public void NonReturningFunction_NoResult_GivenByRefAssignment_WithNamedArgument()
223+
{
224+
const string inputCode = @"
225+
Public Function Foo() As Boolean
226+
ByRefAssign b:=Foo
227+
End Function
228+
229+
Public Sub ByRefAssign(Optional ByVal a As Long, Optional ByRef b As Boolean)
230+
b = False
231+
End Sub
232+
";
233+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
234+
using (var state = MockParser.CreateAndParse(vbe.Object))
235+
{
236+
237+
var inspection = new NonReturningFunctionInspection(state);
238+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
239+
240+
Assert.AreEqual(0, inspectionResults.Count());
241+
}
242+
}
243+
149244
[Test]
150245
[Category("Inspections")]
151246
public void NonReturningFunction_ReturnsResult_InterfaceImplementation()

0 commit comments

Comments
 (0)