Skip to content

Commit

Permalink
Merge pull request #4438 from comintern/bugfix
Browse files Browse the repository at this point in the history
Misc bug fixes
  • Loading branch information
retailcoder committed Oct 26, 2018
2 parents ff42617 + cca1ccd commit d6bf85d
Show file tree
Hide file tree
Showing 6 changed files with 192 additions and 33 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -94,8 +94,14 @@ public sealed class HungarianNotationInspection : InspectionBase
DeclarationType.Variable
};

private static readonly List<DeclarationType> IgnoredProcedureTypes = new List<DeclarationType>
{
DeclarationType.LibraryFunction,
DeclarationType.LibraryProcedure
};

#endregion

private readonly IPersistanceService<CodeInspectionSettings> _settings;

public HungarianNotationInspection(RubberduckParserState state, IPersistanceService<CodeInspectionSettings> settings)
Expand All @@ -112,7 +118,10 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
var hungarians = UserDeclarations
.Where(declaration => !whitelistedNames.Contains(declaration.IdentifierName) &&
TargetDeclarationTypes.Contains(declaration.DeclarationType) &&
HungarianIdentifierRegex.IsMatch(declaration.IdentifierName))
!IgnoredProcedureTypes.Contains(declaration.DeclarationType) &&
!IgnoredProcedureTypes.Contains(declaration.ParentDeclaration.DeclarationType) &&
HungarianIdentifierRegex.IsMatch(declaration.IdentifierName) &&
!IsIgnoringInspectionResultFor(declaration, AnnotationName))
.Select(issue => new DeclarationInspectionResult(this,
string.Format(Resources.Inspections.InspectionResults.IdentifierNameInspection,
RubberduckUI.ResourceManager.GetString($"DeclarationType_{issue.DeclarationType}", CultureInfo.CurrentUICulture),
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()

var targets = Declarations.Where(decl => decl.AsTypeDeclaration != null &&
!decl.AsTypeDeclaration.IsUserDefined &&
decl.AsTypeDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule) &&
decl.AsTypeDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule) &&
((ClassModuleDeclaration)decl.AsTypeDeclaration).IsExtensible)
.SelectMany(decl => decl.References).ToList();
return unresolved
Expand All @@ -33,7 +33,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
usage.Context.Parent.Parent.Equals(access.CallingContext))
)
})
.Where(memberAccess => memberAccess.callingContext != null)
.Where(memberAccess => memberAccess.callingContext != null &&
memberAccess.callingContext.Declaration.DeclarationType != DeclarationType.Control) //TODO - remove this exception after resolving #2592)
.Select(memberAccess => new DeclarationInspectionResult(this,
string.Format(InspectionResults.MemberNotOnInterfaceInspection, memberAccess.access.IdentifierName,
memberAccess.callingContext.Declaration.AsTypeDeclaration.IdentifierName), memberAccess.access));
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,15 @@ public sealed class UnassignedVariableUsageInspection : InspectionBase
public UnassignedVariableUsageInspection(RubberduckParserState state)
: base(state) { }

//See https://github.com/rubberduck-vba/Rubberduck/issues/2010 for why these are being excluded.
private static readonly List<string> IgnoredFunctions = new List<string>
{
"VBE7.DLL;VBA.Strings.Len",
"VBE7.DLL;VBA.Strings.LenB",
"VBA6.DLL;VBA.Strings.Len",
"VBA6.DLL;VBA.Strings.LenB"
};

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var declarations = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
Expand All @@ -27,41 +36,33 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
&& !declaration.IsSelfAssigned
&& !declaration.References.Any(reference => reference.IsAssignment));

//See https://github.com/rubberduck-vba/Rubberduck/issues/2010 for why these are being excluded.
//TODO: These need to be modified to correctly work in VB6.
var lenFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.Len"));
var lenbFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.LenB"));
var excludedDeclarations = BuiltInDeclarations.Where(decl => IgnoredFunctions.Contains(decl.QualifiedName.ToString())).ToList();

return declarations.Where(d => d.References.Any() &&
!DeclarationReferencesContainsReference(lenFunction, d) &&
!DeclarationReferencesContainsReference(lenbFunction, d))
.SelectMany(d => d.References)
.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
.Select(r => new IdentifierReferenceInspectionResult(this,
string.Format(InspectionResults.UnassignedVariableUsageInspection, r.IdentifierName),
State,
r)).ToList();
return declarations
.Where(d => d.References.Any() && !excludedDeclarations.Any(excl => DeclarationReferencesContainsReference(excl, d)))
.SelectMany(d => d.References)
.Distinct()
.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
.Select(r => new IdentifierReferenceInspectionResult(this,
string.Format(InspectionResults.UnassignedVariableUsageInspection, r.IdentifierName),
State,
r)).ToList();
}

private bool DeclarationReferencesContainsReference(Declaration parentDeclaration, Declaration target)
private static bool DeclarationReferencesContainsReference(Declaration parentDeclaration, Declaration target)
{
if (parentDeclaration == null)
{
return false;
}

foreach (var targetReference in target.References)
{
foreach (var reference in parentDeclaration.References)
{
var context = (ParserRuleContext) reference.Context.Parent;
var context = (ParserRuleContext)reference.Context.Parent;
if (context.GetSelection().Contains(targetReference.Selection))
{
return true;
}
}
}

return false;
}
}
Expand Down
71 changes: 67 additions & 4 deletions RubberduckTests/Inspections/HungarianNotationInspectionTests.cs
Original file line number Diff line number Diff line change
Expand Up @@ -200,12 +200,75 @@ public void HungarianNotation_DoesNotReturnResult_WhenWhitelisted()

