Skip to content

Commit 811448b

Browse files
committed
Add AddOrUpdateAttribute to AttributesUpdater
1 parent 97bdd9a commit 811448b

File tree

3 files changed

+322
-29
lines changed

3 files changed

+322
-29
lines changed

Rubberduck.Parsing/VBA/AttributesUpdater.cs

Lines changed: 75 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@
88
using Rubberduck.Parsing.Rewriter;
99
using Rubberduck.Parsing.Symbols;
1010
using Rubberduck.Parsing.VBA.Parsing;
11+
using Rubberduck.VBEditor;
1112

1213
namespace Rubberduck.Parsing.VBA
1314
{
@@ -72,38 +73,50 @@ public void AddAttribute(IRewriteSession rewriteSession, Declaration declaration
7273
var rewriter = rewriteSession.CheckOutModuleRewriter(declaration.QualifiedModuleName);
7374
if (declaration.DeclarationType.HasFlag(DeclarationType.Module))
7475
{
75-
var moduleParseTree = (ParserRuleContext)_parseTreeProvider.GetParseTree(declaration.QualifiedModuleName, CodeKind.AttributesCode);
76-
var lastModuleAttribute = moduleParseTree.GetDescendents<VBAParser.ModuleAttributesContext>()
77-
.Where(moduleAttributes => moduleAttributes.attributeStmt() != null)
78-
.SelectMany(moduleAttributes => moduleAttributes.attributeStmt())
79-
.OrderBy(moduleAttribute => moduleAttribute.stop.TokenIndex)
80-
.LastOrDefault();
81-
if (lastModuleAttribute == null)
82-
{
83-
//This should never happen for a real module.
84-
var codeToInsert = $"Attribute {attribute} = {AttributeValuesText(values)}{Environment.NewLine}";
85-
rewriter.InsertBefore(0, codeToInsert);
86-
}
87-
else
88-
{
89-
var codeToInsert = $"{Environment.NewLine}Attribute {attribute} = {AttributeValuesText(values)}";
90-
rewriter.InsertAfter(lastModuleAttribute.stop.TokenIndex, codeToInsert);
91-
}
76+
var codeToAdd = $"Attribute {attribute} = {AttributeValuesText(values)}";
77+
InsertAfterLastModuleAttribute(rewriter, declaration.QualifiedModuleName, codeToAdd);
9278
}
9379
else
9480
{
95-
var attributesContext = declaration.AttributesPassContext;
96-
var firstEndOfLineInMember = attributesContext.GetDescendent<VBAParser.EndOfLineContext>();
97-
if (firstEndOfLineInMember == null)
98-
{
99-
var codeToInsert = $"{Environment.NewLine}Attribute {attribute} = {AttributeValuesText(values)}";
100-
rewriter.InsertAfter(declaration.AttributesPassContext.Stop.TokenIndex, codeToInsert);
101-
}
102-
else
103-
{
104-
var codeToInsert = $"Attribute {attribute} = {AttributeValuesText(values)}{Environment.NewLine}";
105-
rewriter.InsertAfter(firstEndOfLineInMember.Stop.TokenIndex, codeToInsert);
106-
}
81+
var codeToAdd = $"Attribute {attribute} = {AttributeValuesText(values)}";
82+
InsertAfterFirstEolOfAttributeContext(rewriter, declaration, codeToAdd);
83+
}
84+
}
85+
86+
private void InsertAfterLastModuleAttribute(IModuleRewriter rewriter, QualifiedModuleName module, string codeToAdd)
87+
{
88+
var moduleParseTree = (ParserRuleContext)_parseTreeProvider.GetParseTree(module, CodeKind.AttributesCode);
89+
var lastModuleAttribute = moduleParseTree.GetDescendents<VBAParser.ModuleAttributesContext>()
90+
.Where(moduleAttributes => moduleAttributes.attributeStmt() != null)
91+
.SelectMany(moduleAttributes => moduleAttributes.attributeStmt())
92+
.OrderBy(moduleAttribute => moduleAttribute.stop.TokenIndex)
93+
.LastOrDefault();
94+
if (lastModuleAttribute == null)
95+
{
96+
//This should never happen for a real module.
97+
var codeToInsert = codeToAdd + Environment.NewLine;
98+
rewriter.InsertBefore(0, codeToInsert);
99+
}
100+
else
101+
{
102+
var codeToInsert = Environment.NewLine + codeToAdd;
103+
rewriter.InsertAfter(lastModuleAttribute.stop.TokenIndex, codeToInsert);
104+
}
105+
}
106+
107+
private void InsertAfterFirstEolOfAttributeContext(IModuleRewriter rewriter, Declaration declaration, string codeToAdd)
108+
{
109+
var attributesContext = declaration.AttributesPassContext;
110+
var firstEndOfLineInMember = attributesContext.GetDescendent<VBAParser.EndOfLineContext>();
111+
if (firstEndOfLineInMember == null)
112+
{
113+
var codeToInsert = Environment.NewLine + codeToAdd;
114+
rewriter.InsertAfter(declaration.AttributesPassContext.Stop.TokenIndex, codeToInsert);
115+
}
116+
else
117+
{
118+
var codeToInsert = codeToAdd + Environment.NewLine;
119+
rewriter.InsertAfter(firstEndOfLineInMember.Stop.TokenIndex, codeToInsert);
107120
}
108121
}
109122

@@ -223,5 +236,38 @@ private static void UpdateAttributeValues(IModuleRewriter rewriter, AttributeNod
223236

224237
rewriter.Replace(new Interval(firstIndexToReplace, lastIndexToReplace), replacementText);
225238
}
239+
240+
public void AddOrUpdateAttribute(
241+
IRewriteSession rewriteSession,
242+
Declaration declaration,
243+
string attribute,
244+
IReadOnlyList<string> values)
245+
{
246+
var attributeNodes = ApplicableAttributeNodes(declaration, attribute);
247+
248+
if (!attributeNodes.Any())
249+
{
250+
AddAttribute(rewriteSession, declaration, attribute, values);
251+
return;
252+
}
253+
254+
if (attribute.Equals("VB_Ext_Key"))
255+
{
256+
var newKey = values.First();
257+
var matchingExtKeyAttribute = attributeNodes.FirstOrDefault(node => newKey.Equals(node.Values.FirstOrDefault(), StringComparison.InvariantCultureIgnoreCase));
258+
259+
if (matchingExtKeyAttribute == null)
260+
{
261+
AddAttribute(rewriteSession, declaration, attribute, values);
262+
return;
263+
}
264+
265+
var oldValues = matchingExtKeyAttribute.Values;
266+
UpdateAttribute(rewriteSession, declaration, attribute, values, oldValues);
267+
return;
268+
}
269+
270+
UpdateAttribute(rewriteSession, declaration, attribute, values);
271+
}
226272
}
227273
}

