Skip to content

Commit 6aed60e

Browse files
committed
Merge branch 'CodeExplorer' of https://github.com/retailcoder/Rubberduck.git
2 parents f006282 + b4914bb commit 6aed60e

File tree

64 files changed

+2510
-246
lines changed

Some content is hidden

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

64 files changed

+2510
-246
lines changed

RetailCoder.VBE/App.cs

Lines changed: 3 additions & 65 deletions
Original file line numberDiff line numberDiff line change
@@ -36,9 +36,6 @@ public class App : IDisposable
3636

3737
private Configuration _config;
3838

39-
private readonly ConcurrentDictionary<VBComponent, CancellationTokenSource> _tokenSources =
40-
new ConcurrentDictionary<VBComponent, CancellationTokenSource>();
41-
4239
public App(VBE vbe, IMessageBox messageBox,
4340
IParserErrorsPresenterFactory parserErrorsPresenterFactory,
4441
IRubberduckParser parser,
@@ -94,7 +91,7 @@ private async void hooks_MessageReceived(object sender, HookEventArgs e)
9491
}
9592

9693
var component = _vbe.ActiveCodePane.CodeModule.Parent;
97-
ParseComponentAsync(component);
94+
_parser.ParseComponentAsync(component);
9895

9996
AwaitNextKey();
10097
return;
@@ -141,48 +138,14 @@ private async void hooks_MessageReceived(object sender, HookEventArgs e)
141138

142139
private void _stateBar_Refresh(object sender, EventArgs e)
143140
{
144-
ParseAll();
141+
_parser.State.RequestParse();
145142
}
146143

147144
private void Parser_StateChanged(object sender, EventArgs e)
148145
{
149146
_appMenus.EvaluateCanExecute(_parser.State);
150147
}
151148

152-
private void ParseComponentAsync(VBComponent component, bool resolve = true)
153-
{
154-
var tokenSource = RenewTokenSource(component);
155-
156-
var token = tokenSource.Token;
157-
_parser.ParseAsync(component, token);
158-
159-
if (resolve && !token.IsCancellationRequested)
160-
{
161-
using (var source = new CancellationTokenSource())
162-
{
163-
_parser.Resolve(source.Token);
164-
}
165-
}
166-
}
167-
168-
private CancellationTokenSource RenewTokenSource(VBComponent component)
169-
{
170-
if (_tokenSources.ContainsKey(component))
171-
{
172-
CancellationTokenSource existingTokenSource;
173-
_tokenSources.TryRemove(component, out existingTokenSource);
174-
if (existingTokenSource != null)
175-
{
176-
existingTokenSource.Cancel();
177-
existingTokenSource.Dispose();
178-
}
179-
}
180-
181-
var tokenSource = new CancellationTokenSource();
182-
_tokenSources[component] = tokenSource;
183-
return tokenSource;
184-
}
185-
186149
public void Startup()
187150
{
188151
CleanReloadConfig();
@@ -193,7 +156,7 @@ public void Startup()
193156
Task.Delay(1000).ContinueWith(t =>
194157
{
195158
_parser.State.AddBuiltInDeclarations(_vbe.HostApplication());
196-
ParseAll();
159+
_parser.State.RequestParse();
197160
});
198161

199162
//_hooks.AddHook(new LowLevelKeyboardHook(_vbe));
@@ -202,22 +165,6 @@ public void Startup()
202165
//_hooks.Attach();
203166
}
204167

205-
private void ParseAll()
206-
{
207-
var components = _vbe.VBProjects.Cast<VBProject>()
208-
.SelectMany(project => project.VBComponents.Cast<VBComponent>());
209-
210-
var result = Parallel.ForEach(components, component => { ParseComponentAsync(component, false); });
211-
212-
if (result.IsCompleted)
213-
{
214-
using (var tokenSource = new CancellationTokenSource())
215-
{
216-
_parser.Resolve(tokenSource.Token);
217-
}
218-
}
219-
}
220-
221168
private void CleanReloadConfig()
222169
{
223170
LoadConfig();
@@ -262,15 +209,6 @@ public void Dispose()
262209
_parser.State.StateChanged -= Parser_StateChanged;
263210

264211
_hooks.Dispose();
265-
266-
if (_tokenSources.Any())
267-
{
268-
foreach (var tokenSource in _tokenSources)
269-
{
270-
tokenSource.Value.Cancel();
271-
tokenSource.Value.Dispose();
272-
}
273-
}
274212
}
275213
}
276214
}

