Skip to content

Commit

Permalink
Merge branch 'next' into SuperTypesForDocumentModules
Browse files Browse the repository at this point in the history
# Conflicts:
#	Rubberduck.Resources/Inspections/InspectionInfo.resx
#	Rubberduck.Resources/Inspections/InspectionNames.resx
#	Rubberduck.Resources/Inspections/InspectionResults.resx
  • Loading branch information
MDoerner committed Oct 24, 2020
2 parents 04510b5 + dd95ad5 commit 6870b27
Show file tree
Hide file tree
Showing 104 changed files with 6,398 additions and 2,955 deletions.
Original file line number Diff line number Diff line change
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
Original file line number Diff line number Diff line change
@@ -0,0 +1,68 @@
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;
using System.Linq;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Flags the value-parameter of a property mutators that are declared with an explict ByRef modifier.
/// </summary>
/// <why>
/// Regardless of the presence or absence of an explicit ByRef or ByVal modifier, the value-parameter
/// of a property mutator is always treated as though it had an explicit ByVal modifier.
/// Exception: UserDefinedType parameters are always passed by reference.
/// </why>
/// <example hasResult="true">
/// <module name="MyModule" type="Standard Module">
/// <![CDATA[
/// Private fizzField As Long
/// Public Property Get Fizz() As Long
/// Fizz = fizzFiled
/// End Property
/// Public Property Let Fizz(ByRef arg As Long)
/// fizzFiled = arg
/// End Property
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="MyModule" type="Standard Module">
/// <![CDATA[
/// Private fizzField As Long
/// Public Property Get Fizz() As Long
/// Fizz = fizzFiled
/// End Property
/// Public Property Let Fizz(arg As Long)
/// fizzFiled = arg
/// End Property
/// ]]>
/// </module>
/// </example>
internal sealed class MisleadingByRefParameterInspection : DeclarationInspectionBase
{
public MisleadingByRefParameterInspection(IDeclarationFinderProvider declarationFinderProvider)
: base(declarationFinderProvider, DeclarationType.Parameter)
{ }

protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
{
return declaration is ParameterDeclaration parameter
&& !(parameter.AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.UserDefinedType) ?? false)
&& parameter.ParentDeclaration is ModuleBodyElementDeclaration enclosingMethod
&& (enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertyLet)
|| enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertySet))
&& enclosingMethod.Parameters.Last() == parameter
&& parameter.IsByRef && !parameter.IsImplicitByRef;
}

protected override string ResultDescription(Declaration declaration)
{
return string.Format(
InspectionResults.MisleadingByRefParameterInspection,
declaration.IdentifierName, declaration.ParentDeclaration.QualifiedName.MemberName);
}
}
}
Original file line number Diff line number Diff line change
@@ -1,9 +1,12 @@
using Antlr4.Runtime;
using System.Linq;
using Antlr4.Runtime;
using Antlr4.Runtime.Tree;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.ThunderCode
Expand Down Expand Up @@ -31,6 +34,27 @@ protected override string ResultDescription(QualifiedContext<ParserRuleContext>
return InspectionResults.NegativeLineNumberInspection.ThunderCodeFormat();
}

protected override bool IsResultContext(QualifiedContext<ParserRuleContext> context, DeclarationFinder finder)
{
return !IsOnErrorGotoMinusOne(context.Context)
|| ProcedureHasMinusOneLabel(finder, context);
}

private static bool IsOnErrorGotoMinusOne(ParserRuleContext context)
{
return context is VBAParser.OnErrorStmtContext onErrorStatement
&& "-1".Equals(onErrorStatement.expression()?.GetText().Trim());
}

private static bool ProcedureHasMinusOneLabel(DeclarationFinder finder, QualifiedContext<ParserRuleContext> context)
{
return finder.Members(context.ModuleName, DeclarationType.LineLabel)
.Any(label => label.IdentifierName.Equals("-1")
&& (label.ParentScopeDeclaration
.Context?.GetSelection()
.Contains(context.Context.GetSelection()) ?? false));
}

