Skip to content

Commit c4fd419

Browse files
committed
Merge branch 'next' of https://github.com/rubberduck-vba/Rubberduck into RefactoringDialogRefactor
2 parents 86d2728 + 4e2af2a commit c4fd419

File tree

98 files changed

+3652
-472
lines changed

Some content is hidden

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

98 files changed

+3652
-472
lines changed

Rubberduck.CodeAnalysis/CodePathAnalysis/Walker.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@
55
using System.Collections.Generic;
66
using System.Collections.Immutable;
77
using System.Linq;
8-
using Antlr4.Runtime;
98

109
namespace Rubberduck.Inspections.CodePathAnalysis
1110
{

Rubberduck.CodeAnalysis/Inspections/Abstract/InspectionBase.cs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -166,5 +166,10 @@ public IEnumerable<IInspectionResult> GetInspectionResults(CancellationToken tok
166166
_logger.Trace("Intercepted invocation of '{0}.{1}' ran for {2}ms", GetType().Name, nameof(DoGetInspectionResults), _stopwatch.ElapsedMilliseconds);
167167
return result;
168168
}
169+
170+
public virtual bool ChangesInvalidateResult(IInspectionResult result, ICollection<QualifiedModuleName> modifiedModules)
171+
{
172+
return true;
173+
}
169174
}
170175
}

