Skip to content

Commit 9a094fa

Browse files
committed
Minor renaming to clarify some things
1 parent d66c82f commit 9a094fa

File tree

8 files changed

+19
-25
lines changed

8 files changed

+19
-25
lines changed

Rubberduck.Parsing/Annotations/AnnotationType.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,7 @@ public enum AnnotationType
5757
NoIndent = 1 << 18 | ModuleAnnotation,
5858
Interface = 1 << 19 | ModuleAnnotation,
5959
[FlexibleAttributeValueAnnotation("VB_Description", 1)]
60-
Description = 1 << 13 | Attribute | MemberAnnotation,
60+
MemberDescription = 1 << 13 | Attribute | MemberAnnotation,
6161
[FixedAttributeValueAnnotation("VB_UserMemId", "0")]
6262
DefaultMember = 1 << 14 | Attribute | MemberAnnotation,
6363
[FixedAttributeValueAnnotation("VB_UserMemId", "-4")]

Rubberduck.Parsing/Annotations/DescriptionAnnotation.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ namespace Rubberduck.Parsing.Annotations
1010
public sealed class DescriptionAnnotation : DescriptionAttributeAnnotationBase
1111
{
1212
public DescriptionAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable<string> parameters)
13-
: base(AnnotationType.Description, qualifiedSelection, context, parameters)
13+
: base(AnnotationType.MemberDescription, qualifiedSelection, context, parameters)
1414
{}
1515
}
1616
}

