Skip to content

Commit b130639

Browse files
committed
Merge pull request #839 from retailcoder/next
added missing test class
2 parents f6cda0a + f6d0058 commit b130639

File tree

5 files changed

+82
-6
lines changed

5 files changed

+82
-6
lines changed

RetailCoder.VBE/Inspections/ParameterCanBeByValInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,6 @@ public IEnumerable<CodeInspectionResultBase> GetInspectionResults(VBProjectParse
6060
!ignoredScopes.Contains(declaration.ParentScope)
6161
&& declaration.DeclarationType == DeclarationType.Parameter
6262
&& !interfaceMembers.Select(m => m.Scope).Contains(declaration.ParentScope)
63-
//&& PrimitiveTypes.Contains(declaration.AsTypeName) // suggest passing object types ByRef?
6463
&& ((VBAParser.ArgContext) declaration.Context).BYVAL() == null
6564
&& !IsUsedAsByRefParam(parseResult.Declarations, declaration)
6665
&& !declaration.References.Any(reference => reference.IsAssignment))

RetailCoder.VBE/Inspections/VariableNotAssignedInspection.cs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -28,17 +28,16 @@ public IEnumerable<CodeInspectionResultBase> GetInspectionResults(VBProjectParse
2828
var declarations = parseResult.Declarations.Items.Where(declaration =>
2929
declaration.DeclarationType == DeclarationType.Variable
3030
&& !declaration.IsBuiltIn
31+
&& !declaration.IsWithEvents
3132
&& !arrays.Contains(declaration)
3233
&& !parseResult.Declarations.Items.Any(item =>
3334
item.IdentifierName == declaration.AsTypeName
3435
&& item.DeclarationType == DeclarationType.UserDefinedType) // UDT variables don't need to be assigned
3536
&& !declaration.IsSelfAssigned
3637
&& !declaration.References.Any(reference => reference.IsAssignment));
3738

38-
foreach (var issue in declarations)
39-
{
40-
yield return new IdentifierNotAssignedInspectionResult(this, issue, issue.Context, issue.QualifiedName.QualifiedModuleName);
41-
}
39+
return declarations.Select(issue =>
40+
new IdentifierNotAssignedInspectionResult(this, issue, issue.Context, issue.QualifiedName.QualifiedModuleName));
4241
}
4342
}
4443
}

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -265,6 +265,8 @@ public string Scope
265265
case DeclarationType.PropertyLet:
266266
case DeclarationType.PropertySet:
267267
return _qualifiedName.QualifiedModuleName + "." + _identifierName;
268+
case DeclarationType.Event:
269+
return _parentScope + "." + _identifierName;
268270
default:
269271
return _parentScope;
270272
}

Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -790,7 +790,7 @@ private Declaration FindLocalScopeDeclaration(string identifierName, Declaration
790790
try
791791
{
792792
var results = matches.Where(item =>
793-
item.ParentScope == localScope.Scope
793+
(item.ParentScope == localScope.Scope || (isAssignmentTarget && item.Scope == localScope.Scope))
794794
&& localScope.Context.GetSelection().Contains(item.Selection)
795795
&& !_moduleTypes.Contains(item.DeclarationType))
796796
.ToList();
Lines changed: 76 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,76 @@
1+
using System.Linq;
2+
using Microsoft.Vbe.Interop;
3+
using Microsoft.VisualStudio.TestTools.UnitTesting;
4+
using Moq;
5+
using Rubberduck.Inspections;
6+
using Rubberduck.Parsing.VBA;
7+
using Rubberduck.VBEditor.VBEHost;
8+
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodePane;
9+
using RubberduckTests.Mocks;
10+
11+
namespace RubberduckTests
12+
{
13+
[TestClass]
14+
public class RubberduckParserTests
15+
{
16+
[TestMethod]
17+
public void ParseResultDeclarations_IncludeVbaStandardLibDeclarations()
18+
{
19+
//Arrange
20+
var builder = new MockVbeBuilder();
21+
var project = builder.ProjectBuilder("TestProject1", vbext_ProjectProtection.vbext_pp_none)
22+
.AddComponent("Class1", vbext_ComponentType.vbext_ct_ClassModule, "")
23+
.Build().Object;
24+
25+
var codePaneFactory = new CodePaneWrapperFactory();
26+
var mockHost = new Mock<IHostApplication>();
27+
mockHost.SetupAllProperties();
28+
29+
//Act
30+
var parseResult = new RubberduckParser(codePaneFactory, project.VBE).Parse(project);
31+
32+
//Assert
33+
Assert.IsTrue(parseResult.Declarations.Items.Any(item => item.IsBuiltIn));
34+
}
35+
36+
[TestMethod]
37+
public void ParseResultDeclarations_MockHost_ExcludeExcelDeclarations()
38+
{
39+
//Arrange
40+
var builder = new MockVbeBuilder();
41+
var project = builder.ProjectBuilder("TestProject1", vbext_ProjectProtection.vbext_pp_none)
42+
.AddComponent("Class1", vbext_ComponentType.vbext_ct_ClassModule, "")
43+
.Build().Object;
44+
45+
var codePaneFactory = new CodePaneWrapperFactory();
46+
var mockHost = new Mock<IHostApplication>();
47+
mockHost.SetupAllProperties();
48+
49+
//Act
50+
var parseResult = new RubberduckParser(codePaneFactory, project.VBE).Parse(project);
51+
52+
//Assert
53+
Assert.IsFalse(parseResult.Declarations.Items.Any(item => item.IsBuiltIn && item.ParentScope.StartsWith("Excel")));
54+
}
55+
56+
[TestMethod]
57+
public void ParseResultDeclarations_ExcelHost_IncludesExcelDeclarations()
58+
{
59+
//Arrange
60+
var builder = new MockVbeBuilder();
61+
var project = builder.ProjectBuilder("TestProject1", vbext_ProjectProtection.vbext_pp_none)
62+
.AddComponent("Class1", vbext_ComponentType.vbext_ct_ClassModule, "")
63+
.AddReference("Excel", @"C:\Program Files\Microsoft Office\Office14\EXCEL.EXE", true)
64+
.Build();
65+
var vbe = builder.AddProject(project).Build();
66+
67+
var codePaneFactory = new CodePaneWrapperFactory();
68+
69+
//Act
70+
var parseResult = new RubberduckParser(codePaneFactory, vbe.Object).Parse(project.Object);
71+
72+
//Assert
73+
Assert.IsTrue(parseResult.Declarations.Items.Any(item => item.IsBuiltIn && item.ParentScope.StartsWith("Excel")));
74+
}
75+
}
76+
}

0 commit comments

Comments
 (0)