Skip to content

Commit

Permalink
Consider More than just ClassModules for MemberNotOnInterface
Browse files Browse the repository at this point in the history
fixes #2189
  • Loading branch information
Vogel612 committed Nov 25, 2017
1 parent 002efc8 commit f9f0c2a
Show file tree
Hide file tree
Showing 3 changed files with 66 additions and 5 deletions.
Expand Up @@ -23,16 +23,15 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()

var targets = Declarations.Where(decl => decl.AsTypeDeclaration != null &&
!decl.AsTypeDeclaration.IsUserDefined &&
decl.AsTypeDeclaration.DeclarationType == DeclarationType.ClassModule &&
decl.AsTypeDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule) &&
((ClassModuleDeclaration)decl.AsTypeDeclaration).IsExtensible)
.SelectMany(decl => decl.References).ToList();

return from access in unresolved
let callingContext = targets.FirstOrDefault(usage => usage.Context.Equals(access.CallingContext))
where callingContext != null
select new DeclarationInspectionResult(this,
string.Format(InspectionsUI.MemberNotOnInterfaceInspectionResultFormat, access.IdentifierName, callingContext.Declaration.AsTypeDeclaration.IdentifierName),
access);
string.Format(InspectionsUI.MemberNotOnInterfaceInspectionResultFormat, access.IdentifierName, callingContext.Declaration.AsTypeDeclaration.IdentifierName),
access);
}
}
}
2 changes: 1 addition & 1 deletion Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs
Expand Up @@ -174,7 +174,7 @@ private void ResolveLabel(ParserRuleContext context, string label)
{
var lexpression = expression as VBAParser.LExpressionContext
?? expression.GetChild<VBAParser.LExpressionContext>(0)
?? (expression as VBAParser.LExprContext
?? (expression as VBAParser.LExprContext
?? expression.GetChild<VBAParser.LExprContext>(0))?.lExpression();

if (lexpression != null)
Expand Down
62 changes: 62 additions & 0 deletions RubberduckTests/Inspections/MemberNotOnInterfaceInspectionTests.cs
Expand Up @@ -265,5 +265,67 @@ public void MemberNotOnInterface_Ignored_DoesNotReturnResult()
Assert.IsFalse(inspectionResults.Any());
}
}

[TestMethod]
[DeploymentItem(@"Testfiles\")]
[TestCategory("Inspections")]
public void MemberNotOnInterface_CatchesInvalidUseOfMember()
{
const string userForm1Code = @"
Private _fooBar As String
Public Property Let FooBar(value As String)
_fooBar = value
End Property
Public Property Get FooBar() As String
FooBar = _fooBar
End Property
";

const string analyzedCode = @"Option Explicit
Sub FizzBuzz()
Dim bar As UserForm1
Set bar = New UserForm1
bar.FooBar = ""FooBar""
Dim foo As UserForm
Set foo = New UserForm1
foo.FooBar = ""BarFoo""
End Sub
";
var mockVbe = new MockVbeBuilder();
var projectBuilder = mockVbe.ProjectBuilder("testproject", ProjectProtection.Unprotected);
projectBuilder.MockUserFormBuilder("UserForm1", userForm1Code).MockProjectBuilder()
.AddComponent("ReferencingModule", ComponentType.StandardModule, analyzedCode)
//.AddReference("Excel", MockVbeBuilder.LibraryPathMsExcel)
.AddReference("MSForms", MockVbeBuilder.LibraryPathMsForms);

mockVbe.AddProject(projectBuilder.Build());


var parser = MockParser.Create(mockVbe.Build().Object);

//parser.State.AddTestLibrary("Excel.1.8.xml");
parser.State.AddTestLibrary("MSForms.2.0.xml");

parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error)
{
Assert.Inconclusive("Parser Error");
}

using (var state = parser.State)
{
var inspection = new MemberNotOnInterfaceInspection(state);
var inspectionResults = inspection.GetInspectionResults();

Assert.IsTrue(inspectionResults.Any());
}

}
}
}

0 comments on commit f9f0c2a

Please sign in to comment.