Skip to content

Commit

Permalink
Merge pull request #5556 from BZngr/CodeBuilder_ChangeDefaultRHSParam
Browse files Browse the repository at this point in the history
CodeBuilder - Provide 'casing friendly' default property RHS parameter name
  • Loading branch information
retailcoder committed Aug 15, 2020
2 parents df01e8a + 70edc91 commit d2189da
Show file tree
Hide file tree
Showing 22 changed files with 183 additions and 229 deletions.
40 changes: 16 additions & 24 deletions Rubberduck.Refactorings/Common/CodeBuilder.cs
@@ -1,4 +1,5 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Common;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using System;
using System.Collections.Generic;
Expand All @@ -11,19 +12,13 @@ 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,
Expand All @@ -34,19 +29,14 @@ public interface ICodeBuilder
/// 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>
/// <param name="parameterIdentifier">Defaults to '<paramref name="propertyIdentifier"/>Value' unless otherwise specified</param>
bool TryBuildPropertyGetCodeBlock(Declaration prototype,
string propertyIdentifier,
out string codeBlock,
Expand All @@ -57,11 +47,8 @@ public interface ICodeBuilder
/// 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>
/// <param name="content">Member body content. Formatting is the responsibility of the caller</param>
/// <param name="parameterIdentifier">Defaults to '<paramref name="propertyIdentifier"/>Value' unless otherwise specified</param>
bool TryBuildPropertyLetCodeBlock(Declaration prototype,
string propertyIdentifier,
out string codeBlock,
Expand All @@ -73,21 +60,26 @@ public interface ICodeBuilder
/// 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>
/// <param name="content">Member body content. Formatting is the responsibility of the caller</param>
/// <param name="parameterIdentifier">Defaults to '<paramref name="propertyIdentifier"/>Value' unless otherwise specified</param>
bool TryBuildPropertySetCodeBlock(Declaration prototype,
string propertyIdentifier,
out string codeBlock,
string accessibility = null,
string content = null,
string parameterIdentifier = null);
/// <summary>
/// Generates a default RHS property parameter IdentifierName
/// </summary>
/// <param name="propertyIdentifier">Let/Set Property IdentifierName</param>
string BuildPropertyRhsParameterName(string propertyIdentifier);
}

public class CodeBuilder : ICodeBuilder
{
public string BuildPropertyRhsParameterName(string propertyIdentifier)
=> string.Format(Resources.Refactorings.Refactorings.CodeBuilder_DefaultPropertyRHSParamFormat, propertyIdentifier.ToLowerCaseFirstLetter());

public string BuildMemberBlockFromPrototype(ModuleBodyElementDeclaration declaration,
string content = null,
string accessibility = null,
Expand Down Expand Up @@ -127,7 +119,7 @@ public bool TryBuildPropertySetCodeBlock(Declaration prototype, string propertyI
return false;
}

var propertyValueParam = parameterIdentifier ?? Resources.RubberduckUI.EncapsulateField_DefaultPropertyParameter;
var propertyValueParam = parameterIdentifier ?? BuildPropertyRhsParameterName(propertyIdentifier);

var asType = prototype.IsArray
? $"{Tokens.Variant}"
Expand Down
Expand Up @@ -2,7 +2,6 @@
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Refactorings.Common;
using Rubberduck.Refactorings.EncapsulateField.Extensions;
using Rubberduck.VBEditor;
using System;
using System.Collections.Generic;
Expand All @@ -16,12 +15,14 @@ public class EncapsulateFieldElementsBuilder
private readonly IDeclarationFinderProvider _declarationFinderProvider;
private QualifiedModuleName _targetQMN;
private string _defaultObjectStateUDTTypeName;
private ICodeBuilder _codeBuilder;

public EncapsulateFieldElementsBuilder(IDeclarationFinderProvider declarationFinderProvider, QualifiedModuleName targetQMN)
{
_declarationFinderProvider = declarationFinderProvider;
_targetQMN = targetQMN;
_defaultObjectStateUDTTypeName = $"T{_targetQMN.ComponentName}";
_codeBuilder = new CodeBuilder();
CreateRefactoringElements();
}

Expand Down Expand Up @@ -110,7 +111,7 @@ private IEncapsulateFieldCandidate CreateCandidate(Declaration target, IValidate
if (target.IsUserDefinedType())
{
var udtValidator = EncapsulateFieldValidationsProvider.NameOnlyValidator(NameValidators.UserDefinedType);
var udtField = new UserDefinedTypeCandidate(target, udtValidator) as IUserDefinedTypeCandidate;
var udtField = new UserDefinedTypeCandidate(target, udtValidator, _codeBuilder.BuildPropertyRhsParameterName) as IUserDefinedTypeCandidate;

(Declaration udtDeclaration, IEnumerable<Declaration> udtMembers) = GetUDTAndMembersForField(udtField);

Expand All @@ -125,7 +126,7 @@ private IEncapsulateFieldCandidate CreateCandidate(Declaration target, IValidate
{
udtMemberValidator = EncapsulateFieldValidationsProvider.NameOnlyValidator(NameValidators.UserDefinedTypeMemberArray);
}
var candidateUDTMember = new UserDefinedTypeMemberCandidate(CreateCandidate(udtMemberDeclaration, udtMemberValidator), udtField) as IUserDefinedTypeMemberCandidate;
var candidateUDTMember = new UserDefinedTypeMemberCandidate(CreateCandidate(udtMemberDeclaration, udtMemberValidator), udtField, _codeBuilder.BuildPropertyRhsParameterName) as IUserDefinedTypeMemberCandidate;

udtField.AddMember(candidateUDTMember);
}
Expand All @@ -141,10 +142,10 @@ private IEncapsulateFieldCandidate CreateCandidate(Declaration target, IValidate
}
else if (target.IsArray)
{
return new ArrayCandidate(target, validator);
return new ArrayCandidate(target, validator, _codeBuilder.BuildPropertyRhsParameterName);
}

var candidate = new EncapsulateFieldCandidate(target, validator);
var candidate = new EncapsulateFieldCandidate(target, validator, _codeBuilder.BuildPropertyRhsParameterName);
return candidate;
}

Expand Down
@@ -1,5 +1,4 @@
using Antlr4.Runtime;
using Rubberduck.Parsing;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Resources;
Expand All @@ -17,8 +16,8 @@ public interface IArrayCandidate : IEncapsulateFieldCandidate
public class ArrayCandidate : EncapsulateFieldCandidate, IArrayCandidate
{
private string _subscripts;
public ArrayCandidate(Declaration declaration, IValidateVBAIdentifiers validator)
:base(declaration, validator)
public ArrayCandidate(Declaration declaration, IValidateVBAIdentifiers validator, Func<string,string> parameterNameBuilder)
:base(declaration, validator, parameterNameBuilder)
{
ImplementLet = false;
ImplementSet = false;
Expand Down
@@ -1,11 +1,6 @@
using System;
using System.Collections.Generic;
using System.Collections.Generic;
using System.Linq;
using System.Text;
using System.Threading.Tasks;
using Antlr4.Runtime;
using Rubberduck.Common;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.VBEditor;

Expand Down Expand Up @@ -90,11 +85,7 @@ public bool IsReadOnly
get => _wrapped.IsReadOnly;
}

public string ParameterName
{
set => _wrapped.ParameterName = value;
get => _wrapped.ParameterName;
}
public string ParameterName => _wrapped.ParameterName;

public IValidateVBAIdentifiers NameValidator
{
Expand Down
Expand Up @@ -3,9 +3,7 @@
using Rubberduck.Parsing.Symbols;
using Rubberduck.Refactorings.Common;
using Rubberduck.Refactorings.EncapsulateField.Extensions;
using Rubberduck.Resources;
using Rubberduck.VBEditor;
using Rubberduck.VBEditor.SafeComWrappers;
using System;
using System.Collections.Generic;

Expand All @@ -31,7 +29,7 @@ public interface IEncapsulateFieldCandidate : IEncapsulateFieldRefactoringElemen
bool ImplementLet { get; }
bool ImplementSet { get; }
bool IsReadOnly { set; get; }
string ParameterName { set; get; }
string ParameterName { get; }
IValidateVBAIdentifiers NameValidator { set; get; }
IEncapsulateFieldConflictFinder ConflictFinder { set; get; }
bool TryValidateEncapsulationAttributes(out string errorMessage);
Expand All @@ -47,11 +45,13 @@ public class EncapsulateFieldCandidate : IEncapsulateFieldCandidate
protected int _hashCode;
private string _identifierName;
protected EncapsulationIdentifiers _fieldAndProperty;
private Func<string, string> _parameterNameBuilder;

public EncapsulateFieldCandidate(Declaration declaration, IValidateVBAIdentifiers identifierValidator)
public EncapsulateFieldCandidate(Declaration declaration, IValidateVBAIdentifiers identifierValidator, Func<string, string> parameterNameBuilder)
{
_target = declaration;
NameValidator = identifierValidator;
_parameterNameBuilder = parameterNameBuilder;

_fieldAndProperty = new EncapsulationIdentifiers(declaration.IdentifierName, identifierValidator);
IdentifierName = declaration.IdentifierName;
Expand Down Expand Up @@ -164,8 +164,6 @@ public string PropertyIdentifier
_fieldAndProperty.Property = value;

TryRestoreNewFieldNameAsOriginalFieldIdentifierName();

EncapsulateFieldValidationsProvider.AssignNoConflictParameter(this);
}
}

Expand Down Expand Up @@ -204,7 +202,7 @@ public string IdentifierName

public virtual string ReferenceQualifier { set; get; }

public string ParameterName { set; get; } = RubberduckUI.EncapsulateField_DefaultPropertyParameter;
public string ParameterName => _parameterNameBuilder(PropertyIdentifier);

private bool _implLet;
public bool ImplementLet { get => !IsReadOnly && _implLet; set => _implLet = value; }
Expand Down
@@ -1,20 +1,13 @@
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA.Extensions;
using Rubberduck.Common;
using Rubberduck.Common;
using System.Collections.Generic;
using Rubberduck.Refactorings.EncapsulateField.Extensions;
using System;
using Rubberduck.Resources;

namespace Rubberduck.Refactorings.EncapsulateField
{
public class EncapsulationIdentifiers
{
private static string DEFAULT_WRITE_PARAMETER = RubberduckUI.EncapsulateField_DefaultPropertyParameter;

private KeyValuePair<string, string> _fieldAndProperty;
private string _targetIdentifier;
private string _setLetParameter;

public EncapsulationIdentifiers(string field, IValidateVBAIdentifiers identifierValidator)
{
Expand Down Expand Up @@ -42,7 +35,6 @@ public EncapsulationIdentifiers(string field, IValidateVBAIdentifiers identifier
}

_fieldAndProperty = new KeyValuePair<string, string>(DefaultNewFieldName, DefaultPropertyName);
_setLetParameter = DEFAULT_WRITE_PARAMETER;
}

public string TargetFieldName => _targetIdentifier;
Expand All @@ -68,7 +60,5 @@ public string Property
_fieldAndProperty = new KeyValuePair<string, string>(_fieldAndProperty.Key, value);
}
}

public string SetLetParameter => DEFAULT_WRITE_PARAMETER;
}
}
@@ -1,12 +1,8 @@
using Antlr4.Runtime;
using Rubberduck.Common;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Refactorings.Common;
using System;
using System.Collections.Generic;
using System.Linq;

namespace Rubberduck.Refactorings.EncapsulateField
{
Expand All @@ -21,8 +17,8 @@ public interface IUserDefinedTypeCandidate : IEncapsulateFieldCandidate

public class UserDefinedTypeCandidate : EncapsulateFieldCandidate, IUserDefinedTypeCandidate
{
public UserDefinedTypeCandidate(Declaration declaration, IValidateVBAIdentifiers identifierValidator)
: base(declaration, identifierValidator)
public UserDefinedTypeCandidate(Declaration declaration, IValidateVBAIdentifiers identifierValidator, Func<string,string> parameterNameBuilder)
: base(declaration, identifierValidator, parameterNameBuilder)
{
}

Expand Down
@@ -1,11 +1,9 @@
using Antlr4.Runtime;
using Rubberduck.Parsing;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Refactorings.EncapsulateField.Extensions;
using Rubberduck.VBEditor;
using System;
using System.Collections.Generic;
using System.Diagnostics;
using System.Linq;

namespace Rubberduck.Refactorings.EncapsulateField
Expand All @@ -22,9 +20,11 @@ public class UserDefinedTypeMemberCandidate : IUserDefinedTypeMemberCandidate
{
private int _hashCode;
private readonly string _uniqueID;
public UserDefinedTypeMemberCandidate(IEncapsulateFieldCandidate candidate, IUserDefinedTypeCandidate udtField)
private Func<string, string> _parameterNameBuilder;
public UserDefinedTypeMemberCandidate(IEncapsulateFieldCandidate candidate, IUserDefinedTypeCandidate udtField, Func<string,string> parameterNameBuilder)
{
_wrappedCandidate = candidate;
_parameterNameBuilder = parameterNameBuilder;
UDTField = udtField;
PropertyIdentifier = IdentifierName;
BackingIdentifier = IdentifierName;
Expand Down Expand Up @@ -203,11 +203,7 @@ public QualifiedModuleName QualifiedModuleName

public string PropertyAsTypeName => _wrappedCandidate.PropertyAsTypeName;

public string ParameterName
{
set => _wrappedCandidate.ParameterName = value;
get => _wrappedCandidate.ParameterName;
}
public string ParameterName => _parameterNameBuilder(PropertyIdentifier);

public bool ImplementLet => _wrappedCandidate.ImplementLet;

Expand Down
Expand Up @@ -87,7 +87,7 @@ protected virtual IEncapsulateFieldCandidate AssignNoConflictIdentifier(IEncapsu
isConflictingIdentifier = HasConflictingIdentifierIgnoreEncapsulationFlag(candidate, declarationType, out _);
}

return EncapsulateFieldValidationsProvider.AssignNoConflictParameter(candidate);
return candidate;
}

public bool IsConflictingProposedIdentifier(string fieldName, IEncapsulateFieldCandidate candidate, DeclarationType declarationType)
Expand Down
Expand Up @@ -82,19 +82,6 @@ private void LoadUDTMemberCandidates(IUserDefinedTypeCandidate udtCandidate)
public static IValidateVBAIdentifiers NameOnlyValidator(NameValidators validatorType)
=> _nameOnlyValidators[validatorType];

public static IEncapsulateFieldCandidate AssignNoConflictParameter(IEncapsulateFieldCandidate candidate)
{
candidate.ParameterName = RubberduckUI.EncapsulateField_DefaultPropertyParameter;

var guard = 0;
while (guard++ < 10 && (candidate.BackingIdentifier.IsEquivalentVBAIdentifierTo(candidate.ParameterName)
|| candidate.PropertyIdentifier.IsEquivalentVBAIdentifierTo(candidate.ParameterName)))
{
candidate.ParameterName = candidate.ParameterName.IncrementEncapsulationIdentifier();
}
return candidate;
}

public static IObjectStateUDT AssignNoConflictIdentifiers(IObjectStateUDT stateUDT, IDeclarationFinderProvider declarationFinderProvider)
{
var members = declarationFinderProvider.DeclarationFinder.Members(stateUDT.QualifiedModuleName);
Expand Down

0 comments on commit d2189da

Please sign in to comment.