Skip to content

Commit da7acb4

Browse files
beachasaurus-rexVogel612
authored andcommitted
added ExcelHotKeyAnnotation class.
added test case for new attribute.
1 parent 8531cfb commit da7acb4

File tree

3 files changed

+27
-1
lines changed

3 files changed

+27
-1
lines changed

Rubberduck.Parsing/Annotations/AnnotationType.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,9 @@ public enum AnnotationType
7272
ModuleAttribute = 1 << 20 | Attribute | ModuleAnnotation,
7373
MemberAttribute = 1 << 21 | Attribute | MemberAnnotation | VariableAnnotation,
7474
[FlexibleAttributeValueAnnotation("VB_VarDescription", 1)]
75-
VariableDescription = 1 << 13 | Attribute | VariableAnnotation
75+
VariableDescription = 1 << 13 | Attribute | VariableAnnotation,
76+
[FlexibleAttributeValueAnnotation("VB_ProcData.VB_Invoke_Func", 1)]
77+
ExcelHotKey = 1 << 16 | Attribute | MemberAnnotation
7678
}
7779

7880
[AttributeUsage(AttributeTargets.Field)]
Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,23 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using Rubberduck.Parsing.Grammar;
5+
using Rubberduck.VBEditor;
6+
7+
namespace Rubberduck.Parsing.Annotations
8+
{
9+
public sealed class ExcelHotKeyAnnotation : FlexibleAttributeValueAnnotationBase
10+
{
11+
public ExcelHotKeyAnnotation(AnnotationType annotationType, QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable<string> attributeValues) :
12+
base(annotationType, qualifiedSelection, context, GetHotKeyAttributeValue(attributeValues))
13+
{ }
14+
15+
private static IEnumerable<string> GetHotKeyAttributeValue(IEnumerable<string> attributeValues) =>
16+
attributeValues.Take(1).Select(StripStringLiteralQuotes).Select(v => v[0] + @"\n14").ToList();
17+
18+
private static string StripStringLiteralQuotes(string value) =>
19+
value.StartsWith("\"") && value.EndsWith("\"") && value.Length > 2
20+
? value.Substring(1, value.Length - 2)
21+
: value;
22+
}
23+
}

RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,7 @@ public void ModuleAttributeAnnotationReturnsSpecializedAnnotationsWhereApplicabl
5656
AssertEqual(expectedValues, actualValues);
5757
}
5858

59+
[TestCase("VB_ProcData.VB_Invoke_Func", "A", AnnotationType.ExcelHotKey, @"A\n14")]
5960
[TestCase("VB_Description", "\"SomeDescription\"", AnnotationType.Description, "\"SomeDescription\"")]
6061
[TestCase("VB_VarDescription", "\"SomeDescription\"", AnnotationType.VariableDescription, "\"SomeDescription\"")]
6162
[TestCase("VB_UserMemId", "0", AnnotationType.DefaultMember)]

0 commit comments

Comments
 (0)