Skip to content

Commit

Permalink
Merge branch 'next' into patch-3
Browse files Browse the repository at this point in the history
  • Loading branch information
MDoerner committed Oct 24, 2020
2 parents 2fdc614 + 8c42b1c commit 9e54fb6
Show file tree
Hide file tree
Showing 129 changed files with 7,575 additions and 3,164 deletions.
@@ -0,0 +1,46 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;

namespace Rubberduck.CodeAnalysis.Inspections.Abstract
{
internal abstract class ImplicitSheetReferenceInspectionBase : IdentifierReferenceInspectionFromDeclarationsBase
{
public ImplicitSheetReferenceInspectionBase(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
{ }

protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
{
var excel = finder.Projects
.SingleOrDefault(item => !item.IsUserDefined
&& item.IdentifierName == "Excel");
if (excel == null)
{
return Enumerable.Empty<Declaration>();
}

var globalModules = GlobalObjectClassNames
.Select(className => finder.FindClassModule(className, excel, true))
.OfType<ModuleDeclaration>();

return globalModules
.SelectMany(moduleClass => moduleClass.Members)
.Where(declaration => TargetMemberNames.Contains(declaration.IdentifierName)
&& declaration.DeclarationType.HasFlag(DeclarationType.Member)
&& declaration.AsTypeName == "Range");
}

private static readonly string[] GlobalObjectClassNames =
{
"Global", "_Global"
};

private static readonly string[] TargetMemberNames =
{
"Cells", "Range", "Columns", "Rows"
};
}
}
@@ -0,0 +1,46 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;

namespace Rubberduck.CodeAnalysis.Inspections.Abstract
{
internal abstract class ImplicitWorkbookReferenceInspectionBase : IdentifierReferenceInspectionFromDeclarationsBase
{
internal ImplicitWorkbookReferenceInspectionBase(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
{ }

private static readonly string[] InterestingMembers =
{
"Worksheets", "Sheets", "Names"
};

private static readonly string[] InterestingClasses =
{
"_Global", "_Application", "Global", "Application"
};

protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
{
var excel = finder.Projects
.SingleOrDefault(project => project.IdentifierName == "Excel" && !project.IsUserDefined);
if (excel == null)
{
return Enumerable.Empty<Declaration>();
}

var relevantClasses = InterestingClasses
.Select(className => finder.FindClassModule(className, excel, true))
.OfType<ModuleDeclaration>();

var relevantProperties = relevantClasses
.SelectMany(classDeclaration => classDeclaration.Members)
.OfType<PropertyGetDeclaration>()
.Where(member => InterestingMembers.Contains(member.IdentifierName));

return relevantProperties;
}
}
}
@@ -1,5 +1,4 @@
using System.Collections.Generic;
using System.Linq;
using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Parsing.Symbols;
Expand All @@ -10,7 +9,7 @@
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Locates unqualified Worksheet.Range/Cells/Columns/Rows member calls that implicitly refer to ActiveSheet.
/// Locates unqualified Worksheet.Range/Cells/Columns/Rows member calls inside worksheet modules.
/// </summary>
/// <reference name="Excel" />
/// <why>
Expand Down Expand Up @@ -42,43 +41,18 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
/// </module>
/// </example>
[RequiredLibrary("Excel")]
internal sealed class ImplicitActiveSheetReferenceInspection : IdentifierReferenceInspectionFromDeclarationsBase
internal sealed class ImplicitActiveSheetReferenceInspection : ImplicitSheetReferenceInspectionBase
{
public ImplicitActiveSheetReferenceInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
{}

protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
{
var excel = finder.Projects
.SingleOrDefault(item => !item.IsUserDefined
&& item.IdentifierName == "Excel");
if (excel == null)
{
return Enumerable.Empty<Declaration>();
}

var globalModules = GlobalObjectClassNames
.Select(className => finder.FindClassModule(className, excel, true))
.OfType<ModuleDeclaration>();

return globalModules
.SelectMany(moduleClass => moduleClass.Members)
.Where(declaration => TargetMemberNames.Contains(declaration.IdentifierName)
&& declaration.DeclarationType.HasFlag(DeclarationType.Member)
&& declaration.AsTypeName == "Range");
return !(Declaration.GetModuleParent(reference.ParentNonScoping) is DocumentModuleDeclaration document)
|| !document.SupertypeNames.Contains("Worksheet");
}

private static readonly string[] GlobalObjectClassNames =
{
"Global", "_Global"
};

private static readonly string[] TargetMemberNames =
{
"Cells", "Range", "Columns", "Rows"
};

protected override string ResultDescription(IdentifierReference reference)
{
return string.Format(
Expand Down
Expand Up @@ -40,41 +40,22 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
/// </module>
/// </example>
[RequiredLibrary("Excel")]
internal sealed class ImplicitActiveWorkbookReferenceInspection : IdentifierReferenceInspectionFromDeclarationsBase
internal sealed class ImplicitActiveWorkbookReferenceInspection : ImplicitWorkbookReferenceInspectionBase
{
public ImplicitActiveWorkbookReferenceInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
{}

private static readonly string[] InterestingMembers =
private static readonly List<string> _alwaysActiveWorkbookReferenceParents = new List<string>
{
"Worksheets", "Sheets", "Names"
"_Application", "Application"
};

private static readonly string[] InterestingClasses =
protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
{
"_Global", "_Application", "Global", "Application"
};

protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
{
var excel = finder.Projects
.SingleOrDefault(project => project.IdentifierName == "Excel" && !project.IsUserDefined);
if (excel == null)
{
return Enumerable.Empty<Declaration>();
}

var relevantClasses = InterestingClasses
.Select(className => finder.FindClassModule(className, excel, true))
.OfType<ModuleDeclaration>();

var relevantProperties = relevantClasses
.SelectMany(classDeclaration => classDeclaration.Members)
.OfType<PropertyGetDeclaration>()
.Where(member => InterestingMembers.Contains(member.IdentifierName));

return relevantProperties;
return !(Declaration.GetModuleParent(reference.ParentNonScoping) is DocumentModuleDeclaration document)
|| !document.SupertypeNames.Contains("Workbook")
|| _alwaysActiveWorkbookReferenceParents.Contains(reference.Declaration.ParentDeclaration.IdentifierName);
}

protected override string ResultDescription(IdentifierReference reference)
Expand Down
Expand Up @@ -3,15 +3,19 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using System.Linq;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Highlights implicit ByRef modifiers in user code.
/// </summary>
/// <why>
/// In modern VB (VB.NET), the implicit modifier is ByVal, as it is in most other programming languages.
/// Making the ByRef modifiers explicit can help surface potentially unexpected language defaults.
/// VBA parameters are implicitly ByRef, which differs from modern VB (VB.NET) and most other programming languages which are implicitly ByVal.
/// So, explicitly identifing VBA parameter mechanisms (the ByRef and ByVal modifiers) can help surface potentially unexpected language results.
/// The inspection does not flag an implicit parameter mechanism for the last parameter of Property mutators (Let or Set).
/// VBA applies a ByVal parameter mechanism to the last parameter in the absence (or presence!) of a modifier.
/// Exception: UserDefinedType parameters must always be passed as ByRef.
/// </why>
/// <example hasResult="true">
/// <module name="MyModule" type="Standard Module">
Expand All @@ -31,6 +35,16 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="MyModule" type="Standard Module">
/// <![CDATA[
/// Private theLength As Long
/// Public Property Let Length(newLength As Long)
/// theLength = newLength
/// End Sub
/// ]]>
/// </module>
/// </example>
internal sealed class ImplicitByRefModifierInspection : DeclarationInspectionBase
{
public ImplicitByRefModifierInspection(IDeclarationFinderProvider declarationFinderProvider)
Expand All @@ -41,21 +55,23 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
{
if (!(declaration is ParameterDeclaration parameter)
|| !parameter.IsImplicitByRef
|| parameter.IsParamArray)
|| parameter.IsParamArray
//Exclude parameters of Declare statements
|| !(parameter.ParentDeclaration is ModuleBodyElementDeclaration enclosingMethod))
{
return false;
}

var parentDeclaration = parameter.ParentDeclaration;

if (parentDeclaration is ModuleBodyElementDeclaration enclosingMethod)
{
return !enclosingMethod.IsInterfaceImplementation
&& !finder.FindEventHandlers().Contains(enclosingMethod);
}
return !IsPropertyMutatorRHSParameter(enclosingMethod, parameter)
&& !enclosingMethod.IsInterfaceImplementation
&& !finder.FindEventHandlers().Contains(enclosingMethod);
}

return parentDeclaration.DeclarationType != DeclarationType.LibraryFunction
&& parentDeclaration.DeclarationType != DeclarationType.LibraryProcedure;
private static bool IsPropertyMutatorRHSParameter(ModuleBodyElementDeclaration enclosingMethod, ParameterDeclaration implicitByRefParameter)
{
return (enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertyLet)
|| enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertySet))
&& enclosingMethod.Parameters.Last().Equals(implicitByRefParameter);
}

protected override string ResultDescription(Declaration declaration)
Expand Down
@@ -0,0 +1,72 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Locates unqualified Workbook.Worksheets/Sheets/Names member calls inside workbook document modules that implicitly refer to the containing workbook.
/// </summary>
/// <reference name="Excel" />
/// <why>
/// Implicit references inside a workbook document module can be mistakes for implicit references to the active workbook, which is the behavior in all other modules
/// By explicitly qualifying these member calls with Me, the ambiguity can be resolved.
/// </why>
/// <example hasResult="true">
/// <module name="ThisWorkbook" type="Document Module">
/// <![CDATA[
/// Private Sub Example()
/// Dim summarySheet As Worksheet
/// Set summarySheet = Worksheets("Summary") ' unqualified Worksheets is implicitly querying the containing workbook's Worksheets collection.
/// End Sub
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="ThisWorkbook" type="Document Module">
/// <![CDATA[
/// Private Sub Example()
/// Dim summarySheet As Worksheet
/// Set summarySheet = Me.Worksheets("Summary")
/// End Sub
/// ]]>
/// </module>
/// </example>
[RequiredLibrary("Excel")]
internal sealed class ImplicitContainingWorkbookReferenceInspection : ImplicitWorkbookReferenceInspectionBase
{
public ImplicitContainingWorkbookReferenceInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider)
{ }

private static readonly List<string> _alwaysActiveWorkbookReferenceParents = new List<string>
{
"_Application", "Application"
};

protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
{
return base.ObjectionableDeclarations(finder)
.Where(declaration => !_alwaysActiveWorkbookReferenceParents.Contains(declaration.ParentDeclaration.IdentifierName));
}

protected override bool IsResultReference(IdentifierReference reference, DeclarationFinder finder)
{
return Declaration.GetModuleParent(reference.ParentNonScoping) is DocumentModuleDeclaration document
&& document.SupertypeNames.Contains("Workbook");
}

protected override string ResultDescription(IdentifierReference reference)
{
var referenceText = reference.Context.GetText();
return string.Format(
InspectionResults.ImplicitContainingWorkbookReferenceInspection,
referenceText);
}
}
}

0 comments on commit 9e54fb6

Please sign in to comment.