private class NegativeLineNumberKeywordsListener : InspectionListenerBase<ParserRuleContext>
{
public override void EnterOnErrorStmt(VBAParser.OnErrorStmtContext context)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ internal sealed class PassParameterByValueQuickFix : QuickFixBase
private readonly IDeclarationFinderProvider _declarationFinderProvider;

public PassParameterByValueQuickFix(IDeclarationFinderProvider declarationFinderProvider)
: base(typeof(ParameterCanBeByValInspection))
: base(typeof(ParameterCanBeByValInspection), typeof(MisleadingByRefParameterInspection))
{
_declarationFinderProvider = declarationFinderProvider;
}
Expand Down
22 changes: 22 additions & 0 deletions Rubberduck.Main/Root/RubberduckIoCInstaller.cs
Original file line number Diff line number Diff line change
Expand Up @@ -380,7 +380,14 @@ private void RegisterSpecialFactories(IWindsorContainer container)
container.Register(Component.For<IAnnotationArgumentViewModelFactory>()
.ImplementedBy<AnnotationArgumentViewModelFactory>()
.LifestyleSingleton());

container.Register(Component.For<IReplacePrivateUDTMemberReferencesModelFactory>()
.ImplementedBy<ReplacePrivateUDTMemberReferencesModelFactory>()
.LifestyleSingleton());

RegisterUnreachableCaseFactories(container);

RegisterEncapsulateFieldRefactoringFactories(container);
}

private void RegisterUnreachableCaseFactories(IWindsorContainer container)
Expand All @@ -390,6 +397,21 @@ private void RegisterUnreachableCaseFactories(IWindsorContainer container)
.LifestyleSingleton());
}

private void RegisterEncapsulateFieldRefactoringFactories(IWindsorContainer container)
{
container.Register(Component.For<IEncapsulateFieldCandidateFactory>()
.ImplementedBy<EncapsulateFieldCandidateFactory>()
.LifestyleSingleton());
container.Register(Component.For<IEncapsulateFieldUseBackingUDTMemberModelFactory>()
.ImplementedBy<EncapsulateFieldUseBackingUDTMemberModelFactory>()
.LifestyleSingleton());
container.Register(Component.For<IEncapsulateFieldUseBackingFieldModelFactory>()
.ImplementedBy<EncapsulateFieldUseBackingFieldModelFactory>()
.LifestyleSingleton());
container.Register(Component.For<IEncapsulateFieldModelFactory>()
.ImplementedBy<EncapsulateFieldModelFactory>()
.LifestyleSingleton());
}

private void RegisterQuickFixes(IWindsorContainer container, Assembly[] assembliesToRegister)
{
Expand Down
7 changes: 5 additions & 2 deletions Rubberduck.Parsing/Binding/Bindings/IndexDefaultBinding.cs
Original file line number Diff line number Diff line change
Expand Up @@ -356,8 +356,11 @@ declared type.
private static bool ArgumentListIsCompatible(ICollection<ParameterDeclaration> parameters, ArgumentList argumentList)
{
return (parameters.Count >= (argumentList?.Arguments.Count ?? 0)
|| parameters.Any(parameter => parameter.IsParamArray))
&& parameters.Count(parameter => !parameter.IsOptional && !parameter.IsParamArray) <= (argumentList?.Arguments.Count ?? 0);
|| parameters.Any(parameter => parameter.IsParamArray))
&& parameters.Count(parameter => !parameter.IsOptional && !parameter.IsParamArray) <= (argumentList?.Arguments.Count ?? 0)
|| parameters.Count == 0
&& argumentList?.Arguments.Count == 1
&& argumentList.Arguments.Single().ArgumentType == ArgumentListArgumentType.Missing;
}

private IBoundExpression ResolveRecursiveDefaultMember(Declaration defaultMember, ExpressionClassification defaultMemberClassification, ArgumentList argumentList, ParserRuleContext expression, Declaration parent, int defaultMemberResolutionRecursionDepth, RecursiveDefaultMemberAccessExpression containedExpression)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -646,8 +646,8 @@ private void AddIdentifierStatementLabelDeclaration(VBAParser.IdentifierStatemen

private void AddLineNumberLabelDeclaration(VBAParser.LineNumberLabelContext context)
{
var statementText = context.numberLiteral().GetText();
var statementSelection = context.numberLiteral().GetSelection();
var statementText = context.GetText().Trim();
var statementSelection = context.GetSelection();

AddDeclaration(
CreateDeclaration(
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ protected RefactoringPreviewProviderWrapperBase(

protected abstract QualifiedModuleName ComponentToShow(TModel model);

public string Preview(TModel model)
public virtual string Preview(TModel model)
{
var rewriteSession = RewriteSession(RewriteSessionCodeKind);
_refactoringAction.Refactor(model, rewriteSession);
Expand Down
Loading

0 comments on commit 6870b27

Please sign in to comment.