Skip to content

Commit 82d743f

Browse files
authored
Merge pull request #249 from MDoerner/DebugSCP
Fix for SCP deletion for indexExpr
2 parents 4207b1c + cc138c1 commit 82d743f

File tree

114 files changed

+831
-506
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

+831
-506
lines changed

Rubberduck.API/VBA/Parser.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,11 +12,12 @@
1212
using Rubberduck.Parsing.Symbols.DeclarationLoaders;
1313
using Rubberduck.Parsing.VBA;
1414
using Rubberduck.Parsing.Symbols;
15-
using Rubberduck.Parsing.Symbols.ParsingExceptions;
1615
using Rubberduck.Parsing.UIContext;
1716
using Rubberduck.Parsing.VBA.ComReferenceLoading;
17+
using Rubberduck.Parsing.VBA.DeclarationCaching;
1818
using Rubberduck.Parsing.VBA.DeclarationResolving;
1919
using Rubberduck.Parsing.VBA.Parsing;
20+
using Rubberduck.Parsing.VBA.Parsing.ParsingExceptions;
2021
using Rubberduck.Parsing.VBA.ReferenceManagement;
2122
using Rubberduck.Resources.Registration;
2223
using Rubberduck.VBEditor.ComManagement;

Rubberduck.CodeAnalysis/CodeMetrics/CodeMetricBase.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System.Collections.Generic;
22
using Rubberduck.Parsing.Grammar;
33
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Parsing.VBA.DeclarationCaching;
45
using Rubberduck.VBEditor;
56

67
namespace Rubberduck.CodeAnalysis.CodeMetrics

Rubberduck.CodeAnalysis/CodeMetrics/CodeMetricsAnalyst.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Rubberduck.VBEditor;
55
using System.Collections.Generic;
66
using System.Linq;
7+
using Rubberduck.Parsing.VBA.DeclarationCaching;
78

89
namespace Rubberduck.CodeAnalysis.CodeMetrics
910
{
Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing.Inspections.Abstract;
6+
using Rubberduck.Resources.Inspections;
7+
using Rubberduck.Parsing.VBA;
8+
using Rubberduck.Parsing.Annotations;
9+
10+
namespace Rubberduck.Inspections.Concrete
11+
{
12+
public sealed class ModuleWithoutFolderInspection : InspectionBase
13+
{
14+
public ModuleWithoutFolderInspection(RubberduckParserState state)
15+
: base(state)
16+
{
17+
}
18+
19+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
20+
{
21+
var modulesWithoutFolderAnnotation = State.DeclarationFinder.UserDeclarations(Parsing.Symbols.DeclarationType.Module)
22+
.Where(w => w.Annotations.All(a => a.AnnotationType != AnnotationType.Folder))
23+
.ToList();
24+
25+
return modulesWithoutFolderAnnotation.Select(declaration =>
26+
new DeclarationInspectionResult(this, string.Format(InspectionResults.ModuleWithoutFolderInspection, declaration.IdentifierName), declaration));
27+
}
28+
}
29+
}

Rubberduck.CodeAnalysis/Inspections/Concrete/SheetAccessedUsingStringInspection.cs

Lines changed: 33 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,10 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6060
var component = GetVBComponentMatchingSheetName(reference);
6161
if (component != null)
6262
{
63-
reference.Properties.CodeName = (string)component.Properties.Single(property => property.Name == "CodeName").Value;
63+
using (var properties = component.Properties)
64+
{
65+
reference.Properties.CodeName = (string)properties.Single(property => property.Name == "CodeName").Value;
66+
}
6467
issues.Add(reference);
6568
}
6669
}
@@ -98,9 +101,35 @@ private IVBComponent GetVBComponentMatchingSheetName(IdentifierReferenceInspecti
98101
var sheetName = FormatSheetName(sheetArgumentContext.GetText());
99102
var project = State.Projects.First(p => p.ProjectId == reference.QualifiedName.ProjectId);
100103

101-
return project.VBComponents.FirstOrDefault(c =>
102-
c.Type == ComponentType.Document &&
103-
(string) c.Properties.First(property => property.Name == "Name").Value == sheetName);
104+
105+
//return project.VBComponents.FirstOrDefault(c =>
106+
// c.Type == ComponentType.Document &&
107+
// (string)c.Properties.First(property => property.Name == "Name").Value == sheetName);
108+
using (var components = project.VBComponents)
109+
{
110+
for (var i = 0; i < components.Count; i++)
111+
{
112+
using (var component = components[i])
113+
using (var properties = component.Properties)
114+
{
115+
if (component.Type == ComponentType.Document)
116+
{
117+
for (var j = 0; j < properties.Count; j++)
118+
{
119+
using (var property = properties[j])
120+
{
121+
if (property.Name == "Name" && (string)property.Value == sheetName)
122+
{
123+
return component;
124+
}
125+
}
126+
}
127+
}
128+
}
129+
}
130+
131+
return null;
132+
}
104133
}
105134