Rubberduck.Parsing/VBA/IAttributesUpdater.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,5 +9,6 @@ public interface IAttributesUpdater
99
void AddAttribute(IRewriteSession rewriteSession, Declaration declaration, string attribute, IReadOnlyList<string> values);
1010
void RemoveAttribute(IRewriteSession rewriteSession, Declaration declaration, string attribute, IReadOnlyList<string> values = null);
1111
void UpdateAttribute(IRewriteSession rewriteSession, Declaration declaration, string attribute, IReadOnlyList<string> newValues, IReadOnlyList<string> oldValues = null);
12+
void AddOrUpdateAttribute(IRewriteSession rewriteSession, Declaration declaration, string attribute, IReadOnlyList<string> values);
1213
}
1314
}

RubberduckTests/PostProcessing/AttributesUpdaterTests.cs

Lines changed: 246 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -849,6 +849,252 @@ End Sub
849849
Assert.AreEqual(expectedCode, actualCode);
850850
}
851851

852+
[Test]
853+
[Category("AttributesUpdater")]
854+
public void AddOrUpdateAttribute_UsualAttribute_NotThere_AddsAttribute()
855+
{
856+
const string inputCode =
857+
@"VERSION 1.0 CLASS
858+
BEGIN
859+
MultiUse = -1 'True
860+
END
861+
Attribute VB_Name = ""ClassKeys""
862+
Attribute VB_GlobalNameSpace = False
863+
Public Sub Foo(bar As String)
864+
bar = vbNullString
865+
End Sub
866+
";
867+
868+
const string expectedCode =
869+
@"VERSION 1.0 CLASS
870+
BEGIN
871+
MultiUse = -1 'True
872+
END
873+
Attribute VB_Name = ""ClassKeys""
874+
Attribute VB_GlobalNameSpace = False
875+
Attribute VB_Exposed = True
876+
Public Sub Foo(bar As String)
877+
bar = vbNullString
878+
End Sub
879+
";
880+
var attribute = "VB_Exposed";
881+
var newValues = new List<string> { "True" };
882+
883+
string actualCode;
884+
var (component, rewriteSession, state) = TestSetup(inputCode);
885+
using (state)
886+
{
887+
var moduleDeclaration = state.DeclarationFinder
888+
.UserDeclarations(DeclarationType.Module)
889+
.Single();
890+
var attributesUpdater = new AttributesUpdater(state);
891+
892+
attributesUpdater.AddOrUpdateAttribute(rewriteSession, moduleDeclaration, attribute, newValues);
893+
rewriteSession.TryRewrite();
894+
895+
actualCode = component.CodeModule.Content();
896+
}
897+
Assert.AreEqual(expectedCode, actualCode);
898+
}
899+
900+
[Test]
901+
[Category("AttributesUpdater")]
902+
public void AddOrUpdateAttribute_ExtKey_NotThere_AddsAttribute()
903+
{
904+
const string inputCode =
905+
@"VERSION 1.0 CLASS
906+
BEGIN
907+
MultiUse = -1 'True
908+
END
909+
Attribute VB_Name = ""ClassKeys""
910+
Attribute VB_GlobalNameSpace = False
911+
Public Sub Foo(bar As String)
912+
bar = vbNullString
913+
End Sub
914+
";
915+
916+
const string expectedCode =
917+
@"VERSION 1.0 CLASS
918+
BEGIN
919+
MultiUse = -1 'True
920+
END
921+
Attribute VB_Name = ""ClassKeys""
922+
Attribute VB_GlobalNameSpace = False
923+
Attribute VB_Ext_Key = ""MyKey"", ""MyValue""
924+
Public Sub Foo(bar As String)
925+
bar = vbNullString
926+
End Sub
927+
";
928+
var attribute = "VB_Ext_Key";
929+
var newValues = new List<string> { "\"MyKey\"", "\"MyValue\"" };
930+
931+
string actualCode;
932+
var (component, rewriteSession, state) = TestSetup(inputCode);
933+
using (state)
934+
{
935+
var moduleDeclaration = state.DeclarationFinder
936+
.UserDeclarations(DeclarationType.Module)
937+
.Single();
938+
var attributesUpdater = new AttributesUpdater(state);
939+
940+
attributesUpdater.AddOrUpdateAttribute(rewriteSession, moduleDeclaration, attribute, newValues);
941+
rewriteSession.TryRewrite();
942+
943+
actualCode = component.CodeModule.Content();
944+
}
945+
Assert.AreEqual(expectedCode, actualCode);
946+
}
947+
948+
[Test]
949+
[Category("AttributesUpdater")]
950+
public void AddOrUpdateAttribute_UsualAttribute_AlreadyThere_UpdatesAttribute()
951+
{
952+
const string inputCode =
953+
@"VERSION 1.0 CLASS
954+
BEGIN
955+
MultiUse = -1 'True
956+
END
957+
Attribute VB_Name = ""ClassKeys""
958+
Attribute VB_GlobalNameSpace = False
959+
Attribute VB_Exposed = False
960+
Public Sub Foo(bar As String)
961+
bar = vbNullString
962+
End Sub
963+
";
964+
965+
const string expectedCode =
966+
@"VERSION 1.0 CLASS
967+
BEGIN
968+
MultiUse = -1 'True
969+
END
970+
Attribute VB_Name = ""ClassKeys""
971+
Attribute VB_GlobalNameSpace = False
972+
Attribute VB_Exposed = True
973+
Public Sub Foo(bar As String)
974+
bar = vbNullString
975+
End Sub
976+
";
977+
var attribute = "VB_Exposed";
978+
var newValues = new List<string> { "True" };
979+
980+
string actualCode;
981+
var (component, rewriteSession, state) = TestSetup(inputCode);
982+
using (state)
983+
{
984+
var moduleDeclaration = state.DeclarationFinder
985+
.UserDeclarations(DeclarationType.Module)
986+
.Single();
987+
var attributesUpdater = new AttributesUpdater(state);
988+
989+
attributesUpdater.AddOrUpdateAttribute(rewriteSession, moduleDeclaration, attribute, newValues);
990+
rewriteSession.TryRewrite();
991+
992+
actualCode = component.CodeModule.Content();
993+
}
994+
Assert.AreEqual(expectedCode, actualCode);
995+
}
996+
997+
[Test]
998+
[Category("AttributesUpdater")]
999+
public void AddOrUpdateAttribute_ExtKey_KeyNotThere_AddsAttribute()
1000+
{
1001+
const string inputCode =
1002+
@"VERSION 1.0 CLASS
1003+
BEGIN
1004+
MultiUse = -1 'True
1005+
END
1006+
Attribute VB_Name = ""ClassKeys""
1007+
Attribute VB_GlobalNameSpace = False
1008+
Attribute VB_Ext_Key = ""AnotherKey"", ""MyValuse""
1009+
Public Sub Foo(bar As String)
1010+
bar = vbNullString
1011+
End Sub
1012+
";
1013+
1014+
const string expectedCode =
1015+
@"VERSION 1.0 CLASS
1016+
BEGIN
1017+
MultiUse = -1 'True
1018+
END
1019+
Attribute VB_Name = ""ClassKeys""
1020+
Attribute VB_GlobalNameSpace = False
1021+
Attribute VB_Ext_Key = ""AnotherKey"", ""MyValuse""
1022+
Attribute VB_Ext_Key = ""MyKey"", ""MyValue""
1023+
Public Sub Foo(bar As String)
1024+
bar = vbNullString
1025+
End Sub
1026+
";
1027+
var attribute = "VB_Ext_Key";
1028+
var newValues = new List<string> { "\"MyKey\"", "\"MyValue\"" };
1029+
1030+
string actualCode;
1031+
var (component, rewriteSession, state) = TestSetup(inputCode);
1032+
using (state)
1033+
{
1034+
var moduleDeclaration = state.DeclarationFinder
1035+
.UserDeclarations(DeclarationType.Module)
1036+
.Single();
1037+
var attributesUpdater = new AttributesUpdater(state);
1038+
1039+
attributesUpdater.AddOrUpdateAttribute(rewriteSession, moduleDeclaration, attribute, newValues);
1040+
rewriteSession.TryRewrite();
1041+
1042+
actualCode = component.CodeModule.Content();
1043+
}
1044+
Assert.AreEqual(expectedCode, actualCode);
1045+
}
1046+
1047+
[Test]
1048+
[Category("AttributesUpdater")]
1049+
public void AddOrUpdateAttribute_ExtKey_KeyAlreadyThere_UpdatesAttribute()
1050+
{
1051+
const string inputCode =
1052+
@"VERSION 1.0 CLASS
1053+
BEGIN
1054+
MultiUse = -1 'True
1055+
END
1056+
Attribute VB_Name = ""ClassKeys""
1057+
Attribute VB_GlobalNameSpace = False
1058+
Attribute VB_Ext_Key = ""AnotherKey"", ""MyValue""
1059+
Attribute VB_Ext_Key = ""MyKey"", ""AnotherValue""
1060+
Public Sub Foo(bar As String)
1061+
bar = vbNullString
1062+
End Sub
1063+
";
1064+
1065+
const string expectedCode =
1066+
@"VERSION 1.0 CLASS
1067+
BEGIN
1068+
MultiUse = -1 'True
1069+
END
1070+
Attribute VB_Name = ""ClassKeys""
1071+
Attribute VB_GlobalNameSpace = False
1072+
Attribute VB_Ext_Key = ""AnotherKey"", ""MyValue""
1073+
Attribute VB_Ext_Key = ""MyKey"", ""MyValue""
1074+
Public Sub Foo(bar As String)
1075+
bar = vbNullString
1076+
End Sub
1077+
";
1078+
var attribute = "VB_Ext_Key";
1079+
var newValues = new List<string> { "\"MyKey\"", "\"MyValue\"" };
1080+
1081+
string actualCode;
1082+
var (component, rewriteSession, state) = TestSetup(inputCode);
1083+
using (state)
1084+
{
1085+
var moduleDeclaration = state.DeclarationFinder
1086+
.UserDeclarations(DeclarationType.Module)
1087+
.Single();
1088+
var attributesUpdater = new AttributesUpdater(state);
1089+
1090+
attributesUpdater.AddOrUpdateAttribute(rewriteSession, moduleDeclaration, attribute, newValues);
1091+
rewriteSession.TryRewrite();
1092+
1093+
actualCode = component.CodeModule.Content();
1094+
}
1095+
Assert.AreEqual(expectedCode, actualCode);
1096+
}
1097+
8521098
private (IVBComponent component, IExecutableRewriteSession rewriteSession, RubberduckParserState state) TestSetup(string inputCode)
8531099
{
8541100
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component).Object;

0 commit comments

Comments
 (0)