Skip to content

Commit 8a46009

Browse files
committed
Merge pull request #121 from rubberduck-vba/next
sync with main repo
2 parents 72035d2 + 4a32cae commit 8a46009

File tree

114 files changed

+304
-499
lines changed

Some content is hidden

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

114 files changed

+304
-499
lines changed

RetailCoder.VBE/API/DeclarationType.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
1-
using System;
2-
using System.Runtime.InteropServices;
1+
using System.Runtime.InteropServices;
32

43
namespace Rubberduck.API
54
{

RetailCoder.VBE/App.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,6 @@
1818
using System.Runtime.InteropServices.ComTypes;
1919
using System.Threading.Tasks;
2020
using System.Windows.Forms;
21-
using Rubberduck.Common.Hotkeys;
2221

2322
namespace Rubberduck
2423
{
@@ -335,7 +334,8 @@ async void sink_ProjectRenamed(object sender, DispatcherRenamedEventArgs<VBProje
335334

336335
_logger.Debug("Project '{0}' (ID {1}) was renamed to '{2}'.", e.OldName, e.Item.HelpFile, e.Item.Name);
337336

338-
// note: if a bug is discovered with renaming a project, it may just need to be removed and readded.
337+
_parser.State.RemoveProject(e.Item.HelpFile);
338+
_parser.State.AddProject(e.Item);
339339

340340
_parser.State.OnParseRequested(sender);
341341
}

RetailCoder.VBE/Common/ClipboardWriter.cs

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,4 @@
1-
using System;
2-
using System.Collections.Generic;
31
using System.IO;
4-
using System.Linq;
5-
using System.Text;
6-
using System.Threading.Tasks;
72
using System.Windows;
83
using System.Windows.Media.Imaging;
94

RetailCoder.VBE/Common/DeclarationExtensions.cs

Lines changed: 48 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,25 @@ public static Selection GetVariableStmtContextSelection(this Declaration target)
4848
statement.Stop.Line, statement.Stop.Column);
4949
}
5050

51+
/// <summary>
52+
/// Returns the Selection of a ConstStmtContext.
53+
/// </summary>
54+
/// <exception cref="ArgumentException">Throws when target's DeclarationType is not Constant.</exception>
55+
/// <param name="target"></param>
56+
/// <returns></returns>
57+
public static Selection GetConstStmtContextSelection(this Declaration target)
58+
{
59+
if (target.DeclarationType != DeclarationType.Constant)
60+
{
61+
throw new ArgumentException("Target DeclarationType is not Constant.", "target");
62+
}
63+
64+
var statement = GetConstStmtContext(target);
65+
66+
return new Selection(statement.Start.Line, statement.Start.Column,
67+
statement.Stop.Line, statement.Stop.Column);
68+
}
69+
5170
/// <summary>
5271
/// Returns a VariableStmtContext.
5372
/// </summary>
@@ -70,6 +89,28 @@ public static VBAParser.VariableStmtContext GetVariableStmtContext(this Declarat
7089
return statement;
7190
}
7291

92+
/// <summary>
93+
/// Returns a ConstStmtContext.
94+
/// </summary>
95+
/// <exception cref="ArgumentException">Throws when target's DeclarationType is not Constant.</exception>
96+
/// <param name="target"></param>
97+
/// <returns></returns>
98+
public static VBAParser.ConstStmtContext GetConstStmtContext(this Declaration target)
99+
{
100+
if (target.DeclarationType != DeclarationType.Constant)
101+
{
102+
throw new ArgumentException("Target DeclarationType is not Constant.", "target");
103+
}
104+
105+
var statement = target.Context.Parent as VBAParser.ConstStmtContext;
106+
if (statement == null)
107+
{
108+
throw new MissingMemberException("Statement not found");
109+
}
110+
111+
return statement;
112+
}
113+
73114
/// <summary>
74115
/// Returns whether a variable declaration statement contains multiple declarations in a single statement.
75116
/// </summary>
@@ -225,35 +266,25 @@ public static IEnumerable<Declaration> FindBuiltInEventHandlers(this IEnumerable
225266
var declarationList = declarations.ToList();
226267

227268
var handlerNames = declarationList.Where(declaration => declaration.IsBuiltIn && declaration.DeclarationType == DeclarationType.Event)
228-
.Select(e => e.ParentDeclaration.IdentifierName + "_" + e.IdentifierName);
269+
.SelectMany(e =>
270+
{
271+
var parentModuleSubtypes = ((ClassModuleDeclaration) e.ParentDeclaration).Subtypes;
272+
return parentModuleSubtypes.Any()
273+
? parentModuleSubtypes.Select(v => v.IdentifierName + "_" + e.IdentifierName)
274+
: new[] { e.ParentDeclaration.IdentifierName + "_" + e.IdentifierName };
275+
});
229276

230277
// class module built-in events
231278
var classModuleHandlers = declarationList.Where(item =>
232279
item.DeclarationType == DeclarationType.Procedure &&
233280
item.ParentDeclaration.DeclarationType == DeclarationType.ClassModule &&
234281
(item.IdentifierName == "Class_Initialize" || item.IdentifierName == "Class_Terminate"));
235282

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-
251283
var handlers = declarationList.Where(declaration => !declaration.IsBuiltIn
252284
&& declaration.DeclarationType == DeclarationType.Procedure
253285
&& handlerNames.Contains(declaration.IdentifierName)).ToList();
254286

255287
handlers.AddRange(classModuleHandlers);
256-
handlers.AddRange(userFormHandlers);
257288

258289
return handlers;
259290
}

