Skip to content

Commit 72035d2

Browse files
committed
Merge pull request #120 from rubberduck-vba/next
sync with main repo
2 parents 947ec8c + 7123cac commit 72035d2

30 files changed

+393
-166
lines changed

RetailCoder.VBE/Common/DeclarationExtensions.cs

Lines changed: 31 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -222,12 +222,40 @@ public static IEnumerable<Declaration> FindEventHandlers(this IEnumerable<Declar
222222

223223
public static IEnumerable<Declaration> FindBuiltInEventHandlers(this IEnumerable<Declaration> declarations)
224224
{
225-
var handlerNames = declarations.Where(declaration => declaration.IsBuiltIn && declaration.DeclarationType == DeclarationType.Event)
225+
var declarationList = declarations.ToList();
226+
227+
var handlerNames = declarationList.Where(declaration => declaration.IsBuiltIn && declaration.DeclarationType == DeclarationType.Event)
226228
.Select(e => e.ParentDeclaration.IdentifierName + "_" + e.IdentifierName);
227229

228-
return declarations.Where(declaration => !declaration.IsBuiltIn
230+
// class module built-in events
231+
var classModuleHandlers = declarationList.Where(item =>
232+
item.DeclarationType == DeclarationType.Procedure &&
233+
item.ParentDeclaration.DeclarationType == DeclarationType.ClassModule &&
234+
(item.IdentifierName == "Class_Initialize" || item.IdentifierName == "Class_Terminate"));
235+
236+
// user form built-in events
237+
var userFormHandlers = declarationList.Where(item =>
238+
item.DeclarationType == DeclarationType.Procedure &&
239+
item.ParentDeclaration.DeclarationType == DeclarationType.ClassModule &&
240+
item.QualifiedName.QualifiedModuleName.Component.Type == vbext_ComponentType.vbext_ct_MSForm &&
241+
new[]
242+
{
243+
"UserForm_Activate", "UserForm_AddControl", "UserForm_BeforeDragOver", "UserForm_BeforeDropOrPaste",
244+
"UserForm_Click", "UserForm_DblClick", "UserForm_Deactivate", "UserForm_Error",
245+
"UserForm_Initialize", "UserForm_KeyDown", "UserForm_KeyPress", "UserForm_KeyUp", "UserForm_Layout",
246+
"UserForm_MouseDown", "UserForm_MouseMove", "UserForm_MouseUp", "UserForm_QueryClose",
247+
"UserForm_RemoveControl", "UserForm_Resize", "UserForm_Scroll", "UserForm_Terminate",
248+
"UserForm_Zoom"
249+
}.Contains(item.IdentifierName));
250+
251+
var handlers = declarationList.Where(declaration => !declaration.IsBuiltIn
229252
&& declaration.DeclarationType == DeclarationType.Procedure
230-
&& handlerNames.Contains(declaration.IdentifierName));
253+
&& handlerNames.Contains(declaration.IdentifierName)).ToList();
254+
255+
handlers.AddRange(classModuleHandlers);
256+
handlers.AddRange(userFormHandlers);
257+
258+
return handlers;
231259
}
232260

233261
/// <summary>

RetailCoder.VBE/Inspections/ImplicitByRefParameterInspection.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3030
// ParamArray parameters do not allow an explicit "ByRef" parameter mechanism.
3131
&& !((ParameterDeclaration)item).IsParamArray
3232
&& !interfaceMembers.Select(m => m.Scope).Contains(item.ParentScope)
33+
&& !UserDeclarations.FindBuiltInEventHandlers().Contains(item.ParentDeclaration)
3334
let arg = item.Context as VBAParser.ArgContext
3435
where arg != null && arg.BYREF() == null && arg.BYVAL() == null
3536
select new QualifiedContext<VBAParser.ArgContext>(item.QualifiedName, arg))

RetailCoder.VBE/Inspections/ImplicitVariantReturnTypeInspectionResult.cs

