Skip to content

Commit f0f4183

Browse files
committed
Consolidate ValueTypes lists, add LongPtr to list, closes #2645
1 parent 86e2660 commit f0f4183

File tree

11 files changed

+97
-85
lines changed

11 files changed

+97
-85
lines changed

RetailCoder.VBE/Inspections/ObjectVariableNotSetInspection.cs

Lines changed: 3 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
using Rubberduck.Inspections.Abstract;
44
using Rubberduck.Inspections.Resources;
55
using Rubberduck.Inspections.Results;
6+
using Rubberduck.Parsing;
67
using Rubberduck.Parsing.Grammar;
78
using Rubberduck.Parsing.Symbols;
89
using Rubberduck.Parsing.VBA;
@@ -20,29 +21,13 @@ public ObjectVariableNotSetInspection(RubberduckParserState state)
2021
public override string Description { get { return InspectionsUI.ObjectVariableNotSetInspectionName; } }
2122
public override CodeInspectionType InspectionType { get { return CodeInspectionType.CodeQualityIssues; } }
2223

23-
private static readonly IReadOnlyList<string> ValueTypes = new[]
24-
{
25-
Tokens.Boolean,
26-
Tokens.Byte,
27-
Tokens.Currency,
28-
Tokens.Date,
29-
Tokens.Decimal,
30-
Tokens.Double,
31-
Tokens.Integer,
32-
Tokens.Long,
33-
Tokens.LongLong,
34-
Tokens.Single,
35-
Tokens.String,
36-
Tokens.Variant
37-
};
38-
3924
public override IEnumerable<InspectionResultBase> GetInspectionResults()
4025
{
4126
var interestingDeclarations =
4227
State.AllUserDeclarations.Where(item =>
4328
!item.IsSelfAssigned &&
4429
!item.IsArray &&
45-
!ValueTypes.Contains(item.AsTypeName) &&
30+
!SymbolList.ValueTypes.Contains(item.AsTypeName) &&
4631
(item.AsTypeDeclaration == null || (!ClassModuleDeclaration.HasDefaultMember(item.AsTypeDeclaration) &&
4732
item.AsTypeDeclaration.DeclarationType != DeclarationType.Enumeration &&
4833
item.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType)) &&
@@ -54,7 +39,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
5439
(item.DeclarationType == DeclarationType.Function || item.DeclarationType == DeclarationType.PropertyGet)
5540
&& !item.IsArray
5641
&& item.IsTypeSpecified
57-
&& !ValueTypes.Contains(item.AsTypeName)
42+
&& !SymbolList.ValueTypes.Contains(item.AsTypeName)
5843
&& (item.AsTypeDeclaration == null // null if unresolved (e.g. in unit tests)
5944
|| (item.AsTypeDeclaration.DeclarationType != DeclarationType.Enumeration && item.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType
6045
&& item.AsTypeDeclaration != null

RetailCoder.VBE/Inspections/QuickFixes/RemoveTypeHintsQuickFix.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
using Antlr4.Runtime;
33
using Rubberduck.Inspections.Abstract;
44
using Rubberduck.Inspections.Resources;
5+
using Rubberduck.Parsing;
56
using Rubberduck.Parsing.Grammar;
67
using Rubberduck.Parsing.Symbols;
78
using Rubberduck.VBEditor;
@@ -47,7 +48,7 @@ private void FixTypeHintUsage(string hint, ICodeModule module, Selection selecti
4748
{
4849
var line = module.GetLines(selection.StartLine, 1);
4950

50-
var asTypeClause = ' ' + Tokens.As + ' ' + Declaration.TypeHintToTypeName[hint];
51+
var asTypeClause = ' ' + Tokens.As + ' ' + SymbolList.TypeHintToTypeName[hint];
5152

5253
string fix;
5354

RetailCoder.VBE/Inspections/SelfAssignedDeclarationInspection.cs

Lines changed: 2 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
using Rubberduck.Inspections.Abstract;
44
using Rubberduck.Inspections.QuickFixes;
55
using Rubberduck.Inspections.Resources;
6-
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.Parsing;
77
using Rubberduck.Parsing.VBA;
88
using Rubberduck.Parsing.Symbols;
99

@@ -20,27 +20,12 @@ public SelfAssignedDeclarationInspection(RubberduckParserState state)
2020
public override string Description { get { return InspectionsUI.SelfAssignedDeclarationInspectionName; } }
2121
public override CodeInspectionType InspectionType { get { return CodeInspectionType.CodeQualityIssues; } }
2222

23-
private static readonly IReadOnlyList<string> ValueTypes = new[]
24-
{
25-
Tokens.Boolean,
26-
Tokens.Byte,
27-
Tokens.Currency,
28-
Tokens.Date,
29-
Tokens.Decimal,
30-
Tokens.Double,
31-
Tokens.Integer,
32-
Tokens.Long,
33-
Tokens.LongLong,
34-
Tokens.Single,
35-
Tokens.String
36-
};
37-
3823
public override IEnumerable<InspectionResultBase> GetInspectionResults()
3924
{
4025
return UserDeclarations
4126
.Where(declaration => declaration.IsSelfAssigned
4227
&& declaration.IsTypeSpecified
43-
&& !ValueTypes.Contains(declaration.AsTypeName)
28+
&& !SymbolList.ValueTypes.Contains(declaration.AsTypeName)
4429
&& declaration.DeclarationType == DeclarationType.Variable
4530
&& (declaration.AsTypeDeclaration == null
4631
|| declaration.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType)

RetailCoder.VBE/Navigation/CodeExplorer/CodeExplorerViewModel.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using System.Linq;
55
using NLog;
66
using Rubberduck.Navigation.Folders;
7+
using Rubberduck.Parsing;
78
using Rubberduck.Parsing.Annotations;
89
using Rubberduck.Parsing.Symbols;
910
using Rubberduck.Parsing.VBA;
@@ -201,7 +202,7 @@ public string PanelTitle
201202
}
202203

203204
var typeName = declaration.HasTypeHint
204-
? Declaration.TypeHintToTypeName[declaration.TypeHint]
205+
? SymbolList.TypeHintToTypeName[declaration.TypeHint]
205206
: declaration.AsTypeName;
206207

207208
return nameWithDeclarationType + ": " + typeName;

RetailCoder.VBE/Refactorings/ExtractMethod/ExtractMethodPresenter.cs

Lines changed: 0 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,6 @@
11
using System;
2-
using System.Collections.Generic;
32
using System.Linq;
43
using System.Windows.Forms;
5-
using Rubberduck.Parsing.Grammar;
64
using Rubberduck.SmartIndenter;
75

86
namespace Rubberduck.Refactorings.ExtractMethod
@@ -59,21 +57,6 @@ private void PrepareView(IExtractMethodModel extractedMethodModel, IExtractMetho
5957
_view.OnRefreshPreview();
6058
}
6159

62-
private static readonly IEnumerable<string> ValueTypes = new[]
63-
{
64-
Tokens.Boolean,
65-
Tokens.Byte,
66-
Tokens.Currency,
67-
Tokens.Date,
68-
Tokens.Decimal,
69-
Tokens.Double,
70-
Tokens.Integer,
71-
Tokens.Long,
72-
Tokens.LongLong,
73-
Tokens.Single,
74-
Tokens.String
75-
};
76-
7760
private void GeneratePreview(IExtractMethodModel extractMethodModel,IExtractMethodProc extractMethodProc )
7861
{
7962
extractMethodModel.Method.MethodName = _view.MethodName;

RetailCoder.VBE/UI/Command/MenuItems/CommandBars/IContextFormatter.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
using System.Linq;
2+
using Rubberduck.Parsing;
23
using Rubberduck.Parsing.Symbols;
34
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
45

@@ -39,7 +40,7 @@ private string Format(Declaration declaration)
3940
var formattedDeclaration = string.Empty;
4041
var moduleName = declaration.QualifiedName.QualifiedModuleName;
4142
var typeName = declaration.HasTypeHint
42-
? Declaration.TypeHintToTypeName[declaration.TypeHint]
43+
? SymbolList.TypeHintToTypeName[declaration.TypeHint]
4344
: declaration.AsTypeName;
4445
var declarationType = RubberduckUI.ResourceManager.GetString("DeclarationType_" + declaration.DeclarationType, Settings.Settings.Culture);
4546

Rubberduck.Parsing/Rubberduck.Parsing.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -145,6 +145,7 @@
145145
<Compile Include="ComReflection\ComMember.cs" />
146146
<Compile Include="ComReflection\ComModule.cs" />
147147
<Compile Include="ComReflection\ComProject.cs" />
148+
<Compile Include="SymbolList.cs" />
148149
<Compile Include="Symbols\DeclarationLoaders\SpecialFormDeclarations.cs" />
149150
<Compile Include="Symbols\CommentNode.cs" />
150151
<Compile Include="ComReflection\ComParameter.cs" />

Rubberduck.Parsing/SymbolList.cs

Lines changed: 56 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,56 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using System.Text;
5+
using System.Threading.Tasks;
6+
using Rubberduck.Parsing.Grammar;
7+
8+
namespace Rubberduck.Parsing
9+
{
10+
public static class SymbolList
11+
{
12+
public static readonly IReadOnlyList<string> ValueTypes = new[]
13+
{
14+
Tokens.Boolean,
15+
Tokens.Byte,
16+
Tokens.Currency,
17+
Tokens.Date,
18+
Tokens.Decimal,
19+
Tokens.Double,
20+
Tokens.Integer,
21+
Tokens.Long,
22+
Tokens.LongLong,
23+
Tokens.LongPtr,
24+
Tokens.Single,
25+
Tokens.String,
26+
Tokens.Variant,
27+
};
28+
29+
public static readonly IReadOnlyList<string> ValueTypesUpper = new[]
30+
{
31+
Tokens.Boolean.ToUpper(),
32+
Tokens.Byte.ToUpper(),
33+
Tokens.Currency.ToUpper(),
34+
Tokens.Date.ToUpper(),
35+
Tokens.Decimal.ToUpper(),
36+
Tokens.Double.ToUpper(),
37+
Tokens.Integer.ToUpper(),
38+
Tokens.Long.ToUpper(),
39+
Tokens.LongLong.ToUpper(),
40+
Tokens.LongPtr.ToUpper(),
41+
Tokens.Single.ToUpper(),
42+
Tokens.String.ToUpper(),
43+
Tokens.Variant
44+
};
45+
46+
public static readonly IDictionary<string, string> TypeHintToTypeName = new Dictionary<string, string>
47+
{
48+
{ "%", Tokens.Integer },
49+
{ "&", Tokens.Long },
50+
{ "@", Tokens.Decimal },
51+
{ "!", Tokens.Single },
52+
{ "#", Tokens.Double },
53+
{ "$", Tokens.String }
54+
};
55+
}
56+
}

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 1 addition & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -19,34 +19,6 @@ namespace Rubberduck.Parsing.Symbols
1919
[DebuggerDisplay("({DeclarationType}) {Accessibility} {IdentifierName} As {AsTypeName} | {Selection}")]
2020
public class Declaration : IEquatable<Declaration>
2121
{
22-
public static readonly string[] BaseTypes =
23-
{
24-
"BOOLEAN",
25-
"BYTE",
26-
"CURRENCY",
27-
"DATE",
28-
"DOUBLE",
29-
"INTEGER",
30-
"LONG",
31-
"LONGLONG",
32-
"LONGPTR",
33-
"SINGLE",
34-
"STRING",
35-
"VARIANT",
36-
"OBJECT",
37-
"ANY"
38-
};
39-
40-
public static readonly IDictionary<string, string> TypeHintToTypeName = new Dictionary<string, string>
41-
{
42-
{ "%", Tokens.Integer },
43-
{ "&", Tokens.Long },
44-
{ "@", Tokens.Decimal },
45-
{ "!", Tokens.Single },
46-
{ "#", Tokens.Double },
47-
{ "$", Tokens.String }
48-
};
49-
5022
public Declaration(
5123
QualifiedMemberName qualifiedName,
5224
Declaration parentDeclaration,
@@ -485,7 +457,7 @@ public bool AsTypeIsBaseType
485457
{
486458
get
487459
{
488-
return string.IsNullOrWhiteSpace(AsTypeName) || BaseTypes.Contains(_asTypeName.ToUpperInvariant());
460+
return string.IsNullOrWhiteSpace(AsTypeName) || SymbolList.ValueTypesUpper.Contains(_asTypeName.ToUpperInvariant());
489461
}
490462
}
491463

Rubberduck.Parsing/Symbols/TypeAnnotationPass.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,7 @@ private void AnnotateType(Declaration declaration)
5252
var typeContext = declaration.AsTypeContext;
5353
typeExpression = typeContext.type().complexType().GetText();
5454
}
55-
else if (!string.IsNullOrWhiteSpace(declaration.AsTypeNameWithoutArrayDesignator) && !Declaration.BaseTypes.Contains(declaration.AsTypeNameWithoutArrayDesignator.ToUpperInvariant()))
55+
else if (!string.IsNullOrWhiteSpace(declaration.AsTypeNameWithoutArrayDesignator) && !SymbolList.ValueTypesUpper.Contains(declaration.AsTypeNameWithoutArrayDesignator.ToUpperInvariant()))
5656
{
5757
typeExpression = declaration.AsTypeNameWithoutArrayDesignator;
5858
}

0 commit comments

Comments
 (0)