Skip to content

Commit f9b3599

Browse files
committed
ignored arrays in unassigned variable inspection; added note in ParameterCanBeByVal inspection, we need to relate args calls to parameters, and parameters to procedures to be able to tell if we're passing a parameter to another proc as a ByRef arg.
1 parent 5664c97 commit f9b3599

File tree

6 files changed

+21
-8
lines changed

6 files changed

+21
-8
lines changed

RetailCoder.VBE/Inspections/ParameterCanBeByValInspection.cs

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,8 @@
1+
using System;
12
using System.Collections.Generic;
23
using Rubberduck.Parsing;
34
using System.Linq;
5+
using Microsoft.CSharp.RuntimeBinder;
46
using Rubberduck.Parsing.Grammar;
57
using Rubberduck.Parsing.Symbols;
68

@@ -59,12 +61,18 @@ public IEnumerable<CodeInspectionResultBase> GetInspectionResults(VBProjectParse
5961
&& !interfaceMembers.Select(m => m.Scope).Contains(declaration.ParentScope)
6062
&& PrimitiveTypes.Contains(declaration.AsTypeName)
6163
&& ((VBAParser.ArgContext) declaration.Context).BYVAL() == null
64+
&& !IsUsedAsByRefParam(parseResult.Declarations, declaration)
6265
&& !declaration.References.Any(reference => reference.IsAssignment))
6366
.Select(issue => new ParameterCanBeByValInspectionResult(string.Format(Name, issue.IdentifierName), Severity, issue.Context, issue.QualifiedName));
6467

6568
return issues;
6669
}
6770

68-
71+
private bool IsUsedAsByRefParam(Declarations declarations, Declaration parameter)
72+
{
73+
// todo: enable tracking parameter references
74+
// by linking Parameter declarations to their parent Procedure/Function/Property member.
75+
return false;
76+
}
6977
}
7078
}

RetailCoder.VBE/Inspections/VariableNotAssignedInspection.cs

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -18,10 +18,15 @@ public VariableNotAssignedInspection()
1818

1919
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(VBProjectParseResult parseResult)
2020
{
21+
// ignore arrays. todo: ArrayIndicesNotAccessedInspection
22+
var arrays = parseResult.Declarations.Items.Where(declaration =>
23+
declaration.DeclarationType == DeclarationType.Variable
24+
&& declaration.IsArray()).ToList();
25+
2126
var declarations = parseResult.Declarations.Items.Where(declaration =>
22-
!declaration.IsBuiltIn
23-
&& declaration.DeclarationType == DeclarationType.Variable
24-
&& !declaration.IsArray() // ignore arrays... not ideal though
27+
declaration.DeclarationType == DeclarationType.Variable
28+
&& !declaration.IsBuiltIn
29+
&& !arrays.Contains(declaration)
2530
&& !parseResult.Declarations.Items.Any(item =>
2631
item.IdentifierName == declaration.AsTypeName
2732
&& item.DeclarationType == DeclarationType.UserDefinedType) // UDT variables don't need to be assigned

RetailCoder.VBE/Inspections/VariableNotUsedInspection.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,8 +20,9 @@ public IEnumerable<CodeInspectionResultBase> GetInspectionResults(VBProjectParse
2020
{
2121
var declarations = parseResult.Declarations.Items.Where(declaration =>
2222
!declaration.IsBuiltIn
23+
//&& !declaration.IsArray()
2324
&& declaration.DeclarationType == DeclarationType.Variable
24-
&& !declaration.References.Any(reference => !reference.IsAssignment));
25+
&& declaration.References.All(reference => reference.IsAssignment));
2526

2627
foreach (var issue in declarations)
2728
{

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,7 @@ public bool IsArray()
135135

136136
try
137137
{
138-
var declaration = ((dynamic)Context.Parent); // Context is AmbiguousIdentifier - parent is the declaration sub-statement where the array parens are
138+
var declaration = ((dynamic)Context); // Context is AmbiguousIdentifier - parent is the declaration sub-statement where the array parens are
139139
return declaration.LPAREN() != null && declaration.RPAREN() != null;
140140
}
141141
catch (RuntimeBinderException)

Rubberduck.Parsing/Symbols/DeclarationSymbolsListener.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -258,7 +258,7 @@ public override void EnterArgList(VBAParser.ArgListContext context)
258258
: asTypeClause.type().GetText();
259259

260260
var identifier = argContext.ambiguousIdentifier();
261-
_declarations.Add(CreateDeclaration(identifier.GetText(), asTypeName, Accessibility.Implicit, DeclarationType.Parameter, argContext, argContext.ambiguousIdentifier().GetSelection()));
261+
_declarations.Add(CreateDeclaration(identifier.GetText(), asTypeName, Accessibility.Implicit, DeclarationType.Parameter, argContext, identifier.GetSelection()));
262262
}
263263
}
264264

Rubberduck.Parsing/Symbols/IdentifierReferenceListener.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Linq;
4-
using System.Windows.Forms;
54
using Antlr4.Runtime;
65
using Antlr4.Runtime.Tree;
76
using Rubberduck.Parsing.Grammar;

0 commit comments

Comments
 (0)