[Test]
[Category("Inspections")]
public void InspectionName()
public void HungarianNotation_DoesNotReturnResult_Ignored()
{
const string inspectionName = "UseMeaningfulNameInspection";
var inspection = new UseMeaningfulNameInspection(null, null);
const string inputCode =
@"Sub Hungarian()
'@Ignore HungarianNotation
Dim oFoo As Object
End Sub";

var builder = new MockVbeBuilder();
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
.Build();
var vbe = builder.AddProject(project).Build();

using (var state = MockParser.CreateAndParse(vbe.Object))
{
var inspection = new HungarianNotationInspection(state, UseMeaningfulNameInspectionTests.GetInspectionSettings().Object);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

Assert.AreEqual(0, inspectionResults.Count());
}
}

[Test]
[Category("Inspections")]
public void HungarianNotation_DoesNotReturnResult_LibraryFunctionParameters()
{
const string inputCode =
@"
Private Declare Function GetUserName Lib ""advapi32.dll"" Alias ""GetUserNameA"" (ByVal lpBuffer As String, nSize As Long) As Long
";

var builder = new MockVbeBuilder();
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
.Build();
var vbe = builder.AddProject(project).Build();

using (var state = MockParser.CreateAndParse(vbe.Object))
{
var inspection = new HungarianNotationInspection(state, UseMeaningfulNameInspectionTests.GetInspectionSettings().Object);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

Assert.AreEqual(inspectionName, inspection.Name);
Assert.AreEqual(0, inspectionResults.Count());
}
}

[Test]
[Category("Inspections")]
public void HungarianNotation_DoesNotReturnResult_LibraryFunction()
{
const string inputCode =
@"
Private Declare Sub chkVoid Lib ""somelib.dll"" Alias ""chkVoidA"" (number As Long)
";

var builder = new MockVbeBuilder();
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
.Build();
var vbe = builder.AddProject(project).Build();

using (var state = MockParser.CreateAndParse(vbe.Object))
{
var inspection = new HungarianNotationInspection(state, UseMeaningfulNameInspectionTests.GetInspectionSettings().Object);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

Assert.AreEqual(0, inspectionResults.Count());
}
}
}
}
25 changes: 21 additions & 4 deletions RubberduckTests/Inspections/MemberNotOnInterfaceInspectionTests.cs
Original file line number Diff line number Diff line change
Expand Up @@ -379,13 +379,30 @@ End Sub
}

[Test]
[Ignore("Test concurrency issue. Only passes if run individually.")]
[Category("Inspections")]
public void InspectionName()
public void MemberNotOnInterface_DoesNotReturnResult_ControlObject()
{
const string inspectionName = "MemberNotOnInterfaceInspection";
var inspection = new MemberNotOnInterfaceInspection(null);
const string inputCode =
@"Sub Foo(bar as MSForms.TextBox)
Debug.Print bar.Left
End Sub";

var vbeBuilder = new MockVbeBuilder();
var projectBuilder = vbeBuilder.ProjectBuilder("testproject", ProjectProtection.Unprotected);
projectBuilder.MockUserFormBuilder("UserForm1", inputCode).AddFormToProjectBuilder()
.AddReference("MSForms", MockVbeBuilder.LibraryPathMsForms, 2, 0, true);

Assert.AreEqual(inspectionName, inspection.Name);
vbeBuilder.AddProject(projectBuilder.Build());
var vbe = vbeBuilder.Build();

using (var state = MockParser.CreateAndParse(vbe.Object))
{
var inspection = new MemberNotOnInterfaceInspection(state);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

Assert.IsTrue(!inspectionResults.Any());
}
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -112,6 +112,30 @@ public void UnassignedVariableUsage_Ignored_DoesNotReturnResult()
}
}

[Test]
[Category("Inspections")]
public void UnassignedVariableUsage_Ignored_DoesNotReturnResultMultipleIgnores()
{
const string inputCode =
@"Sub Foo()
Dim b As Boolean
Dim bb As Boolean
'@Ignore UnassignedVariableUsage, VariableNotAssigned
bb = b
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
using (var state = MockParser.CreateAndParse(vbe.Object))
{

var inspection = new UnassignedVariableUsageInspection(state);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

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

[Test]
[Category("Inspections")]
public void UnassignedVariableUsage_NoResultIfNoReferences()
Expand All @@ -132,6 +156,50 @@ Dim foo
}
}

[Test]
[Ignore("Test concurrency issue. Only passes if run individually.")]
[Category("Inspections")]
public void UnassignedVariableUsage_NoResultForLenFunction()
{
const string inputCode =
@"Sub DoSomething()
Dim foo As LongPtr
Debug.Print Len(foo)
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
using (var state = MockParser.CreateAndParse(vbe.Object))
{

var inspection = new UnassignedVariableUsageInspection(state);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

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

[Test]
[Ignore("Test concurrency issue. Only passes if run individually.")]
[Category("Inspections")]
public void UnassignedVariableUsage_NoResultForLenBFunction()
{
const string inputCode =
@"Sub DoSomething()
Dim foo As LongPtr
Debug.Print LenB(foo)
End Sub";

var vbe = MockVbeBuilder.BuildFromSingleModule(inputCode, ComponentType.ClassModule, out _);
using (var state = MockParser.CreateAndParse(vbe.Object))
{

var inspection = new UnassignedVariableUsageInspection(state);
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);

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

[Test]
[Category("Inspections")]
public void InspectionName()
Expand Down

0 comments on commit d6bf85d

Please sign in to comment.