Skip to content

Commit f4b04c3

Browse files
authored
Merge pull request #6049 from BZngr/SetFromLetCodeBuilder
Fix CodeBuilder create Let/Set code block issue
2 parents 3a9b233 + 162c50d commit f4b04c3

File tree

2 files changed

+225
-26
lines changed

2 files changed

+225
-26
lines changed

Rubberduck.Refactorings/Common/CodeBuilder.cs

Lines changed: 61 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -105,6 +105,8 @@ bool TryBuildUserDefinedTypeDeclaration(string udtIdentifier,
105105

106106
public class CodeBuilder : ICodeBuilder
107107
{
108+
private const string paramSeparator = ", ";
109+
108110
public CodeBuilder(IIndenter indenter)
109111
{
110112
Indenter = indenter;
@@ -137,21 +139,41 @@ public bool TryBuildPropertyGetCodeBlock(Declaration prototype,
137139
=> TryBuildPropertyBlockFromPrototype(prototype, DeclarationType.PropertyGet,
138140
propertyIdentifier, out codeBlock, accessibility, content);
139141

140-
public bool TryBuildPropertyLetCodeBlock(Declaration prototype,
141-
string propertyIdentifier, out string codeBlock,
142-
Accessibility accessibility = Accessibility.Public,
142+
public bool TryBuildPropertyLetCodeBlock(Declaration prototype,
143+
string propertyIdentifier, out string codeBlock,
144+
Accessibility accessibility = Accessibility.Public,
143145
string content = null, string valueParameterIdentifier = null)
146+
{
147+
codeBlock = string.Empty;
148+
if (IsMutatorPropertyForObjectType(prototype))
149+
{
150+
return false;
151+
}
144152

145-
=> TryBuildPropertyBlockFromPrototype(prototype, DeclarationType.PropertyLet,
146-
propertyIdentifier, out codeBlock, accessibility, content, valueParameterIdentifier);
153+
return TryBuildPropertyBlockFromPrototype(prototype, DeclarationType.PropertyLet,
154+
propertyIdentifier, out codeBlock, accessibility, content, valueParameterIdentifier);
155+
}
147156

148157
public bool TryBuildPropertySetCodeBlock(Declaration prototype,
149158
string propertyIdentifier, out string codeBlock,
150159
Accessibility accessibility = Accessibility.Public,
151160
string content = null, string valueParameterIdentifier = null)
161+
{
162+
codeBlock = string.Empty;
163+
if (prototype.IsMutatorProperty())
164+
{
165+
var prototypeAsTypeName = AsTypeNameFromMutatorProperty(prototype);
166+
if (!(prototypeAsTypeName == Tokens.Variant
167+
|| IsMutatorPropertyForObjectType(prototype)))
168+
169+
{
170+
return false;
171+
}
172+
}
152173

153-
=> TryBuildPropertyBlockFromPrototype(prototype, DeclarationType.PropertySet,
154-
propertyIdentifier, out codeBlock, accessibility, content, valueParameterIdentifier);
174+
return TryBuildPropertyBlockFromPrototype(prototype, DeclarationType.PropertySet,
175+
propertyIdentifier, out codeBlock, accessibility, content, valueParameterIdentifier);
176+
}
155177

156178
private bool TryBuildPropertyBlockFromPrototype(Declaration prototype,
157179
DeclarationType letSetGetTypeToCreate, string propertyIdentifier,
@@ -186,22 +208,7 @@ private bool TryBuildPropertyBlockFromPrototype(Declaration prototype,
186208
private static string CreateLetSetPropertyBlock(Declaration prototype, DeclarationType declarationTypeToCreate,
187209
Accessibility accessibility, string methodName, string valueParameterIdentifier, string memberBody)
188210
{
189-
var paramMechanism = prototype.IsUserDefinedType() ? Tokens.ByRef : Tokens.ByVal;
190-
191-
var asTypeClause = $"{Tokens.As} {PrototypeToPropertyAsTypeName(prototype)}";
192-
193-
var valueParameterName = valueParameterIdentifier
194-
?? Resources.Refactorings.Refactorings.CodeBuilder_DefaultPropertyRHSParam;
195-
196-
var valueParameterExpression = $"{paramMechanism} {valueParameterName} {asTypeClause}";
197-
198-
var parameters = prototype is IParameterizedDeclaration pDec
199-
? pDec.Parameters.Select(GetParameterExpression).ToList()
200-
: new List<string>();
201-
202-
parameters.Add(valueParameterExpression);
203-
204-
var parameterList = string.Join(", ", parameters);
211+
var parameterList = CreateLetSetParameterList(prototype, valueParameterIdentifier);
205212

206213
var codeBlock = string.Join(
207214
Environment.NewLine,
@@ -221,7 +228,7 @@ private static string CreateGetPropertyBlock(Declaration prototype, Accessibilit
221228
.Select(GetParameterExpression)
222229
: Enumerable.Empty<string>();
223230

224-
var parameterList = string.Join(", ", parameters);
231+
var parameterList = string.Join(paramSeparator, parameters);
225232

226233
var asTypeClause = $"{Tokens.As} {PrototypeToPropertyAsTypeName(prototype)}";
227234

@@ -268,7 +275,7 @@ public string ImprovedArgumentList(ModuleBodyElementDeclaration declaration)
268275
&& !declaration.DeclarationType.Equals(DeclarationType.PropertyGet)));
269276
}
270277

271-
return $"{string.Join(", ", arguments)}";
278+
return $"{string.Join(paramSeparator, arguments)}";
272279
}
273280

274281
private static string BuildParameterDeclaration(ParameterDeclaration parameter, bool forceExplicitByValAccess)
@@ -433,6 +440,35 @@ private static string AsTypeNameFromMutatorProperty(Declaration prototype)
433440
return paramDeclaration.Parameters.Last().AsTypeName;
434441
}
435442

443+
private static string CreateLetSetParameterList(Declaration prototype, string valueParameterIdentifier = null)
444+
{
445+
if (prototype.IsMutatorProperty())
446+
{
447+
var parameterizedDeclaration = prototype as IParameterizedDeclaration;
448+
return string.Join(paramSeparator, parameterizedDeclaration.Parameters.Select(GetParameterExpression));
449+
}
450+
451+
var paramMechanism = prototype.IsUserDefinedType() ? Tokens.ByRef : Tokens.ByVal;
452+
453+
var asTypeClause = $"{Tokens.As} {PrototypeToPropertyAsTypeName(prototype)}";
454+
455+
var valueParameterName = valueParameterIdentifier
456+
?? Resources.Refactorings.Refactorings.CodeBuilder_DefaultPropertyRHSParam;
457+
458+
var parameters = prototype is IParameterizedDeclaration pDec
459+
? pDec.Parameters.Select(GetParameterExpression).ToList() //Property Get prototype
460+
: new List<string>(); //Variable, UDT Member, Function prototypes
461+
462+
var valueParameterExpression = $"{paramMechanism} {valueParameterName} {asTypeClause}";
463+
parameters.Add(valueParameterExpression);
464+
465+
return string.Join(paramSeparator, parameters);
466+
}
467+
468+
private static bool IsMutatorPropertyForObjectType(Declaration prototype)
469+
=> prototype.IsMutatorProperty()
470+
&& prototype is IParameterizedDeclaration pd && pd.Parameters.Last().IsObject;
471+
436472
private static string AccessibilityToken(Accessibility accessibility)
437473
=> accessibility.Equals(Accessibility.Implicit)
438474
? Tokens.Public

RubberduckTests/CodeBuilderTests.cs

Lines changed: 164 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
using NUnit.Framework;
22
using Rubberduck.Common;
3-
using Rubberduck.Parsing.Grammar;
43
using Rubberduck.Parsing.Symbols;
54
using Rubberduck.Refactorings;
65
using Rubberduck.SmartIndenter;
@@ -356,6 +355,170 @@ public void PropertyGetFromFromPropertySetWithParameters(string accessibilityTok
356355
StringAssert.Contains(expected, result);
357356
}
358357

358+
//Creating a Set from a Set prototype typicaly needs a new name
359+
[TestCase(DeclarationType.PropertySet, "NewSetProperty")]
360+
[TestCase(DeclarationType.PropertyLet, null)]
361+
[Category(nameof(CodeBuilder))]
362+
public void PropertySetFromPropertyMutator(DeclarationType prototypeDeclarationType, string propertyName)
363+
{
364+
(string procType, string endStmt) = ProcedureTypeIdentifier(prototypeDeclarationType);
365+
366+
string inputCode =
367+
$@"
368+
Public {procType} {_defaultPropertyIdentifier}(ByVal RHS As Variant)
369+
End Property
370+
";
371+
372+
var prototype = GetPrototypeDeclaration<ModuleBodyElementDeclaration>(
373+
inputCode, _defaultPropertyIdentifier, prototypeDeclarationType);
374+
375+
var tryResult = CreateCodeBuilder().TryBuildPropertySetCodeBlock(
376+
prototype, propertyName ?? _defaultPropertyIdentifier,
377+
out var result, prototype.Accessibility);
378+
379+
Assert.IsTrue(tryResult,
380+
"TryBuildPropertySetCodeBlock(...) returned false");
381+
382+
var expected =
383+
$"Public Property Set {propertyName ?? _defaultPropertyIdentifier}(ByVal RHS As Variant)";
384+
385+
StringAssert.Contains(expected, result);
386+
}
387+
388+
//Creating a Set from a Set prototype typicaly needs a new name
389+
[TestCase(DeclarationType.PropertySet, "NewSetProperty")]
390+
[TestCase(DeclarationType.PropertyLet, null)]
391+
[Category(nameof(CodeBuilder))]
392+
public void PropertySetFromParameterizedPropertyMutator(DeclarationType prototypeDeclarationType, string propertyName)
393+
{
394+
(string procType, string endStmt) = ProcedureTypeIdentifier(prototypeDeclarationType);
395+
396+
string inputCode =
397+
$@"
398+
Public {procType} {_defaultPropertyIdentifier}(ByVal index1 As Long, ByVal index2 As Long, ByVal RHS As Variant)
399+
End Property
400+
";
401+
402+
var prototype = GetPrototypeDeclaration<ModuleBodyElementDeclaration>(
403+
inputCode, _defaultPropertyIdentifier, prototypeDeclarationType);
404+
405+
var tryResult = CreateCodeBuilder().TryBuildPropertySetCodeBlock(
406+
prototype, propertyName ?? _defaultPropertyIdentifier,
407+
out var result, prototype.Accessibility);
408+
409+
Assert.IsTrue(tryResult,
410+
"TryBuildPropertySetCodeBlock(...) returned false");
411+
412+
var expected =
413+
$"Public Property Set {propertyName ?? _defaultPropertyIdentifier}(ByVal index1 As Long, ByVal index2 As Long, ByVal RHS As Variant)";
414+
415+
StringAssert.Contains(expected, result);
416+
}
417+
418+
//Creating a Let from a Let prototype typicaly needs a new name
419+
[TestCase(DeclarationType.PropertyLet, "NewLetProperty")]
420+
[TestCase(DeclarationType.PropertySet, null)]
421+
[Category(nameof(CodeBuilder))]
422+
public void PropertyLetFromPropertyMutator(DeclarationType prototypeDeclarationType, string propertyName)
423+
{
424+
(string procType, string endStmt) = ProcedureTypeIdentifier(prototypeDeclarationType);
425+
426+
string inputCode =
427+
$@"
428+
Public {procType} {_defaultPropertyIdentifier}(ByVal RHS As Variant)
429+
End Property
430+
";
431+
432+
var prototype = GetPrototypeDeclaration<ModuleBodyElementDeclaration>(
433+
inputCode, _defaultPropertyIdentifier, prototypeDeclarationType);
434+
435+
var tryResult = CreateCodeBuilder().TryBuildPropertyLetCodeBlock(
436+
prototype, propertyName ?? _defaultPropertyIdentifier,
437+
out var result, prototype.Accessibility);
438+
439+
Assert.IsTrue(tryResult,
440+
"TryBuildPropertyLetCodeBlock(...) returned false");
441+
442+
var expected =
443+
$"Public Property Let {propertyName ?? _defaultPropertyIdentifier}(ByVal RHS As Variant)";
444+
445+
StringAssert.Contains(expected, result);
446+
}
447+
448+
//Creating a Let from a Let prototype typicaly needs a new name
449+
[TestCase(DeclarationType.PropertyLet, "NewLetProperty")]
450+
[TestCase(DeclarationType.PropertySet, null)]
451+
[Category(nameof(CodeBuilder))]
452+
public void PropertyLetFromParameterizedPropertyMutator(DeclarationType prototypeDeclarationType, string propertyName)
453+
{
454+
(string procType, string endStmt) = ProcedureTypeIdentifier(prototypeDeclarationType);
455+
456+
string inputCode =
457+
$@"
458+
Public {procType} {_defaultPropertyIdentifier}(ByVal index1 As Long, ByVal index2 As Long, ByVal RHS As Variant)
459+
End Property
460+
";
461+
462+
var prototype = GetPrototypeDeclaration<ModuleBodyElementDeclaration>(
463+
inputCode, _defaultPropertyIdentifier, prototypeDeclarationType);
464+
465+
var tryResult = CreateCodeBuilder().TryBuildPropertyLetCodeBlock(
466+
prototype, propertyName ?? _defaultPropertyIdentifier,
467+
out var result, prototype.Accessibility);
468+
469+
Assert.IsTrue(tryResult,
470+
"TryBuildPropertyLetCodeBlock(...) returned false");
471+
472+
var expected =
473+
$"Public Property Let {propertyName ?? _defaultPropertyIdentifier}(ByVal index1 As Long, ByVal index2 As Long, ByVal RHS As Variant)";
474+
475+
StringAssert.Contains(expected, result);
476+
}
477+
478+
[Test]
479+
[Category(nameof(CodeBuilder))]
480+
public void PropertyLetFromObjectPropertySet_ReturnsFalse()
481+
{
482+
(string procType, string endStmt) = ProcedureTypeIdentifier(DeclarationType.PropertySet);
483+
484+
string inputCode =
485+
$@"
486+
Public {procType} {_defaultPropertyIdentifier}(ByVal RHS As Collection)
487+
End Property
488+
";
489+
490+
var prototype = GetPrototypeDeclaration<ModuleBodyElementDeclaration>(
491+
inputCode, _defaultPropertyIdentifier, DeclarationType.PropertySet);
492+
493+
var tryResult = CreateCodeBuilder().TryBuildPropertyLetCodeBlock(
494+
prototype, _defaultPropertyIdentifier,
495+
out var result, prototype.Accessibility);
496+
497+
Assert.IsFalse(tryResult);
498+
}
499+
500+
[Test]
501+
[Category(nameof(CodeBuilder))]
502+
public void PropertySetFromSimpleValueTypePropertyLet_ReturnsFalse()
503+
{
504+
(string procType, string endStmt) = ProcedureTypeIdentifier(DeclarationType.PropertyLet);
505+
506+
string inputCode =
507+
$@"
508+
Public {procType} {_defaultPropertyIdentifier}(ByVal RHS As Long)
509+
End Property
510+
";
511+
512+
var prototype = GetPrototypeDeclaration<ModuleBodyElementDeclaration>(
513+
inputCode, _defaultPropertyIdentifier, DeclarationType.PropertyLet);
514+
515+
var tryResult = CreateCodeBuilder().TryBuildPropertySetCodeBlock(
516+
prototype, _defaultPropertyIdentifier,
517+
out var result, prototype.Accessibility);
518+
519+
Assert.IsFalse(tryResult);
520+
}
521+
359522
[TestCase("fizz", DeclarationType.Variable, "Integer")]
360523
[TestCase("FirstValue", DeclarationType.UserDefinedTypeMember, "Long")]
361524
[TestCase("fazz", DeclarationType.Variable, "Long")]

0 commit comments

Comments
 (0)