RetailCoder.VBE/Common/ExportFormatter.cs

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,7 @@
11
using System;
2-
using System.Collections.Generic;
32
using System.IO;
4-
using System.Linq;
53
using System.Net;
64
using System.Text;
7-
using System.Threading.Tasks;
85
using System.Xml;
96

107
namespace Rubberduck.Common

RetailCoder.VBE/Common/Hotkeys/Hotkey.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
using System;
22
using System.Collections.Generic;
3-
using System.Diagnostics;
43
using System.Windows.Forms;
54
using System.Windows.Input;
65
using Rubberduck.Common.WinAPI;

RetailCoder.VBE/Common/RubberduckHooks.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System;
22
using System.Collections.Generic;
33
using System.ComponentModel;
4-
using System.Diagnostics;
54
using System.Linq;
65
using System.Runtime.InteropServices;
76
using System.Windows.Forms;

RetailCoder.VBE/Common/WinAPI/DeviceInfoHid.cs

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,4 @@
1-
using System;
2-
using System.Collections.Generic;
3-
using System.Linq;
4-
using System.Text;
5-
using System.Threading.Tasks;
6-
7-
namespace Rubberduck.Common.WinAPI
1+
namespace Rubberduck.Common.WinAPI
82
{
93
public struct DeviceInfoHid
104
{

RetailCoder.VBE/Common/WinAPI/DeviceInfoMouse.cs

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,4 @@
1-
using System;
2-
using System.Collections.Generic;
3-
using System.Linq;
4-
using System.Text;
5-
using System.Threading.Tasks;
6-
7-
namespace Rubberduck.Common.WinAPI
1+
namespace Rubberduck.Common.WinAPI
82
{
93
public struct DeviceInfoMouse
104
{

RetailCoder.VBE/Common/WinAPI/DeviceNotification.cs

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,4 @@
1-
using System;
2-
using System.Collections.Generic;
3-
using System.Linq;
4-
using System.Text;
5-
using System.Threading.Tasks;
6-
7-
namespace Rubberduck.Common.WinAPI
1+
namespace Rubberduck.Common.WinAPI
82
{
93
enum DeviceNotification
104
{

RetailCoder.VBE/Common/WinAPI/HidUsage.cs

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,4 @@
1-
using System;
2-
using System.Collections.Generic;
3-
using System.Linq;
4-
using System.Text;
5-
using System.Threading.Tasks;
6-
7-
namespace Rubberduck.Common.WinAPI
1+
namespace Rubberduck.Common.WinAPI
82
{
93
public enum HidUsage : ushort
104
{

RetailCoder.VBE/Common/WinAPI/IRawDevice.cs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,4 @@
1-
using System;
2-
3-
namespace Rubberduck.Common.WinAPI
1+
namespace Rubberduck.Common.WinAPI
42
{
53
public interface IRawDevice
64
{

RetailCoder.VBE/Common/WinAPI/RawInput.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
using System;
33
using System.Collections.Generic;
44
using System.ComponentModel;
5-
using System.Diagnostics;
65
using System.Runtime.InteropServices;
76
using System.Windows.Forms;
87

RetailCoder.VBE/Common/WinAPI/Rawinputheader.cs

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,5 @@
11
using System;
2-
using System.Collections.Generic;
3-
using System.Linq;
42
using System.Runtime.InteropServices;
5-
using System.Text;
6-
using System.Threading.Tasks;
73

84
namespace Rubberduck.Common.WinAPI
95
{

RetailCoder.VBE/Common/WindowsOperatingSystem.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
1-
using System;
2-
using System.Diagnostics;
1+
using System.Diagnostics;
32

43
namespace Rubberduck.Common
54
{

RetailCoder.VBE/Inspections/ConstantNotUsedInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2222
declaration.DeclarationType == DeclarationType.Constant && !declaration.References.Any());
2323

2424
return results.Select(issue =>
25-
new IdentifierNotUsedInspectionResult(this, issue, ((dynamic)issue.Context).identifier(), issue.QualifiedName.QualifiedModuleName)).Cast<InspectionResultBase>();
25+
new IdentifierNotUsedInspectionResult(this, issue, ((dynamic)issue.Context).identifier(), issue.QualifiedName.QualifiedModuleName));
2626
}
2727
}
2828
}

RetailCoder.VBE/Inspections/DefaultProjectNameInspection.cs

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -2,18 +2,14 @@
22
using System.Linq;
33
using Rubberduck.Parsing.Symbols;
44
using Rubberduck.Parsing.VBA;
5-
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodePane;
65

76
namespace Rubberduck.Inspections
87
{
98
public sealed class DefaultProjectNameInspection : InspectionBase
109
{
11-
private readonly ICodePaneWrapperFactory _wrapperFactory;
12-
1310
public DefaultProjectNameInspection(RubberduckParserState state)
1411
: base(state, CodeInspectionSeverity.Suggestion)
1512
{
16-
_wrapperFactory = new CodePaneWrapperFactory();
1713
}
1814

1915
public override string Meta { get { return InspectionsUI.DefaultProjectNameInspectionMeta; } }
@@ -25,7 +21,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2521
var issues = UserDeclarations
2622
.Where(declaration => declaration.DeclarationType == DeclarationType.Project
2723
&& declaration.IdentifierName.StartsWith("VBAProject"))
28-
.Select(issue => new DefaultProjectNameInspectionResult(this, issue, State, _wrapperFactory))
24+
.Select(issue => new DefaultProjectNameInspectionResult(this, issue, State))
2925
.ToList();
3026

3127
return issues;

RetailCoder.VBE/Inspections/DefaultProjectNameInspectionResult.cs

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@
77
using Rubberduck.UI;
88
using Rubberduck.UI.Refactorings;
99
using Rubberduck.VBEditor;
10-
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodePane;
1110
using MessageBox = Rubberduck.UI.MessageBox;
1211

1312
namespace Rubberduck.Inspections
@@ -16,12 +15,12 @@ public class DefaultProjectNameInspectionResult : InspectionResultBase
1615
{
1716
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
1817

19-
public DefaultProjectNameInspectionResult(IInspection inspection, Declaration target, RubberduckParserState state, ICodePaneWrapperFactory wrapperFactory)
18+
public DefaultProjectNameInspectionResult(IInspection inspection, Declaration target, RubberduckParserState state)
2019
: base(inspection, target)
2120
{
2221
_quickFixes = new[]
2322
{
24-
new RenameProjectQuickFix(target.Context, target.QualifiedSelection, target, state, wrapperFactory),
23+
new RenameProjectQuickFix(target.Context, target.QualifiedSelection, target, state),
2524
};
2625
}
2726

@@ -40,14 +39,12 @@ public class RenameProjectQuickFix : CodeInspectionQuickFix
4039
{
4140
private readonly Declaration _target;
4241
private readonly RubberduckParserState _state;
43-
private readonly ICodePaneWrapperFactory _wrapperFactory;
4442

45-
public RenameProjectQuickFix(ParserRuleContext context, QualifiedSelection selection, Declaration target, RubberduckParserState state, ICodePaneWrapperFactory wrapperFactory)
43+
public RenameProjectQuickFix(ParserRuleContext context, QualifiedSelection selection, Declaration target, RubberduckParserState state)
4644
: base(context, selection, string.Format(RubberduckUI.Rename_DeclarationType, RubberduckUI.ResourceManager.GetString("DeclarationType_" + DeclarationType.Project, RubberduckUI.Culture)))
4745
{
4846
_target = target;
4947
_state = state;
50-
_wrapperFactory = wrapperFactory;
5148
}
5249

5350
public override void Fix()

RetailCoder.VBE/Inspections/EncapsulatePublicFieldInspection.cs

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -2,18 +2,14 @@
22
using System.Linq;
33
using Rubberduck.Parsing.Symbols;
44
using Rubberduck.Parsing.VBA;
5-
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodePane;
65

76
namespace Rubberduck.Inspections
87
{
98
public sealed class EncapsulatePublicFieldInspection : InspectionBase
109
{
11-
private readonly ICodePaneWrapperFactory _wrapperFactory;
12-
1310
public EncapsulatePublicFieldInspection(RubberduckParserState state)
1411
: base(state, CodeInspectionSeverity.Suggestion)
1512
{
16-
_wrapperFactory = new CodePaneWrapperFactory();
1713
}
1814

1915
public override string Meta { get { return InspectionsUI.EncapsulatePublicFieldInspectionMeta; } }
@@ -25,7 +21,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2521
var issues = UserDeclarations
2622
.Where(declaration => declaration.DeclarationType == DeclarationType.Variable
2723
&& declaration.Accessibility == Accessibility.Public)
28-
.Select(issue => new EncapsulatePublicFieldInspectionResult(this, issue, State, _wrapperFactory))
24+
.Select(issue => new EncapsulatePublicFieldInspectionResult(this, issue, State))
2925
.ToList();
3026

3127
return issues;

RetailCoder.VBE/Inspections/EncapsulatePublicFieldInspectionResult.cs

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -6,20 +6,19 @@
66
using Rubberduck.Refactorings.EncapsulateField;
77
using Rubberduck.UI.Refactorings;
88
using Rubberduck.VBEditor;
9-
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodePane;
109

1110
namespace Rubberduck.Inspections
1211
{
1312
public class EncapsulatePublicFieldInspectionResult : InspectionResultBase
1413
{
1514
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
1615

17-
public EncapsulatePublicFieldInspectionResult(IInspection inspection, Declaration target, RubberduckParserState state, ICodePaneWrapperFactory wrapperFactory)
16+
public EncapsulatePublicFieldInspectionResult(IInspection inspection, Declaration target, RubberduckParserState state)
1817
: base(inspection, target)
1918
{
2019
_quickFixes = new[]
2120
{
22-
new EncapsulateFieldQuickFix(target.Context, target.QualifiedSelection, target, state, wrapperFactory),
21+
new EncapsulateFieldQuickFix(target.Context, target.QualifiedSelection, target, state),
2322
};
2423
}
2524

@@ -38,14 +37,12 @@ public class EncapsulateFieldQuickFix : CodeInspectionQuickFix
3837
{
3938
private readonly Declaration _target;
4039
private readonly RubberduckParserState _state;
41-
private readonly ICodePaneWrapperFactory _wrapperFactory;
4240

43-
public EncapsulateFieldQuickFix(ParserRuleContext context, QualifiedSelection selection, Declaration target, RubberduckParserState state, ICodePaneWrapperFactory wrapperFactory)
41+
public EncapsulateFieldQuickFix(ParserRuleContext context, QualifiedSelection selection, Declaration target, RubberduckParserState state)
4442
: base(context, selection, string.Format(InspectionsUI.EncapsulatePublicFieldInspectionQuickFix, target.IdentifierName))
4543
{
4644
_target = target;
4745
_state = state;
48-
_wrapperFactory = wrapperFactory;
4946
}
5047

5148
public override void Fix()

RetailCoder.VBE/Inspections/FunctionReturnValueNotUsedInspection.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
using Rubberduck.Parsing.Symbols;
55
using Rubberduck.Parsing.VBA;
66
using Rubberduck.Parsing.Grammar;
7-
using Antlr4.Runtime;
87
using Rubberduck.Common;
98
using Rubberduck.VBEditor;
109

@@ -110,7 +109,6 @@ private bool IsReturnValueUsed(Declaration function)
110109

111110
private bool IsAddressOfCall(IdentifierReference usage)
112111
{
113-
var what = usage.Context.GetType();
114112
return ParserRuleContextHelper.HasParent<VBAParser.AddressOfExpressionContext>(usage.Context);
115113
}
116114

0 commit comments

Comments
 (0)