Skip to content

Commit 6870b27

Browse files
committed
Merge branch 'next' into SuperTypesForDocumentModules
# Conflicts: # Rubberduck.Resources/Inspections/InspectionInfo.resx # Rubberduck.Resources/Inspections/InspectionNames.resx # Rubberduck.Resources/Inspections/InspectionResults.resx
2 parents 04510b5 + dd95ad5 commit 6870b27

File tree

104 files changed

+6398
-2955
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

104 files changed

+6398
-2955
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitByRefModifierInspection.cs

Lines changed: 28 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -3,15 +3,19 @@
33
using Rubberduck.Parsing.VBA;
44
using Rubberduck.Parsing.VBA.DeclarationCaching;
55
using Rubberduck.Resources.Inspections;
6+
using System.Linq;
67

78
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
89
{
910
/// <summary>
1011
/// Highlights implicit ByRef modifiers in user code.
1112
/// </summary>
1213
/// <why>
13-
/// In modern VB (VB.NET), the implicit modifier is ByVal, as it is in most other programming languages.
14-
/// Making the ByRef modifiers explicit can help surface potentially unexpected language defaults.
14+
/// VBA parameters are implicitly ByRef, which differs from modern VB (VB.NET) and most other programming languages which are implicitly ByVal.
15+
/// So, explicitly identifing VBA parameter mechanisms (the ByRef and ByVal modifiers) can help surface potentially unexpected language results.
16+
/// The inspection does not flag an implicit parameter mechanism for the last parameter of Property mutators (Let or Set).
17+
/// VBA applies a ByVal parameter mechanism to the last parameter in the absence (or presence!) of a modifier.
18+
/// Exception: UserDefinedType parameters must always be passed as ByRef.
1519
/// </why>
1620
/// <example hasResult="true">
1721
/// <module name="MyModule" type="Standard Module">
@@ -31,6 +35,16 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
3135
/// ]]>
3236
/// </module>
3337
/// </example>
38+
/// <example hasResult="false">
39+
/// <module name="MyModule" type="Standard Module">
40+
/// <![CDATA[
41+
/// Private theLength As Long
42+
/// Public Property Let Length(newLength As Long)
43+
/// theLength = newLength
44+
/// End Sub
45+
/// ]]>
46+
/// </module>
47+
/// </example>
3448
internal sealed class ImplicitByRefModifierInspection : DeclarationInspectionBase
3549
{
3650
public ImplicitByRefModifierInspection(IDeclarationFinderProvider declarationFinderProvider)
@@ -41,21 +55,23 @@ protected override bool IsResultDeclaration(Declaration declaration, Declaration
4155
{
4256
if (!(declaration is ParameterDeclaration parameter)
4357
|| !parameter.IsImplicitByRef
44-
|| parameter.IsParamArray)
58+
|| parameter.IsParamArray
59+
//Exclude parameters of Declare statements
60+
|| !(parameter.ParentDeclaration is ModuleBodyElementDeclaration enclosingMethod))
4561
{
4662
return false;
4763
}
4864

49-
var parentDeclaration = parameter.ParentDeclaration;
50-
51-
if (parentDeclaration is ModuleBodyElementDeclaration enclosingMethod)
52-
{
53-
return !enclosingMethod.IsInterfaceImplementation
54-
&& !finder.FindEventHandlers().Contains(enclosingMethod);
55-
}
65+
return !IsPropertyMutatorRHSParameter(enclosingMethod, parameter)
66+
&& !enclosingMethod.IsInterfaceImplementation
67+
&& !finder.FindEventHandlers().Contains(enclosingMethod);
68+
}
5669

57-
return parentDeclaration.DeclarationType != DeclarationType.LibraryFunction
58-
&& parentDeclaration.DeclarationType != DeclarationType.LibraryProcedure;
70+
private static bool IsPropertyMutatorRHSParameter(ModuleBodyElementDeclaration enclosingMethod, ParameterDeclaration implicitByRefParameter)
71+
{
72+
return (enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertyLet)
73+
|| enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertySet))
74+
&& enclosingMethod.Parameters.Last().Equals(implicitByRefParameter);
5975
}
6076

