Skip to content

Commit

Permalink
Merge branch 'rubberduck-vba/next' into MoveMember_3618
Browse files Browse the repository at this point in the history
  • Loading branch information
BZngr committed May 24, 2020
2 parents 5f1481f + 65bf91e commit c8ef102
Show file tree
Hide file tree
Showing 6 changed files with 66 additions and 13 deletions.
Expand Up @@ -19,12 +19,20 @@ protected MemberAccessMayReturnNothingInspectionBase(IDeclarationFinderProvider
: base(declarationFinderProvider)
{}

/// <summary>
/// Members that might return Nothing
/// </summary>
/// <remarks>
/// It must not be legal to call the members unqualified. In particular, user-defined members will not be considered.
/// Moreover, this disqualifies all members on global objects.
/// </remarks>
public abstract IEnumerable<Declaration> MembersUnderTest(DeclarationFinder finder);
public abstract string ResultTemplate { get; }

protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
{
return MembersUnderTest(finder);
//This restriction is in place because the inspection currently cannot handle unqualified accesses.
return MembersUnderTest(finder).Where(member => !member.IsUserDefined);
}

protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
Expand All @@ -46,7 +54,7 @@ protected override bool IsResultReference(IdentifierReference reference, Declara
{
return usageContext is VBAParser.MemberAccessExprContext
|| !(usageContext is VBAParser.CallStmtContext)
&& !ContextIsNothingTest(usageContext);
&& !ContextIsNothing(usageContext);
}

var assignedTo = AssignmentTarget(reference, finder, setter);
Expand All @@ -65,14 +73,21 @@ private static IdentifierReference AssignmentTarget(IdentifierReference referenc

private static RuleContext UsageContext(IdentifierReference reference)
{
var access = reference.Context.GetAncestor<VBAParser.MemberAccessExprContext>();
var usageContext = access.Parent is VBAParser.IndexExprContext indexExpr
//We prefer the with member access over the member access, because the accesses are resolved right to left.
var access = reference.Context.GetAncestor<VBAParser.WithMemberAccessExprContext>() as VBAParser.LExpressionContext
?? reference.Context.GetAncestor<VBAParser.MemberAccessExprContext>();

if (access == null)
{
return null;
}

return access.Parent is VBAParser.IndexExprContext indexExpr
? indexExpr.Parent
: access.Parent;
return usageContext;
}

private static bool ContextIsNothingTest(IParseTree context)
private static bool ContextIsNothing(IParseTree context)
{
return context is VBAParser.LExprContext
&& context.Parent is VBAParser.RelationalOpContext comparison
Expand All @@ -86,7 +101,7 @@ private static bool IsUsedBeforeCheckingForNothing(IdentifierReference assignedT
var firstUse = GetReferenceNodes(tree).FirstOrDefault();

return !(firstUse is null)
&& !ContextIsNothingTest(firstUse.Reference.Context.Parent);
&& !ContextIsNothing(firstUse.Reference.Context.Parent);
}

private static IEnumerable<INode> GetReferenceNodes(INode node)
Expand Down
Expand Up @@ -200,7 +200,6 @@
SelectedItem="{Binding SelectedItem}"
SelectionUnit="FullRow"
ItemsSource="{Binding Results, NotifyOnSourceUpdated=True}"
RequestBringIntoView="InspectionResultsGrid_RequestBringIntoView"
VirtualizingPanel.IsVirtualizingWhenGrouping="True"
ScrollViewer.CanContentScroll="True"
ScrollViewer.VerticalScrollBarVisibility="Auto"
Expand Down
Expand Up @@ -144,6 +144,7 @@
Text="{Binding Path=PropertyName, Mode=TwoWay, UpdateSourceTrigger=PropertyChanged}"
TabIndex="1" Margin="10,5"
VerticalAlignment="Center"
VerticalContentAlignment="Center"
Height="22" />
<Image Grid.Row="1" Style="{StaticResource InvalidNameIconStyle}"
Visibility="{Binding Path=SelectionHasValidEncapsulationAttributes, Converter={StaticResource BoolToHiddenVisibility}}" />
Expand Down
9 changes: 6 additions & 3 deletions Rubberduck.Core/UI/UnitTesting/TestExplorerViewModel.cs
Expand Up @@ -256,6 +256,7 @@ public bool CanExecuteIgnoreSelectedTests(object obj)

return false;
}

public bool CanExecuteUnignoreSelectedTests(object obj)
{
if (!Model.IsBusy && obj is IList viewModels && viewModels.Count > 0)
Expand All @@ -273,12 +274,14 @@ public bool CanExecuteIgnoreGroupCommand(object obj)

return groupItems.Cast<TestMethodViewModel>().Count(test => test.Method.IsIgnored) != groupItems.Count;
}

public bool CanExecuteUnignoreGroupCommand(object obj)
{
var groupItems = MouseOverGroup?.Items
?? GroupContainingSelectedTest(MouseOverTest).Items;

return groupItems.Cast<TestMethodViewModel>().Any(test => test.Method.IsIgnored);
?? GroupContainingSelectedTest(MouseOverTest)?.Items;

return groupItems != null
&& groupItems.Cast<TestMethodViewModel>().Any(test => test.Method.IsIgnored);
}

#region Commands
Expand Down
4 changes: 2 additions & 2 deletions Rubberduck.Resources/Inspections/InspectionResults.de.resx
Expand Up @@ -183,7 +183,7 @@
<value>Der Variable '{0}' wird kein Wert zugewiesen.</value>
</data>
<data name="EmptyStringLiteralInspection" xml:space="preserve">
<value>vbNullString' sollte statt einem leeren String-Literal verwendet werden.</value>
<value>'vbNullString' sollte statt einem leeren String-Literal verwendet werden.</value>
</data>
<data name="ObjectVariableNotSetInspection" xml:space="preserve">
<value>Objektvariable '{0}' wird ohne das 'Set'-Schlüsselwort zugewiesen.</value>
Expand Down Expand Up @@ -467,4 +467,4 @@ In Memoriam, 1972-2018</value>
<data name="SuperfluousAnnotationArgumentInspection" xml:space="preserve">
<value>Die Annotation '{0}' erwartet weniger Argumente.</value>
</data>
</root>
</root>
Expand Up @@ -26,6 +26,22 @@ End Sub
Assert.AreEqual(1, InspectionResults(inputCode).Count());
}

[Test]
[Category("Inspections")]
public void ExcelMemberMayReturnNothing_ReturnsResult_WithMemberAccessOnFind()
{
const string inputCode =
@"Sub UnderTest()
Dim ws As Worksheet
Set ws = Sheet1
With ws.UsedRange
foo = .Find(""foo"").Row
End With
End Sub
";
Assert.AreEqual(1, InspectionResults(inputCode).Count());
}

[Test]
[Category("Inspections")]
public void ExcelMemberMayReturnNothing_Ignored_DoesNotReturnResult()
Expand Down Expand Up @@ -111,6 +127,25 @@ End Sub
Assert.AreEqual(1, InspectionResults(inputCode).Count());
}

[Test]
[Category("Inspections")]
public void ExcelMemberMayReturnNothing_ReturnsResult_AssignedAndNotTested_FromWithMemberAccess()
{
const string inputCode =
@"Sub UnderTest()
Dim ws As Worksheet
Set ws = Sheet1
Dim result As Range
With ws.UsedRange
Set result = .Find(""foo"")
End With
result.Value = ""bar""
End Sub
";

Assert.AreEqual(1, InspectionResults(inputCode).Count());
}

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

0 comments on commit c8ef102

Please sign in to comment.