Skip to content

Commit e973f64

Browse files
committed
Merge branch 'next' into AnnotateCommand
2 parents a80cf79 + cfe1ad3 commit e973f64

21 files changed

+815
-346
lines changed
Lines changed: 284 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,284 @@
1+
using Rubberduck.Parsing.Grammar;
2+
using Rubberduck.Parsing.Symbols;
3+
using System;
4+
using System.Collections.Generic;
5+
using System.Linq;
6+
7+
namespace Rubberduck.Refactorings
8+
{
9+
public interface ICodeBuilder
10+
{
11+
/// <summary>
12+
/// Returns ModuleBodyElementDeclaration signature with an ImprovedArgument list
13+
/// </summary>
14+
/// <param name="declaration"></param>
15+
/// <returns></returns>
16+
string ImprovedFullMemberSignature(ModuleBodyElementDeclaration declaration);
17+
18+
/// <summary>
19+
/// Returns a ModuleBodyElementDeclaration block
20+
/// with an ImprovedArgument List
21+
/// </summary>
22+
/// <param name="declaration"></param>
23+
/// <param name="content">Main body content/logic of the member</param>
24+
/// <param name="accessibility"></param>
25+
/// <param name="newIdentifier"></param>
26+
/// <returns></returns>
27+
string BuildMemberBlockFromPrototype(ModuleBodyElementDeclaration declaration,
28+
string content = null,
29+
string accessibility = null,
30+
string newIdentifier = null);
31+
32+
/// <summary>
33+
/// Returns the argument list for the input ModuleBodyElementDeclaration with the following improvements:
34+
/// 1. Explicitly declares Property Let\Set value parameter as ByVal
35+
/// 2. Ensures UserDefined Type parameters are declared either explicitly or implicitly as ByRef
36+
/// </summary>
37+
/// <param name="declaration"></param>
38+
/// <returns></returns>
39+
string ImprovedArgumentList(ModuleBodyElementDeclaration declaration);
40+
41+
/// <summary>
42+
/// Generates a Property Get codeblock based on the prototype declaration
43+
/// </summary>
44+
/// <param name="prototype">VariableDeclaration or UserDefinedTypeMember</param>
45+
/// <param name="propertyIdentifier"></param>
46+
/// <param name="accessibility"></param>
47+
/// <param name="content">Member body content. Formatting is the responsibility of the caller</param>
48+
/// <param name="parameterIdentifier">Defaults to 'value' unless otherwise specified</param>
49+
/// <returns></returns>
50+
bool TryBuildPropertyGetCodeBlock(Declaration prototype,
51+
string propertyIdentifier,
52+
out string codeBlock,
53+
string accessibility = null,
54+
string content = null);
55+
56+
/// <summary>
57+
/// Generates a Property Let codeblock based on the prototype declaration
58+
/// </summary>
59+
/// <param name="prototype">VariableDeclaration or UserDefinedTypeMember</param>
60+
/// <param name="propertyIdentifier"></param>
61+
/// <param name="accessibility"></param>
62+
/// <param name="content">Membmer body content. Formatting is the responsibility of the caller</param>
63+
/// <param name="parameterIdentifier">Defaults to 'value' unless otherwise specified</param>
64+
/// <returns></returns>
65+
bool TryBuildPropertyLetCodeBlock(Declaration prototype,
66+
string propertyIdentifier,
67+
out string codeBlock,
68+
string accessibility = null,
69+
string content = null,
70+
string parameterIdentifier = null);
71+
72+
/// <summary>
73+
/// Generates a Property Set codeblock based on the prototype declaration
74+
/// </summary>
75+
/// <param name="prototype">VariableDeclaration or UserDefinedTypeMember</param>
76+
/// <param name="propertyIdentifier"></param>
77+
/// <param name="accessibility"></param>
78+
/// <param name="content">Membmer body content. Formatting is the responsibility of the caller</param>
79+
/// <param name="parameterIdentifier">Defaults to 'value' unless otherwise specified</param>
80+
/// <returns></returns>
81+
bool TryBuildPropertySetCodeBlock(Declaration prototype,
82+
string propertyIdentifier,
83+
out string codeBlock,
84+
string accessibility = null,
85+
string content = null,
86+
string parameterIdentifier = null);
87+
}
88+
89+
public class CodeBuilder : ICodeBuilder
90+
{
91+
public string BuildMemberBlockFromPrototype(ModuleBodyElementDeclaration declaration,
92+
string content = null,
93+
string accessibility = null,
94+
string newIdentifier = null)
95+
{
96+
97+
var elements = new List<string>()
98+
{
99+
ImprovedFullMemberSignatureInternal(declaration, accessibility, newIdentifier),
100+
Environment.NewLine,
101+
string.IsNullOrEmpty(content) ? null : $"{content}{Environment.NewLine}",
102+
ProcedureEndStatement(declaration.DeclarationType),
103+
Environment.NewLine,
104+
};
105+
return string.Concat(elements);
106+
}
107+
108+
public bool TryBuildPropertyGetCodeBlock(Declaration prototype, string propertyIdentifier, out string codeBlock, string accessibility = null, string content = null)
109+
=> TryBuildPropertyBlockFromTarget(prototype, DeclarationType.PropertyGet, propertyIdentifier, out codeBlock, accessibility, content);
110+
111+
public bool TryBuildPropertyLetCodeBlock(Declaration prototype, string propertyIdentifier, out string codeBlock, string accessibility = null, string content = null, string parameterIdentifier = null)
112+
=> TryBuildPropertyBlockFromTarget(prototype, DeclarationType.PropertyLet, propertyIdentifier, out codeBlock, accessibility, content, parameterIdentifier);
113+
114+
public bool TryBuildPropertySetCodeBlock(Declaration prototype, string propertyIdentifier, out string codeBlock, string accessibility = null, string content = null, string parameterIdentifier = null)
115+
=> TryBuildPropertyBlockFromTarget(prototype, DeclarationType.PropertySet, propertyIdentifier, out codeBlock, accessibility, content, parameterIdentifier);
116+
117+
private bool TryBuildPropertyBlockFromTarget<T>(T prototype, DeclarationType letSetGetType, string propertyIdentifier, out string codeBlock, string accessibility = null, string content = null, string parameterIdentifier = null) where T : Declaration
118+
{
119+
codeBlock = string.Empty;
120+
if (!letSetGetType.HasFlag(DeclarationType.Property))
121+
{
122+
throw new ArgumentException();
123+
}
124+
125+
if (!(prototype is VariableDeclaration || prototype.DeclarationType.HasFlag(DeclarationType.UserDefinedTypeMember)))
126+
{
127+
return false;
128+
}
129+
130+
var propertyValueParam = parameterIdentifier ?? Resources.RubberduckUI.EncapsulateField_DefaultPropertyParameter;
131+
132+
var asType = prototype.IsArray
133+
? $"{Tokens.Variant}"
134+
: IsEnumField(prototype) && prototype.AsTypeDeclaration.Accessibility.Equals(Accessibility.Private)
135+
? $"{Tokens.Long}"
136+
: $"{prototype.AsTypeName}";
137+
138+
var asTypeClause = $"{Tokens.As} {asType}";
139+
140+
var paramMechanism = IsUserDefinedType(prototype) ? Tokens.ByRef : Tokens.ByVal;
141+
142+
var letSetParamExpression = $"{paramMechanism} {propertyValueParam} {asTypeClause}";
143+
144+
codeBlock = letSetGetType.HasFlag(DeclarationType.PropertyGet)
145+
? string.Join(Environment.NewLine, $"{accessibility ?? Tokens.Public} {ProcedureTypeStatement(letSetGetType)} {propertyIdentifier}() {asTypeClause}", content, ProcedureEndStatement(letSetGetType))
146+
: string.Join(Environment.NewLine, $"{accessibility ?? Tokens.Public} {ProcedureTypeStatement(letSetGetType)} {propertyIdentifier}({letSetParamExpression})", content, ProcedureEndStatement(letSetGetType));
147+
return true;
148+
}
149+
150+
public string ImprovedFullMemberSignature(ModuleBodyElementDeclaration declaration)
151+
=> ImprovedFullMemberSignatureInternal(declaration);
152+
153+
private string ImprovedFullMemberSignatureInternal(ModuleBodyElementDeclaration declaration, string accessibility = null, string newIdentifier = null)
154+
{
155+
var accessibilityToken = declaration.Accessibility.Equals(Accessibility.Implicit)
156+
? Tokens.Public
157+
: $"{declaration.Accessibility.ToString()}";
158+
159+
var asTypeName = string.IsNullOrEmpty(declaration.AsTypeName)
160+
? string.Empty
161+
: $" {Tokens.As} {declaration.AsTypeName}";
162+
163+
var elements = new List<string>()
164+
{
165+
accessibility ?? accessibilityToken,
166+
$" {ProcedureTypeStatement(declaration.DeclarationType)} ",
167+
newIdentifier ?? declaration.IdentifierName,
168+
$"({ImprovedArgumentList(declaration)})",
169+
asTypeName
170+
};
171+
return string.Concat(elements).Trim();
172+
173+
}
174+
175+
public string ImprovedArgumentList(ModuleBodyElementDeclaration declaration)
176+
{
177+
var arguments = Enumerable.Empty<string>();
178+
if (declaration is IParameterizedDeclaration parameterizedDeclaration)
179+
{
180+
arguments = parameterizedDeclaration.Parameters
181+
.OrderBy(parameter => parameter.Selection)
182+
.Select(parameter => BuildParameterDeclaration(
183+
parameter,
184+
parameter.Equals(parameterizedDeclaration.Parameters.LastOrDefault())
185+
&& declaration.DeclarationType.HasFlag(DeclarationType.Property)
186+
&& !declaration.DeclarationType.Equals(DeclarationType.PropertyGet)));
187+
}
188+
return $"{string.Join(", ", arguments)}";
189+
}
190+
191+
private static string BuildParameterDeclaration(ParameterDeclaration parameter, bool forceExplicitByValAccess)
192+
{
193+
var optionalParamType = parameter.IsParamArray
194+
? Tokens.ParamArray
195+
: parameter.IsOptional ? Tokens.Optional : string.Empty;
196+
197+
var paramMechanism = parameter.IsImplicitByRef
198+
? string.Empty
199+
: parameter.IsByRef ? Tokens.ByRef : Tokens.ByVal;
200+
201+
if (forceExplicitByValAccess
202+
&& (string.IsNullOrEmpty(paramMechanism) || paramMechanism.Equals(Tokens.ByRef))
203+
&& !IsUserDefinedType(parameter))
204+
{
205+
paramMechanism = Tokens.ByVal;
206+
}
207+
208+
var name = parameter.IsArray
209+
? $"{parameter.IdentifierName}()"
210+
: parameter.IdentifierName;
211+
212+
var paramDeclarationElements = new List<string>()
213+
{
214+
FormatOptionalElement(optionalParamType),
215+
FormatOptionalElement(paramMechanism),
216+
$"{name} ",
217+
FormatAsTypeName(parameter.AsTypeName),
218+
FormatDefaultValue(parameter.DefaultValue)
219+
};
220+
221+
return string.Concat(paramDeclarationElements).Trim();
222+
}
223+
224+
private static string FormatOptionalElement(string element)
225+
=> string.IsNullOrEmpty(element) ? string.Empty : $"{element} ";
226+
227+
private static string FormatAsTypeName(string AsTypeName)
228+
=> string.IsNullOrEmpty(AsTypeName) ? string.Empty : $"As {AsTypeName} ";
229+
230+
private static string FormatDefaultValue(string DefaultValue)
231+
=> string.IsNullOrEmpty(DefaultValue) ? string.Empty : $"= {DefaultValue}";
232+
233+
private static string ProcedureEndStatement(DeclarationType declarationType)
234+
{
235+
switch (declarationType)
236+
{
237+
case DeclarationType.Function:
238+
return $"{Tokens.End} {Tokens.Function}";
239+
case DeclarationType.Procedure:
240+
return $"{Tokens.End} {Tokens.Sub}";
241+
case DeclarationType.PropertyGet:
242+
case DeclarationType.PropertyLet:
243+
case DeclarationType.PropertySet:
244+
return $"{Tokens.End} {Tokens.Property}";
245+
default:
246+
throw new ArgumentException();
247+
}
248+
}
249+
250+
private static string ProcedureTypeStatement(DeclarationType declarationType)
251+
{
252+
switch (declarationType)
253+
{
254+
case DeclarationType.Function:
255+
return Tokens.Function;
256+
case DeclarationType.Procedure:
257+
return Tokens.Sub;
258+
case DeclarationType.PropertyGet:
259+
return $"{Tokens.Property} {Tokens.Get}";
260+
case DeclarationType.PropertyLet:
261+
return $"{Tokens.Property} {Tokens.Let}";
262+
case DeclarationType.PropertySet:
263+
return $"{Tokens.Property} {Tokens.Set}";
264+
default:
265+
throw new ArgumentException();
266+
}
267+
}
268+
269+
private static bool IsEnumField(VariableDeclaration declaration)
270+
=> IsMemberVariable(declaration)
271+
&& (declaration.AsTypeDeclaration?.DeclarationType.Equals(DeclarationType.Enumeration) ?? false);
272+
273+
private static bool IsEnumField(Declaration declaration)
274+
=> IsMemberVariable(declaration)
275+
&& (declaration.AsTypeDeclaration?.DeclarationType.Equals(DeclarationType.Enumeration) ?? false);
276+
277+
private static bool IsUserDefinedType(Declaration declaration)
278+
=> (declaration.AsTypeDeclaration?.DeclarationType.Equals(DeclarationType.UserDefinedType) ?? false);
279+
280+
private static bool IsMemberVariable(Declaration declaration)
281+
=> declaration.DeclarationType.HasFlag(DeclarationType.Variable)
282+
&& !declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Member);
283+
}
284+
}
Lines changed: 0 additions & 61 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,6 @@
11
using Rubberduck.Parsing;
22
using Rubberduck.Parsing.Grammar;
33
using Rubberduck.Parsing.Symbols;
4-
using Rubberduck.Refactorings.Common;
5-
using System;
6-
using System.Collections.Generic;
7-
using System.Linq;
84

