Skip to content

Commit

Permalink
Merge branch 'next' into AnnotateCommand
Browse files Browse the repository at this point in the history
  • Loading branch information
MDoerner committed Jun 7, 2020
2 parents a80cf79 + cfe1ad3 commit e973f64
Show file tree
Hide file tree
Showing 21 changed files with 815 additions and 346 deletions.
284 changes: 284 additions & 0 deletions Rubberduck.Refactorings/Common/CodeBuilder.cs
@@ -0,0 +1,284 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using System;
using System.Collections.Generic;
using System.Linq;

namespace Rubberduck.Refactorings
{
public interface ICodeBuilder
{
/// <summary>
/// Returns ModuleBodyElementDeclaration signature with an ImprovedArgument list
/// </summary>
/// <param name="declaration"></param>
/// <returns></returns>
string ImprovedFullMemberSignature(ModuleBodyElementDeclaration declaration);

/// <summary>
/// Returns a ModuleBodyElementDeclaration block
/// with an ImprovedArgument List
/// </summary>
/// <param name="declaration"></param>
/// <param name="content">Main body content/logic of the member</param>
/// <param name="accessibility"></param>
/// <param name="newIdentifier"></param>
/// <returns></returns>
string BuildMemberBlockFromPrototype(ModuleBodyElementDeclaration declaration,
string content = null,
string accessibility = null,
string newIdentifier = null);

/// <summary>
/// Returns the argument list for the input ModuleBodyElementDeclaration with the following improvements:
/// 1. Explicitly declares Property Let\Set value parameter as ByVal
/// 2. Ensures UserDefined Type parameters are declared either explicitly or implicitly as ByRef
/// </summary>
/// <param name="declaration"></param>
/// <returns></returns>
string ImprovedArgumentList(ModuleBodyElementDeclaration declaration);

/// <summary>
/// Generates a Property Get codeblock based on the prototype declaration
/// </summary>
/// <param name="prototype">VariableDeclaration or UserDefinedTypeMember</param>
/// <param name="propertyIdentifier"></param>
/// <param name="accessibility"></param>
/// <param name="content">Member body content. Formatting is the responsibility of the caller</param>
/// <param name="parameterIdentifier">Defaults to 'value' unless otherwise specified</param>
/// <returns></returns>
bool TryBuildPropertyGetCodeBlock(Declaration prototype,
string propertyIdentifier,
out string codeBlock,
string accessibility = null,
string content = null);

/// <summary>
/// Generates a Property Let codeblock based on the prototype declaration
/// </summary>
/// <param name="prototype">VariableDeclaration or UserDefinedTypeMember</param>
/// <param name="propertyIdentifier"></param>
/// <param name="accessibility"></param>
/// <param name="content">Membmer body content. Formatting is the responsibility of the caller</param>
/// <param name="parameterIdentifier">Defaults to 'value' unless otherwise specified</param>
/// <returns></returns>
bool TryBuildPropertyLetCodeBlock(Declaration prototype,
string propertyIdentifier,
out string codeBlock,
string accessibility = null,
string content = null,
string parameterIdentifier = null);

/// <summary>
/// Generates a Property Set codeblock based on the prototype declaration
/// </summary>
/// <param name="prototype">VariableDeclaration or UserDefinedTypeMember</param>
/// <param name="propertyIdentifier"></param>
/// <param name="accessibility"></param>
/// <param name="content">Membmer body content. Formatting is the responsibility of the caller</param>
/// <param name="parameterIdentifier">Defaults to 'value' unless otherwise specified</param>
/// <returns></returns>
bool TryBuildPropertySetCodeBlock(Declaration prototype,
string propertyIdentifier,
out string codeBlock,
string accessibility = null,
string content = null,
string parameterIdentifier = null);
}

public class CodeBuilder : ICodeBuilder
{
public string BuildMemberBlockFromPrototype(ModuleBodyElementDeclaration declaration,
string content = null,
string accessibility = null,
string newIdentifier = null)
{

var elements = new List<string>()
{
ImprovedFullMemberSignatureInternal(declaration, accessibility, newIdentifier),
Environment.NewLine,
string.IsNullOrEmpty(content) ? null : $"{content}{Environment.NewLine}",
ProcedureEndStatement(declaration.DeclarationType),
Environment.NewLine,
};
return string.Concat(elements);
}

public bool TryBuildPropertyGetCodeBlock(Declaration prototype, string propertyIdentifier, out string codeBlock, string accessibility = null, string content = null)
=> TryBuildPropertyBlockFromTarget(prototype, DeclarationType.PropertyGet, propertyIdentifier, out codeBlock, accessibility, content);

public bool TryBuildPropertyLetCodeBlock(Declaration prototype, string propertyIdentifier, out string codeBlock, string accessibility = null, string content = null, string parameterIdentifier = null)
=> TryBuildPropertyBlockFromTarget(prototype, DeclarationType.PropertyLet, propertyIdentifier, out codeBlock, accessibility, content, parameterIdentifier);

public bool TryBuildPropertySetCodeBlock(Declaration prototype, string propertyIdentifier, out string codeBlock, string accessibility = null, string content = null, string parameterIdentifier = null)
=> TryBuildPropertyBlockFromTarget(prototype, DeclarationType.PropertySet, propertyIdentifier, out codeBlock, accessibility, content, parameterIdentifier);

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
{
codeBlock = string.Empty;
if (!letSetGetType.HasFlag(DeclarationType.Property))
{
throw new ArgumentException();
}

if (!(prototype is VariableDeclaration || prototype.DeclarationType.HasFlag(DeclarationType.UserDefinedTypeMember)))
{
return false;
}

var propertyValueParam = parameterIdentifier ?? Resources.RubberduckUI.EncapsulateField_DefaultPropertyParameter;

var asType = prototype.IsArray
? $"{Tokens.Variant}"
: IsEnumField(prototype) && prototype.AsTypeDeclaration.Accessibility.Equals(Accessibility.Private)
? $"{Tokens.Long}"
: $"{prototype.AsTypeName}";

var asTypeClause = $"{Tokens.As} {asType}";

var paramMechanism = IsUserDefinedType(prototype) ? Tokens.ByRef : Tokens.ByVal;

var letSetParamExpression = $"{paramMechanism} {propertyValueParam} {asTypeClause}";

codeBlock = letSetGetType.HasFlag(DeclarationType.PropertyGet)
? string.Join(Environment.NewLine, $"{accessibility ?? Tokens.Public} {ProcedureTypeStatement(letSetGetType)} {propertyIdentifier}() {asTypeClause}", content, ProcedureEndStatement(letSetGetType))
: string.Join(Environment.NewLine, $"{accessibility ?? Tokens.Public} {ProcedureTypeStatement(letSetGetType)} {propertyIdentifier}({letSetParamExpression})", content, ProcedureEndStatement(letSetGetType));
return true;
}

public string ImprovedFullMemberSignature(ModuleBodyElementDeclaration declaration)
=> ImprovedFullMemberSignatureInternal(declaration);

private string ImprovedFullMemberSignatureInternal(ModuleBodyElementDeclaration declaration, string accessibility = null, string newIdentifier = null)
{
var accessibilityToken = declaration.Accessibility.Equals(Accessibility.Implicit)
? Tokens.Public
: $"{declaration.Accessibility.ToString()}";

var asTypeName = string.IsNullOrEmpty(declaration.AsTypeName)
? string.Empty
: $" {Tokens.As} {declaration.AsTypeName}";

var elements = new List<string>()
{
accessibility ?? accessibilityToken,
$" {ProcedureTypeStatement(declaration.DeclarationType)} ",
newIdentifier ?? declaration.IdentifierName,
$"({ImprovedArgumentList(declaration)})",
asTypeName
};
return string.Concat(elements).Trim();

}

public string ImprovedArgumentList(ModuleBodyElementDeclaration declaration)
{
var arguments = Enumerable.Empty<string>();
if (declaration is IParameterizedDeclaration parameterizedDeclaration)
{
arguments = parameterizedDeclaration.Parameters
.OrderBy(parameter => parameter.Selection)
.Select(parameter => BuildParameterDeclaration(
parameter,
parameter.Equals(parameterizedDeclaration.Parameters.LastOrDefault())
&& declaration.DeclarationType.HasFlag(DeclarationType.Property)
&& !declaration.DeclarationType.Equals(DeclarationType.PropertyGet)));
}
return $"{string.Join(", ", arguments)}";
}

private static string BuildParameterDeclaration(ParameterDeclaration parameter, bool forceExplicitByValAccess)
{
var optionalParamType = parameter.IsParamArray
? Tokens.ParamArray
: parameter.IsOptional ? Tokens.Optional : string.Empty;

var paramMechanism = parameter.IsImplicitByRef
? string.Empty
: parameter.IsByRef ? Tokens.ByRef : Tokens.ByVal;

if (forceExplicitByValAccess
&& (string.IsNullOrEmpty(paramMechanism) || paramMechanism.Equals(Tokens.ByRef))
&& !IsUserDefinedType(parameter))
{
paramMechanism = Tokens.ByVal;
}

var name = parameter.IsArray
? $"{parameter.IdentifierName}()"
: parameter.IdentifierName;

var paramDeclarationElements = new List<string>()
{
FormatOptionalElement(optionalParamType),
FormatOptionalElement(paramMechanism),
$"{name} ",
FormatAsTypeName(parameter.AsTypeName),
FormatDefaultValue(parameter.DefaultValue)
};

return string.Concat(paramDeclarationElements).Trim();
}

private static string FormatOptionalElement(string element)
=> string.IsNullOrEmpty(element) ? string.Empty : $"{element} ";

private static string FormatAsTypeName(string AsTypeName)
=> string.IsNullOrEmpty(AsTypeName) ? string.Empty : $"As {AsTypeName} ";

private static string FormatDefaultValue(string DefaultValue)
=> string.IsNullOrEmpty(DefaultValue) ? string.Empty : $"= {DefaultValue}";

private static string ProcedureEndStatement(DeclarationType declarationType)
{
switch (declarationType)
{
case DeclarationType.Function:
return $"{Tokens.End} {Tokens.Function}";
case DeclarationType.Procedure:
return $"{Tokens.End} {Tokens.Sub}";
case DeclarationType.PropertyGet:
case DeclarationType.PropertyLet:
case DeclarationType.PropertySet:
return $"{Tokens.End} {Tokens.Property}";
default:
throw new ArgumentException();
}
}

private static string ProcedureTypeStatement(DeclarationType declarationType)
{
switch (declarationType)
{
case DeclarationType.Function:
return Tokens.Function;
case DeclarationType.Procedure:
return Tokens.Sub;
case DeclarationType.PropertyGet:
return $"{Tokens.Property} {Tokens.Get}";
case DeclarationType.PropertyLet:
return $"{Tokens.Property} {Tokens.Let}";
case DeclarationType.PropertySet:
return $"{Tokens.Property} {Tokens.Set}";
default:
throw new ArgumentException();
}
}

private static bool IsEnumField(VariableDeclaration declaration)
=> IsMemberVariable(declaration)
&& (declaration.AsTypeDeclaration?.DeclarationType.Equals(DeclarationType.Enumeration) ?? false);

private static bool IsEnumField(Declaration declaration)
=> IsMemberVariable(declaration)
&& (declaration.AsTypeDeclaration?.DeclarationType.Equals(DeclarationType.Enumeration) ?? false);

private static bool IsUserDefinedType(Declaration declaration)
=> (declaration.AsTypeDeclaration?.DeclarationType.Equals(DeclarationType.UserDefinedType) ?? false);

private static bool IsMemberVariable(Declaration declaration)
=> declaration.DeclarationType.HasFlag(DeclarationType.Variable)
&& !declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Member);
}
}
61 changes: 0 additions & 61 deletions Rubberduck.Refactorings/Common/DeclarationExtensions.cs
@@ -1,10 +1,6 @@
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Refactorings.Common;
using System;
using System.Collections.Generic;
using System.Linq;

