Skip to content

Commit

Permalink
Expose IIndenter on ICodeBuilder
Browse files Browse the repository at this point in the history
Also corrects merge error and minor changes to signatures and comments
  • Loading branch information
BZngr committed Oct 7, 2020
1 parent 7714e66 commit 51ce8a7
Show file tree
Hide file tree
Showing 2 changed files with 15 additions and 10 deletions.
19 changes: 12 additions & 7 deletions Rubberduck.Refactorings/Common/CodeBuilder.cs
Original file line number Diff line number Diff line change
Expand Up @@ -87,18 +87,20 @@ bool TryBuildPropertySetCodeBlock(Declaration prototype,
/// No validation or conflict analysis is applied to the identifiers.
/// </remarks>
/// <param name="prototype">DeclarationType with flags: Variable, Constant, UserDefinedTypeMember, or Function</param>
bool TryBuildUDTMemberDeclaration(string identifier, Declaration prototype, out string declaration);
bool TryBuildUDTMemberDeclaration(Declaration prototype, string identifier, out string declaration);

IIndenter Indenter { get; }
}

public class CodeBuilder : ICodeBuilder
{
private readonly IIndenter _indenter;

public CodeBuilder(IIndenter indenter)
{
_indenter = indenter;
Indenter = indenter;
}

public IIndenter Indenter { get; }

public string BuildMemberBlockFromPrototype(ModuleBodyElementDeclaration declaration,
string content = null,
Accessibility accessibility = Accessibility.Public,
Expand Down Expand Up @@ -135,6 +137,9 @@ private bool TryBuildPropertyBlockFromTarget<T>(T prototype, DeclarationType let

var propertyValueParam = parameterIdentifier ?? Resources.Refactorings.Refactorings.CodeBuilder_DefaultPropertyRHSParam;

//TODO: Improve generated Array properties
//Add logic to conditionally return Arrays or Variant depending on Office version.
//Ability to return an Array from a Function or Property was added in Office 2000 http://www.cpearson.com/excel/passingandreturningarrays.htm
var asType = prototype.IsArray
? $"{Tokens.Variant}"
: IsEnumField(prototype) && prototype.AsTypeDeclaration.Accessibility.Equals(Accessibility.Private)
Expand All @@ -151,7 +156,7 @@ private bool TryBuildPropertyBlockFromTarget<T>(T prototype, DeclarationType let
? string.Join(Environment.NewLine, $"{AccessibilityToken(accessibility)} {TypeToken(letSetGetType)} {propertyIdentifier}() {asTypeClause}", content, EndStatement(letSetGetType))
: string.Join(Environment.NewLine, $"{AccessibilityToken(accessibility)} {TypeToken(letSetGetType)} {propertyIdentifier}({letSetParamExpression})", content, EndStatement(letSetGetType));

codeBlock = string.Join(Environment.NewLine, _indenter.Indent(codeBlock));
codeBlock = string.Join(Environment.NewLine, Indenter.Indent(codeBlock));
return true;
}

Expand Down Expand Up @@ -270,12 +275,12 @@ public bool TryBuildUserDefinedTypeDeclaration(string udtIdentifier, IEnumerable

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

declaration = string.Join(Environment.NewLine, _indenter.Indent(blockLines));
declaration = string.Join(Environment.NewLine, Indenter.Indent(blockLines));

return true;
}

public bool TryBuildUDTMemberDeclaration(string udtMemberIdentifier, Declaration prototype, out string declaration)
public bool TryBuildUDTMemberDeclaration(Declaration prototype, string udtMemberIdentifier, out string declaration)
{
declaration = string.Empty;

Expand Down
6 changes: 3 additions & 3 deletions RubberduckTests/CodeBuilderTests.cs
Original file line number Diff line number Diff line change
Expand Up @@ -545,7 +545,7 @@ public void UDT_NullIdentifierInPrototypeList_NoResult()
[Category(nameof(CodeBuilder))]
public void UDT_NullPrototype_NoResult()
{
var result = CreateCodeBuilder().TryBuildUDTMemberDeclaration(_defaultUDTIdentifier, null, out var declaration);
var result = CreateCodeBuilder().TryBuildUDTMemberDeclaration(null, _defaultUDTIdentifier, out var declaration);
Assert.IsFalse(result);
Assert.IsTrue(string.IsNullOrEmpty(declaration));
}
Expand All @@ -561,7 +561,7 @@ public void UDT_NullUDTIdentifierBuildUDTMember_NoResult()
var target = state.DeclarationFinder.DeclarationsWithType(DeclarationType.Variable)
.Single(d => d.IdentifierName == "test");

var result = CreateCodeBuilder().TryBuildUDTMemberDeclaration(null, target, out var declaration);
var result = CreateCodeBuilder().TryBuildUDTMemberDeclaration(target, null, out var declaration);

Assert.IsFalse(result);
Assert.IsTrue(string.IsNullOrEmpty(declaration));
Expand Down Expand Up @@ -645,7 +645,7 @@ private static string ImprovedArgumentListTest(ModuleBodyElementDeclaration mbed
=> CreateCodeBuilder().ImprovedArgumentList(mbed);

private static string MemberBlockFromPrototypeTest(ModuleBodyElementDeclaration mbed, MemberBlockFromPrototypeTestParams testParams)
=> CreateCodeBuilder().BuildMemberBlockFromPrototype(mbed, testParams.Accessibility, testParams.Content, testParams.NewIdentifier);
=> CreateCodeBuilder().BuildMemberBlockFromPrototype(mbed, testParams.Content, testParams.Accessibility, testParams.NewIdentifier);

private static ICodeBuilder CreateCodeBuilder()
=> new CodeBuilder(new Indenter(null, CreateIndenterSettings));
Expand Down

0 comments on commit 51ce8a7

Please sign in to comment.