106135
private static string FormatSheetName(string sheetName)

Rubberduck.CodeAnalysis/Inspections/Concrete/UnreachableCaseInspection/UnreachableCaseInspection.cs

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -20,15 +20,15 @@ public sealed class UnreachableCaseInspection : ParseTreeInspectionBase
2020
private readonly IUnreachableCaseInspectorFactory _unreachableCaseInspectorFactory;
2121
private readonly IParseTreeValueFactory _valueFactory;
2222

23-
private enum CaseInpectionResult { Unreachable, InherentlyUnreachable, MismatchType, Overflow, CaseElse };
23+
private enum CaseInspectionResult { Unreachable, InherentlyUnreachable, MismatchType, Overflow, CaseElse };
2424

25-
private static readonly Dictionary<CaseInpectionResult, string> ResultMessages = new Dictionary<CaseInpectionResult, string>()
25+
private static readonly Dictionary<CaseInspectionResult, string> ResultMessages = new Dictionary<CaseInspectionResult, string>()
2626
{
27-
[CaseInpectionResult.Unreachable] = InspectionResults.UnreachableCaseInspection_Unreachable,
28-
[CaseInpectionResult.InherentlyUnreachable] = InspectionResults.UnreachableCaseInspection_InherentlyUnreachable,
29-
[CaseInpectionResult.MismatchType] = InspectionResults.UnreachableCaseInspection_TypeMismatch,
30-
[CaseInpectionResult.Overflow] = InspectionResults.UnreachableCaseInspection_Overflow,
31-
[CaseInpectionResult.CaseElse] = InspectionResults.UnreachableCaseInspection_CaseElse
27+
[CaseInspectionResult.Unreachable] = InspectionResults.UnreachableCaseInspection_Unreachable,
28+
[CaseInspectionResult.InherentlyUnreachable] = InspectionResults.UnreachableCaseInspection_InherentlyUnreachable,
29+
[CaseInspectionResult.MismatchType] = InspectionResults.UnreachableCaseInspection_TypeMismatch,
30+
[CaseInspectionResult.Overflow] = InspectionResults.UnreachableCaseInspection_Overflow,
31+
[CaseInspectionResult.CaseElse] = InspectionResults.UnreachableCaseInspection_CaseElse
3232
};
3333

3434
public UnreachableCaseInspection(RubberduckParserState state) : base(state)
@@ -62,11 +62,11 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6262

6363
selectCaseInspector.InspectForUnreachableCases();
6464

65-
selectCaseInspector.UnreachableCases.ForEach(uc => CreateInspectionResult(qualifiedSelectCaseStmt, uc, ResultMessages[CaseInpectionResult.Unreachable]));
66-
selectCaseInspector.MismatchTypeCases.ForEach(mm => CreateInspectionResult(qualifiedSelectCaseStmt, mm, ResultMessages[CaseInpectionResult.MismatchType]));
67-
selectCaseInspector.OverflowCases.ForEach(mm => CreateInspectionResult(qualifiedSelectCaseStmt, mm, ResultMessages[CaseInpectionResult.Overflow]));
68-
selectCaseInspector.InherentlyUnreachableCases.ForEach(mm => CreateInspectionResult(qualifiedSelectCaseStmt, mm, ResultMessages[CaseInpectionResult.InherentlyUnreachable]));
69-
selectCaseInspector.UnreachableCaseElseCases.ForEach(ce => CreateInspectionResult(qualifiedSelectCaseStmt, ce, ResultMessages[CaseInpectionResult.CaseElse]));
65+
selectCaseInspector.UnreachableCases.ForEach(uc => CreateInspectionResult(qualifiedSelectCaseStmt, uc, ResultMessages[CaseInspectionResult.Unreachable]));
66+
selectCaseInspector.MismatchTypeCases.ForEach(mm => CreateInspectionResult(qualifiedSelectCaseStmt, mm, ResultMessages[CaseInspectionResult.MismatchType]));
67+
selectCaseInspector.OverflowCases.ForEach(mm => CreateInspectionResult(qualifiedSelectCaseStmt, mm, ResultMessages[CaseInspectionResult.Overflow]));
68+
selectCaseInspector.InherentlyUnreachableCases.ForEach(mm => CreateInspectionResult(qualifiedSelectCaseStmt, mm, ResultMessages[CaseInspectionResult.InherentlyUnreachable]));
69+
selectCaseInspector.UnreachableCaseElseCases.ForEach(ce => CreateInspectionResult(qualifiedSelectCaseStmt, ce, ResultMessages[CaseInspectionResult.CaseElse]));
7070
}
7171
return _inspectionResults;
7272
}

Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -81,6 +81,7 @@
8181
<Compile Include="Inspections\Concrete\EmptyForEachBlockInspection.cs" />
8282
<Compile Include="Inspections\Concrete\EmptyForLoopBlockInspection.cs" />
8383
<Compile Include="Inspections\Concrete\BooleanAssignedInIfElseInspection.cs" />
84+
<Compile Include="Inspections\Concrete\ModuleWithoutFolderInspection.cs" />
8485
<Compile Include="Inspections\Concrete\EmptyWhileWendBlockInspection.cs" />
8586
<Compile Include="Inspections\Concrete\ObsoleteCallingConventionInspection.cs" />
8687
<Compile Include="Inspections\Concrete\ObsoleteErrorSyntaxInspection.cs" />