Rubberduck.Parsing/Annotations/ExcelHotKeyAnnotation.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8,8 +8,8 @@ namespace Rubberduck.Parsing.Annotations
88
{
99
public sealed class ExcelHotKeyAnnotation : FlexibleAttributeValueAnnotationBase
1010
{
11-
public ExcelHotKeyAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable<string> parameters) :
12-
base(AnnotationType.ExcelHotKey, qualifiedSelection, context, GetHotKeyAttributeValue(parameters))
11+
public ExcelHotKeyAnnotation(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable<string> annotationParameterValues) :
12+
base(AnnotationType.ExcelHotKey, qualifiedSelection, context, GetHotKeyAttributeValue(annotationParameterValues))
1313
{ }
1414

1515
private static IEnumerable<string> GetHotKeyAttributeValue(IEnumerable<string> parameters) =>

Rubberduck.Parsing/Annotations/FlexibleAttributeValueAnnotationBase.cs

Lines changed: 8 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -8,26 +8,19 @@ namespace Rubberduck.Parsing.Annotations
88
{
99
public abstract class FlexibleAttributeValueAnnotationBase : AnnotationBase, IAttributeAnnotation
1010
{
11-
protected FlexibleAttributeValueAnnotationBase(AnnotationType annotationType, QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable<string> parameters)
11+
public string Attribute { get; }
12+
public IReadOnlyList<string> AttributeValues { get; }
13+
14+
protected FlexibleAttributeValueAnnotationBase(AnnotationType annotationType, QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable<string> attributeValues)
1215
:base(annotationType, qualifiedSelection, context)
1316
{
1417
var flexibleAttributeValueInfo = FlexibleAttributeValueInfo(annotationType);
1518

16-
if (flexibleAttributeValueInfo == null)
17-
{
18-
Attribute = string.Empty;
19-
AttributeValues = new List<string>();
20-
return;
21-
}
22-
23-
Attribute = flexibleAttributeValueInfo.Value.attribute;
24-
AttributeValues = parameters?.Take(flexibleAttributeValueInfo.Value.numberOfValues).ToList() ?? new List<string>();
19+
Attribute = flexibleAttributeValueInfo.attribute;
20+
AttributeValues = attributeValues?.Take(flexibleAttributeValueInfo.numberOfValues).ToList() ?? new List<string>();
2521
}
2622

27-
public string Attribute { get; }
28-
public IReadOnlyList<string> AttributeValues { get; }
29-
30-
private static (string attribute, int numberOfValues)? FlexibleAttributeValueInfo(AnnotationType annotationType)
23+
private static (string attribute, int numberOfValues) FlexibleAttributeValueInfo(AnnotationType annotationType)
3124
{
3225
var type = annotationType.GetType();
3326
var name = Enum.GetName(type, annotationType);
@@ -38,7 +31,7 @@ private static (string attribute, int numberOfValues)? FlexibleAttributeValueInf
3831

3932
if (attribute == null)
4033
{
41-
return null;
34+
return ("", 0);
4235
}
4336

4437
return (attribute.AttributeName, attribute.NumberOfParameters);

Rubberduck.Parsing/Annotations/VBAParserAnnotationFactory.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ public VBAParserAnnotationFactory()
2424
_creators.Add(AnnotationType.Folder.ToString().ToUpperInvariant(), typeof(FolderAnnotation));
2525
_creators.Add(AnnotationType.NoIndent.ToString().ToUpperInvariant(), typeof(NoIndentAnnotation));
2626
_creators.Add(AnnotationType.Interface.ToString().ToUpperInvariant(), typeof(InterfaceAnnotation));
27-
_creators.Add(AnnotationType.Description.ToString().ToUpperInvariant(), typeof (DescriptionAnnotation));
27+
_creators.Add(AnnotationType.MemberDescription.ToString().ToUpperInvariant(), typeof (DescriptionAnnotation));
2828
_creators.Add(AnnotationType.PredeclaredId.ToString().ToUpperInvariant(), typeof(PredeclaredIdAnnotation));
2929
_creators.Add(AnnotationType.DefaultMember.ToString().ToUpperInvariant(), typeof(DefaultMemberAnnotation));
3030
_creators.Add(AnnotationType.Enumerator.ToString().ToUpperInvariant(), typeof(EnumeratorMemberAnnotation));

RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
namespace RubberduckTests.Annotations
66
{
77
[TestFixture]
8+
[Category("Annotations")]
89
public class AttributeAnnotationProviderTests
910
{
1011
[Test]
@@ -57,13 +58,13 @@ public void ModuleAttributeAnnotationReturnsSpecializedAnnotationsWhereApplicabl
5758
}
5859

5960
[TestCase("VB_ProcData.VB_Invoke_Func", @"A\n14", AnnotationType.ExcelHotKey, "A")]
60-
[TestCase("VB_Description", "\"SomeDescription\"", AnnotationType.Description, "\"SomeDescription\"")]
61+
[TestCase("VB_Description", "\"SomeDescription\"", AnnotationType.MemberDescription, "\"SomeDescription\"")]
6162
[TestCase("VB_VarDescription", "\"SomeDescription\"", AnnotationType.VariableDescription, "\"SomeDescription\"")]
6263
[TestCase("VB_UserMemId", "0", AnnotationType.DefaultMember)]
6364
[TestCase("VB_UserMemId", "-4", AnnotationType.Enumerator)]
64-
public void MemberAttributeAnnotationReturnsSpecializedAnnotationsWhereApplicable(string attributeName, string annotationValue, AnnotationType expectedAnnotationType, string expectedValue = null)
65+
public void MemberAttributeAnnotationReturnsSpecializedAnnotationsWhereApplicable(string attributeName, string attributeValue, AnnotationType expectedAnnotationType, string expectedValue = null)
6566
{
66-
var attributeValues = new List<string> { annotationValue };
67+
var attributeValues = new List<string> { attributeValue };
6768
var expectedValues = expectedValue != null
6869
? new List<string> { expectedValue }
6970
: new List<string>();

RubberduckTests/Grammar/AnnotationTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -139,7 +139,7 @@ public void MemberAttributeAnnotation_TypeIsMemberAttribute()
139139
public void DescriptionAnnotation_TypeIsDescription()
140140
{
141141
var annotation = new DescriptionAnnotation(new QualifiedSelection(), null, new[] { "Desc"});
142-
Assert.AreEqual(AnnotationType.Description, annotation.AnnotationType);
142+
Assert.AreEqual(AnnotationType.MemberDescription, annotation.AnnotationType);
143143
}
144144

145145
[Category("Grammar")]

RubberduckTests/PostProcessing/AnnotationUpdaterTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -728,7 +728,7 @@ End Sub
728728
var fooDeclaration = state.DeclarationFinder
729729
.UserDeclarations(DeclarationType.Procedure)
730730
.First(decl => decl.IdentifierName == "Foo");
731-
var annotationToUpdate = fooDeclaration.Annotations.First(annotation => annotation.AnnotationType == AnnotationType.Description);
731+
var annotationToUpdate = fooDeclaration.Annotations.First(annotation => annotation.AnnotationType == AnnotationType.MemberDescription);
732732
var annotationUpdater = new AnnotationUpdater();
733733

734734
annotationUpdater.UpdateAnnotation(rewriteSession, annotationToUpdate, newAnnotation, newAnnotationValues);

0 commit comments

Comments
 (0)