Skip to content

Commit 6c1a6b8

Browse files
committed
Merge pull request #1192 from retailcoder/TypeInfo
Fixes #1191
2 parents 16c548a + 0a17840 commit 6c1a6b8

File tree

3 files changed

+49
-6
lines changed

3 files changed

+49
-6
lines changed

RetailCoder.VBE/Inspections/ParameterCanBeByValInspection.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -67,7 +67,8 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
6767
var ignoredScopes = formEventHandlerScopes.Concat(eventScopes).Concat(declareScopes);
6868

6969
var issues = declarations.Where(declaration =>
70-
!ignoredScopes.Contains(declaration.ParentScope)
70+
!declaration.IsArray()
71+
&& !ignoredScopes.Contains(declaration.ParentScope)
7172
&& declaration.DeclarationType == DeclarationType.Parameter
7273
&& !interfaceMembers.Select(m => m.Scope).Contains(declaration.ParentScope)
7374
&& ((VBAParser.ArgContext) declaration.Context).BYVAL() == null

Rubberduck.Parsing/VBA/AttributeParser.cs

Lines changed: 20 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -105,7 +105,10 @@ public override void EnterSubStmt(AttributesParser.SubStmtContext context)
105105

106106
public override void ExitSubStmt(AttributesParser.SubStmtContext context)
107107
{
108-
_attributes.Add(_currentScope, _currentScopeAttributes);
108+
if (_currentScopeAttributes.Any())
109+
{
110+
_attributes.Add(_currentScope, _currentScopeAttributes);
111+
}
109112
}
110113

111114
public override void EnterFunctionStmt(AttributesParser.FunctionStmtContext context)
@@ -115,7 +118,10 @@ public override void EnterFunctionStmt(AttributesParser.FunctionStmtContext cont
115118

116119
public override void ExitFunctionStmt(AttributesParser.FunctionStmtContext context)
117120
{
118-
_attributes.Add(_currentScope, _currentScopeAttributes);
121+
if (_currentScopeAttributes.Any())
122+
{
123+
_attributes.Add(_currentScope, _currentScopeAttributes);
124+
}
119125
}
120126

121127
public override void EnterPropertyGetStmt(AttributesParser.PropertyGetStmtContext context)
@@ -125,7 +131,10 @@ public override void EnterPropertyGetStmt(AttributesParser.PropertyGetStmtContex
125131

126132
public override void ExitPropertyGetStmt(AttributesParser.PropertyGetStmtContext context)
127133
{
128-
_attributes.Add(_currentScope, _currentScopeAttributes);
134+
if (_currentScopeAttributes.Any())
135+
{
136+
_attributes.Add(_currentScope, _currentScopeAttributes);
137+
}
129138
}
130139

131140
public override void EnterPropertyLetStmt(AttributesParser.PropertyLetStmtContext context)
@@ -135,7 +144,10 @@ public override void EnterPropertyLetStmt(AttributesParser.PropertyLetStmtContex
135144

136145
public override void ExitPropertyLetStmt(AttributesParser.PropertyLetStmtContext context)
137146
{
138-
_attributes.Add(_currentScope, _currentScopeAttributes);
147+
if (_currentScopeAttributes.Any())
148+
{
149+
_attributes.Add(_currentScope, _currentScopeAttributes);
150+
}
139151
}
140152

141153
public override void EnterPropertySetStmt(AttributesParser.PropertySetStmtContext context)
@@ -145,7 +157,10 @@ public override void EnterPropertySetStmt(AttributesParser.PropertySetStmtContex
145157

146158
public override void ExitPropertySetStmt(AttributesParser.PropertySetStmtContext context)
147159
{
148-
_attributes.Add(_currentScope, _currentScopeAttributes);
160+
if (_currentScopeAttributes.Any())
161+
{
162+
_attributes.Add(_currentScope, _currentScopeAttributes);
163+
}
149164
}
150165

151166
public override void ExitAttributeStmt(AttributesParser.AttributeStmtContext context)

RubberduckTests/Inspections/ParameterCanBeByValInspectionTests.cs

Lines changed: 27 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -218,6 +218,33 @@ public void ParameterCanByByVal_ReturnsResult_QuickFixWorks_PassedByRefUnassigne
218218
Assert.AreEqual(expectedCode, module.Lines());
219219
}
220220

221+
[TestMethod]
222+
public void GivenArrayParameter_ReturnsNoResult()
223+
{
224+
const string inputCode =
225+
@"Sub Foo(ByRef arg1() As Variant)
226+
End Sub";
227+
228+
//Arrange
229+
var builder = new MockVbeBuilder();
230+
VBComponent component;
231+
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
232+
var project = vbe.Object.VBProjects.Item(0);
233+
var module = project.VBComponents.Item(0).CodeModule;
234+
var mockHost = new Mock<IHostApplication>();
235+
mockHost.SetupAllProperties();
236+
var parser = MockParser.Create(vbe.Object, new RubberduckParserState());
237+
238+
parser.Parse();
239+
if (parser.State.Status == ParserState.Error) { Assert.Inconclusive("Parser Error"); }
240+
241+
var inspection = new ParameterCanBeByValInspection(parser.State);
242+
243+
var results = inspection.GetInspectionResults().ToList();
244+
245+
Assert.AreEqual(0, results.Count);
246+
}
247+
221248
[TestMethod]
222249
public void InspectionType()
223250
{

0 commit comments

Comments
 (0)