6177
protected override string ResultDescription(Declaration declaration)
Lines changed: 68 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,68 @@
1+
using Rubberduck.CodeAnalysis.Inspections.Abstract;
2+
using Rubberduck.Parsing.Symbols;
3+
using Rubberduck.Parsing.VBA;
4+
using Rubberduck.Parsing.VBA.DeclarationCaching;
5+
using Rubberduck.Resources.Inspections;
6+
using System.Linq;
7+
8+
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
9+
{
10+
/// <summary>
11+
/// Flags the value-parameter of a property mutators that are declared with an explict ByRef modifier.
12+
/// </summary>
13+
/// <why>
14+
/// Regardless of the presence or absence of an explicit ByRef or ByVal modifier, the value-parameter
15+
/// of a property mutator is always treated as though it had an explicit ByVal modifier.
16+
/// Exception: UserDefinedType parameters are always passed by reference.
17+
/// </why>
18+
/// <example hasResult="true">
19+
/// <module name="MyModule" type="Standard Module">
20+
/// <![CDATA[
21+
/// Private fizzField As Long
22+
/// Public Property Get Fizz() As Long
23+
/// Fizz = fizzFiled
24+
/// End Property
25+
/// Public Property Let Fizz(ByRef arg As Long)
26+
/// fizzFiled = arg
27+
/// End Property
28+
/// ]]>
29+
/// </module>
30+
/// </example>
31+
/// <example hasResult="false">
32+
/// <module name="MyModule" type="Standard Module">
33+
/// <![CDATA[
34+
/// Private fizzField As Long
35+
/// Public Property Get Fizz() As Long
36+
/// Fizz = fizzFiled
37+
/// End Property
38+
/// Public Property Let Fizz(arg As Long)
39+
/// fizzFiled = arg
40+
/// End Property
41+
/// ]]>
42+
/// </module>
43+
/// </example>
44+
internal sealed class MisleadingByRefParameterInspection : DeclarationInspectionBase
45+
{
46+
public MisleadingByRefParameterInspection(IDeclarationFinderProvider declarationFinderProvider)
47+
: base(declarationFinderProvider, DeclarationType.Parameter)
48+
{ }
49+
50+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
51+
{
52+
return declaration is ParameterDeclaration parameter
53+
&& !(parameter.AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.UserDefinedType) ?? false)
54+
&& parameter.ParentDeclaration is ModuleBodyElementDeclaration enclosingMethod
55+
&& (enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertyLet)
56+
|| enclosingMethod.DeclarationType.HasFlag(DeclarationType.PropertySet))
57+
&& enclosingMethod.Parameters.Last() == parameter
58+
&& parameter.IsByRef && !parameter.IsImplicitByRef;
59+
}
60+
61+
protected override string ResultDescription(Declaration declaration)
62+
{
63+
return string.Format(
64+
InspectionResults.MisleadingByRefParameterInspection,
65+
declaration.IdentifierName, declaration.ParentDeclaration.QualifiedName.MemberName);
66+
}
67+
}
68+
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ThunderCode/NegativeLineNumberInspection.cs

Lines changed: 25 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,12 @@
1-
using Antlr4.Runtime;
1+
using System.Linq;
2+
using Antlr4.Runtime;
23
using Antlr4.Runtime.Tree;
34
using Rubberduck.CodeAnalysis.Inspections.Abstract;
45
using Rubberduck.Parsing;
56
using Rubberduck.Parsing.Grammar;
7+
using Rubberduck.Parsing.Symbols;
68
using Rubberduck.Parsing.VBA;
9+
using Rubberduck.Parsing.VBA.DeclarationCaching;
710
using Rubberduck.Resources.Inspections;
811

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

37+
protected override bool IsResultContext(QualifiedContext<ParserRuleContext> context, DeclarationFinder finder)
38+
{
39+
return !IsOnErrorGotoMinusOne(context.Context)
40+
|| ProcedureHasMinusOneLabel(finder, context);
41+
}
42+
43+
private static bool IsOnErrorGotoMinusOne(ParserRuleContext context)
44+
{
45+
return context is VBAParser.OnErrorStmtContext onErrorStatement
46+
&& "-1".Equals(onErrorStatement.expression()?.GetText().Trim());
47+
}
48+
49+
private static bool ProcedureHasMinusOneLabel(DeclarationFinder finder, QualifiedContext<ParserRuleContext> context)
50+
{
51+
return finder.Members(context.ModuleName, DeclarationType.LineLabel)
52+
.Any(label => label.IdentifierName.Equals("-1")
53+
&& (label.ParentScopeDeclaration
54+
.Context?.GetSelection()
55+
.Contains(context.Context.GetSelection()) ?? false));
56+
}
57+
3458
private class NegativeLineNumberKeywordsListener : InspectionListenerBase<ParserRuleContext>
3559
{
3660
public override void EnterOnErrorStmt(VBAParser.OnErrorStmtContext context)

Rubberduck.CodeAnalysis/QuickFixes/Concrete/PassParameterByValueQuickFix.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ internal sealed class PassParameterByValueQuickFix : QuickFixBase
3838
private readonly IDeclarationFinderProvider _declarationFinderProvider;
3939

4040
public PassParameterByValueQuickFix(IDeclarationFinderProvider declarationFinderProvider)
41-
: base(typeof(ParameterCanBeByValInspection))
41+
: base(typeof(ParameterCanBeByValInspection), typeof(MisleadingByRefParameterInspection))
4242
{
4343
_declarationFinderProvider = declarationFinderProvider;
4444
}

Rubberduck.Main/Root/RubberduckIoCInstaller.cs

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -380,7 +380,14 @@ private void RegisterSpecialFactories(IWindsorContainer container)
380380
container.Register(Component.For<IAnnotationArgumentViewModelFactory>()
381381
.ImplementedBy<AnnotationArgumentViewModelFactory>()
382382
.LifestyleSingleton());
383+
384+
container.Register(Component.For<IReplacePrivateUDTMemberReferencesModelFactory>()
385+
.ImplementedBy<ReplacePrivateUDTMemberReferencesModelFactory>()
386+
.LifestyleSingleton());
387+
383388
RegisterUnreachableCaseFactories(container);
389+
390+
RegisterEncapsulateFieldRefactoringFactories(container);
384391
}
385392

