Skip to content

Commit

Permalink
Merge branch 'rubberduck-vba-next' into VariableTypeInference
Browse files Browse the repository at this point in the history
  • Loading branch information
BZngr committed Oct 24, 2020
2 parents e4e3f09 + 6e7c82a commit 5b7e35e
Show file tree
Hide file tree
Showing 99 changed files with 6,311 additions and 2,953 deletions.
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,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);
}
}
}
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
Expand Up @@ -383,8 +383,14 @@ private void RegisterSpecialFactories(IWindsorContainer container)
.ImplementedBy<AnnotationArgumentViewModelFactory>()
.LifestyleSingleton());

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

RegisterUnreachableCaseFactories(container);

RegisterEncapsulateFieldRefactoringFactories(container);

RegisterImplicitTypeToExplicitRefactoringAction(container);
}

Expand All @@ -395,6 +401,22 @@ 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());
}

//FIXME: Do not think this explicit registration should be necessary.
//CW could not resolve ICodeOnlyRefactoringAction<ImplicitTypeToExplicitModel> without this
private void RegisterImplicitTypeToExplicitRefactoringAction(IWindsorContainer container)
Expand Down
Expand Up @@ -20,7 +20,7 @@ public abstract class RefactoringPreviewProviderWrapperBase<TModel> : IRefactori

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

0 comments on commit 5b7e35e

Please sign in to comment.