Skip to content

Commit 5f18ec3

Browse files
committed
Initial working version - all tests pass
Adds method and property generation code to extension classes. Allows removal two files/classes and duplicate function/content in EncapsulateField refactoring and ImplementInterface refactoring. Moves Encapsulate Field Declaration Extensions to RefactoringCommon folder to share content with ImplementInterface.
1 parent 09b7209 commit 5f18ec3

18 files changed

+457
-391
lines changed

Rubberduck.Refactorings/EncapsulateField/Extensions/DeclarationExtensions.cs renamed to Rubberduck.Refactorings/Common/DeclarationExtensions.cs

Lines changed: 35 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,12 @@
11
using Rubberduck.Parsing;
22
using Rubberduck.Parsing.Grammar;
33
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Refactorings.Common;
5+
using System;
46
using System.Collections.Generic;
57
using System.Linq;
68

7-
namespace Rubberduck.Refactorings.EncapsulateField.Extensions
9+
namespace Rubberduck.Refactorings.Common
810
{
911
public static class DeclarationExtensions
1012
{
@@ -43,5 +45,37 @@ public static bool IsDeclaredInList(this Declaration declaration)
4345
return declaration.Context.TryGetAncestor<VBAParser.VariableListStmtContext>(out var varList)
4446
&& varList.ChildCount > 1;
4547
}
48+
49+
public static string FieldToPropertyBlock(this Declaration variable, DeclarationType letSetGetType, string propertyIdentifier, string accessibility, string content, string parameterIdentifier = "value")
50+
{
51+
var template = string.Join(Environment.NewLine, accessibility + " {0}{1} {2}{3}", $"{content}", Tokens.End + " {0}", string.Empty);
52+
53+
var asType = variable.IsArray
54+
? $"{Tokens.Variant}"
55+
: variable.IsEnumField() && variable.AsTypeDeclaration.HasPrivateAccessibility()
56+
? $"{Tokens.Long}"
57+
: $"{variable.AsTypeName}";
58+
59+
var paramAccessibility = variable.IsUserDefinedType() ? Tokens.ByRef : Tokens.ByVal;
60+
61+
var letSetParameter = $"({paramAccessibility} {parameterIdentifier} {Tokens.As} {asType})";
62+
63+
if (letSetGetType.Equals(DeclarationType.PropertyGet))
64+
{
65+
return string.Format(template, Tokens.Property, $" {Tokens.Get}", $"{propertyIdentifier}()", $" {Tokens.As} {asType}");
66+
}
67+
68+
if (letSetGetType.Equals(DeclarationType.PropertyLet))
69+
{
70+
return string.Format(template, Tokens.Property, $" {Tokens.Let}", $"{propertyIdentifier}{letSetParameter}", string.Empty);
71+
}
72+
73+
if (letSetGetType.Equals(DeclarationType.PropertySet))
74+
{
75+
return string.Format(template, Tokens.Property, $" {Tokens.Set}", $"{propertyIdentifier}{letSetParameter}", string.Empty);
76+
}
77+
78+
return string.Empty;
79+
}
4680
}
4781
}
Lines changed: 171 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,171 @@
1+
using Rubberduck.Parsing.Grammar;
2+
using Rubberduck.Parsing.Symbols;
3+
using System;
4+
using System.Collections.Generic;
5+
using System.Linq;
6+
using System.Text;
7+
using System.Threading.Tasks;
8+
9+
namespace Rubberduck.Refactorings.Common
10+
{
11+
public static class ModuleBodyElementDeclarationExtensions
12+
{
13+
/// <summary>
14+
/// Returns ModuleBodyElementDeclaration signature with an ImprovedArgument list
15+
/// 1. Explicitly declares Property Let\Set value parameter as ByVal
16+
/// 2. Ensures UserDefined Type parameters are declared either explicitly or implicitly as ByRef
17+
/// </summary>
18+
/// <param name="declaration"></param>
19+
/// <returns></returns>
20+
public static string FullMemberSignature(this ModuleBodyElementDeclaration declaration,
21+
string accessibility = null,
22+
string newIdentifier = null)
23+
{
24+
var identifier = newIdentifier ?? declaration.IdentifierName;
25+
26+
var fullSignatureFormat = string.Empty;
27+
switch (declaration.Context)
28+
{
29+
case VBAParser.SubStmtContext _:
30+
fullSignatureFormat = $"{{0}} {Tokens.Sub} {identifier}({{1}}){{2}}";
31+
break;
32+
case VBAParser.FunctionStmtContext _:
33+
fullSignatureFormat = $"{{0}} {Tokens.Function} {identifier}({{1}}){{2}}";
34+
break;
35+
case VBAParser.PropertyGetStmtContext _:
36+
fullSignatureFormat = $"{{0}} {Tokens.Property} {Tokens.Get} {identifier}({{1}}){{2}}";
37+
break;
38+
case VBAParser.PropertyLetStmtContext _:
39+
fullSignatureFormat = $"{{0}} {Tokens.Property} {Tokens.Let} {identifier}({{1}}){{2}}";
40+
break;
41+
case VBAParser.PropertySetStmtContext _:
42+
fullSignatureFormat = $"{{0}} {Tokens.Property} {Tokens.Set} {identifier}({{1}}){{2}}";
43+
break;
44+
default:
45+
throw new ArgumentException();
46+
}
47+
48+
var accessibilityToken = declaration.Accessibility.Equals(Accessibility.Implicit)
49+
? Tokens.Public
50+
: $"{declaration.Accessibility.ToString()}";
51+
52+
accessibilityToken = accessibility ?? accessibilityToken;
53+
54+
var improvedArgList = ImprovedArgumentList(declaration);
55+
56+
var asTypeSuffix = declaration.AsTypeName == null
57+
? string.Empty
58+
: $" {Tokens.As} {declaration.AsTypeName}";
59+
60+
var fullSignature = string.Format(fullSignatureFormat, accessibilityToken, improvedArgList, asTypeSuffix);
61+
return fullSignature.Trim();
62+
}
63+
64+
public static string AsCodeBlock(this ModuleBodyElementDeclaration declaration,
65+
string content = null,
66+
string accessibility = null,
67+
string newIdentifier = null)
68+
{
69+
var endStatement = string.Empty;
70+
switch (declaration.Context)
71+
{
72+
case VBAParser.SubStmtContext _:
73+
endStatement = $"{Tokens.End} {Tokens.Sub}";
74+
break;
75+
case VBAParser.FunctionStmtContext _:
76+
endStatement = $"{Tokens.End} {Tokens.Function}";
77+
break;
78+
case VBAParser.PropertyGetStmtContext _:
79+
case VBAParser.PropertyLetStmtContext _:
80+
case VBAParser.PropertySetStmtContext _:
81+
endStatement = $"{Tokens.End} {Tokens.Property}";
82+
break;
83+
default:
84+
throw new ArgumentException();
85+
}
86+
87+
if (content != null)
88+
{
89+
return string.Format("{0}{1}{2}{1}{3}{1}",
90+
FullMemberSignature(declaration, accessibility, newIdentifier),
91+
Environment.NewLine,
92+
content,
93+
endStatement);
94+
}
95+
96+
return string.Format("{0}{1}{2}{1}",
97+
FullMemberSignature(declaration, accessibility, newIdentifier),
98+
Environment.NewLine,
99+
endStatement);
100+
//return $"{FullMemberSignature(declaration)}{Environment.NewLine}{endStatement}{Environment.NewLine}";
101+
}
102+
103+
/// <summary>
104+
/// 1. Explicitly declares Property Let\Set value parameter as ByVal
105+
/// 2. Ensures UserDefined Type parameters are declared either explicitly or implicitly as ByRef
106+
/// </summary>
107+
/// <param name="declaration"></param>
108+
/// <returns></returns>
109+
public static string ImprovedArgumentList(this ModuleBodyElementDeclaration declaration)
110+
{
111+
var arguments = Enumerable.Empty<string>();
112+
if (declaration is IParameterizedDeclaration parameterizedDeclaration)
113+
{
114+
arguments = parameterizedDeclaration.Parameters
115+
.OrderBy(parameter => parameter.Selection)
116+
.Select(parameter => BuildParameterDeclaration(
117+
parameter,
118+
parameter.Equals(parameterizedDeclaration.Parameters.LastOrDefault())
119+
&& declaration.DeclarationType.HasFlag(DeclarationType.Property)
120+
&& !declaration.DeclarationType.Equals(DeclarationType.PropertyGet)));
121+
}
122+
return $"{string.Join(", ", arguments)}";
123+
}
124+
125+
private static string BuildParameterDeclaration(ParameterDeclaration parameter, bool forceExplicitByValAccess)
126+
{
127+
var accessibility = parameter.IsImplicitByRef
128+
? string.Empty
129+
: parameter.IsByRef
130+
? Tokens.ByRef
131+
: Tokens.ByVal;
132+
133+
if (forceExplicitByValAccess)
134+
{
135+
accessibility = Tokens.ByVal;
136+
}
137+
138+
if (accessibility.Equals(Tokens.ByVal)
139+
&& (parameter.AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.UserDefinedType) ?? false))
140+
{
141+
accessibility = Tokens.ByRef;
142+
}
143+
144+
var name = parameter.IsArray
145+
? $"{parameter.IdentifierName}()"
146+
: parameter.IdentifierName;
147+
148+
var optional = parameter.IsParamArray
149+
? Tokens.ParamArray
150+
: parameter.IsOptional
151+
? Tokens.Optional
152+
: string.Empty;
153+
154+
var defaultValue = parameter.DefaultValue;
155+
156+
return $"{FormatStandardElement(optional)}{FormatStandardElement(accessibility)}{FormatStandardElement(name)}{FormattedAsTypeName(parameter.AsTypeName)}{FormattedDefaultValue(defaultValue)}".Trim();
157+
}
158+
159+
private static string FormatStandardElement(string element) => string.IsNullOrEmpty(element)
160+
? string.Empty
161+
: $"{element} ";
162+
163+
private static string FormattedAsTypeName(string AsTypeName) => string.IsNullOrEmpty(AsTypeName)
164+
? string.Empty
165+
: $"As {AsTypeName} ";
166+
167+
private static string FormattedDefaultValue(string DefaultValue) => string.IsNullOrEmpty(DefaultValue)
168+
? string.Empty
169+
: $"= {DefaultValue}";
170+
}
171+
}

