@@ -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
0 commit comments