RetailCoder.VBE/Common/DeclarationExtensions.cs

Lines changed: 85 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,12 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Diagnostics;
4+
using System.Diagnostics.CodeAnalysis;
45
using System.Linq;
56
using System.Windows.Media.Imaging;
67
using Microsoft.Vbe.Interop;
78
using Rubberduck.Annotations;
9+
using Rubberduck.Parsing;
810
using Rubberduck.Parsing.Grammar;
911
using Rubberduck.Parsing.Symbols;
1012
using Rubberduck.VBEditor;
@@ -77,7 +79,56 @@ public static bool HasMultipleDeclarationsInStatement(this Declaration target)
7779

7880
var statement = target.Context.Parent as VBAParser.VariableListStmtContext;
7981

80-
return statement != null && statement.children.Count(i => i is VBAParser.VariableSubStmtContext) > 1;
82+
return statement != null && statement.children.OfType<VBAParser.VariableSubStmtContext>().Count() > 1;
83+
}
84+
85+
/// <summary>
86+
/// Returns the number of variable declarations in a single statement.
87+
/// </summary>
88+
/// <exception cref="ArgumentException">Throws when target's DeclarationType is not Variable.</exception>
89+
/// <param name="target"></param>
90+
/// <returns></returns>
91+
public static int CountOfDeclarationsInStatement(this Declaration target)
92+
{
93+
if (target.DeclarationType != DeclarationType.Variable)
94+
{
95+
throw new ArgumentException("Target DeclarationType is not Variable.", "target");
96+
}
97+
98+
var statement = target.Context.Parent as VBAParser.VariableListStmtContext;
99+
100+
if (statement != null)
101+
{
102+
return statement.children.OfType<VBAParser.VariableSubStmtContext>().Count();
103+
}
104+
105+
throw new ArgumentException("'target.Context.Parent' is not type VBAParser.VariabelListStmtContext", "target");
106+
}
107+
108+
/// <summary>
109+
/// Returns the number of variable declarations in a single statement. Adjusted to be 1-indexed rather than 0-indexed.
110+
/// </summary>
111+
/// <exception cref="ArgumentException">Throws when target's DeclarationType is not Variable.</exception>
112+
/// <param name="target"></param>
113+
/// <returns></returns>
114+
public static int IndexOfVariableDeclarationInStatement(this Declaration target)
115+
{
116+
if (target.DeclarationType != DeclarationType.Variable)
117+
{
118+
throw new ArgumentException("Target DeclarationType is not Variable.", "target");
119+
}
120+
121+
var statement = target.Context.Parent as VBAParser.VariableListStmtContext;
122+
123+
if (statement != null)
124+
{
125+
return statement.children.OfType<VBAParser.VariableSubStmtContext>()
126+
.ToList()
127+
.IndexOf((VBAParser.VariableSubStmtContext)target.Context) + 1;
128+
}
129+
130+
// ReSharper disable once LocalizableElement
131+
throw new ArgumentException("'target.Context.Parent' is not type VBAParser.VariabelListStmtContext", "target");
81132
}
82133

83134
public static readonly DeclarationType[] ProcedureTypes =
@@ -441,5 +492,38 @@ public static Declaration FindVariable(this IEnumerable<Declaration> declaration
441492
}
442493
return null;
443494
}
495+
496+
/// <summary>
497+
/// Returns the interface for a QualifiedSelection contained by a statement similar to "Implements IClass1"
498+
/// </summary>
499+
/// <param name="declarations"></param>
500+
/// <param name="selection"></param>
501+
/// <returns></returns>
502+
[SuppressMessage("ReSharper", "LoopCanBeConvertedToQuery")]
503+
public static Declaration FindInterface(this IEnumerable<Declaration> declarations, QualifiedSelection selection)
504+
{
505+
foreach (var declaration in declarations.FindInterfaces())
506+
{
507+
foreach (var reference in declaration.References)
508+
{
509+
var implementsStmt = reference.Context.Parent as VBAParser.ImplementsStmtContext;
510+
511+
if (implementsStmt == null) { continue; }
512+
513+
var completeSelection = new Selection(implementsStmt.GetSelection().StartLine,
514+
implementsStmt.GetSelection().StartColumn, reference.Selection.EndLine,
515+
reference.Selection.EndColumn);
516+
517+
if (reference.QualifiedModuleName.ComponentName == selection.QualifiedName.ComponentName &&
518+
reference.QualifiedModuleName.Project == selection.QualifiedName.Project &&
519+
completeSelection.Contains(selection.Selection))
520+
{
521+
return declaration;
522+
}
523+
}
524+
}
525+
526+
return null;
527+
}
444528
}
445529
}