Rubberduck.Refactorings/EncapsulateField/EncapsulationStrategies/ConvertFieldsToUDTMembers.cs

Lines changed: 30 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,10 @@
11
using Antlr4.Runtime;
2+
using Rubberduck.Parsing.Grammar;
23
using Rubberduck.Parsing.Rewriter;
4+
using Rubberduck.Parsing.Symbols;
35
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.Refactorings.Common;
7+
using Rubberduck.Refactorings.EncapsulateField.Extensions;
48
using Rubberduck.SmartIndenter;
59
using Rubberduck.VBEditor;
610
using System;
@@ -66,10 +70,33 @@ protected override void LoadNewPropertyBlocks()
6670
{
6771
var propertyGenerationSpecs = SelectedFields.SelectMany(f => f.PropertyAttributeSets);
6872

69-
var generator = new PropertyGenerator();
70-
foreach (var spec in propertyGenerationSpecs)
73+
foreach (var selectedField in SelectedFields)
7174
{
72-
AddContentBlock(NewContentTypes.MethodBlock, generator.AsPropertyBlock(spec, _indenter));
75+
var converted = selectedField as IConvertToUDTMember;
76+
foreach (var set in selectedField.PropertyAttributeSets)
77+
{
78+
if (converted.Declaration is VariableDeclaration variableDeclaration)
79+
{
80+
var getContent = $"{set.PropertyName} = {set.BackingField}";
81+
if (set.UsesSetAssignment) // variableDeclaration.AsTypeName.Equals(Tokens.Variant) || converted.Declaration.IsObject)
82+
{
83+
getContent = $"{Tokens.Set} {getContent}";
84+
}
85+
AddContentBlock(NewContentTypes.MethodBlock, variableDeclaration.FieldToPropertyBlock(DeclarationType.PropertyGet, set.PropertyName, Tokens.Public, getContent));
86+
if (converted.IsReadOnly)
87+
{
88+
continue;
89+
}
90+
if (set.GenerateLetter)
91+
{
92+
AddContentBlock(NewContentTypes.MethodBlock, variableDeclaration.FieldToPropertyBlock(DeclarationType.PropertyLet, set.PropertyName, Tokens.Public, $"{set.BackingField} = {set.ParameterName}"));
93+
}
94+
if (set.GenerateSetter)
95+
{
96+
AddContentBlock(NewContentTypes.MethodBlock, variableDeclaration.FieldToPropertyBlock(DeclarationType.PropertySet, set.PropertyName, Tokens.Public, $"{Tokens.Set} {set.BackingField} = {set.ParameterName}"));
97+
}
98+
}
99+
}
73100
}
74101
}
75102

