Skip to content

Commit 02c5750

Browse files
authored
Merge pull request #2849 from rubberduck-vba/next
v2.0.13
2 parents 166f2e3 + b64572d commit 02c5750

File tree

284 files changed

+6617
-11986
lines changed

Some content is hidden

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

284 files changed

+6617
-11986
lines changed

.gitignore

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -115,6 +115,10 @@ csx
115115
# Windows Store app package directory
116116
AppPackages/
117117

118+
# IDE Configuration
119+
.vs/
120+
.vscode/
121+
118122
# Others
119123
sql/
120124
*.Cache
@@ -126,6 +130,7 @@ ClientBin/
126130
*.[Pp]ublish.xml
127131
*.pfx
128132
*.publishsettings
133+
*.playlist
129134

130135
# Monodevelop detritus
131136
*.userprefs

RetailCoder.VBE/API/ParserState.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -161,7 +161,7 @@ public void Dispose()
161161
}
162162

163163

164-
_vbe.Release();
164+
//_vbe.Release();
165165
_disposed = true;
166166
}
167167
}

RetailCoder.VBE/App.cs

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
using Rubberduck.UI;
88
using Rubberduck.UI.Command.MenuItems;
99
using System;
10+
using System.Diagnostics;
1011
using System.Globalization;
1112
using System.Windows.Forms;
1213
using Rubberduck.Inspections.Resources;
@@ -81,6 +82,26 @@ private static void EnsureLogFolderPathExists()
8182
}
8283
}
8384

