Skip to content

Commit 91f8c70

Browse files
committed
Merge branch 'next' into RecoveringMemberAttributes
2 parents 6a8a8a4 + 99c2d75 commit 91f8c70

File tree

54 files changed

+2582
-335
lines changed

Some content is hidden

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

54 files changed

+2582
-335
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/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/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)

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

Lines changed: 72 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,12 @@ public interface IParseTreeValueVisitor : IParseTreeVisitor<IParseTreeVisitorRes
1414
event EventHandler<ValueResultEventArgs> OnValueResultCreated;
1515
}
1616

17-
public class ParseTreeValueVisitor : IParseTreeValueVisitor
17+
public interface ITestParseTreeVisitor
18+
{
19+
void InjectValuedDeclarationEvaluator(Func<Declaration, (bool, string, string)> func);
20+
}
21+
22+
public class ParseTreeValueVisitor : IParseTreeValueVisitor, ITestParseTreeVisitor
1823
{
1924
private class EnumMember
2025
{
@@ -41,8 +46,6 @@ public ParseTreeValueVisitor(IParseTreeValueFactory valueFactory, List<VBAParser
4146
_contextValues = new ParseTreeVisitorResults();
4247
OnValueResultCreated += _contextValues.OnNewValueResult;
4348
_enumStmtContexts = allEnums;
44-
_enumMembers = new List<EnumMember>();
45-
LoadEnumMemberValues();
4649
}
4750

4851
private Func<ParserRuleContext, (bool success, IdentifierReference idRef)> IdRefRetriever { set; get; } = null;
@@ -272,9 +275,41 @@ private bool TryGetLExprValue(VBAParser.LExprContext lExprContext, out string ex
272275
return true;
273276
}
274277

278+
if (lExprContext.TryGetChildContext(out VBAParser.IndexExprContext idxExpr)
279+
&& ParseTreeValue.TryGetNonPrintingControlCharCompareToken(idxExpr.GetText(), out string comparableToken))
280+
{
281+
declaredTypeName = Tokens.String;
282+
expressionValue = comparableToken;
283+
return true;
284+
}
285+
275286
return false;
276287
}
277288

289+
private Func<Declaration, (bool, string, string)> _valueDeclarationEvaluator;
290+
private Func<Declaration, (bool, string, string)> ValuedDeclarationEvaluator
291+
{
292+
set
293+
{
294+
_valueDeclarationEvaluator = value;
295+
}
296+
get
297+
{
298+
return _valueDeclarationEvaluator ?? GetValuedDeclaration;
299+
}
300+
}
301+
302+
303+
private (bool IsType, string ExpressionValue, string TypeName) GetValuedDeclaration(Declaration declaration)
304+
{
305+
if (declaration is ValuedDeclaration valuedDeclaration)
306+
{
307+
var typeName = GetBaseTypeForDeclaration(declaration);
308+
return (true, valuedDeclaration.Expression, typeName);
309+
}
310+
return (false, null, null);
311+
}
312+
278313
private void GetContextValue(ParserRuleContext context, out string declaredTypeName, out string expressionValue)
279314
{
280315
expressionValue = context.GetText();
@@ -286,6 +321,25 @@ private void GetContextValue(ParserRuleContext context, out string declaredTypeN
286321
expressionValue = rangeClauseIdentifierReference.IdentifierName;
287322
declaredTypeName = GetBaseTypeForDeclaration(declaration);
288323

324+
(bool IsValuedDeclaration, string ExpressionValue, string TypeName) = ValuedDeclarationEvaluator(declaration);
325+
326+
if( IsValuedDeclaration)
327+
{
328+
expressionValue = ExpressionValue;
329+
declaredTypeName = TypeName;
330+
331+
if (ParseTreeValue.TryGetNonPrintingControlCharCompareToken(expressionValue, out string resolvedValue))
332+
{
333+
expressionValue = resolvedValue;
334+
declaredTypeName = Tokens.String;
335+
return;
336+
}
337+
else if (long.TryParse(expressionValue, out _))
338+
{
339+
return;
340+
}
341+
}
342+
289343
if (declaration.DeclarationType.HasFlag(DeclarationType.Constant))
290344
{
291345
expressionValue = GetConstantContextValueToken(declaration.Context);
@@ -296,12 +350,12 @@ private void GetContextValue(ParserRuleContext context, out string declaredTypeN
296350
expressionValue = GetConstantContextValueToken(declaration.Context);
297351
if (expressionValue.Equals(string.Empty))
298352
{
299-
var enumValues = _enumMembers.Where(dt => dt.ConstantContext == declaration.Context);
300-
if (enumValues.Any())
353+
if (_enumMembers is null)
301354
{
302-
var enumValue = enumValues.First();
303-
expressionValue = enumValue.Value.ToString();
355+
LoadEnumMemberValues();
304356
}
357+
var enumValue = _enumMembers.SingleOrDefault(dt => dt.ConstantContext == declaration.Context);
358+
expressionValue = enumValue?.Value.ToString() ?? string.Empty;
305359
}
306360
}
307361
}
@@ -321,6 +375,11 @@ private bool TryGetIdentifierReferenceForContext(ParserRuleContext context, out
321375

322376
private string GetConstantContextValueToken(ParserRuleContext context)
323377
{
378+
if (context is null)
379+
{
380+
return string.Empty;
381+
}
382+
324383
var declarationContextChildren = context.children.ToList();
325384
var equalsSymbolIndex = declarationContextChildren.FindIndex(ch => ch.Equals(context.GetToken(VBAParser.EQ, 0)));
326385

@@ -378,8 +437,12 @@ private static bool IsBinaryOpEvaluationContext<T>(T context)
378437
return false;
379438
}
380439

440+
public void InjectValuedDeclarationEvaluator( Func<Declaration, (bool, string, string)> func)
441+
=> ValuedDeclarationEvaluator = func;
442+
381443
private void LoadEnumMemberValues()
382444
{
445+
_enumMembers = new List<EnumMember>();
383446
foreach (var enumStmt in _enumStmtContexts)
384447
{
385448
long enumAssignedValue = -1;
@@ -390,6 +453,8 @@ private void LoadEnumMemberValues()
390453
var enumMember = new EnumMember(enumConstContext, enumAssignedValue);
391454
if (enumMember.HasAssignment)
392455
{
456+
Visit(enumMember.ConstantContext);
457+
393458
var valueText = GetConstantContextValueToken(enumMember.ConstantContext);
394459
if (!valueText.Equals(string.Empty))
395460
{

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

Lines changed: 17 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -51,13 +51,11 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5151
var qualifiedSelectCaseStmts = Listener.Contexts
5252
.Where(result => !IsIgnoringInspectionResultFor(result.ModuleName, result.Context.Start.Line));
5353

54-
var listener = (UnreachableCaseInspectionListener)Listener;
55-
var parseTreeValueVisitor = CreateParseTreeValueVisitor(_valueFactory, listener.EnumerationStmtContexts.ToList(), GetIdentifierReferenceForContext);
56-
parseTreeValueVisitor.OnValueResultCreated += ValueResults.OnNewValueResult;
54+
ParseTreeValueVisitor.OnValueResultCreated += ValueResults.OnNewValueResult;
5755

5856
foreach (var qualifiedSelectCaseStmt in qualifiedSelectCaseStmts)
5957
{
60-
qualifiedSelectCaseStmt.Context.Accept(parseTreeValueVisitor);
58+
qualifiedSelectCaseStmt.Context.Accept(ParseTreeValueVisitor);
6159
var selectCaseInspector = _unreachableCaseInspectorFactory.Create((VBAParser.SelectCaseStmtContext)qualifiedSelectCaseStmt.Context, ValueResults, _valueFactory, GetVariableTypeName);
6260

6361
selectCaseInspector.InspectForUnreachableCases();
@@ -71,6 +69,20 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
7169
return _inspectionResults;
7270
}
7371

72+
private IParseTreeValueVisitor _parseTreeValueVisitor;
73+
public IParseTreeValueVisitor ParseTreeValueVisitor
74+
{
75+
get
76+
{
77+
if (_parseTreeValueVisitor is null)
78+
{
79+
var listener = (UnreachableCaseInspectionListener)Listener;
80+
_parseTreeValueVisitor = CreateParseTreeValueVisitor(_valueFactory, listener.EnumerationStmtContexts.ToList(), GetIdentifierReferenceForContext);
81+
}
82+
return _parseTreeValueVisitor;
83+
}
84+
}
85+
7486
private void CreateInspectionResult(QualifiedContext<ParserRuleContext> selectStmt, ParserRuleContext unreachableBlock, string message)
7587
{
7688
var result = new QualifiedContextInspectionResult(this,
@@ -80,9 +92,7 @@ private void CreateInspectionResult(QualifiedContext<ParserRuleContext> selectSt
8092
}
8193

8294
public static IParseTreeValueVisitor CreateParseTreeValueVisitor(IParseTreeValueFactory valueFactory, List<VBAParser.EnumerationStmtContext> allEnums, Func<ParserRuleContext, (bool success, IdentifierReference idRef)> func)
83-
{
84-
return new ParseTreeValueVisitor(valueFactory, allEnums, func);
85-
}
95+
=> new ParseTreeValueVisitor(valueFactory, allEnums, func);
8696

8797
//Method is used as a delegate to avoid propogating RubberduckParserState beyond this class
8898
private (bool success, IdentifierReference idRef) GetIdentifierReferenceForContext(ParserRuleContext context)
Lines changed: 47 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,47 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Concrete;
5+
using Rubberduck.Parsing.Annotations;
6+
using Rubberduck.Parsing.Inspections.Abstract;
7+
using Rubberduck.Parsing.Rewriter;
8+
using Rubberduck.Parsing.Symbols;
9+
using Rubberduck.Parsing.VBA;
10+
11+
namespace Rubberduck.Inspections.QuickFixes
12+
{
13+
public class AddAttributeAnnotationQuickFix : QuickFixBase
14+
{
15+
private readonly IAnnotationUpdater _annotationUpdater;
16+
private readonly IAttributeAnnotationProvider _attributeAnnotationProvider;
17+
18+
public AddAttributeAnnotationQuickFix(IAnnotationUpdater annotationUpdater, IAttributeAnnotationProvider attributeAnnotationProvider)
19+
: base(typeof(MissingModuleAnnotationInspection), typeof(MissingMemberAnnotationInspection))
20+
{
21+
_annotationUpdater = annotationUpdater;
22+
_attributeAnnotationProvider = attributeAnnotationProvider;
23+
}
24+
25+
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
26+
{
27+
var declaration = result.Target;
28+
string attributeName = result.Properties.AttributeName;
29+
IReadOnlyList<string> attributeValues = result.Properties.AttributeValues;
30+
var (annotationType, annotationValues) = declaration.DeclarationType.HasFlag(DeclarationType.Module)
31+
? _attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues)
32+
: _attributeAnnotationProvider.MemberAttributeAnnotation(AttributeBaseName(attributeName, declaration), attributeValues);
33+
_annotationUpdater.AddAnnotation(rewriteSession, declaration, annotationType, annotationValues);
34+
}
35+
36+
private static string AttributeBaseName(string attributeName, Declaration declaration)
37+
{
38+
return Attributes.AttributeBaseName(attributeName, declaration.IdentifierName);
39+
}
40+
41+
public override string Description(IInspectionResult result) => Resources.Inspections.QuickFixes.AddAttributeAnnotationQuickFix;
42+
43+
public override bool CanFixInProcedure => true;
44+
public override bool CanFixInModule => true;
45+
public override bool CanFixInProject => true;
46+
}
47+
}

0 commit comments

Comments
 (0)