Rubberduck.Core/AutoComplete/Service/SelfClosingPairCompletionService.cs

Lines changed: 38 additions & 86 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
using System.Windows.Forms;
44
using Antlr4.Runtime;
55
using Antlr4.Runtime.Misc;
6+
using Antlr4.Runtime.Tree;
67
using Rubberduck.Parsing;
78
using Rubberduck.Parsing.Grammar;
89
using Rubberduck.Parsing.VBA.Parsing;
@@ -208,8 +209,8 @@ private Selection FindMatchingTokenPosition(SelfClosingPair pair, CodeString ori
208209
}
209210
}
210211
var visitor = new MatchingTokenVisitor(pair, original);
211-
visitor.Visit(result.parseTree);
212-
return visitor.Result;
212+
var matchingTokenPosition = visitor.Visit(result.parseTree);
213+
return matchingTokenPosition;
213214
}
214215

215216

@@ -219,151 +220,102 @@ private class MatchingTokenVisitor : VBAParserBaseVisitor<Selection>
219220
private readonly SelfClosingPair _pair;
220221
private readonly CodeString _code;
221222

222-
public Selection Result { get; private set; }
223-
224223
public MatchingTokenVisitor(SelfClosingPair pair, CodeString code)
225224
{
226225
_pair = pair;
227226
_code = code;
228227
}
229228

230-
231-
public override Selection VisitArgumentList(VBAParser.ArgumentListContext context)
229+
protected override bool ShouldVisitNextChild(IRuleNode node, Selection currentResult)
232230
{
233-
if (context.Start.Text.StartsWith(_pair.OpeningChar.ToString())
234-
&& context.Start.Text.EndsWith(_pair.ClosingChar.ToString()))
235-
{
236-
if (_code.CaretPosition.StartLine == context.Start.Line - 1
237-
&& _code.CaretPosition.StartColumn == context.Start.Column + 1)
238-
{
239-
Result = new Selection(context.Start.Line - 1, context.Stop.Column + context.Stop.Text.Length - 1);
240-
}
241-
}
242-
var inner = context.GetDescendents<VBAParser.ArgumentListContext>();
243-
foreach (var item in inner)
244-
{
245-
if (context != item)
246-
{
247-
var result = Visit(item);
248-
if (result != default)
249-
{
250-
Result = result;
251-
}
252-
}
253-
}
254-
255-
return base.VisitArgumentList(context);
231+
return currentResult.Equals(default);
256232
}
257233

258234
public override Selection VisitLiteralExpr([NotNull] VBAParser.LiteralExprContext context)
259235
{
236+
var innerResult = VisitChildren(context);
237+
if (innerResult != DefaultResult)
238+
{
239+
return innerResult;
240+
}
241+
260242
if (context.Start.Text.StartsWith(_pair.OpeningChar.ToString())
261243
&& context.Start.Text.EndsWith(_pair.ClosingChar.ToString()))
262244
{
263245
if (_code.CaretPosition.StartLine == context.Start.Line - 1
264246
&& _code.CaretPosition.StartColumn == context.Start.Column + 1)
265247
{
266-
Result = new Selection(context.Start.Line - 1, context.Stop.Column + context.Stop.Text.Length - 1);
267-
}
268-
}
269-
var inner = context.GetDescendents<VBAParser.LiteralExprContext>();
270-
foreach (var item in inner)
271-
{
272-
if (context != item)
273-
{
274-
var result = Visit(item);
275-
if (result != default)
276-
{
277-
Result = result;
278-
}
248+
return new Selection(context.Start.Line - 1, context.Stop.Column + context.Stop.Text.Length - 1);
279249
}
280250
}
281251

282-
return base.VisitLiteralExpr(context);
252+
return DefaultResult;
283253
}
284254