Lines changed: 38 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,12 @@
1+
using System;
12
using System.Collections.Generic;
3+
using System.Linq;
24
using Antlr4.Runtime;
5+
using Antlr4.Runtime.Tree;
36
using Rubberduck.Parsing;
47
using Rubberduck.Parsing.Grammar;
58
using Rubberduck.Parsing.Symbols;
6-
using Rubberduck.Parsing.VBA.Nodes;
9+
using Rubberduck.Parsing.VBA;
710
using Rubberduck.UI;
811
using Rubberduck.VBEditor;
912

@@ -51,16 +54,12 @@ public SetExplicitVariantReturnTypeQuickFix(ParserRuleContext context, Qualified
5154

5255
public override void Fix()
5356
{
54-
// note: turns a multiline signature into a one-liner signature.
55-
// bug: removes all comments.
56-
57-
var node = GetNode(Context as VBAParser.FunctionStmtContext)
58-
?? GetNode(Context as VBAParser.PropertyGetStmtContext);
59-
60-
var signature = node.Signature.TrimEnd();
61-
6257
var procedure = Context.GetText();
63-
var result = procedure.Replace(signature, signature + ' ' + Tokens.As + ' ' + Tokens.Variant);
58+
var indexOfLastClosingParen = procedure.LastIndexOf(')');
59+
60+
var result = indexOfLastClosingParen == procedure.Length
61+
? procedure + ' ' + Tokens.As + ' ' + Tokens.Variant
62+
: procedure.Insert(procedure.LastIndexOf(')') + 1, ' ' + Tokens.As + ' ' + Tokens.Variant);
6463

6564
var module = Selection.QualifiedName.Component.CodeModule;
6665
var selection = Context.GetSelection();
@@ -69,28 +68,49 @@ public override void Fix()
6968
module.InsertLines(selection.StartLine, result);
7069
}
7170

72-
private ProcedureNode GetNode(VBAParser.FunctionStmtContext context)
71+
private string GetSignature(VBAParser.FunctionStmtContext context)
7372
{
7473
if (context == null)
7574
{
7675
return null;
7776
}
7877

79-
var scope = Selection.QualifiedName.ToString();
80-
var localScope = scope + "." + context.functionName().identifier().GetText();
81-
return new ProcedureNode(context, scope, localScope);
78+
var @static = context.STATIC() == null ? string.Empty : context.STATIC().GetText() + ' ';
79+
var keyword = context.FUNCTION().GetText() + ' ';
80+
var args = context.argList() == null ? "()" : context.argList().GetText() + ' ';
81+
var asTypeClause = context.asTypeClause() == null ? string.Empty : context.asTypeClause().GetText();
82+
var visibility = context.visibility() == null ? string.Empty : context.visibility().GetText() + ' ';
83+
84+
return visibility + @static + keyword + context.functionName().identifier().GetText() + args + asTypeClause;
8285
}
8386

84-
private ProcedureNode GetNode(VBAParser.PropertyGetStmtContext context)
87+
private string GetSignature(VBAParser.PropertyGetStmtContext context)
8588
{
8689
if (context == null)
8790
{
8891
return null;
8992
}
9093

91-
var scope = Selection.QualifiedName.ToString();
92-
var localScope = scope + "." + context.functionName().identifier().GetText();
93-
return new ProcedureNode(context, scope, localScope);
94+
var @static = context.STATIC() == null ? string.Empty : context.STATIC().GetText() + ' ';
95+
var keyword = context.PROPERTY_GET().GetText() + ' ';
96+
var args = context.argList() == null ? "()" : context.argList().GetText() + ' ';
97+
var asTypeClause = context.asTypeClause() == null ? string.Empty : context.asTypeClause().GetText();
98+
var visibility = context.visibility() == null ? string.Empty : context.visibility().GetText() + ' ';
99+
100+
return visibility + @static + keyword + context.functionName().identifier().GetText() + args + asTypeClause;
101+
}
102+
103+
private string GetSignature(VBAParser.DeclareStmtContext context)
104+
{
105+
if (context == null)
106+
{
107+
return null;
108+
}
109+
110+
var args = context.argList() == null ? "()" : context.argList().GetText() + ' ';
111+
var asTypeClause = context.asTypeClause() == null ? string.Empty : context.asTypeClause().GetText();
112+
113+
return args + asTypeClause;
94114
}
95115
}
96116
}