namespace Rubberduck.Refactorings.Common
{
Expand Down Expand Up @@ -45,62 +41,5 @@ public static bool IsDeclaredInList(this Declaration declaration)
return declaration.Context.TryGetAncestor<VBAParser.VariableListStmtContext>(out var varList)
&& varList.ChildCount > 1;
}

/// <summary>
/// Generates a Property Member code block specified by the letSetGet DeclarationType argument.
/// </summary>
/// <param name="variable"></param>
/// <param name="letSetGetType"></param>
/// <param name="propertyIdentifier"></param>
/// <param name="accessibility"></param>
/// <param name="content"></param>
/// <param name="parameterIdentifier"></param>
/// <returns></returns>
public static string FieldToPropertyBlock(this Declaration variable, DeclarationType letSetGetType, string propertyIdentifier, string accessibility = null, string content = null, string parameterIdentifier = null)
{
//"value" is the default
var propertyValueParam = parameterIdentifier ?? Resources.RubberduckUI.EncapsulateField_DefaultPropertyParameter;

var propertyEndStmt = $"{Tokens.End} {Tokens.Property}";

var asType = variable.IsArray
? $"{Tokens.Variant}"
: variable.IsEnumField() && variable.AsTypeDeclaration.HasPrivateAccessibility()
? $"{Tokens.Long}"
: $"{variable.AsTypeName}";

var asTypeClause = $"{Tokens.As} {asType}";

var paramAccessibility = variable.IsUserDefinedType() ? Tokens.ByRef : Tokens.ByVal;

var letSetParameter = $"{paramAccessibility} {propertyValueParam} {Tokens.As} {asType}";

switch (letSetGetType)
{
case DeclarationType.PropertyGet:
return string.Join(Environment.NewLine, $"{accessibility ?? Tokens.Public} {PropertyTypeStatement(letSetGetType)} {propertyIdentifier}() {asTypeClause}", content, propertyEndStmt);
case DeclarationType.PropertyLet:
case DeclarationType.PropertySet:
return string.Join(Environment.NewLine, $"{accessibility ?? Tokens.Public} {PropertyTypeStatement(letSetGetType)} {propertyIdentifier}({letSetParameter})", content, propertyEndStmt);
default:
throw new ArgumentException();
}
}

private static string PropertyTypeStatement(DeclarationType declarationType)
{
switch (declarationType)
{
case DeclarationType.PropertyGet:
return $"{Tokens.Property} {Tokens.Get}";
case DeclarationType.PropertyLet:
return $"{Tokens.Property} {Tokens.Let}";
case DeclarationType.PropertySet:
return $"{Tokens.Property} {Tokens.Set}";
default:
throw new ArgumentException();
}

}
}
}

0 comments on commit e973f64

Please sign in to comment.