285255
public override Selection VisitIndexExpr([NotNull] VBAParser.IndexExprContext context)
286256
{
257+
var innerResult = VisitChildren(context);
258+
if (innerResult != DefaultResult)
259+
{
260+
return innerResult;
261+
}
262+
287263
if (context.LPAREN()?.Symbol.Text[0] == _pair.OpeningChar
288264
&& context.RPAREN()?.Symbol.Text[0] == _pair.ClosingChar)
289265
{
290266
if (_code.CaretPosition.StartLine == context.LPAREN().Symbol.Line - 1
291-
&& _code.CaretPosition.StartColumn == context.RPAREN().Symbol.Column)
267+
&& _code.CaretPosition.StartColumn == context.LPAREN().Symbol.Column + 1)
292268
{
293269
var token = context.RPAREN().Symbol;
294-
Result = new Selection(token.Line - 1, token.Column);
295-
}
296-
}
297-
var inner = context.GetDescendents<VBAParser.IndexExprContext>();
298-
foreach (var item in inner)
299-
{
300-
if (context != item)
301-
{
302-
var result = Visit(item);
303-
if (result != default)
304-
{
305-
Result = result;
306-
}
270+
return new Selection(token.Line - 1, token.Column);
307271
}
308272
}
309273

310-
return base.VisitIndexExpr(context);
274+
return DefaultResult;
311275
}
312276

313277
public override Selection VisitArgList([NotNull] VBAParser.ArgListContext context)
314278
{
279+
var innerResult = VisitChildren(context);
280+
if (innerResult != DefaultResult)
281+
{
282+
return innerResult;
283+
}
284+
315285
if (context.Start.Text[0] == _pair.OpeningChar
316286
&& context.Stop.Text[0] == _pair.ClosingChar)
317287
{
318288
if (_code.CaretPosition.StartLine == context.Start.Line - 1
319289
&& _code.CaretPosition.StartColumn == context.Start.Column + 1)
320290
{
321291
var token = context.Stop;
322-
Result = new Selection(token.Line - 1, token.Column);
323-
}
324-
}
325-
var inner = context.GetDescendents<VBAParser.ArgListContext>();
326-
foreach (var item in inner)
327-
{
328-
if (context != item)
329-
{
330-
var result = Visit(item);
331-
if (result != default)
332-
{
333-
Result = result;
334-
}
292+
return new Selection(token.Line - 1, token.Column);
335293
}
336294
}
337295

338-
return base.VisitArgList(context);
296+
return DefaultResult;
339297
}
340298

341299
public override Selection VisitParenthesizedExpr([NotNull] VBAParser.ParenthesizedExprContext context)
342300
{
301+
var innerResult = VisitChildren(context);
302+
if (innerResult != DefaultResult)
303+
{
304+
return innerResult;
305+
}
306+
343307
if (context.Start.Text[0] == _pair.OpeningChar
344308
&& context.Stop.Text[0] == _pair.ClosingChar)
345309
{
346310
if (_code.CaretPosition.StartLine == context.Start.Line - 1
347311
&& _code.CaretPosition.StartColumn == context.Start.Column + 1)
348312
{
349313
var token = context.Stop;
350-
Result = new Selection(token.Line - 1, token.Column);
351-
}
352-
}
353-
var inner = context.GetDescendents<VBAParser.ParenthesizedExprContext>();
354-
foreach (var item in inner)
355-
{
356-
if (context != item)
357-
{
358-
var result = Visit(item);
359-
if (result != default)
360-
{
361-
Result = result;
362-
}
314+
return new Selection(token.Line - 1, token.Column);
363315
}
364316
}
365317

366-
return base.VisitParenthesizedExpr(context);
318+
return DefaultResult;
367319
}
368320
}
369321
}

Rubberduck.Core/CodeAnalysis/CodeMetrics/ICodeMetricsParseTreeListener.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
using Rubberduck.Parsing.Symbols;
33
using Rubberduck.VBEditor;
44
using System.Collections.Generic;
5+
using Rubberduck.Parsing.VBA.DeclarationCaching;
56

67
namespace Rubberduck.CodeAnalysis.CodeMetrics
78
{

Rubberduck.Core/Properties/Settings.Designer.cs

Lines changed: 6 additions & 4 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

0 commit comments

Comments
 (0)