85+
private static void EnsureTempPathExists()
86+
{
87+
// This is required by the parser - allow this to throw.
88+
if (!Directory.Exists(ApplicationConstants.RUBBERDUCK_TEMP_PATH))
89+
{
90+
Directory.CreateDirectory(ApplicationConstants.RUBBERDUCK_TEMP_PATH);
91+
}
92+
// The parser swallows the error if deletions fail - clean up any temp files on startup
93+
foreach (var file in new DirectoryInfo(ApplicationConstants.RUBBERDUCK_TEMP_PATH).GetFiles())
94+
{ try
95+
{
96+
file.Delete();
97+
}
98+
catch
99+
{
100+
// Yeah, don't care here either.
101+
}
102+
}
103+
}
104+
84105
private void UpdateLoggingLevel()
85106
{
86107
LogLevelHelper.SetMinimumLogLevel(LogLevel.FromOrdinal(_config.UserSettings.GeneralSettings.MinimumLogLevel));
@@ -89,6 +110,7 @@ private void UpdateLoggingLevel()
89110
public void Startup()
90111
{
91112
EnsureLogFolderPathExists();
113+
EnsureTempPathExists();
92114
LogRubberduckSart();
93115
LoadConfig();
94116
CheckForLegacyIndenterSettings();
@@ -108,6 +130,7 @@ public void Shutdown()
108130
{
109131
try
110132
{
133+
Debug.WriteLine("App calling Hooks.Detach.");
111134
_hooks.Detach();
112135
}
113136
catch

RetailCoder.VBE/Common/ApplicationConstants.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,5 +7,6 @@ public static class ApplicationConstants
77
{
88
public static readonly string RUBBERDUCK_FOLDER_PATH = Path.Combine(Environment.GetFolderPath(Environment.SpecialFolder.ApplicationData), "Rubberduck");
99
public static readonly string LOG_FOLDER_PATH = Path.Combine(RUBBERDUCK_FOLDER_PATH, "Logs");
10+
public static readonly string RUBBERDUCK_TEMP_PATH = Path.Combine(Path.GetTempPath(), "Rubberduck");
1011
}
1112
}
Lines changed: 10 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
using System.IO;
1+
using System;
2+
using System.IO;
23
using System.Reflection;
34
using Rubberduck.Parsing.VBA;
45
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
@@ -7,18 +8,22 @@ namespace Rubberduck.Common
78
{
89
public class ModuleExporter : IModuleExporter
910
{
11+
public bool TempFile { get; private set; }
12+
1013
public string ExportPath
1114
{
1215
get
1316
{
14-
var assemblyLocation = Assembly.GetAssembly(typeof(App)).Location;
15-
return Path.GetDirectoryName(assemblyLocation);
17+
return TempFile
18+
? ApplicationConstants.RUBBERDUCK_TEMP_PATH
19+
: Path.GetDirectoryName(Assembly.GetAssembly(typeof(App)).Location);
1620
}
1721
}
1822

19-
public string Export(IVBComponent component)
23+
public string Export(IVBComponent component, bool tempFile = false)
2024
{
21-
return component.ExportAsSourceFile(ExportPath);
25+
TempFile = tempFile;
26+
return component.ExportAsSourceFile(ExportPath, tempFile);
2227
}
2328
}
2429
}

RetailCoder.VBE/Extension.cs

Lines changed: 12 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -14,11 +14,13 @@
1414
using System.Runtime.InteropServices;
1515
using System.Windows.Forms;
1616
using System.Windows.Threading;
17+
using Microsoft.Vbe.Interop;
1718
using Ninject.Extensions.Interception;
1819
using NLog;
1920
using Rubberduck.Settings;
2021
using Rubberduck.SettingsProvider;
2122
using Rubberduck.VBEditor.Events;
23+
using Rubberduck.VBEditor.SafeComWrappers;
2224
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
2325

2426
namespace Rubberduck
@@ -52,13 +54,13 @@ public void OnConnection(object Application, ext_ConnectMode ConnectMode, object
5254
{
5355
try
5456
{
55-
if (Application is Microsoft.Vbe.Interop.VBE)
57+
if (Application is VBE)
5658
{
57-
var vbe = (Microsoft.Vbe.Interop.VBE) Application;
59+
var vbe = (VBE) Application;
5860
_ide = new VBEditor.SafeComWrappers.VBA.VBE(vbe);
5961
VBENativeServices.HookEvents(_ide);
6062

61-
var addin = (Microsoft.Vbe.Interop.AddIn)AddInInst;
63+
var addin = (AddIn)AddInInst;
6264
_addin = new VBEditor.SafeComWrappers.VBA.AddIn(addin) { Object = this };
6365
}
6466
else if (Application is Microsoft.VB6.Interop.VBIDE.VBE)
@@ -221,35 +223,31 @@ private void Startup()
221223

222224
private void ShutdownAddIn()
223225
{
226+
Debug.WriteLine("Extension unhooking VBENativeServices events.");
224227
VBENativeServices.UnhookEvents();
225228

226229
var currentDomain = AppDomain.CurrentDomain;
227230
currentDomain.AssemblyResolve -= LoadFromSameFolder;
228-
231+
Debug.WriteLine("Extension broadcasting shutdown.");
229232
User32.EnumChildWindows(_ide.MainWindow.Handle(), EnumCallback, new IntPtr(0));
230233

234+
Debug.WriteLine("Extension calling ReleaseDockableHosts.");
235+
VBEditor.SafeComWrappers.VBA.Windows.ReleaseDockableHosts();
236+
231237
if (_app != null)
232238
{
239+
Debug.WriteLine("Extension calling App.Shutdown.");
233240
_app.Shutdown();
234241
_app = null;
235242
}
236243

237244
if (_kernel != null)
238245
{
246+
Debug.WriteLine("Extension calling Kernel.Dispose.");
239247
_kernel.Dispose();
240248
_kernel = null;
241249
}
242250

243-
try
244-
{
245-
_ide.Release();
246-
}
247-
catch (Exception e)
248-
{
249-
_logger.Error(e);
250-
}
251-
252-
GC.WaitForPendingFinalizers();
253251
_isInitialized = false;
254252
}
255253

RetailCoder.VBE/Inspections/Concrete/Inspector.cs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -126,14 +126,16 @@ before moving them into the ParseTreeResults after qualifying them
126126
var emptyStringLiteralListener = IsDisabled<EmptyStringLiteralInspection>(settings) ? null : new EmptyStringLiteralInspection.EmptyStringLiteralListener();
127127
var argListWithOneByRefParamListener = IsDisabled<ProcedureCanBeWrittenAsFunctionInspection>(settings) ? null : new ProcedureCanBeWrittenAsFunctionInspection.SingleByRefParamArgListListener();
128128
var invalidAnnotationListener = IsDisabled<MissingAnnotationArgumentInspection>(settings) ? null : new MissingAnnotationArgumentInspection.InvalidAnnotationStatementListener();
129+
var optionBaseZeroListener = IsDisabled<OptionBaseZeroInspection>(settings) ? null : new OptionBaseZeroInspection.OptionBaseStatementListener();
129130

130131
var combinedListener = new CombinedParseTreeListener(new IParseTreeListener[]{
131132
obsoleteCallStatementListener,
132133
obsoleteLetStatementListener,
133134
obsoleteCommentSyntaxListener,
134135
emptyStringLiteralListener,
135136
argListWithOneByRefParamListener,
136-
invalidAnnotationListener
137+
invalidAnnotationListener,
138+
optionBaseZeroListener
137139
});
138140

139141
ParseTreeWalker.Default.Walk(combinedListener, componentTreePair.Value);
@@ -162,6 +164,10 @@ before moving them into the ParseTreeResults after qualifying them
162164
{
163165
result.AddRange(invalidAnnotationListener.Contexts.Select(context => new QualifiedContext<VBAParser.AnnotationContext>(componentTreePair.Key, context)));
164166
}
167+
if (optionBaseZeroListener != null)
168+
{
169+
result.AddRange(optionBaseZeroListener.Contexts.Select(context => new QualifiedContext<VBAParser.OptionBaseStmtContext>(componentTreePair.Key, context)));
170+
}
165171
}
166172
return result;
167173
}
Lines changed: 53 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,53 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Resources;
5+
using Rubberduck.Inspections.Results;
6+
using Rubberduck.Parsing;
7+
using Rubberduck.Parsing.Grammar;
8+
using Rubberduck.Parsing.VBA;
9+
10+
namespace Rubberduck.Inspections
11+
{
12+
public sealed class OptionBaseZeroInspection : InspectionBase, IParseTreeInspection<VBAParser.OptionBaseStmtContext>
13+
{
14+
private IEnumerable<QualifiedContext> _parseTreeResults;
15+
16+
public OptionBaseZeroInspection(RubberduckParserState state)
17+
: base(state, CodeInspectionSeverity.Hint)
18+
{
19+
}
20+
21+
public override string Meta { get { return InspectionsUI.OptionBaseZeroInspectionMeta; } }
22+
public override string Description { get { return InspectionsUI.OptionBaseZeroInspectionName; } }
23+
public override CodeInspectionType InspectionType { get { return CodeInspectionType.MaintainabilityAndReadabilityIssues; } }
24+
25+
public IEnumerable<QualifiedContext<VBAParser.OptionBaseStmtContext>> ParseTreeResults { get { return _parseTreeResults.OfType<QualifiedContext<VBAParser.OptionBaseStmtContext>>(); } }
26+
public void SetResults(IEnumerable<QualifiedContext> results) { _parseTreeResults = results; }
27+
28+
public override IEnumerable<InspectionResultBase> GetInspectionResults()
29+
{
30+
if (ParseTreeResults == null)
31+
{
32+
return new InspectionResultBase[] { };
33+
}
34+
35+
return ParseTreeResults.Where(context => !IsIgnoringInspectionResultFor(context.ModuleName.Component, context.Context.Start.Line))
36+
.Select(context => new OptionBaseZeroInspectionResult(this, new QualifiedContext<VBAParser.OptionBaseStmtContext>(context.ModuleName, context.Context)));
37+
}
38+
39+
public class OptionBaseStatementListener : VBAParserBaseListener
40+
{
41+
private readonly IList<VBAParser.OptionBaseStmtContext> _contexts = new List<VBAParser.OptionBaseStmtContext>();
42+
public IEnumerable<VBAParser.OptionBaseStmtContext> Contexts { get { return _contexts; } }
43+
44+
public override void ExitOptionBaseStmt(VBAParser.OptionBaseStmtContext context)
45+
{
46+
if (context.numberLiteral()?.INTEGERLITERAL().Symbol.Text == "0")
47+
{
48+
_contexts.Add(context);
49+
}
50+
}
51+
}
52+
}
53+
}

RetailCoder.VBE/Inspections/ParameterCanBeByValInspection.cs

Lines changed: 37 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -23,53 +23,61 @@ public ParameterCanBeByValInspection(RubberduckParserState state)
2323

2424
public override IEnumerable<InspectionResultBase> GetInspectionResults()
2525
{
26-
var declarations = UserDeclarations.ToList();
26+
var declarations = UserDeclarations.ToArray();
2727
var issues = new List<ParameterCanBeByValInspectionResult>();
2828

29-
var interfaceDeclarationMembers = declarations.FindInterfaceMembers().ToList();
30-
var interfaceScopes = declarations.FindInterfaceImplementationMembers().Concat(interfaceDeclarationMembers).Select(s => s.Scope);
29+
var interfaceDeclarationMembers = declarations.FindInterfaceMembers().ToArray();
30+
var interfaceScopes = declarations.FindInterfaceImplementationMembers().Concat(interfaceDeclarationMembers).Select(s => s.Scope).ToArray();
3131

3232
issues.AddRange(GetResults(declarations, interfaceDeclarationMembers));
3333

34-
var eventMembers = declarations.Where(item => !item.IsBuiltIn && item.DeclarationType == DeclarationType.Event).ToList();
35-
var formEventHandlerScopes = State.FindFormEventHandlers().Select(handler => handler.Scope);
36-
var eventHandlerScopes = State.DeclarationFinder.FindEventHandlers().Concat(declarations.FindUserEventHandlers()).Select(e => e.Scope);
34+
var eventMembers = declarations.Where(item => !item.IsBuiltIn && item.DeclarationType == DeclarationType.Event).ToArray();
35+
var formEventHandlerScopes = State.FindFormEventHandlers().Select(handler => handler.Scope).ToArray();
36+
var eventHandlerScopes = State.DeclarationFinder.FindEventHandlers().Concat(declarations.FindUserEventHandlers()).Select(e => e.Scope).ToArray();
3737
var eventScopes = eventMembers.Select(s => s.Scope)
3838
.Concat(formEventHandlerScopes)
39-
.Concat(eventHandlerScopes);
39+
.Concat(eventHandlerScopes)
40+
.ToArray();
4041

4142
issues.AddRange(GetResults(declarations, eventMembers));
4243

4344
var declareScopes = declarations.Where(item =>
4445
item.DeclarationType == DeclarationType.LibraryFunction
4546
|| item.DeclarationType == DeclarationType.LibraryProcedure)
46-
.Select(e => e.Scope);
47+
.Select(e => e.Scope)
48+
.ToArray();
4749

48-
issues.AddRange(declarations.Where(declaration =>
50+
issues.AddRange(declarations.OfType<ParameterDeclaration>()
51+
.Where(declaration => IsIssue(declaration, declarations, declareScopes, eventScopes, interfaceScopes))
52+
.Select(issue => new ParameterCanBeByValInspectionResult(this, State, issue, issue.Context, issue.QualifiedName)));
53+
54+
return issues;
55+
}
56+
57+
private bool IsIssue(ParameterDeclaration declaration, Declaration[] userDeclarations, string[] declareScopes, string[] eventScopes, string[] interfaceScopes)
58+
{
59+
var isIssue =
4960
!declaration.IsArray
50-
&& (declaration.AsTypeDeclaration == null || declaration.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType)
61+
&& !declaration.IsParamArray
62+
&& (declaration.IsByRef || declaration.IsImplicitByRef)
63+
&& (declaration.AsTypeDeclaration == null || declaration.AsTypeDeclaration.DeclarationType != DeclarationType.ClassModule && declaration.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType && declaration.AsTypeDeclaration.DeclarationType != DeclarationType.Enumeration)
5164
&& !declareScopes.Contains(declaration.ParentScope)
5265
&& !eventScopes.Contains(declaration.ParentScope)
5366
&& !interfaceScopes.Contains(declaration.ParentScope)
54-
&& declaration.DeclarationType == DeclarationType.Parameter
55-
&& ((VBAParser.ArgContext)declaration.Context).BYVAL() == null
56-
&& !IsUsedAsByRefParam(declarations, declaration)
57-
&& !declaration.References.Any(reference => reference.IsAssignment))
58-
.Select(issue => new ParameterCanBeByValInspectionResult(this, State, issue, issue.Context, issue.QualifiedName)));
59-
60-
return issues;
67+
&& !IsUsedAsByRefParam(userDeclarations, declaration)
68+
&& (!declaration.References.Any() || !declaration.References.Any(reference => reference.IsAssignment));
69+
return isIssue;
6170
}
6271

63-
private IEnumerable<ParameterCanBeByValInspectionResult> GetResults(List<Declaration> declarations, List<Declaration> declarationMembers)
72+
private IEnumerable<ParameterCanBeByValInspectionResult> GetResults(Declaration[] declarations, Declaration[] declarationMembers)
6473
{
6574
foreach (var declaration in declarationMembers)
6675
{
67-
var declarationParameters =
68-
declarations.Where(d => d.DeclarationType == DeclarationType.Parameter &&
69-
Equals(d.ParentDeclaration, declaration))
70-
.OrderBy(o => o.Selection.StartLine)
71-
.ThenBy(t => t.Selection.StartColumn)
72-
.ToList();
76+
var declarationParameters = declarations.OfType<ParameterDeclaration>()
77+
.Where(d => Equals(d.ParentDeclaration, declaration))
78+
.OrderBy(o => o.Selection.StartLine)
79+
.ThenBy(t => t.Selection.StartColumn)
80+
.ToList();
7381

7482
if (!declarationParameters.Any()) { continue; }
7583
var parametersAreByRef = declarationParameters.Select(s => true).ToList();
@@ -80,12 +88,11 @@ private IEnumerable<ParameterCanBeByValInspectionResult> GetResults(List<Declara
8088

8189
foreach (var member in members)
8290
{
83-
var parameters =
84-
declarations.Where(d => d.DeclarationType == DeclarationType.Parameter &&
85-
Equals(d.ParentDeclaration, member))
86-
.OrderBy(o => o.Selection.StartLine)
87-
.ThenBy(t => t.Selection.StartColumn)
88-
.ToList();
91+
var parameters = declarations.OfType<ParameterDeclaration>()
92+
.Where(d => Equals(d.ParentDeclaration, member))
93+
.OrderBy(o => o.Selection.StartLine)
94+
.ThenBy(t => t.Selection.StartColumn)
95+
.ToList();
8996

9097
for (var i = 0; i < parameters.Count; i++)
9198
{

0 commit comments

Comments
 (0)