RetailCoder.VBE/Inspections/AssignedByValParameterInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -22,11 +22,11 @@ public AssignedByValParameterInspection()
2222

2323
private string AnnotationName { get { return Name.Replace("Inspection", string.Empty); } }
2424

25-
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState parseResult)
25+
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
2626
{
2727
var name = AnnotationName;
2828
var assignedByValParameters =
29-
parseResult.AllDeclarations.Where(declaration => !declaration.IsInspectionDisabled(name)
29+
state.AllDeclarations.Where(declaration => !declaration.IsInspectionDisabled(name)
3030
&& !declaration.IsBuiltIn
3131
&& declaration.DeclarationType == DeclarationType.Parameter
3232
&& ((VBAParser.ArgContext)declaration.Context).BYVAL() != null

RetailCoder.VBE/Inspections/ConstantNotUsedInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,9 +18,9 @@ public ConstantNotUsedInspection()
1818
public CodeInspectionType InspectionType { get { return CodeInspectionType.CodeQualityIssues; } }
1919
public CodeInspectionSeverity Severity { get; set; }
2020

21-
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState parseResult)
21+
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
2222
{
23-
var results = parseResult.AllDeclarations.Where(declaration =>
23+
var results = state.AllDeclarations.Where(declaration =>
2424
!declaration.IsBuiltIn
2525
&& declaration.DeclarationType == DeclarationType.Constant
2626
&& !declaration.References.Any());

RetailCoder.VBE/Inspections/DefaultProjectNameInspection.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -22,13 +22,13 @@ public DefaultProjectNameInspection()
2222
public CodeInspectionType InspectionType { get { return CodeInspectionType.MaintainabilityAndReadabilityIssues; } }
2323
public CodeInspectionSeverity Severity { get; set; }
2424

25-
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState parseResult)
25+
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
2626
{
27-
var issues = parseResult.AllDeclarations
27+
var issues = state.AllDeclarations
2828
.Where(declaration => !declaration.IsBuiltIn
2929
&& declaration.DeclarationType == DeclarationType.Project
3030
&& declaration.IdentifierName.StartsWith("VBAProject"))
31-
.Select(issue => new DefaultProjectNameInspectionResult(this, issue, parseResult, _wrapperFactory))
31+
.Select(issue => new DefaultProjectNameInspectionResult(this, issue, state, _wrapperFactory))
3232
.ToList();
3333

3434
return issues;
Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,30 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Antlr4.Runtime;
4+
using Rubberduck.Parsing;
5+
using Rubberduck.Parsing.VBA;
6+
7+
namespace Rubberduck.Inspections
8+
{
9+
public class EmptyStringLiteralInspection : IInspection
10+
{
11+
public EmptyStringLiteralInspection()
12+
{
13+
Severity = CodeInspectionSeverity.Warning;
14+
}
15+
16+
public string Name { get { return "EmptyStringLiteralInspection"; } }
17+
public string Description { get { return InspectionsUI.EmptyStringLiteralInspection; } }
18+
public CodeInspectionType InspectionType { get { return CodeInspectionType.LanguageOpportunities; } }
19+
public CodeInspectionSeverity Severity { get; set; }
20+
21+
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
22+
{
23+
return
24+
state.EmptyStringLiterals.Select(
25+
context =>
26+
new EmptyStringLiteralInspectionResult(this,
27+
new QualifiedContext<ParserRuleContext>(context.ModuleName, context.Context)));
28+
}
29+
}
30+
}
Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,46 @@
1+
using System.Collections.Generic;
2+
using Antlr4.Runtime;
3+
using Rubberduck.Parsing;
4+
using Rubberduck.Parsing.Grammar;
5+
using Rubberduck.VBEditor;
6+
7+
namespace Rubberduck.Inspections
8+
{
9+
public class EmptyStringLiteralInspectionResult : CodeInspectionResultBase
10+
{
11+
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
12+
13+
public EmptyStringLiteralInspectionResult(IInspection inspection, QualifiedContext<ParserRuleContext> qualifiedContext)
14+
: base(inspection, inspection.Description, qualifiedContext.ModuleName, qualifiedContext.Context)
15+
{
16+
_quickFixes = new[]
17+
{
18+
new RepaceEmptyStringLiteralStatementQuickFix(Context, QualifiedSelection),
19+
};
20+
}
21+
22+
public override IEnumerable<CodeInspectionQuickFix> QuickFixes { get { return _quickFixes; } }
23+
}
24+
25+
public class RepaceEmptyStringLiteralStatementQuickFix : CodeInspectionQuickFix
26+
{
27+
public RepaceEmptyStringLiteralStatementQuickFix(ParserRuleContext context, QualifiedSelection selection)
28+
: base(context, selection, InspectionsUI.EmptyStringLiteralInspectionQuickFix)
29+
{
30+
}
31+
32+
public override void Fix()
33+
{
34+
var module = Selection.QualifiedName.Component.CodeModule;
35+
if (module == null)
36+
{
37+
return;
38+
}
39+
40+
var literal = (VBAParser.LiteralContext)Context;
41+
var newCodeLines = module.Lines[literal.Start.Line, 1].Replace("\"\"", "vbNullString");
42+
43+
module.ReplaceLine(literal.Start.Line, newCodeLines);
44+
}
45+
}
46+
}

RetailCoder.VBE/Inspections/IInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,6 @@ public interface IInspection : IInspectionModel
1212
/// Runs code inspection on specified parse trees.
1313
/// </summary>
1414
/// <returns>Returns inspection results, if any.</returns>
15-
IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState parseResult);
15+
IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state);
1616
}
1717
}

