Skip to content

Commit f1b6bb0

Browse files
committed
Make ImplicitByRef- and RedundantByRefInspection declaration inspections
1 parent 7d620a8 commit f1b6bb0

12 files changed

+188
-146
lines changed
Lines changed: 23 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,8 @@
1-
using System.Linq;
2-
using Antlr4.Runtime;
31
using Rubberduck.Inspections.Abstract;
4-
using Rubberduck.Parsing;
5-
using Rubberduck.Parsing.Grammar;
6-
using Rubberduck.Parsing.Inspections.Abstract;
72
using Rubberduck.Resources.Inspections;
83
using Rubberduck.Parsing.VBA;
9-
using Rubberduck.JunkDrawer.Extensions;
4+
using Rubberduck.Parsing.Symbols;
5+
using Rubberduck.Parsing.VBA.DeclarationCaching;
106

117
namespace Rubberduck.Inspections.Concrete
128
{
@@ -31,48 +27,38 @@ namespace Rubberduck.Inspections.Concrete
3127
/// End Sub
3228
/// ]]>
3329
/// </example>
34-
public sealed class ImplicitByRefModifierInspection : ParseTreeInspectionBase
30+
public sealed class ImplicitByRefModifierInspection : DeclarationInspectionBase
3531
{
3632
public ImplicitByRefModifierInspection(RubberduckParserState state)
37-
: base(state)
33+
: base(state, DeclarationType.Parameter)
3834
{}
3935

40-
public override IInspectionListener Listener { get; } = new ImplicitByRefModifierListener();
41-
protected override string ResultDescription(QualifiedContext<ParserRuleContext> context)
36+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
4237
{
43-
var identifier = ((VBAParser.ArgContext)context.Context)
44-
.unrestrictedIdentifier()
45-
.identifier();
38+
if (!(declaration is ParameterDeclaration parameter)
39+
|| !parameter.IsImplicitByRef
40+
|| parameter.IsParamArray)
41+
{
42+
return false;
43+
}
4644

47-
var identifierText = identifier.untypedIdentifier() != null
48-
? identifier.untypedIdentifier().identifierValue().GetText()
49-
: identifier.typedIdentifier().untypedIdentifier().identifierValue().GetText();
45+
var parentDeclaration = parameter.ParentDeclaration;
5046

51-
return string.Format(
52-
InspectionResults.ImplicitByRefModifierInspection,
53-
identifierText);
54-
}
55-
56-
protected override bool IsResultContext(QualifiedContext<ParserRuleContext> context)
57-
{
58-
//FIXME : This should really be a declaration inspection on the parameter.
59-
var finder = DeclarationFinderProvider.DeclarationFinder;
60-
var builtInEventHandlerContexts = finder.FindEventHandlers().Select(handler => handler.Context).ToHashSet();
61-
var interfaceImplementationMemberContexts = finder.FindAllInterfaceImplementingMembers().Select(member => member.Context).ToHashSet();
47+
if (parentDeclaration is ModuleBodyElementDeclaration enclosingMethod)
48+
{
49+
return !enclosingMethod.IsInterfaceImplementation
50+
&& !finder.FindEventHandlers().Contains(enclosingMethod);
51+
}
6252

63-
return !builtInEventHandlerContexts.Contains(context.Context.Parent.Parent)
64-
&& !interfaceImplementationMemberContexts.Contains(context.Context.Parent.Parent);
53+
return parentDeclaration.DeclarationType != DeclarationType.LibraryFunction
54+
&& parentDeclaration.DeclarationType != DeclarationType.LibraryProcedure;
6555
}
6656

67-
public class ImplicitByRefModifierListener : InspectionListenerBase
57+
protected override string ResultDescription(Declaration declaration)
6858
{
69-
public override void ExitArg(VBAParser.ArgContext context)
70-
{
71-
if (context.PARAMARRAY() == null && context.BYVAL() == null && context.BYREF() == null)
72-
{
73-
SaveContext(context);
74-
}
75-
}
59+
return string.Format(
60+
InspectionResults.ImplicitByRefModifierInspection,
61+
declaration.IdentifierName);
7662
}
7763
}
7864
}
Lines changed: 26 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,8 @@
1-
using System.Linq;
2-
using Antlr4.Runtime;
3-
using Rubberduck.Inspections.Abstract;
4-
using Rubberduck.Parsing;
5-
using Rubberduck.Parsing.Grammar;
6-
using Rubberduck.Parsing.Inspections.Abstract;
1+
using Rubberduck.Inspections.Abstract;
72
using Rubberduck.Resources.Inspections;
83
using Rubberduck.Parsing.VBA;
9-
using Rubberduck.JunkDrawer.Extensions;
4+
using Rubberduck.Parsing.Symbols;
5+
using Rubberduck.Parsing.VBA.DeclarationCaching;
106

