Skip to content

Commit 7714e66

Browse files
committed
Merge branch 'EF_IncorporateIndenter' into EF_CodeBuilderChanges
2 parents 948b733 + 361948a commit 7714e66

File tree

13 files changed

+279
-133
lines changed

13 files changed

+279
-133
lines changed

Rubberduck.Refactorings/Common/CodeBuilder.cs

Lines changed: 30 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using Rubberduck.Parsing;
22
using Rubberduck.Parsing.Grammar;
33
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.SmartIndenter;
45
using System;
56
using System.Collections.Generic;
67
using System.Linq;
@@ -35,7 +36,8 @@ string BuildMemberBlockFromPrototype(ModuleBodyElementDeclaration declaration,
3536
/// Generates a Property Get codeblock based on the prototype declaration
3637
/// </summary>
3738
/// <param name="prototype">DeclarationType with flags: Variable, Constant, UserDefinedTypeMember, or Function</param>
38-
/// <param name="content">Member body content. Null results in an empty body. Formatting is the responsibility of the caller</param>
39+
/// <param name="content">Member body content.</param>
40+
/// <param name="parameterIdentifier">Defaults to '<paramref name="propertyIdentifier"/>Value' unless otherwise specified</param>
3941
bool TryBuildPropertyGetCodeBlock(Declaration prototype,
4042
string propertyIdentifier,
4143
out string codeBlock,
@@ -46,7 +48,7 @@ bool TryBuildPropertyGetCodeBlock(Declaration prototype,
4648
/// Generates a Property Let codeblock based on the prototype declaration
4749
/// </summary>
4850
/// <param name="prototype">DeclarationType with flags: Variable, Constant, UserDefinedTypeMember, or Function</param>
49-
/// <param name="content">Member body content. Null results in an empty body. Formatting is the responsibility of the caller</param>
51+
/// <param name="content">Member body content.</param>
5052
/// <param name="parameterIdentifier">Defaults to 'RHS' unless otherwise specified</param>
5153
bool TryBuildPropertyLetCodeBlock(Declaration prototype,
5254
string propertyIdentifier,
@@ -59,7 +61,7 @@ bool TryBuildPropertyLetCodeBlock(Declaration prototype,
5961
/// Generates a Property Set codeblock based on the prototype declaration
6062
/// </summary>
6163
/// <param name="prototype">DeclarationType with flags: Variable, Constant, UserDefinedTypeMember, or Function</param>
62-
/// <param name="content">Member body content. Null results in an empty body. Formatting is the responsibility of the caller</param>
64+
/// <param name="content">Member body content.</param>
6365
/// <param name="parameterIdentifier">Defaults to 'RHS' unless otherwise specified</param>
6466
bool TryBuildPropertySetCodeBlock(Declaration prototype,
6567
string propertyIdentifier,
@@ -72,27 +74,36 @@ bool TryBuildPropertySetCodeBlock(Declaration prototype,
7274
/// Generates a UserDefinedType (UDT) declaration using the prototype declarations for
7375
/// creating the UserDefinedTypeMember declarations.
7476
/// </summary>
75-
/// <remarks>No validation or conflict analysis is applied to the identifiers.
77+
/// <remarks>
78+
/// No validation or conflict analysis is applied to the identifiers.
7679
/// </remarks>
7780
/// <param name="memberPrototypes">DeclarationTypes with flags: Variable, Constant, UserDefinedTypeMember, or Function</param>
7881
bool TryBuildUserDefinedTypeDeclaration(string udtIdentifier, IEnumerable<(Declaration Prototype, string UDTMemberIdentifier)> memberPrototypes, out string declaration, Accessibility accessibility = Accessibility.Private);
7982

8083
/// <summary>
8184
/// Generates a <c>UserDefinedTypeMember</c> declaration expression based on the prototype declaration
8285
/// </summary>
86+
/// <remarks>
87+
/// No validation or conflict analysis is applied to the identifiers.
88+
/// </remarks>
8389
/// <param name="prototype">DeclarationType with flags: Variable, Constant, UserDefinedTypeMember, or Function</param>
84-
/// <param name="indentation">If left null, 4 spaces of indentation are applied</param>
85-
bool TryBuildUDTMemberDeclaration(string identifier, Declaration prototype, out string declaration, string indentation = null);
90+
bool TryBuildUDTMemberDeclaration(string identifier, Declaration prototype, out string declaration);
8691
}
8792

8893
public class CodeBuilder : ICodeBuilder
8994
{
95+
private readonly IIndenter _indenter;
96+
97+
public CodeBuilder(IIndenter indenter)
98+
{
99+
_indenter = indenter;
100+
}
101+
90102
public string BuildMemberBlockFromPrototype(ModuleBodyElementDeclaration declaration,
91103
string content = null,
92104
Accessibility accessibility = Accessibility.Public,
93105
string newIdentifier = null)
94106
{
95-
96107
var elements = new List<string>()
97108
{
98109
ImprovedFullMemberSignatureInternal(declaration, accessibility, newIdentifier),
@@ -116,12 +127,8 @@ public bool TryBuildPropertySetCodeBlock(Declaration prototype, string propertyI
116127
private bool TryBuildPropertyBlockFromTarget<T>(T prototype, DeclarationType letSetGetType, string propertyIdentifier, out string codeBlock, Accessibility accessibility, string content = null, string parameterIdentifier = null) where T : Declaration
117128
{
118129
codeBlock = string.Empty;
119-
if (!letSetGetType.HasFlag(DeclarationType.Property))
120-
{
121-
throw new ArgumentException();
122-
}
123-
124-
if (!IsValidPrototypeDeclarationType(prototype.DeclarationType))
130+
if (!letSetGetType.HasFlag(DeclarationType.Property)
131+
|| !IsValidPrototypeDeclarationType(prototype.DeclarationType))
125132
{
126133
return false;
127134
}
@@ -143,6 +150,8 @@ private bool TryBuildPropertyBlockFromTarget<T>(T prototype, DeclarationType let
143150
codeBlock = letSetGetType.HasFlag(DeclarationType.PropertyGet)
144151
? string.Join(Environment.NewLine, $"{AccessibilityToken(accessibility)} {TypeToken(letSetGetType)} {propertyIdentifier}() {asTypeClause}", content, EndStatement(letSetGetType))
145152
: string.Join(Environment.NewLine, $"{AccessibilityToken(accessibility)} {TypeToken(letSetGetType)} {propertyIdentifier}({letSetParamExpression})", content, EndStatement(letSetGetType));
153+
154+
codeBlock = string.Join(Environment.NewLine, _indenter.Indent(codeBlock));
146155
return true;
147156
}
148157

@@ -163,8 +172,8 @@ private string ImprovedFullMemberSignatureInternal(ModuleBodyElementDeclaration
163172
$"({ImprovedArgumentList(declaration)})",
164173
asTypeName
165174
};
166-
return string.Concat(elements).Trim();
167175

176+
return string.Concat(elements).Trim();
168177
}
169178

170179
public string ImprovedArgumentList(ModuleBodyElementDeclaration declaration)
@@ -180,6 +189,7 @@ public string ImprovedArgumentList(ModuleBodyElementDeclaration declaration)
180189
&& declaration.DeclarationType.HasFlag(DeclarationType.Property)
181190
&& !declaration.DeclarationType.Equals(DeclarationType.PropertyGet)));
182191
}
192+
183193
return $"{string.Join(", ", arguments)}";
184194
}
185195

@@ -260,11 +270,12 @@ public bool TryBuildUserDefinedTypeDeclaration(string udtIdentifier, IEnumerable
260270

261271
blockLines.Add($"{Tokens.End} {Tokens.Type}");
262272

263-
declaration = string.Join(Environment.NewLine, blockLines);
273+
declaration = string.Join(Environment.NewLine, _indenter.Indent(blockLines));
274+
264275
return true;
265276
}
266277

267-
public bool TryBuildUDTMemberDeclaration(string udtMemberIdentifier, Declaration prototype, out string declaration, string indentation = null)
278+
public bool TryBuildUDTMemberDeclaration(string udtMemberIdentifier, Declaration prototype, out string declaration)
268279
{
269280
declaration = string.Empty;
270281

@@ -275,11 +286,11 @@ public bool TryBuildUDTMemberDeclaration(string udtMemberIdentifier, Declaration
275286
return false;
276287
}
277288

278-
declaration = BuildUDTMemberDeclaration(udtMemberIdentifier, prototype, indentation);
289+
declaration = BuildUDTMemberDeclaration(udtMemberIdentifier, prototype);
279290
return true;
280291
}
281292

282-
private static string BuildUDTMemberDeclaration(string udtMemberIdentifier, Declaration prototype, string indentation = null)
293+
private static string BuildUDTMemberDeclaration(string udtMemberIdentifier, Declaration prototype)
283294
{
284295
var identifierExpression = udtMemberIdentifier;
285296
if (prototype.IsArray)
@@ -289,7 +300,7 @@ private static string BuildUDTMemberDeclaration(string udtMemberIdentifier, Decl
289300
: $"{udtMemberIdentifier}()";
290301
}
291302

292-
return $"{indentation ?? " "}{identifierExpression} {Tokens.As} {prototype.AsTypeName}";
303+
return $"{identifierExpression} {Tokens.As} {prototype.AsTypeName}";
293304
}
294305

295306
private static string AccessibilityToken(Accessibility accessibility)

Rubberduck.Refactorings/CreateUDTMember/CreateUDTMemberRefactoringAction.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -70,9 +70,9 @@ private IEnumerable<string> GenerateUserDefinedMemberDeclarations(IEnumerable<(D
7070
var declarations = new List<string>();
7171
foreach (var (Prototype, UDTMemberIdentifier) in newMemberPairs)
7272
{
73-
if (_codeBuilder.TryBuildUDTMemberDeclaration(UDTMemberIdentifier, Prototype, out var declaration, indentation))
73+
if (_codeBuilder.TryBuildUDTMemberDeclaration(UDTMemberIdentifier, Prototype, out var declaration))
7474
{
75-
declarations.Add(declaration);
75+
declarations.Add($"{indentation}{declaration}");
7676
}
7777
}
7878
return declarations;

Rubberduck.Refactorings/EncapsulateField/EncapsulateFieldInsertNewCode/EncapsulateFieldCodeBuilder.cs

Lines changed: 28 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -20,9 +20,6 @@ public interface IEncapsulateFieldCodeBuilder
2020
/// </summary>
2121
public class EncapsulateFieldCodeBuilder : IEncapsulateFieldCodeBuilder
2222
{
23-
private const string FourSpaces = " ";
24-
private static string _doubleSpace = $"{Environment.NewLine}{Environment.NewLine}";
25-
2623
private readonly ICodeBuilder _codeBuilder;
2724

2825
public EncapsulateFieldCodeBuilder(ICodeBuilder codeBuilder)
@@ -32,68 +29,60 @@ public EncapsulateFieldCodeBuilder(ICodeBuilder codeBuilder)
3229

3330
public (string Get, string Let, string Set) BuildPropertyBlocks(PropertyAttributeSet propertyAttributes)
3431
{
35-
string propertyLet = null;
36-
string propertySet = null;
32+
if (!(propertyAttributes.Declaration.DeclarationType.HasFlag(DeclarationType.Variable)
33+
|| propertyAttributes.Declaration.DeclarationType.HasFlag(DeclarationType.UserDefinedTypeMember)))
34+
{
35+
throw new ArgumentException("Invalid prototype DeclarationType", nameof(propertyAttributes));
36+
}
37+
38+
(string Get, string Let, string Set) blocks = (string.Empty, string.Empty, string.Empty);
39+
40+
var mutatorBody = $"{propertyAttributes.BackingField} = {propertyAttributes.RHSParameterIdentifier}";
3741

3842
if (propertyAttributes.GeneratePropertyLet)
3943
{
40-
var letterContent = $"{FourSpaces}{propertyAttributes.BackingField} = {propertyAttributes.RHSParameterIdentifier}";
41-
if (!_codeBuilder.TryBuildPropertyLetCodeBlock(propertyAttributes.Declaration, propertyAttributes.PropertyName, out propertyLet, content: letterContent))
42-
{
43-
throw new ArgumentException();
44-
}
44+
_codeBuilder.TryBuildPropertyLetCodeBlock(propertyAttributes.Declaration, propertyAttributes.PropertyName, out blocks.Let, content: mutatorBody);
4545
}
4646

4747
if (propertyAttributes.GeneratePropertySet)
4848
{
49-
var setterContent = $"{FourSpaces}{Tokens.Set} {propertyAttributes.BackingField} = {propertyAttributes.RHSParameterIdentifier}";
50-
if (!_codeBuilder.TryBuildPropertySetCodeBlock(propertyAttributes.Declaration, propertyAttributes.PropertyName, out propertySet, content: setterContent))
51-
{
52-
throw new ArgumentException();
53-
}
49+
_codeBuilder.TryBuildPropertySetCodeBlock(propertyAttributes.Declaration, propertyAttributes.PropertyName, out blocks.Set, content: $"{Tokens.Set} {mutatorBody}");
5450
}
5551

56-
var getterContent = $"{propertyAttributes.PropertyName} = {propertyAttributes.BackingField}";
57-
if (propertyAttributes.UsesSetAssignment)
58-
{
59-
getterContent = $"{Tokens.Set} {getterContent}";
60-
}
52+
var propertyGetBody = propertyAttributes.UsesSetAssignment
53+
? $"{Tokens.Set} {propertyAttributes.PropertyName} = {propertyAttributes.BackingField}"
54+
: $"{propertyAttributes.PropertyName} = {propertyAttributes.BackingField}";
6155

6256
if (propertyAttributes.AsTypeName.Equals(Tokens.Variant) && !propertyAttributes.Declaration.IsArray)
6357
{
64-
getterContent = string.Join(Environment.NewLine,
58+
propertyGetBody = string.Join(
6559
$"{Tokens.If} IsObject({propertyAttributes.BackingField}) {Tokens.Then}",
66-
$"{FourSpaces}{Tokens.Set} {propertyAttributes.PropertyName} = {propertyAttributes.BackingField}",
60+
$"{Tokens.Set} {propertyAttributes.PropertyName} = {propertyAttributes.BackingField}",
6761
Tokens.Else,
68-
$"{FourSpaces}{propertyAttributes.PropertyName} = {propertyAttributes.BackingField}",
69-
$"{Tokens.End} {Tokens.If}",
70-
Environment.NewLine);
62+
$"{propertyAttributes.PropertyName} = {propertyAttributes.BackingField}",
63+
$"{Tokens.End} {Tokens.If}");
7164
}
7265

73-
if (!_codeBuilder.TryBuildPropertyGetCodeBlock(propertyAttributes.Declaration, propertyAttributes.PropertyName, out var propertyGet, content: $"{FourSpaces}{getterContent}"))
74-
{
75-
throw new ArgumentException();
76-
}
66+
_codeBuilder.TryBuildPropertyGetCodeBlock(propertyAttributes.Declaration, propertyAttributes.PropertyName, out blocks.Get, content: propertyGetBody);
7767

78-
return (propertyGet, propertyLet, propertySet);
68+
return (blocks.Get, blocks.Let, blocks.Set);
7969
}
8070

8171
public string BuildUserDefinedTypeDeclaration(IObjectStateUDT objectStateUDT, IEnumerable<IEncapsulateFieldCandidate> candidates)
8272
{
83-
var selected = candidates.Where(c => c.EncapsulateFlag);
84-
85-
var newUDTMembers = selected
73+
var newUDTMembers = candidates.Where(c => c.EncapsulateFlag)
8674
.Select(m => (m.Declaration, m.BackingIdentifier));
8775

88-
_codeBuilder.TryBuildUserDefinedTypeDeclaration(objectStateUDT.AsTypeName, newUDTMembers, out var declaration);
76+
if (_codeBuilder.TryBuildUserDefinedTypeDeclaration(objectStateUDT.AsTypeName, newUDTMembers, out var declaration))
77+
{
78+
return declaration;
79+
}
8980

90-
return declaration ?? string.Empty;
81+
return string.Empty;
9182
}
9283

93-
public string BuildObjectStateFieldDeclaration(IObjectStateUDT objectStateUDT)
94-
{
95-
return $"{Accessibility.Private} {objectStateUDT.IdentifierName} {Tokens.As} {objectStateUDT.AsTypeName}";
96-
}
84+
public string BuildObjectStateFieldDeclaration(IObjectStateUDT objectStateUDT)
85+
=> $"{Accessibility.Private} {objectStateUDT.IdentifierName} {Tokens.As} {objectStateUDT.AsTypeName}";
9786

9887
public string BuildFieldDeclaration(Declaration target, string identifier)
9988
{

0 commit comments

Comments
 (0)