386393
private void RegisterUnreachableCaseFactories(IWindsorContainer container)
@@ -390,6 +397,21 @@ private void RegisterUnreachableCaseFactories(IWindsorContainer container)
390397
.LifestyleSingleton());
391398
}
392399

400+
private void RegisterEncapsulateFieldRefactoringFactories(IWindsorContainer container)
401+
{
402+
container.Register(Component.For<IEncapsulateFieldCandidateFactory>()
403+
.ImplementedBy<EncapsulateFieldCandidateFactory>()
404+
.LifestyleSingleton());
405+
container.Register(Component.For<IEncapsulateFieldUseBackingUDTMemberModelFactory>()
406+
.ImplementedBy<EncapsulateFieldUseBackingUDTMemberModelFactory>()
407+
.LifestyleSingleton());
408+
container.Register(Component.For<IEncapsulateFieldUseBackingFieldModelFactory>()
409+
.ImplementedBy<EncapsulateFieldUseBackingFieldModelFactory>()
410+
.LifestyleSingleton());
411+
container.Register(Component.For<IEncapsulateFieldModelFactory>()
412+
.ImplementedBy<EncapsulateFieldModelFactory>()
413+
.LifestyleSingleton());
414+
}
393415

394416
private void RegisterQuickFixes(IWindsorContainer container, Assembly[] assembliesToRegister)
395417
{

Rubberduck.Parsing/Binding/Bindings/IndexDefaultBinding.cs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -356,8 +356,11 @@ declared type.
356356
private static bool ArgumentListIsCompatible(ICollection<ParameterDeclaration> parameters, ArgumentList argumentList)
357357
{
358358
return (parameters.Count >= (argumentList?.Arguments.Count ?? 0)
359-
|| parameters.Any(parameter => parameter.IsParamArray))
360-
&& parameters.Count(parameter => !parameter.IsOptional && !parameter.IsParamArray) <= (argumentList?.Arguments.Count ?? 0);
359+
|| parameters.Any(parameter => parameter.IsParamArray))
360+
&& parameters.Count(parameter => !parameter.IsOptional && !parameter.IsParamArray) <= (argumentList?.Arguments.Count ?? 0)
361+
|| parameters.Count == 0
362+
&& argumentList?.Arguments.Count == 1
363+
&& argumentList.Arguments.Single().ArgumentType == ArgumentListArgumentType.Missing;
361364
}
362365

363366
private IBoundExpression ResolveRecursiveDefaultMember(Declaration defaultMember, ExpressionClassification defaultMemberClassification, ArgumentList argumentList, ParserRuleContext expression, Declaration parent, int defaultMemberResolutionRecursionDepth, RecursiveDefaultMemberAccessExpression containedExpression)

Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationSymbolsListener.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -646,8 +646,8 @@ private void AddIdentifierStatementLabelDeclaration(VBAParser.IdentifierStatemen
646646

647647
private void AddLineNumberLabelDeclaration(VBAParser.LineNumberLabelContext context)
648648
{
649-
var statementText = context.numberLiteral().GetText();
650-
var statementSelection = context.numberLiteral().GetSelection();
649+
var statementText = context.GetText().Trim();
650+
var statementSelection = context.GetSelection();
651651

652652
AddDeclaration(
653653
CreateDeclaration(

Rubberduck.Refactorings/Abstract/RefactoringPreviewProviderWrapperBase.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ protected RefactoringPreviewProviderWrapperBase(
2020

2121
protected abstract QualifiedModuleName ComponentToShow(TModel model);
2222

23-
public string Preview(TModel model)
23+
public virtual string Preview(TModel model)
2424
{
2525
var rewriteSession = RewriteSession(RewriteSessionCodeKind);
2626
_refactoringAction.Refactor(model, rewriteSession);

0 commit comments

Comments
 (0)