95
namespace Rubberduck.Refactorings.Common
106
{
@@ -45,62 +41,5 @@ public static bool IsDeclaredInList(this Declaration declaration)
4541
return declaration.Context.TryGetAncestor<VBAParser.VariableListStmtContext>(out var varList)
4642
&& varList.ChildCount > 1;
4743
}
48-
49-
/// <summary>
50-
/// Generates a Property Member code block specified by the letSetGet DeclarationType argument.
51-
/// </summary>
52-
/// <param name="variable"></param>
53-
/// <param name="letSetGetType"></param>
54-
/// <param name="propertyIdentifier"></param>
55-
/// <param name="accessibility"></param>
56-
/// <param name="content"></param>
57-
/// <param name="parameterIdentifier"></param>
58-
/// <returns></returns>
59-
public static string FieldToPropertyBlock(this Declaration variable, DeclarationType letSetGetType, string propertyIdentifier, string accessibility = null, string content = null, string parameterIdentifier = null)
60-
{
61-
//"value" is the default
62-
var propertyValueParam = parameterIdentifier ?? Resources.RubberduckUI.EncapsulateField_DefaultPropertyParameter;
63-
64-
var propertyEndStmt = $"{Tokens.End} {Tokens.Property}";
65-
66-
var asType = variable.IsArray
67-
? $"{Tokens.Variant}"
68-
: variable.IsEnumField() && variable.AsTypeDeclaration.HasPrivateAccessibility()
69-
? $"{Tokens.Long}"
70-
: $"{variable.AsTypeName}";
71-
72-
var asTypeClause = $"{Tokens.As} {asType}";
73-
74-
var paramAccessibility = variable.IsUserDefinedType() ? Tokens.ByRef : Tokens.ByVal;
75-
76-
var letSetParameter = $"{paramAccessibility} {propertyValueParam} {Tokens.As} {asType}";
77-
78-
switch (letSetGetType)
79-
{
80-
case DeclarationType.PropertyGet:
81-
return string.Join(Environment.NewLine, $"{accessibility ?? Tokens.Public} {PropertyTypeStatement(letSetGetType)} {propertyIdentifier}() {asTypeClause}", content, propertyEndStmt);
82-
case DeclarationType.PropertyLet:
83-
case DeclarationType.PropertySet:
84-
return string.Join(Environment.NewLine, $"{accessibility ?? Tokens.Public} {PropertyTypeStatement(letSetGetType)} {propertyIdentifier}({letSetParameter})", content, propertyEndStmt);
85-
default:
86-
throw new ArgumentException();
87-
}
88-
}
89-
90-
private static string PropertyTypeStatement(DeclarationType declarationType)
91-
{
92-
switch (declarationType)
93-
{
94-
case DeclarationType.PropertyGet:
95-
return $"{Tokens.Property} {Tokens.Get}";
96-
case DeclarationType.PropertyLet:
97-
return $"{Tokens.Property} {Tokens.Let}";
98-
case DeclarationType.PropertySet:
99-
return $"{Tokens.Property} {Tokens.Set}";
100-
default:
101-
throw new ArgumentException();
102-
}
103-
104-
}
10544
}
10645
}

0 commit comments

Comments
 (0)