RetailCoder.VBE/Inspections/InspectionResultBase.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
using System.Linq;
33
using Antlr4.Runtime;
44
using Rubberduck.Parsing;
5-
using Rubberduck.Parsing.Nodes;
65
using Rubberduck.Parsing.Symbols;
76
using Rubberduck.UI;
87
using Rubberduck.UI.Controls;

RetailCoder.VBE/Inspections/ObsoleteCommentSyntaxInspectionResult.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
using System.Collections.Generic;
22
using Antlr4.Runtime;
33
using Rubberduck.Parsing.Grammar;
4-
using Rubberduck.Parsing.Nodes;
4+
using Rubberduck.Parsing.Symbols;
55
using Rubberduck.Parsing.VBA;
66
using Rubberduck.VBEditor;
77

RetailCoder.VBE/Inspections/OptionBaseInspectionResult.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
using Rubberduck.Parsing.Grammar;
2-
using Rubberduck.Parsing.Nodes;
2+
using Rubberduck.Parsing.Symbols;
33
using Rubberduck.VBEditor;
44

55
namespace Rubberduck.Inspections

RetailCoder.VBE/Inspections/OptionExplicitInspectionResult.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
using System.Collections.Generic;
33
using Antlr4.Runtime;
44
using Rubberduck.Parsing.Grammar;
5-
using Rubberduck.Parsing.Nodes;
5+
using Rubberduck.Parsing.Symbols;
66
using Rubberduck.VBEditor;
77

88
namespace Rubberduck.Inspections

RetailCoder.VBE/Inspections/ParameterCanBeByValInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
4949

5050
var eventScopes = declarations.Where(item =>
5151
!item.IsBuiltIn && item.DeclarationType == DeclarationType.Event)
52-
.Select(e => e.Scope);
52+
.Select(e => e.Scope).Concat(declarations.FindBuiltInEventHandlers().Select(e => e.Scope));
5353

5454
var declareScopes = declarations.Where(item =>
5555
item.DeclarationType == DeclarationType.LibraryFunction

RetailCoder.VBE/Inspections/ParameterNotUsedInspection.cs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,13 +2,11 @@
22
using System.Linq;
33
using Microsoft.Vbe.Interop;
44
using Rubberduck.Common;
5-
using Rubberduck.Parsing.Grammar;
65
using Rubberduck.Parsing.Symbols;
76
using Rubberduck.Parsing.VBA;
87
using Rubberduck.Refactorings.RemoveParameters;
98
using Rubberduck.UI;
109
using Rubberduck.UI.Refactorings;
11-
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodePane;
1210

1311
namespace Rubberduck.Inspections
1412
{
@@ -38,8 +36,9 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3836
var builtInHandlers = declarations.FindBuiltInEventHandlers();
3937

4038
var parameters = declarations.Where(parameter => parameter.DeclarationType == DeclarationType.Parameter
41-
&& !(parameter.Context.Parent.Parent is VBAParser.EventStmtContext)
42-
&& !(parameter.Context.Parent.Parent is VBAParser.DeclareStmtContext));
39+
&& parameter.ParentDeclaration.DeclarationType != DeclarationType.Event
40+
&& parameter.ParentDeclaration.DeclarationType != DeclarationType.LibraryFunction
41+
&& parameter.ParentDeclaration.DeclarationType != DeclarationType.LibraryProcedure);
4342

4443
var unused = parameters.Where(parameter => !parameter.References.Any()).ToList();
4544
var quickFixRefactoring =

RetailCoder.VBE/Inspections/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -71,7 +71,8 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
7171
if (declaration == null) { return false; } // rather be safe than sorry
7272

7373
return UserDeclarations.Where(item => item.IsWithEvents)
74-
.All(withEvents => UserDeclarations.FindEventProcedures(withEvents) == null);
74+
.All(withEvents => UserDeclarations.FindEventProcedures(withEvents) == null) &&
75+
!UserDeclarations.FindBuiltInEventHandlers().Contains(declaration);
7576
});
7677

7778
return ParseTreeResults.ArgListsWithOneByRefParam

0 commit comments

Comments
 (0)