Skip to content

Commit 0b97908

Browse files
authored
Merge pull request #5101 from Vogel612/feature/excel-hotkey-annotation
Add Excel Hotkey Annotation, Closes #4959
2 parents 8531cfb + 870cbdf commit 0b97908

6 files changed

+44
-18
lines changed

Rubberduck.Parsing/Annotations/AnnotationType.cs

+3-1
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)]

Rubberduck.Parsing/Annotations/AttributeAnnotationProvider.cs

+5
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,11 @@ public class AttributeAnnotationProvider : IAttributeAnnotationProvider
3333
var flexibleValueAttributeAnnotation = FirstMatchingFlexibleAttributeValueAnnotation(annotationTypes, attributeName, attributeValues.Count);
3434
if (flexibleValueAttributeAnnotation != default)
3535
{
36+
// FIXME special cased bodge for ExcelHotKeyAnnotation to deal with the value transformation:
37+
if (flexibleValueAttributeAnnotation == AnnotationType.ExcelHotKey)
38+
{
39+
return (flexibleValueAttributeAnnotation, attributeValues.Select(keySpec => keySpec.Substring(0, 1)).ToList());
40+
}
3641
return (flexibleValueAttributeAnnotation, attributeValues);
3742
}
3843

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(QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable<string> annotationParameterValues) :
12+
base(AnnotationType.ExcelHotKey, qualifiedSelection, context, GetHotKeyAttributeValue(annotationParameterValues))
13+
{ }
14+
15+
private static IEnumerable<string> GetHotKeyAttributeValue(IEnumerable<string> parameters) =>
16+
parameters.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+
}

Rubberduck.Parsing/Annotations/FlexibleAttributeValueAnnotationBase.cs

+8-15
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

+1
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@ public VBAParserAnnotationFactory()
3333
_creators.Add(AnnotationType.ModuleAttribute.ToString().ToUpperInvariant(), typeof(ModuleAttributeAnnotation));
3434
_creators.Add(AnnotationType.MemberAttribute.ToString().ToUpperInvariant(), typeof(MemberAttributeAnnotation));
3535
_creators.Add(AnnotationType.ModuleDescription.ToString().ToUpperInvariant(), typeof(ModuleDescriptionAnnotation));
36+
_creators.Add(AnnotationType.ExcelHotKey.ToString().ToUpperInvariant(), typeof(ExcelHotKeyAnnotation));
3637
}
3738

3839
public IAnnotation Create(VBAParser.AnnotationContext context, QualifiedSelection qualifiedSelection)

RubberduckTests/Annotations/AttributeAnnotationProviderTests.cs

+4-2
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]
@@ -56,13 +57,14 @@ public void ModuleAttributeAnnotationReturnsSpecializedAnnotationsWhereApplicabl
5657
AssertEqual(expectedValues, actualValues);
5758
}
5859

60+
[TestCase("VB_ProcData.VB_Invoke_Func", @"A\n14", AnnotationType.ExcelHotKey, "A")]
5961
[TestCase("VB_Description", "\"SomeDescription\"", AnnotationType.Description, "\"SomeDescription\"")]
6062
[TestCase("VB_VarDescription", "\"SomeDescription\"", AnnotationType.VariableDescription, "\"SomeDescription\"")]
6163
[TestCase("VB_UserMemId", "0", AnnotationType.DefaultMember)]
6264
[TestCase("VB_UserMemId", "-4", AnnotationType.Enumerator)]
63-
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)
6466
{
65-
var attributeValues = new List<string> { annotationValue };
67+
var attributeValues = new List<string> { attributeValue };
6668
var expectedValues = expectedValue != null
6769
? new List<string> { expectedValue }
6870
: new List<string>();

0 commit comments

Comments
 (0)