Skip to content

Commit 18774ce

Browse files
committed
Merge branch 'next' into LetReferenceInspectionsUseBaseClass
2 parents 999a846 + 9811522 commit 18774ce

File tree

9 files changed

+161
-21
lines changed

9 files changed

+161
-21
lines changed

README.md

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -20,9 +20,8 @@ If you like this project and would like to thank its contributors, you are welco
2020
[![Chat on stackexchange](https://img.shields.io/badge/chat-on%20stackexchange-blue.svg)](https://chat.stackexchange.com/rooms/14929/vba-rubberducking)
2121
[![License](https://img.shields.io/github/license/rubberduck-vba/Rubberduck.svg)](https://github.com/rubberduck-vba/Rubberduck/blob/next/LICENSE)
2222

23-
> **[rubberduckvba.com](http://rubberduckvba.com)** [Wiki](https://github.com/rubberduck-vba/Rubberduck/wiki) [Rubberduck News](https://rubberduckvba.wordpress.com/)
24-
> devs@rubberduckvba.com
25-
> Follow [@rubberduckvba](https://twitter.com/rubberduckvba) on Twitter
23+
> **[rubberduckvba.com](http://rubberduckvba.com)** | **[Rubberduck News](https://rubberduckvba.wordpress.com/)**
24+
| **[Twitter (@rubberduckvba)](https://twitter.com/rubberduckvba)** | **[Wiki](https://github.com/rubberduck-vba/Rubberduck/wiki)**
2625

2726
---
2827

Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueAlwaysDiscardedInspection.cs

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -144,7 +144,14 @@ private static bool IsCalledAsProcedure(ParserRuleContext context)
144144
? methodCall
145145
: context;
146146
var memberAccessParent = ownFunctionCallExpression.GetAncestor<VBAParser.MemberAccessExprContext>();
147-
return memberAccessParent == null;
147+
if (memberAccessParent != null)
148+
{
149+
return false;
150+
}
151+
152+
//If we are in an output list, the value is used somewhere in defining the argument.
153+
var outputListParent = context.GetAncestor<VBAParser.OutputListContext>();
154+
return outputListParent == null;
148155
}
149156

150157
protected override string ResultDescription(Declaration declaration)

Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueDiscardedInspection.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -83,7 +83,9 @@ private static bool IsCalledAsProcedure(ParserRuleContext context)
8383
return false;
8484
}
8585

86-
return true;
86+
//If we are in an output list, the value is used somewhere in defining the argument.
87+
var outputListParent = context.GetAncestor<VBAParser.OutputListContext>();
88+
return outputListParent == null;
8789
}
8890

8991
protected override string ResultDescription(IdentifierReference reference, dynamic properties = null)

Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs

Lines changed: 11 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,7 @@ public class DeclarationFinder
3030

3131
private readonly IReadOnlyDictionary<QualifiedModuleName, IFailedResolutionStore> _failedResolutionStores;
3232
private readonly ConcurrentDictionary<QualifiedModuleName, IMutableFailedResolutionStore> _newFailedResolutionStores;
33-
private readonly ConcurrentDictionary<QualifiedMemberName, ConcurrentBag<Declaration>> _newUndeclared;
33+
private readonly ConcurrentDictionary<(QualifiedMemberName memberName, DeclarationType declarationType), ConcurrentBag<Declaration>> _newUndeclared;
3434

3535
private IDictionary<(QualifiedModuleName module, int annotatedLine), List<IParseTreeAnnotation>> _annotations;
3636
private IDictionary<Declaration, List<ParameterDeclaration>> _parametersByParent;
@@ -78,7 +78,7 @@ public DeclarationFinder(
7878
_failedResolutionStores = failedResolutionStores;
7979

8080
_newFailedResolutionStores = new ConcurrentDictionary<QualifiedModuleName, IMutableFailedResolutionStore>();
81-
_newUndeclared = new ConcurrentDictionary<QualifiedMemberName, ConcurrentBag<Declaration>>();
81+
_newUndeclared = new ConcurrentDictionary<(QualifiedMemberName memberName, DeclarationType declarationType), ConcurrentBag<Declaration>>();
8282

8383
var collectionConstructionActions = CollectionConstructionActions(declarations, annotations);
8484
ExecuteCollectionConstructionActions(collectionConstructionActions);
@@ -986,13 +986,14 @@ public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string i
986986
null,
987987
!isReDimVariable);
988988

989-
var hasUndeclared = _newUndeclared.ContainsKey(enclosingProcedure.QualifiedName);
989+
var enclosingScope = (enclosingProcedure.QualifiedName, enclosingProcedure.DeclarationType);
990+
var hasUndeclared = _newUndeclared.ContainsKey(enclosingScope);
990991
if (hasUndeclared)
991992
{
992993
ConcurrentBag<Declaration> undeclared;
993-
while (!_newUndeclared.TryGetValue(enclosingProcedure.QualifiedName, out undeclared))
994+
while (!_newUndeclared.TryGetValue(enclosingScope, out undeclared))
994995
{
995-
_newUndeclared.TryGetValue(enclosingProcedure.QualifiedName, out undeclared);
996+
_newUndeclared.TryGetValue(enclosingScope, out undeclared);
996997
}
997998
var inScopeUndeclared = undeclared.FirstOrDefault(d => d.IdentifierName == identifierName);
998999
if (inScopeUndeclared != null)
@@ -1003,7 +1004,7 @@ public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string i
10031004
}
10041005
else
10051006
{
1006-
_newUndeclared.TryAdd(enclosingProcedure.QualifiedName, new ConcurrentBag<Declaration> { undeclaredLocal });
1007+
_newUndeclared.TryAdd(enclosingScope, new ConcurrentBag<Declaration> { undeclaredLocal });
10071008
}
10081009
return undeclaredLocal;
10091010
}
@@ -1067,14 +1068,16 @@ public Declaration OnBracketedExpression(string expression, ParserRuleContext co
10671068
Debug.Assert(hostApp != null, "Host application project can't be null. Make sure VBA standard library is included if host is unknown.");
10681069

10691070
var qualifiedName = hostApp.QualifiedName.QualifiedModuleName.QualifyMemberName(expression);
1071+
var declarationType = DeclarationType.BracketedExpression;
1072+
var undeclaredScope = (qualifiedName, declarationType);
10701073

1071-
if (_newUndeclared.TryGetValue(qualifiedName, out var undeclared))
1074+
if (_newUndeclared.TryGetValue(undeclaredScope, out var undeclared))
10721075
{
10731076
return undeclared.SingleOrDefault();
10741077
}
10751078

10761079
var item = new Declaration(qualifiedName, hostApp, hostApp, Tokens.Variant, string.Empty, false, false, Accessibility.Global, DeclarationType.BracketedExpression, context, null, context.GetSelection(), true, null);
1077-
_newUndeclared.TryAdd(qualifiedName, new ConcurrentBag<Declaration> { item });
1080+
_newUndeclared.TryAdd(undeclaredScope, new ConcurrentBag<Declaration> { item });
10781081
return item;
10791082
}
10801083

Rubberduck.VBEEditor/Utility/AddComponentService.cs

Lines changed: 29 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
1-
using Rubberduck.VBEditor.ComManagement;
1+
using System.Runtime.InteropServices;
2+
using NLog;
3+
using Rubberduck.VBEditor.ComManagement;
24
using Rubberduck.VBEditor.SafeComWrappers;
35
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
46
using Rubberduck.VBEditor.SourceCodeHandling;
@@ -11,6 +13,8 @@ public class AddComponentService : IAddComponentService
1113
private readonly IComponentSourceCodeHandler _codePaneSourceCodeHandler;
1214
private readonly IComponentSourceCodeHandler _attributeSourceCodeHandler;
1315

16+
private static ILogger _logger = LogManager.GetCurrentClassLogger();
17+
1418
public AddComponentService(
1519
IProjectsProvider projectsProvider,
1620
IComponentSourceCodeHandler codePaneComponentSourceCodeProvider,
@@ -21,17 +25,17 @@ public AddComponentService(
2125
_attributeSourceCodeHandler = attributesComponentSourceCodeProvider;
2226
}
2327

24-
public void AddComponent(string projectId, ComponentType componentType, string code = null, string additionalPrefixInModule = null)
28+
public void AddComponent(string projectId, ComponentType componentType, string code = null, string additionalPrefixInModule = null, string componentName = null)
2529
{
26-
AddComponent(_codePaneSourceCodeHandler, projectId, componentType, code, additionalPrefixInModule);
30+
AddComponent(_codePaneSourceCodeHandler, projectId, componentType, code, additionalPrefixInModule, componentName);
2731
}
2832

29-
public void AddComponentWithAttributes(string projectId, ComponentType componentType, string code, string prefixInModule = null)
33+
public void AddComponentWithAttributes(string projectId, ComponentType componentType, string code, string prefixInModule = null, string componentName = null)
3034
{
31-
AddComponent(_attributeSourceCodeHandler, projectId, componentType, code, prefixInModule);
35+
AddComponent(_attributeSourceCodeHandler, projectId, componentType, code, prefixInModule, componentName);
3236
}
3337

34-
public void AddComponent(IComponentSourceCodeHandler sourceCodeHandler, string projectId, ComponentType componentType, string code = null, string prefixInModule = null)
38+
public void AddComponent(IComponentSourceCodeHandler sourceCodeHandler, string projectId, ComponentType componentType, string code = null, string prefixInModule = null, string componentName = null)
3539
{
3640
using (var newComponent = CreateComponent(projectId, componentType))
3741
{
@@ -45,17 +49,36 @@ public void AddComponent(IComponentSourceCodeHandler sourceCodeHandler, string p
4549
using (var loadedComponent = sourceCodeHandler.SubstituteCode(newComponent, code))
4650
{
4751
AddPrefix(loadedComponent, prefixInModule);
52+
RenameComponent(loadedComponent, componentName);
4853
ShowComponent(loadedComponent);
4954
}
5055
}
5156
else
5257
{
5358
AddPrefix(newComponent, prefixInModule);
59+
RenameComponent(newComponent, componentName);
5460
ShowComponent(newComponent);
5561
}
5662
}
5763
}
5864

65+
private static void RenameComponent(IVBComponent newComponent, string componentName)
66+
{
67+
if (componentName == null)
68+
{
69+
return;
70+
}
71+
72+
try
73+
{
74+
newComponent.Name = componentName;
75+
}
76+
catch (COMException ex)
77+
{
78+
_logger.Debug(ex, $"Unable to rename component to {componentName}.");
79+
}
80+
}
81+
5982
private static void ShowComponent(IVBComponent component)
6083
{
6184
if (component == null)

Rubberduck.VBEEditor/Utility/IAddComponentService.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ namespace Rubberduck.VBEditor.Utility
44
{
55
public interface IAddComponentService
66
{
7-
void AddComponent(string projectId, ComponentType componentType, string code = null, string additionalPrefixInModule = null);
8-
void AddComponentWithAttributes(string projectId, ComponentType componentType, string code, string prefixInModule = null);
7+
void AddComponent(string projectId, ComponentType componentType, string code = null, string additionalPrefixInModule = null, string componentName = null);
8+
void AddComponentWithAttributes(string projectId, ComponentType componentType, string code, string prefixInModule = null, string componentName = null);
99
}
1010
}

RubberduckTests/Grammar/ResolverTests.cs

Lines changed: 72 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7300,5 +7300,77 @@ End Function
73007300
Assert.AreEqual(expectedReferenceText, enumMemberReference.IdentifierName);
73017301
}
73027302
}
7303+
7304+
[Category("Grammar")]
7305+
[Category("Resolver")]
7306+
[Test]
7307+
public void OneUndeclaredVariablePerMemberAndUndeclaredIdentifier_DifferentMemberName()
7308+
{
7309+
var moduleCode = @"
7310+
Private Sub Foo
7311+
bar = 42 + 23
7312+
bar = bar + bar
7313+
bar = bar * bar
7314+
fooBar = 42
7315+
End Sub
7316+
7317+
Private Sub DoSomething
7318+
bar = 42 + 23
7319+
bar = bar + bar
7320+
bar = bar * bar
7321+
fooBaz = 42
7322+
End Sub
7323+
";
7324+
7325+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(moduleCode, out _);
7326+
7327+
using (var state = Resolve(vbe.Object))
7328+
{
7329+
var finder = state.DeclarationFinder;
7330+
var module = finder.UserDeclarations(DeclarationType.ProceduralModule)
7331+
.Single();
7332+
var undeclared = finder.Members(module.QualifiedModuleName)
7333+
.Where(declaration => declaration.IsUndeclared)
7334+
.ToList();
7335+
7336+
Assert.AreEqual(4, undeclared.Count);
7337+
}
7338+
}
7339+
7340+
[Category("Grammar")]
7341+
[Category("Resolver")]
7342+
[Test]
7343+
public void OneUndeclaredVariablePerMemberAndUndeclaredIdentifier_DifferentDeclarationType()
7344+
{
7345+
var moduleCode = @"
7346+
Private Property Get Foo() As Variant
7347+
bar = 42 + 23
7348+
bar = bar + bar
7349+
bar = bar * bar
7350+
fooBar = 42
7351+
End Property
7352+
7353+
Private Property Let Foo(arg As Variant)
7354+
bar = 42 + 23
7355+
bar = bar + bar
7356+
bar = bar * bar
7357+
fooBaz = 42
7358+
End Property
7359+
";
7360+
7361+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(moduleCode, out _);
7362+
7363+
using (var state = Resolve(vbe.Object))
7364+
{
7365+
var finder = state.DeclarationFinder;
7366+
var module = finder.UserDeclarations(DeclarationType.ProceduralModule)
7367+
.Single();
7368+
var undeclared = finder.Members(module.QualifiedModuleName)
7369+
.Where(declaration => declaration.IsUndeclared)
7370+
.ToList();
7371+
7372+
Assert.AreEqual(4, undeclared.Count);
7373+
}
7374+
}
73037375
}
73047376
}

RubberduckTests/Inspections/FunctionReturnValueAlwaysDiscardedInspectionTests.cs

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -323,6 +323,23 @@ End Sub
323323
Assert.AreEqual(0, InspectionResultsForStandardModule(code).Count());
324324
}
325325

326+
[Test]
327+
[Category("Inspections")]
328+
[Category("Unused Value")]
329+
public void OutputListFunctionCall_DoesNotReturnResult()
330+
{
331+
const string code = @"
332+
Public Function Foo(ByVal bar As String) As Integer
333+
Foo = 42
334+
End Function
335+
336+
Public Sub Baz()
337+
Debug.Print Foo(""Test"")
338+
End Sub
339+
";
340+
Assert.AreEqual(0, InspectionResultsForStandardModule(code).Count());
341+
}
342+
326343
[Test]
327344
[Category("Inspections")]
328345
[Category("Unused Value")]

RubberduckTests/Inspections/FunctionReturnValueDiscardedInspectionTests.cs

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -281,6 +281,23 @@ End Sub
281281
Assert.AreEqual(0, InspectionResultsForStandardModule(code).Count());
282282
}
283283

284+
[Test]
285+
[Category("Inspections")]
286+
[Category("Unused Value")]
287+
public void FunctionReturnValueDiscarded_DoesNotReturnResult_OutputListFunctionCall()
288+
{
289+
const string code = @"
290+
Public Function Foo(ByVal bar As String) As Integer
291+
Foo = 42
292+
End Function
293+
294+
Public Sub Baz()
295+
Debug.Print Foo(""Test"")
296+
End Sub
297+
";
298+
Assert.AreEqual(0, InspectionResultsForStandardModule(code).Count());
299+
}
300+
284301
[Test]
285302
[Category("Inspections")]
286303
[Category("Unused Value")]

0 commit comments

Comments
 (0)