117
namespace Rubberduck.Inspections.Concrete
128
{
@@ -36,49 +32,39 @@ namespace Rubberduck.Inspections.Concrete
3632
/// End Sub
3733
/// ]]>
3834
/// </example>
39-
public sealed class RedundantByRefModifierInspection : ParseTreeInspectionBase
35+
public sealed class RedundantByRefModifierInspection : DeclarationInspectionBase
4036
{
4137
public RedundantByRefModifierInspection(RubberduckParserState state)
42-
: base(state)
43-
{
44-
}
38+
: base(state, DeclarationType.Parameter)
39+
{ }
4540

46-
public override IInspectionListener Listener { get; } = new RedundantByRefModifierListener();
47-
protected override string ResultDescription(QualifiedContext<ParserRuleContext> context)
41+
protected override bool IsResultDeclaration(Declaration declaration, DeclarationFinder finder)
4842
{
49-
var identifier = ((VBAParser.ArgContext)context.Context)
50-
.unrestrictedIdentifier()
51-
.identifier();
52-
53-
var identifierText = identifier.untypedIdentifier() != null
54-
? identifier.untypedIdentifier().identifierValue().GetText()
55-
: identifier.typedIdentifier().untypedIdentifier().identifierValue().GetText();
43+
if (!(declaration is ParameterDeclaration parameter)
44+
|| parameter.IsImplicitByRef
45+
|| !parameter.IsByRef
46+
|| parameter.IsParamArray)
47+
{
48+
return false;
49+
}
5650

57-
return string.Format(
58-
InspectionResults.RedundantByRefModifierInspection,
59-
identifierText);
60-
}
51+
var parentDeclaration = parameter.ParentDeclaration;
6152

62-
protected override bool IsResultContext(QualifiedContext<ParserRuleContext> context)
63-
{
64-
//FIXME This should be an inspection on parameter declarations.
65-
var finder = DeclarationFinderProvider.DeclarationFinder;
66-
var builtInEventHandlerContexts = finder.FindEventHandlers().Select(handler => handler.Context).ToHashSet();
67-
var interfaceImplementationMemberContexts = finder.FindAllInterfaceImplementingMembers().Select(member => member.Context).ToHashSet();
53+
if (parentDeclaration is ModuleBodyElementDeclaration enclosingMethod)
54+
{
55+
return !enclosingMethod.IsInterfaceImplementation
56+
&& !finder.FindEventHandlers().Contains(enclosingMethod);
57+
}
6858

69-
return !builtInEventHandlerContexts.Contains(context.Context.Parent.Parent)
70-
&& !interfaceImplementationMemberContexts.Contains(context.Context.Parent.Parent);
59+
return parentDeclaration.DeclarationType != DeclarationType.LibraryFunction
60+
&& parentDeclaration.DeclarationType != DeclarationType.LibraryProcedure;
7161
}
7262

73-
public class RedundantByRefModifierListener : InspectionListenerBase
63+
protected override string ResultDescription(Declaration declaration)
7464
{
75-
public override void ExitArg(VBAParser.ArgContext context)
76-
{
77-
if (context.BYREF() != null)
78-
{
79-
SaveContext(context);
80-
}
81-
}
65+
return string.Format(
66+
InspectionResults.RedundantByRefModifierInspection,
67+
declaration.IdentifierName);
8268
}
8369
}
8470
}