Rubberduck.Refactorings/EncapsulateField/EncapsulationStrategies/EncapsulateFieldStrategyBase.cs

Lines changed: 54 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
using Rubberduck.Parsing.Grammar;
44
using Rubberduck.Parsing.Symbols;
55
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.Refactorings.Common;
67
using Rubberduck.Refactorings.EncapsulateField.Extensions;
78
using Rubberduck.Resources;
89
using Rubberduck.SmartIndenter;
@@ -15,6 +16,20 @@
1516

1617
namespace Rubberduck.Refactorings.EncapsulateField
1718
{
19+
20+
public struct PropertyAttributeSet
21+
{
22+
public string PropertyName { get; set; }
23+
public string BackingField { get; set; }
24+
public string AsTypeName { get; set; }
25+
public string ParameterName { get; set; }
26+
public bool GenerateLetter { get; set; }
27+
public bool GenerateSetter { get; set; }
28+
public bool UsesSetAssignment { get; set; }
29+
public bool IsUDTProperty { get; set; }
30+
public Declaration Declaration { get; set; }
31+
}
32+
1833
public interface IEncapsulateStrategy
1934
{
2035
IEncapsulateFieldRewriteSession RefactorRewrite(IEncapsulateFieldRewriteSession refactorRewriteSession, bool asPreview);
@@ -102,6 +117,15 @@ private void InsertNewContent(IEncapsulateFieldRewriteSession refactorRewriteSes
102117
.Concat(_newContent[NewContentTypes.PostContentMessage]))
103118
.Trim();
104119

120+
var maxConsecutiveNewLines = 3;
121+
var target = string.Join(string.Empty, Enumerable.Repeat(Environment.NewLine, maxConsecutiveNewLines).ToList());
122+
var replacement = string.Join(string.Empty, Enumerable.Repeat(Environment.NewLine, maxConsecutiveNewLines - 1).ToList());
123+
for (var counter = 1; counter < 10 && newContentBlock.Contains(target); counter++)
124+
{
125+
newContentBlock = newContentBlock.Replace(target, replacement);
126+
}
127+
128+
105129
var rewriter = refactorRewriteSession.CheckOutModuleRewriter(_targetQMN);
106130
if (_codeSectionStartIndex.HasValue)
107131
{
@@ -115,12 +139,37 @@ private void InsertNewContent(IEncapsulateFieldRewriteSession refactorRewriteSes
115139

116140
protected virtual void LoadNewPropertyBlocks()
117141
{
118-
var propertyGenerationSpecs = SelectedFields.SelectMany(f => f.PropertyAttributeSets);
119-
120-
var generator = new PropertyGenerator();
121-
foreach (var spec in propertyGenerationSpecs)
142+
foreach (var set in SelectedFields.SelectMany(f => f.PropertyAttributeSets))
122143
{
123-
AddContentBlock(NewContentTypes.MethodBlock, generator.AsPropertyBlock(spec, _indenter));
144+
if (set.Declaration is VariableDeclaration || set.Declaration.DeclarationType.Equals(DeclarationType.UserDefinedTypeMember))
145+
{
146+
var getContent = $"{set.PropertyName} = {set.BackingField}";
147+
if (set.UsesSetAssignment)
148+
{
149+
getContent = $"{Tokens.Set} {getContent}";
150+
}
151+
if (set.AsTypeName.Equals(Tokens.Variant) && !set.Declaration.IsArray)
152+
{
153+
getContent = string.Join(Environment.NewLine,
154+
$"If IsObject({set.BackingField}) Then",
155+
$" Set {set.PropertyName} = {set.BackingField}",
156+
"Else",
157+
$" {set.PropertyName} = {set.BackingField}",
158+
"End If",
159+
Environment.NewLine);
160+
}
161+
162+
AddContentBlock(NewContentTypes.MethodBlock, set.Declaration.FieldToPropertyBlock(DeclarationType.PropertyGet, set.PropertyName, Tokens.Public, $" {getContent}"));
163+
164+
if (set.GenerateLetter)
165+
{
166+
AddContentBlock(NewContentTypes.MethodBlock, set.Declaration.FieldToPropertyBlock(DeclarationType.PropertyLet, set.PropertyName, Tokens.Public, $" {set.BackingField} = {set.ParameterName}"));
167+
}
168+
if (set.GenerateSetter)
169+
{
170+
AddContentBlock(NewContentTypes.MethodBlock, set.Declaration.FieldToPropertyBlock(DeclarationType.PropertySet, set.PropertyName, Tokens.Public, $" {Tokens.Set} {set.BackingField} = {set.ParameterName}"));
171+
}
172+
}
124173
}
125174
}
126175

Rubberduck.Refactorings/EncapsulateField/EncapsulationStrategies/UseBackingFields.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
using Rubberduck.Parsing.Grammar;
33
using Rubberduck.Parsing.Symbols;
44
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.Refactorings.Common;
56
using Rubberduck.Refactorings.EncapsulateField.Extensions;
67
using Rubberduck.SmartIndenter;
78
using Rubberduck.VBEditor;

Rubberduck.Refactorings/EncapsulateField/Extensions/IModuleRewriterExtensions.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
using Rubberduck.Parsing.Grammar;
33
using Rubberduck.Parsing.Rewriter;
44
using Rubberduck.Parsing.Symbols;
5+
using Rubberduck.Refactorings.Common;
56
using System;
67
using System.Linq;
78

Rubberduck.Refactorings/EncapsulateField/FieldCandidates/EncapsulateFieldCandidate.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using Antlr4.Runtime;
22
using Rubberduck.Parsing.Grammar;
33
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.Refactorings.Common;
45
using Rubberduck.Refactorings.EncapsulateField.Extensions;
56
using Rubberduck.Resources;
67
using Rubberduck.VBEditor;
@@ -229,7 +230,8 @@ protected virtual PropertyAttributeSet AsPropertyAttributeSet
229230
GenerateLetter = ImplementLet,
230231
GenerateSetter = ImplementSet,
231232
UsesSetAssignment = Declaration.IsObject,
232-
IsUDTProperty = false
233+
IsUDTProperty = false,
234+
Declaration = Declaration
233235
};
234236
}
235237
}

0 commit comments

Comments
 (0)