RetailCoder.VBE/Inspections/ImplicitActiveSheetReferenceInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,15 +31,15 @@ public ImplicitActiveSheetReferenceInspection(VBE vbe)
3131
"Cells", "Range", "Columns", "Rows"
3232
};
3333

34-
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState parseResult)
34+
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
3535
{
3636
if (_hostApp().ApplicationName != "Excel")
3737
{
3838
return new CodeInspectionResultBase[] {};
3939
// if host isn't Excel, the ExcelObjectModel declarations shouldn't be loaded anyway.
4040
}
4141

42-
var issues = parseResult.AllDeclarations.Where(item => item.IsBuiltIn
42+
var issues = state.AllDeclarations.Where(item => item.IsBuiltIn
4343
&& item.ParentScope == "Excel.Global"
4444
&& Targets.Contains(item.IdentifierName)
4545
&& item.References.Any())

RetailCoder.VBE/Inspections/ImplicitActiveWorkbookReferenceInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -29,15 +29,15 @@ public ImplicitActiveWorkbookReferenceInspection(VBE vbe)
2929
"Worksheets", "Sheets", "Names",
3030
};
3131

32-
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState parseResult)
32+
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(RubberduckParserState state)
3333
{
3434
if (!_hostApp.IsValueCreated || _hostApp.Value == null || _hostApp.Value.ApplicationName != "Excel")
3535
{
3636
return new CodeInspectionResultBase[] {};
3737
// if host isn't Excel, the ExcelObjectModel declarations shouldn't be loaded anyway.
3838
}
3939

40-
var issues = parseResult.AllDeclarations.Where(item => item.IsBuiltIn
40+
var issues = state.AllDeclarations.Where(item => item.IsBuiltIn
4141
&& item.ParentScope == "Excel.Global"
4242
&& Targets.Contains(item.IdentifierName)
4343
&& item.References.Any())

0 commit comments

Comments
 (0)