Rubberduck.CodeAnalysis/Inspections/Concrete/UnhandledOnErrorResumeNextInspection.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ namespace Rubberduck.Inspections.Concrete
3535
/// End Sub
3636
/// ]]>
3737
/// </example>
38-
public class UnhandledOnErrorResumeNextInspection : ParseTreeInspectionBase<IList<ParserRuleContext>>
38+
public class UnhandledOnErrorResumeNextInspection : ParseTreeInspectionBase<IReadOnlyList<ParserRuleContext>>
3939
{
4040
private readonly Dictionary<QualifiedContext<ParserRuleContext>, List<ParserRuleContext>> _unhandledContextsMap =
4141
new Dictionary<QualifiedContext<ParserRuleContext>, List<ParserRuleContext>>();
@@ -47,12 +47,12 @@ public UnhandledOnErrorResumeNextInspection(RubberduckParserState state)
4747
}
4848

4949
public override IInspectionListener Listener { get; }
50-
protected override string ResultDescription(QualifiedContext<ParserRuleContext> context, IList<ParserRuleContext> properties)
50+
protected override string ResultDescription(QualifiedContext<ParserRuleContext> context, IReadOnlyList<ParserRuleContext> properties)
5151
{
5252
return InspectionResults.UnhandledOnErrorResumeNextInspection;
5353
}
5454

55-
protected override (bool isResult, IList<ParserRuleContext> properties) IsResultContextWithAdditionalProperties(QualifiedContext<ParserRuleContext> context)
55+
protected override (bool isResult, IReadOnlyList<ParserRuleContext> properties) IsResultContextWithAdditionalProperties(QualifiedContext<ParserRuleContext> context)
5656
{
5757
return (true, _unhandledContextsMap[context]);
5858
}

Rubberduck.CodeAnalysis/QuickFixes/RemoveExplicitByRefModifierQuickFix.cs

Lines changed: 54 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
1-
using System;
2-
using Rubberduck.Parsing.Grammar;
1+
using Rubberduck.Parsing.Grammar;
32
using System.Linq;
43
using Rubberduck.Inspections.Abstract;
54
using Rubberduck.Inspections.Concrete;
@@ -8,6 +7,7 @@
87
using Rubberduck.Parsing.Rewriter;
98
using Rubberduck.Parsing.Symbols;
109
using Rubberduck.Parsing.VBA;
10+
using Rubberduck.Parsing.VBA.DeclarationCaching;
1111