Rubberduck.CodeAnalysis/Inspections/Abstract/InspectionResultBase.cs

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
using System.IO;
1+
using System.Collections.Generic;
2+
using System.IO;
23
using Antlr4.Runtime;
34
using Rubberduck.Common;
45
using Rubberduck.Parsing.Inspections;
@@ -39,6 +40,12 @@ protected InspectionResultBase(IInspection inspection,
3940
public Declaration Target { get; }
4041
public dynamic Properties { get; }
4142

43+
public virtual bool ChangesInvalidateResult(ICollection<QualifiedModuleName> modifiedModules)
44+
{
45+
return modifiedModules.Contains(QualifiedName)
46+
|| Inspection.ChangesInvalidateResult(this, modifiedModules);
47+
}
48+
4249
/// <summary>
4350
/// Gets the information needed to select the target instruction in the VBE.
4451
/// </summary>

Rubberduck.CodeAnalysis/Inspections/Concrete/AssignmentNotUsedInspection.cs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
using Rubberduck.Parsing.Symbols;
77
using Rubberduck.Inspections.CodePathAnalysis.Extensions;
88
using System.Linq;
9+
using Rubberduck.Inspections.CodePathAnalysis.Nodes;
910
using Rubberduck.Inspections.Results;
1011
using Rubberduck.Parsing;
1112
using Rubberduck.Parsing.Grammar;
@@ -30,7 +31,15 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3031
var nodes = new List<IdentifierReference>();
3132
foreach (var variable in variables)
3233
{
33-
var tree = _walker.GenerateTree(variable.ParentScopeDeclaration.Context, variable);
34+
var parentScopeDeclaration = variable.ParentScopeDeclaration;
35+
36+
if (parentScopeDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
37+
{
38+
continue;
39+
}
40+
41+
var tree = _walker.GenerateTree(parentScopeDeclaration.Context, variable);
42+
3443

3544
nodes.AddRange(tree.GetIdentifierReferences());
3645
}

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingMemberAnnotationInspection.cs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -77,10 +77,7 @@ private static bool MissesCorrespondingMemberAnnotation(Declaration declaration,
7777

7878
private static string AttributeBaseName(Declaration declaration, AttributeNode attribute)
7979
{
80-
var attributeName = attribute.Name;
81-
return attributeName.StartsWith($"{declaration.IdentifierName}.")
82-
? attributeName.Substring(declaration.IdentifierName.Length + 1)
83-
: attributeName;
80+
return Attributes.AttributeBaseName(attribute.Name, declaration.IdentifierName);
8481
}
8582
}
8683
}

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs

Lines changed: 1 addition & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -61,27 +61,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
6161

6262
private static bool IsDefaultAttribute(Declaration declaration, AttributeNode attribute)
6363
{
64-
switch (attribute.Name)
65-
{
66-
case "VB_Name":
67-
return true;
68-
case "VB_GlobalNameSpace":
69-
return declaration.DeclarationType.HasFlag(DeclarationType.ClassModule)
70-
&& attribute.Values[0].Equals(Tokens.False);
71-
case "VB_Exposed":
72-
return declaration.DeclarationType.HasFlag(DeclarationType.ClassModule)
73-
&& attribute.Values[0].Equals(Tokens.False);
74-
case "VB_Creatable":
75-
return declaration.DeclarationType.HasFlag(DeclarationType.ClassModule)
76-
&& attribute.Values[0].Equals(Tokens.False);
77-
case "VB_PredeclaredId":
78-
return (declaration.QualifiedModuleName.ComponentType == ComponentType.ClassModule
79-
&& attribute.Values[0].Equals(Tokens.False))
80-
|| (declaration.QualifiedModuleName.ComponentType == ComponentType.UserForm
81-
&& attribute.Values[0].Equals(Tokens.True));
82-
default:
83-
return false;
84-
}
64+
return Attributes.IsDefaultAttribute(declaration.QualifiedModuleName.ComponentType, attribute.Name, attribute.Values);
8565
}
8666

8767
private static bool MissesCorrespondingModuleAnnotation(Declaration declaration, AttributeNode attribute)

Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleWithoutFolderInspection.cs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -13,16 +13,17 @@ public sealed class ModuleWithoutFolderInspection : InspectionBase
1313
{
1414
public ModuleWithoutFolderInspection(RubberduckParserState state)
1515
: base(state)
16-
{
17-
}
16+
{}
1817

1918
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2019
{
2120
var modulesWithoutFolderAnnotation = State.DeclarationFinder.UserDeclarations(Parsing.Symbols.DeclarationType.Module)
2221
.Where(w => w.Annotations.All(a => a.AnnotationType != AnnotationType.Folder))
2322
.ToList();
2423

25-
return modulesWithoutFolderAnnotation.Select(declaration =>
24+
return modulesWithoutFolderAnnotation
25+
.Where(declaration => !IsIgnoringInspectionResultFor(declaration, AnnotationName))
26+
.Select(declaration =>
2627
new DeclarationInspectionResult(this, string.Format(InspectionResults.ModuleWithoutFolderInspection, declaration.IdentifierName), declaration));
2728
}
2829
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 25 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,11 @@ public ProcedureCanBeWrittenAsFunctionInspection(RubberduckParserState state)
2626

2727
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2828
{
29+
if (!Listener.Contexts.Any())
30+
{
31+
return Enumerable.Empty<IInspectionResult>();
32+
}
33+
2934
var userDeclarations = UserDeclarations.ToList();
3035
var builtinHandlers = State.DeclarationFinder.FindEventHandlers().ToList();
3136

@@ -38,17 +43,31 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3843

3944
return Listener.Contexts
4045
.Where(context => context.Context.Parent is VBAParser.SubStmtContext
41-
&& contextLookup[context.Context.GetChild<VBAParser.ArgContext>()].References
42-
.Any(reference => reference.IsAssignment))
43-
.Select(context => contextLookup[(VBAParser.SubStmtContext)context.Context.Parent])
44-
.Where(decl => !IsIgnoringInspectionResultFor(decl, AnnotationName) &&
45-
!ignored.Contains(decl) &&
46-
userDeclarations.Where(item => item.IsWithEvents)
46+
&& HasArgumentReferencesWithIsAssignmentFlagged(context))
47+
.Select(context => GetSubStmtParentDeclaration(context))
48+
.Where(decl => decl != null &&
49+
!IsIgnoringInspectionResultFor(decl, AnnotationName) &&
50+
!ignored.Contains(decl) &&
51+
userDeclarations.Where(item => item.IsWithEvents)
4752
.All(withEvents => userDeclarations.FindEventProcedures(withEvents) == null) &&
4853
!builtinHandlers.Contains(decl))
4954
.Select(result => new DeclarationInspectionResult(this,
5055
string.Format(InspectionResults.ProcedureCanBeWrittenAsFunctionInspection, result.IdentifierName),
5156
result));
57+
58+
bool HasArgumentReferencesWithIsAssignmentFlagged(QualifiedContext<ParserRuleContext> context)
59+
{
60+
return contextLookup.TryGetValue(context.Context.GetChild<VBAParser.ArgContext>(), out Declaration decl)
61+
? decl.References.Any(rf => rf.IsAssignment)
62+
: false;
63+
}
64+
65+
Declaration GetSubStmtParentDeclaration(QualifiedContext<ParserRuleContext> context)
66+
{
67+
return contextLookup.TryGetValue(context.Context.Parent as VBAParser.SubStmtContext, out Declaration decl)
68+
? decl
69+
: null;
70+
}
5271
}
5372

5473
public class SingleByRefParamArgListListener : VBAParserBaseListener, IInspectionListener

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

Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using Rubberduck.Parsing.Grammar;
22
using Rubberduck.Parsing.PreProcessing;
33
using System;
4+
using System.Collections.Generic;
45
using System.Globalization;
56

67
namespace Rubberduck.Inspections.Concrete.UnreachableCaseInspection
@@ -22,6 +23,31 @@ public struct ParseTreeValue : IParseTreeValue
2223
private StringLiteralExpression _stringConstant;
2324
private bool? _exceedsValueTypeRange;
2425

26+
private static Dictionary<string,string> ControlCharacterCompareTokens = new Dictionary<string, string>()
27+
{
28+
["Chr$(8)"] = "Chr$(8)", //vbBack
29+
["Chr$(13)"] = "Chr$(13)", //vbCr
30+
["Chr$(13) + Chr$(10)"] = "Chr$(13)Chr$(10)", //vbCrLf
31+
["Chr$(10)"] = "Chr$(10)", //vbLf
32+
["Chr$(12)"] = "Chr$(12)", //vbFormFeed
33+
["Chr$(13) & Chr$(10)"] = "Chr$(13)Chr$(10)", //vbNewLine
34+
["Chr$(0)"] = "Chr$(0)", //vbNullChar
35+
["Chr$(9)"] = "Chr$(9)", //vbTab
36+
["Chr$(11)"] = "Chr$(11)", //vbVerticalTab
37+
["Chr$(13)Chr$(10)"] = "Chr$(13)Chr$(10)",
38+
};
39+
40+
public static bool TryGetNonPrintingControlCharCompareToken(string controlCharCandidate, out string comparableToken)
41+
{
42+
comparableToken = controlCharCandidate;
43+
if (controlCharCandidate.StartsWith(Tokens.Chr))
44+
{
45+
var key = controlCharCandidate.Replace("Chr(", "Chr$(");
46+
return ControlCharacterCompareTokens.TryGetValue(key, out comparableToken);
47+
}
48+
return false;
49+
}
50+
2551
public static IParseTreeValue CreateValueType(TypeTokenPair value)
2652
{
2753
if (value.ValueType.Equals(Tokens.Date) || value.ValueType.Equals(Tokens.String))
@@ -89,6 +115,11 @@ public ParseTreeValue(TypeTokenPair valuePair)
89115
_stringConstant = new StringLiteralExpression(new ConstantExpression(new StringValue(_typeTokenPair.Token)));
90116
ParsesToConstantValue = true;
91117
}
118+
else if (valuePair.ValueType.Equals(Tokens.String)
119+
&& TryGetNonPrintingControlCharCompareToken(valuePair.Token, out _))
120+
{
121+
ParsesToConstantValue = true;
122+
}
92123
}
93124

94125
public string ValueType => _typeTokenPair.ValueType;

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

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -72,6 +72,12 @@ public IParseTreeValue CreateDeclaredType(string expression, string declaredType
7272
throw new ArgumentNullException();
7373
}
7474

75+
if (ParseTreeValue.TryGetNonPrintingControlCharCompareToken(expression, out string comparableToken))
76+
{
77+
var charConversion = new TypeTokenPair(Tokens.String, comparableToken);
78+
return ParseTreeValue.CreateValueType(charConversion);
79+
}
80+
7581
var goalTypeTokenPair = new TypeTokenPair(declaredTypeName, null);
7682
var typeToken = TypeTokenPair.ConformToType(declaredTypeName, expression);
7783
if (typeToken.HasValue)

0 commit comments

Comments
 (0)