Skip to content

Commit

Permalink
added ExcelHotKeyAnnotation class.
Browse files Browse the repository at this point in the history
added test case for new attribute.
  • Loading branch information
beachasaurus-rex committed May 19, 2019
1 parent 5bece81 commit 7f42db1
Show file tree
Hide file tree
Showing 3 changed files with 27 additions and 1 deletion.
4 changes: 3 additions & 1 deletion Rubberduck.Parsing/Annotations/AnnotationType.cs
Expand Up @@ -72,7 +72,9 @@ public enum AnnotationType
ModuleAttribute = 1 << 20 | Attribute | ModuleAnnotation,
MemberAttribute = 1 << 21 | Attribute | MemberAnnotation | VariableAnnotation,
[FlexibleAttributeValueAnnotation("VB_VarDescription", 1)]
VariableDescription = 1 << 13 | Attribute | VariableAnnotation
VariableDescription = 1 << 13 | Attribute | VariableAnnotation,
[FlexibleAttributeValueAnnotation("VB_ProcData.VB_Invoke_Func", 1)]
ExcelHotKey = 1 << 16 | Attribute | MemberAnnotation
}

[AttributeUsage(AttributeTargets.Field)]
Expand Down
23 changes: 23 additions & 0 deletions Rubberduck.Parsing/Annotations/ExcelHotKeyAnnotation.cs
@@ -0,0 +1,23 @@
using System;
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Parsing.Grammar;
using Rubberduck.VBEditor;

namespace Rubberduck.Parsing.Annotations
{
public sealed class ExcelHotKeyAnnotation : FlexibleAttributeValueAnnotationBase
{
public ExcelHotKeyAnnotation(AnnotationType annotationType, QualifiedSelection qualifiedSelection, VBAParser.AnnotationContext context, IEnumerable<string> attributeValues) :
base(annotationType, qualifiedSelection, context, GetHotKeyAttributeValue(attributeValues))
{ }

private static IEnumerable<string> GetHotKeyAttributeValue(IEnumerable<string> attributeValues) =>
attributeValues.Take(1).Select(StripStringLiteralQuotes).Select(v => v[0] + @"\n14").ToList();

private static string StripStringLiteralQuotes(string value) =>
value.StartsWith("\"") && value.EndsWith("\"") && value.Length > 2
? value.Substring(1, value.Length - 2)
: value;
}
}
Expand Up @@ -56,6 +56,7 @@ public void ModuleAttributeAnnotationReturnsSpecializedAnnotationsWhereApplicabl
AssertEqual(expectedValues, actualValues);
}

[TestCase("VB_ProcData.VB_Invoke_Func", "A", AnnotationType.ExcelHotKey, @"A\n14")]
[TestCase("VB_Description", "\"SomeDescription\"", AnnotationType.Description, "\"SomeDescription\"")]
[TestCase("VB_VarDescription", "\"SomeDescription\"", AnnotationType.VariableDescription, "\"SomeDescription\"")]
[TestCase("VB_UserMemId", "0", AnnotationType.DefaultMember)]
Expand Down

0 comments on commit 7f42db1

Please sign in to comment.