1212
namespace Rubberduck.Inspections.QuickFixes
1313
{
@@ -50,38 +50,57 @@ public RemoveExplicitByRefModifierQuickFix(IDeclarationFinderProvider declaratio
5050

5151
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
5252
{
53-
var context = (VBAParser.ArgContext) result.Context;
53+
if (!(result.Target is ParameterDeclaration parameter))
54+
{
55+
return;
56+
}
5457

55-
RemoveByRefIdentifier(rewriteSession.CheckOutModuleRewriter(result.QualifiedSelection.QualifiedName), context);
58+
RemoveByRefIdentifier(rewriteSession, parameter);
5659

57-
var interfaceMembers = _declarationFinderProvider.DeclarationFinder.FindAllInterfaceMembers().ToArray();
60+
var finder = _declarationFinderProvider.DeclarationFinder;
61+
var parentDeclaration = parameter.ParentDeclaration;
5862

59-
var matchingInterfaceMemberContext = interfaceMembers.Select(member => member.Context).FirstOrDefault(c => c == context.Parent.Parent);
63+
if (parentDeclaration is ModuleBodyElementDeclaration enclosingMember
64+
&& enclosingMember.IsInterfaceMember)
65+
{
66+
var parameterIndex = ParameterIndex(parameter, enclosingMember);
67+
RemoveByRefIdentifierFromImplementations(enclosingMember, parameterIndex, finder, rewriteSession);
68+
}
6069

61-
if (matchingInterfaceMemberContext != null)
70+
if (parentDeclaration is EventDeclaration enclosingEvent)
6271
{
63-
var interfaceParameterIndex = GetParameterIndex(context);
64-
65-
var implementationMembers =
66-
_declarationFinderProvider.DeclarationFinder.FindInterfaceImplementationMembers(interfaceMembers.First(
67-
member => member.Context == matchingInterfaceMemberContext)).ToHashSet();
68-
69-
var parameters =
70-
_declarationFinderProvider.DeclarationFinder.UserDeclarations(DeclarationType.Parameter)
71-
.Where(p => implementationMembers.Contains(p.ParentDeclaration))
72-
.Cast<ParameterDeclaration>()
73-
.ToArray();
74-
75-
foreach (var parameter in parameters)
76-
{
77-
var parameterContext = (VBAParser.ArgContext) parameter.Context;
78-
var parameterIndex = GetParameterIndex(parameterContext);
79-
80-
if (parameterIndex == interfaceParameterIndex)
81-
{
82-
RemoveByRefIdentifier(rewriteSession.CheckOutModuleRewriter(parameter.QualifiedModuleName), parameterContext);
83-
}
84-
}
72+
var parameterIndex = ParameterIndex(parameter, enclosingEvent);
73+
RemoveByRefIdentifierFromHandlers(enclosingEvent, parameterIndex, finder, rewriteSession);
74+
}
75+
}
76+
77+
private static void RemoveByRefIdentifierFromImplementations(
78+
ModuleBodyElementDeclaration interfaceMember,
79+
int parameterIndex,
80+
DeclarationFinder finder,
81+
IRewriteSession rewriteSession)
82+
{
83+
var implementationParameters = finder.FindInterfaceImplementationMembers(interfaceMember)
84+
.Select(implementation => implementation.Parameters[parameterIndex]);
85+
86+
foreach (var parameter in implementationParameters)
87+
{
88+
RemoveByRefIdentifier(rewriteSession, parameter);
89+
}
90+
}
91+
92+
private static void RemoveByRefIdentifierFromHandlers(
93+
EventDeclaration eventDeclaration,
94+
int parameterIndex,
95+
DeclarationFinder finder,
96+
IRewriteSession rewriteSession)
97+
{
98+
var handlers = finder.FindEventHandlers(eventDeclaration)
99+
.Select(implementation => implementation.Parameters[parameterIndex]);
100+
101+
foreach (var parameter in handlers)
102+
{
103+
RemoveByRefIdentifier(rewriteSession, parameter);
85104
}
86105
}
87106

@@ -91,13 +110,16 @@ public override void Fix(IInspectionResult result, IRewriteSession rewriteSessio
91110
public override bool CanFixInModule => true;
92111
public override bool CanFixInProject => true;
93112

94-
private static int GetParameterIndex(VBAParser.ArgContext context)
113+
private static int ParameterIndex(ParameterDeclaration parameter, IParameterizedDeclaration enclosingMember)
95114
{
96-
return Array.IndexOf(((VBAParser.ArgListContext)context.Parent).arg().ToArray(), context);
115+
return enclosingMember.Parameters.IndexOf(parameter);
97116
}
98117

99-
private static void RemoveByRefIdentifier(IModuleRewriter rewriter, VBAParser.ArgContext context)
118+
private static void RemoveByRefIdentifier(IRewriteSession rewriteSession, ParameterDeclaration parameter)
100119
{
120+
var rewriter = rewriteSession.CheckOutModuleRewriter(parameter.QualifiedModuleName);
121+
var context = (VBAParser.ArgContext)parameter.Context;
122+
101123
if (context.BYREF() != null)
102124
{
103125
rewriter.Remove(context.BYREF());

Rubberduck.CodeAnalysis/QuickFixes/RestoreErrorHandlingQuickFix.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
using Antlr4.Runtime;
44
using Rubberduck.Inspections.Abstract;
55
using Rubberduck.Inspections.Concrete;
6+
using Rubberduck.JunkDrawer.Extensions;
67
using Rubberduck.Parsing;
78
using Rubberduck.Parsing.Grammar;
89
using Rubberduck.Parsing.Inspections.Abstract;
@@ -55,7 +56,7 @@ public RestoreErrorHandlingQuickFix()
5556

5657
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
5758
{
58-
if (!(result is IWithInspectionResultProperties<IList<ParserRuleContext>> resultProperties))
59+
if (!(result is IWithInspectionResultProperties<IReadOnlyList<ParserRuleContext>> resultProperties))
5960
{
6061
return;
6162
}

0 commit comments

Comments
 (0)