Skip to content

Commit 604e692

Browse files
committed
Expand prototype DeclarationType options
Expanded the acceptable prototypes to include DeclarationTypes having flags Function and Constant in addition to Variable and UserDefinedTypeMember.
1 parent 9185e67 commit 604e692

File tree

7 files changed

+342
-106
lines changed

7 files changed

+342
-106
lines changed

Rubberduck.Refactorings/Common/CodeBuilder.cs

Lines changed: 55 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
1-
using Rubberduck.Common;
2-
using Rubberduck.Parsing;
1+
using Rubberduck.Parsing;
32
using Rubberduck.Parsing.Grammar;
43
using Rubberduck.Parsing.Symbols;
54
using System;
@@ -35,7 +34,7 @@ string BuildMemberBlockFromPrototype(ModuleBodyElementDeclaration declaration,
3534
/// <summary>
3635
/// Generates a Property Get codeblock based on the prototype declaration
3736
/// </summary>
38-
/// <param name="prototype">VariableDeclaration or UserDefinedTypeMember</param>
37+
/// <param name="prototype">DeclarationType with flags: Variable, Constant, UserDefinedTypeMember, or Function</param>
3938
/// <param name="content">Member body content. Formatting is the responsibility of the caller</param>
4039
/// <param name="parameterIdentifier">Defaults to '<paramref name="propertyIdentifier"/>Value' unless otherwise specified</param>
4140
bool TryBuildPropertyGetCodeBlock(Declaration prototype,
@@ -47,7 +46,7 @@ bool TryBuildPropertyGetCodeBlock(Declaration prototype,
4746
/// <summary>
4847
/// Generates a Property Let codeblock based on the prototype declaration
4948
/// </summary>
50-
/// <param name="prototype">VariableDeclaration or UserDefinedTypeMember</param>
49+
/// <param name="prototype">DeclarationType with flags: Variable, Constant, UserDefinedTypeMember, or Function</param>
5150
/// <param name="content">Member body content. Formatting is the responsibility of the caller</param>
5251
/// <param name="parameterIdentifier">Defaults to '<paramref name="propertyIdentifier"/>Value' unless otherwise specified</param>
5352
bool TryBuildPropertyLetCodeBlock(Declaration prototype,
@@ -60,7 +59,7 @@ bool TryBuildPropertyLetCodeBlock(Declaration prototype,
6059
/// <summary>
6160
/// Generates a Property Set codeblock based on the prototype declaration
6261
/// </summary>
63-
/// <param name="prototype">VariableDeclaration or UserDefinedTypeMember</param>
62+
/// <param name="prototype">DeclarationType with flags: Variable, Constant, UserDefinedTypeMember, or Function</param>
6463
/// <param name="content">Member body content. Formatting is the responsibility of the caller</param>
6564
/// <param name="parameterIdentifier">Defaults to '<paramref name="propertyIdentifier"/>Value' unless otherwise specified</param>
6665
bool TryBuildPropertySetCodeBlock(Declaration prototype,
@@ -71,16 +70,20 @@ bool TryBuildPropertySetCodeBlock(Declaration prototype,
7170
string parameterIdentifier = null);
7271

7372
/// <summary>
74-
/// Generates a UserDefinedType (UDT) declaration using a <c>VariableDeclaration</c> as the prototype for
75-
/// creating the UserDefinedTypeMember.
73+
/// Generates a UserDefinedType (UDT) declaration using the prototype declarations for
74+
/// creating the UserDefinedTypeMember declarations.
7675
/// </summary>
77-
/// <remarks> At least one <c>VariableDeclaration</c> must be provided and
78-
/// all <c>UDTMemberIdentifiers</c> must be unique
76+
/// <remarks>No validation or conflict analysis is applied to the identifiers.
7977
/// </remarks>
80-
/// <param name="memberPrototypes">Collection of prototypes and their required identifier. Must have 1 or more elements</param>
81-
string BuildUserDefinedTypeDeclaration(string udtIdentifier, IEnumerable<(VariableDeclaration Field, string UDTMemberIdentifier)> memberPrototypes, Accessibility accessibility = Accessibility.Private);
78+
/// <param name="memberPrototypes">DeclarationTypes with flags: Variable, Constant, UserDefinedTypeMember, or Function</param>
79+
bool TryBuildUserDefinedTypeDeclaration(string udtIdentifier, IEnumerable<(Declaration Prototype, string UDTMemberIdentifier)> memberPrototypes, out string declaration, Accessibility accessibility = Accessibility.Private);
8280

83-
string UDTMemberDeclaration(string identifier, string typeName, string indention = null);
81+
/// <summary>
82+
/// Generates a <c>UserDefinedTypeMember</c> declaration expression based on the prototype declaration
83+
/// </summary>
84+
/// <param name="prototype">DeclarationType with flags: Variable, Constant, UserDefinedTypeMember, or Function</param>
85+
/// <param name="indentation">Defaults is 4 spaces</param>
86+
bool TryBuildUDTMemberDeclaration(string identifier, Declaration prototype, out string declaration, string indentation = null);
8487
}
8588

8689
public class CodeBuilder : ICodeBuilder
@@ -119,7 +122,7 @@ private bool TryBuildPropertyBlockFromTarget<T>(T prototype, DeclarationType let
119122
throw new ArgumentException();
120123
}
121124

122-
if (!(prototype is VariableDeclaration || prototype.DeclarationType.HasFlag(DeclarationType.UserDefinedTypeMember)))
125+
if (!IsValidPrototypeDeclarationType(prototype.DeclarationType))
123126
{
124127
return false;
125128
}
@@ -243,47 +246,64 @@ private static string EndStatement(DeclarationType declarationType)
243246
private static string TypeToken(DeclarationType declarationType)
244247
=> _declarationTypeTokens[declarationType].TypeToken;
245248

246-
public string BuildUserDefinedTypeDeclaration(string udtIdentifier, IEnumerable<(VariableDeclaration Field, string UDTMemberIdentifier)> memberPrototypes, Accessibility accessibility = Accessibility.Private)
249+
public bool TryBuildUserDefinedTypeDeclaration(string udtIdentifier, IEnumerable<(Declaration Prototype, string UDTMemberIdentifier)> memberPrototypes, out string declaration, Accessibility accessibility = Accessibility.Private)
247250
{
248-
if (!memberPrototypes.Any())
251+
if (udtIdentifier is null
252+
||!memberPrototypes.Any()
253+
|| memberPrototypes.Any(p => p.Prototype is null || p.UDTMemberIdentifier is null)
254+
|| memberPrototypes.Any(mp => !IsValidPrototypeDeclarationType(mp.Prototype.DeclarationType)))
249255
{
250-
throw new ArgumentOutOfRangeException();
256+
declaration = string.Empty;
257+
return false;
251258
}
252259

253-
var hasDuplicateMemberNames = memberPrototypes.Select(pr => pr.UDTMemberIdentifier.ToUpperInvariant())
254-
.GroupBy(uc => uc).Any(g => g.Count() > 1);
255-
if (hasDuplicateMemberNames)
256-
{
257-
throw new ArgumentException();
258-
}
260+
var blockLines = memberPrototypes
261+
.Select(m => BuildUDTMemberDeclaration(m.UDTMemberIdentifier, m.Prototype))
262+
.ToList();
259263

260-
var newMemberTokenPairs = memberPrototypes.Select(m => (GetDeclarationIdentifier(m.Field, m.UDTMemberIdentifier), m.Field.AsTypeName))
261-
.Cast<(string Identifier, string AsTypeName)>();
264+
blockLines.Insert(0, $"{accessibility.TokenString()} {Tokens.Type} {udtIdentifier}");
262265

263-
var blockLines = new List<string>();
266+
blockLines.Add($"{Tokens.End} {Tokens.Type}");
264267

265-
blockLines.Add($"{accessibility.TokenString()} {Tokens.Type} {udtIdentifier}");
268+
declaration = string.Join(Environment.NewLine, blockLines);
269+
return true;
270+
}
266271

267-
blockLines.AddRange(newMemberTokenPairs.Select(m => UDTMemberDeclaration(m.Identifier, m.AsTypeName)));
272+
public bool TryBuildUDTMemberDeclaration(string udtMemberIdentifier, Declaration prototype, out string declaration, string indentation = null)
273+
{
274+
declaration = string.Empty;
268275

269-
blockLines.Add($"{Tokens.End} {Tokens.Type}");
276+
if (udtMemberIdentifier is null
277+
|| prototype is null
278+
|| !IsValidPrototypeDeclarationType(prototype.DeclarationType))
279+
{
280+
return false;
281+
}
270282

271-
return string.Join(Environment.NewLine, blockLines);
283+
declaration = BuildUDTMemberDeclaration(udtMemberIdentifier, prototype, indentation);
284+
return true;
272285
}
273286

274-
private static string GetDeclarationIdentifier(Declaration field, string udtMemberIdentifier)
287+
private static string BuildUDTMemberDeclaration(string udtMemberIdentifier, Declaration prototype, string indentation = null)
275288
{
276-
if (field.IsArray)
289+
var identifierExpression = udtMemberIdentifier;
290+
if (prototype.IsArray)
277291
{
278-
return field.Context.TryGetChildContext<VBAParser.SubscriptsContext>(out var ctxt)
292+
identifierExpression = prototype.Context.TryGetChildContext<VBAParser.SubscriptsContext>(out var ctxt)
279293
? $"{udtMemberIdentifier}({ctxt.GetText()})"
280294
: $"{udtMemberIdentifier}()";
281295
}
282-
return udtMemberIdentifier;
296+
297+
return $"{indentation ?? " "}{identifierExpression} {Tokens.As} {prototype.AsTypeName}";
283298
}
284299

285-
public string UDTMemberDeclaration(string identifier, string typeName, string indention = null)
286-
=> $"{indention ?? " "}{identifier} {Tokens.As} {typeName}";
300+
private static bool IsValidPrototypeDeclarationType(DeclarationType declarationType)
301+
{
302+
return declarationType.HasFlag(DeclarationType.Variable)
303+
|| declarationType.HasFlag(DeclarationType.UserDefinedTypeMember)
304+
|| declarationType.HasFlag(DeclarationType.Constant)
305+
|| declarationType.HasFlag(DeclarationType.Function);
306+
}
287307

288308
private static bool IsEnumField(VariableDeclaration declaration)
289309
=> IsMemberVariable(declaration)

Rubberduck.Refactorings/CreateUDTMember/CreateUDTMemberModel.cs

Lines changed: 19 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -7,25 +7,30 @@ namespace Rubberduck.Refactorings.CreateUDTMember
77
{
88
public class CreateUDTMemberModel : IRefactoringModel
99
{
10-
private Dictionary<Declaration, List<(VariableDeclaration prototype, string UDTMemberIdentifier)>> _targets { get; } = new Dictionary<Declaration, List<(VariableDeclaration, string)>>();
10+
private Dictionary<Declaration, List<(Declaration prototype, string UDTMemberIdentifier)>> _targets { get; } = new Dictionary<Declaration, List<(Declaration, string)>>();
1111

1212
public CreateUDTMemberModel()
1313
{ }
1414

15-
public CreateUDTMemberModel(Declaration userDefinedType, IEnumerable<(VariableDeclaration prototype, string UserDefinedTypeMemberIdentifier)> conversionModels)
15+
public CreateUDTMemberModel(Declaration userDefinedType, IEnumerable<(Declaration prototype, string UserDefinedTypeMemberIdentifier)> conversionModels)
1616
{
17-
foreach ((VariableDeclaration prototype, string UDTMemberIdentifier) in conversionModels)
17+
if (conversionModels.Any(cm => !IsValidPrototypeDeclarationType(cm.prototype.DeclarationType)))
18+
{
19+
throw new ArgumentException();
20+
}
21+
22+
foreach ((Declaration prototype, string UDTMemberIdentifier) in conversionModels)
1823
{
1924
AssignPrototypeToUserDefinedType(userDefinedType, prototype, UDTMemberIdentifier);
2025
}
2126
}
2227

2328
public IReadOnlyCollection<Declaration> UserDefinedTypeTargets => _targets.Keys;
2429

25-
public IEnumerable<(VariableDeclaration prototype, string userDefinedTypeMemberIdentifier)> this[Declaration udt]
30+
public IEnumerable<(Declaration prototype, string userDefinedTypeMemberIdentifier)> this[Declaration udt]
2631
=> _targets[udt].Select(pr => (pr.prototype, pr.UDTMemberIdentifier));
2732

28-
private void AssignPrototypeToUserDefinedType(Declaration udt, VariableDeclaration prototype, string udtMemberIdentifierName = null)
33+
private void AssignPrototypeToUserDefinedType(Declaration udt, Declaration prototype, string udtMemberIdentifierName = null)
2934
{
3035
if (!udt.DeclarationType.HasFlag(DeclarationType.UserDefinedType))
3136
{
@@ -34,7 +39,7 @@ private void AssignPrototypeToUserDefinedType(Declaration udt, VariableDeclarati
3439

3540
if (!(_targets.TryGetValue(udt, out var memberPrototypes)))
3641
{
37-
_targets.Add(udt, new List<(VariableDeclaration, string)>());
42+
_targets.Add(udt, new List<(Declaration, string)>());
3843
}
3944
else
4045
{
@@ -50,5 +55,13 @@ private void AssignPrototypeToUserDefinedType(Declaration udt, VariableDeclarati
5055

5156
_targets[udt].Add((prototype, udtMemberIdentifierName ?? prototype.IdentifierName));
5257
}
58+
59+
private static bool IsValidPrototypeDeclarationType(DeclarationType declarationType)
60+
{
61+
return declarationType.HasFlag(DeclarationType.Variable)
62+
|| declarationType.HasFlag(DeclarationType.UserDefinedTypeMember)
63+
|| declarationType.HasFlag(DeclarationType.Constant)
64+
|| declarationType.HasFlag(DeclarationType.Function);
65+
}
5366
}
5467
}

Rubberduck.Refactorings/CreateUDTMember/CreateUDTMemberRefactoringAction.cs

Lines changed: 22 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -27,19 +27,24 @@ public override void Refactor(CreateUDTMemberModel model, IRewriteSession rewrit
2727
throw new ArgumentException();
2828
}
2929

30+
var rewriter = rewriteSession.CheckOutModuleRewriter(model.UserDefinedTypeTargets.First().QualifiedModuleName);
31+
3032
foreach (var udt in model.UserDefinedTypeTargets)
3133
{
32-
InsertNewMembersBlock(BuildNewMembersBlock(udt, model[udt]),
33-
GetInsertionIndex(udt.Context as VBAParser.UdtDeclarationContext),
34-
rewriteSession.CheckOutModuleRewriter(udt.QualifiedModuleName));
34+
var newMembersBlock = BuildNewMembersBlock(udt, model);
35+
36+
var insertionIndex = (udt.Context as VBAParser.UdtDeclarationContext)
37+
.END_TYPE().Symbol.TokenIndex - 1;
38+
39+
rewriter.InsertBefore(insertionIndex, $"{newMembersBlock}");
3540
}
3641
}
3742

38-
private string BuildNewMembersBlock(Declaration udt, IEnumerable<(VariableDeclaration Field, string UDTMemberIdentifier)> newMemberPairs)
43+
private string BuildNewMembersBlock(Declaration udt, CreateUDTMemberModel model)
3944
{
4045
var indentation = DetermineIndentationFromLastMember(udt);
4146

42-
var newMemberStatements = GenerateUserDefinedMemberDeclarations(newMemberPairs, indentation);
47+
var newMemberStatements = GenerateUserDefinedMemberDeclarations(model[udt], indentation);
4348

4449
return string.Concat(newMemberStatements);
4550
}
@@ -55,13 +60,17 @@ private string DetermineIndentationFromLastMember(Declaration udt)
5560
return endOfStatementContextPrototype.GetText();
5661
}
5762

58-
private IEnumerable<string> GenerateUserDefinedMemberDeclarations(IEnumerable<(VariableDeclaration Field, string UDTMemberIdentifier)> newMemberPairs, string indentation)
59-
=> newMemberPairs.Select(pr => _codeBuilder.UDTMemberDeclaration(pr.UDTMemberIdentifier, pr.Field.AsTypeName, indentation));
60-
61-
private static void InsertNewMembersBlock(string newMembersBlock, int insertionIndex, IModuleRewriter rewriter)
62-
=> rewriter.InsertBefore(insertionIndex, $"{newMembersBlock}");
63-
64-
private int GetInsertionIndex(VBAParser.UdtDeclarationContext udtContext)
65-
=> udtContext.END_TYPE().Symbol.TokenIndex - 1;
63+
private IEnumerable<string> GenerateUserDefinedMemberDeclarations(IEnumerable<(Declaration Prototype, string UDTMemberIdentifier)> newMemberPairs, string indentation)
64+
{
65+
var declarations = new List<string>();
66+
foreach (var (Prototype, UDTMemberIdentifier) in newMemberPairs)
67+
{
68+
if (_codeBuilder.TryBuildUDTMemberDeclaration(UDTMemberIdentifier, Prototype, out var declaration, indentation))
69+
{
70+
declarations.Add(declaration);
71+
}
72+
}
73+
return declarations;
74+
}
6675
}
6776
}

Rubberduck.Refactorings/EncapsulateField/EncapsulateFieldInsertNewCode/EncapsulateFieldCodeBuilder.cs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -78,9 +78,11 @@ public string BuildUserDefinedTypeDeclaration(IObjectStateUDT objectStateUDT, IE
7878
var selected = candidates.Where(c => c.EncapsulateFlag);
7979

8080
var newUDTMembers = selected
81-
.Select(m => (m.Declaration as VariableDeclaration, m.BackingIdentifier));
81+
.Select(m => (m.Declaration, m.BackingIdentifier));
8282

83-
return _codeBuilder.BuildUserDefinedTypeDeclaration(objectStateUDT.AsTypeName, newUDTMembers);
83+
_codeBuilder.TryBuildUserDefinedTypeDeclaration(objectStateUDT.AsTypeName, newUDTMembers, out var declaration);
84+
85+
return declaration ?? string.Empty;
8486
}
8587

8688
public string BuildObjectStateFieldDeclaration(IObjectStateUDT objectStateUDT)

Rubberduck.Refactorings/EncapsulateField/EncapsulateFieldUseBackingUDTMember/EncapsulateFieldUseBackingUDTMemberRefactoringAction.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -65,7 +65,7 @@ private void ModifyFields(EncapsulateFieldUseBackingUDTMemberModel encapsulateFi
6565
if (encapsulateFieldModel.ObjectStateUDTField.IsExistingDeclaration)
6666
{
6767
var conversionPairs = encapsulateFieldModel.SelectedFieldCandidates
68-
.Select(c => (c.Declaration as VariableDeclaration, c.BackingIdentifier));
68+
.Select(c => (c.Declaration, c.BackingIdentifier));
6969

7070
var model = new CreateUDTMemberModel(encapsulateFieldModel.ObjectStateUDTField.AsTypeDeclaration, conversionPairs);
7171
_createUDTMemberRefactoringAction.Refactor(model, rewriteSession);

0 commit comments

Comments
 (0)