Skip to content

Commit a968440

Browse files
authored
Merge pull request #5692 from BZngr/5664_ReadOnlyLocalFields
EncapsulateFieldRefactoring - avoid uncompilable code for ReadOnly encapsulation requests
2 parents 0cac5e6 + 8cb54eb commit a968440

27 files changed

+2903
-844
lines changed

Rubberduck.Core/UI/Refactorings/EncapsulateField/EncapsulateFieldViewModel.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -136,8 +136,9 @@ public bool SelectedFieldIsPrivateUDT
136136

137137
public bool SelectedFieldHasEditablePropertyName => !SelectedFieldIsPrivateUDT;
138138

139-
public bool EnableReadOnlyOption
140-
=> !(_masterDetailManager.DetailField?.IsRequiredToBeReadOnly ?? false);
139+
public bool EnableReadOnlyOption
140+
=> !((_masterDetailManager.DetailField?.IsRequiredToBeReadOnly ?? false)
141+
|| (_masterDetailManager.DetailField?.IsRequiredToBeReadWrite ?? false));
141142

142143
public string GroupBoxHeaderContent
143144
=> $"{_masterDetailManager.DetailField?.TargetID ?? string.Empty} {RefactoringsUI.EncapsulateField_PropertyName} ";

Rubberduck.Core/UI/Refactorings/EncapsulateField/ViewableEncapsulatedField.cs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
using Rubberduck.Refactorings.EncapsulateField;
2+
using System.Linq;
23

34
namespace Rubberduck.UI.Refactorings.EncapsulateField
45
{
@@ -10,9 +11,10 @@ public interface IEncapsulatedFieldViewData
1011
bool IsReadOnly { set; get; }
1112
bool CanBeReadWrite { get; }
1213
bool HasValidEncapsulationAttributes { get; }
13-
string TargetDeclarationExpression { set; get; }
14+
string TargetDeclarationExpression { get; }
1415
bool IsPrivateUserDefinedType { get; }
1516
bool IsRequiredToBeReadOnly { get; }
17+
bool IsRequiredToBeReadWrite { get; }
1618
string ValidationErrorMessage { get; }
1719
bool TryValidateEncapsulationAttributes(out string errorMessage);
1820
}
@@ -69,6 +71,7 @@ public bool TryValidateEncapsulationAttributes(out string errorMessage)
6971

7072
public bool CanBeReadWrite => _efd.CanBeReadWrite;
7173

74+
public bool IsAssignedExternally => _efd.IsAssignedExternally;
7275
public string PropertyName { get => _efd.PropertyIdentifier; set => _efd.PropertyIdentifier = value; }
7376

7477
public bool EncapsulateFlag { get => _efd.EncapsulateFlag; set => _efd.EncapsulateFlag = value; }
@@ -77,11 +80,8 @@ public bool TryValidateEncapsulationAttributes(out string errorMessage)
7780

7881
public bool IsRequiredToBeReadOnly => !_efd.CanBeReadWrite;
7982

80-
private string _targetDeclarationExpressions;
81-
public string TargetDeclarationExpression
82-
{
83-
set => _targetDeclarationExpressions = value;
84-
get => $"{_efd.Declaration.Accessibility} {_efd.Declaration.Context.GetText()}";
85-
}
83+
public bool IsRequiredToBeReadWrite => _efd.IsAssignedExternally;
84+
85+
public string TargetDeclarationExpression => $"{_efd.Declaration.Accessibility} {_efd.Declaration.Context.GetText()}";
8686
}
8787
}

Rubberduck.Main/Root/RubberduckIoCInstaller.cs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -390,10 +390,6 @@ private void RegisterSpecialFactories(IWindsorContainer container)
390390
.ImplementedBy<AnnotationArgumentViewModelFactory>()
391391
.LifestyleSingleton());
392392

393-
container.Register(Component.For<IReplacePrivateUDTMemberReferencesModelFactory>()
394-
.ImplementedBy<ReplacePrivateUDTMemberReferencesModelFactory>()
395-
.LifestyleSingleton());
396-
397393
RegisterUnreachableCaseFactories(container);
398394

399395
RegisterEncapsulateFieldRefactoringFactories(container);
@@ -420,6 +416,9 @@ private void RegisterEncapsulateFieldRefactoringFactories(IWindsorContainer cont
420416
container.Register(Component.For<IEncapsulateFieldModelFactory>()
421417
.ImplementedBy<EncapsulateFieldModelFactory>()
422418
.LifestyleSingleton());
419+
container.Register(Component.For<IEncapsulateFieldReferenceReplacerFactory>()
420+
.ImplementedBy<EncapsulateFieldReferenceReplacerFactory>()
421+
.LifestyleSingleton());
423422
}
424423

425424
private void RegisterQuickFixes(IWindsorContainer container, Assembly[] assembliesToRegister)

Rubberduck.Refactorings/EncapsulateField/EncapsulateFieldRefactoringActionsProvider.cs

Lines changed: 0 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1,15 +1,11 @@
11
using Rubberduck.Refactorings.ReplaceDeclarationIdentifier;
2-
using Rubberduck.Refactorings.ReplaceReferences;
3-
using Rubberduck.Refactorings.ReplacePrivateUDTMemberReferences;
42
using Rubberduck.Refactorings.EncapsulateFieldInsertNewCode;
53
using Rubberduck.Refactorings.ModifyUserDefinedType;
64

75
namespace Rubberduck.Refactorings.EncapsulateField
86
{
97
public interface IEncapsulateFieldRefactoringActionsProvider
108
{
11-
ICodeOnlyRefactoringAction<ReplaceReferencesModel> ReplaceReferences { get; }
12-
ICodeOnlyRefactoringAction<ReplacePrivateUDTMemberReferencesModel> ReplaceUDTMemberReferences { get; }
139
ICodeOnlyRefactoringAction<ReplaceDeclarationIdentifierModel> ReplaceDeclarationIdentifiers { get; }
1410
ICodeOnlyRefactoringAction<ModifyUserDefinedTypeModel> ModifyUserDefinedType { get; }
1511
ICodeOnlyRefactoringAction<EncapsulateFieldInsertNewCodeModel> EncapsulateFieldInsertNewCode { get; }
@@ -21,35 +17,23 @@ public interface IEncapsulateFieldRefactoringActionsProvider
2117
/// </summary>
2218
public class EncapsulateFieldRefactoringActionsProvider : IEncapsulateFieldRefactoringActionsProvider
2319
{
24-
private readonly ReplaceReferencesRefactoringAction _replaceReferences;
2520
private readonly ReplaceDeclarationIdentifierRefactoringAction _replaceDeclarationIdentifiers;
26-
private readonly ReplacePrivateUDTMemberReferencesRefactoringAction _replaceUDTMemberReferencesRefactoringAction;
2721
private readonly ModifyUserDefinedTypeRefactoringAction _modifyUDTRefactoringAction;
2822
private readonly EncapsulateFieldInsertNewCodeRefactoringAction _encapsulateFieldInsertNewCodeRefactoringAction;
2923

3024
public EncapsulateFieldRefactoringActionsProvider(
31-
ReplaceReferencesRefactoringAction replaceReferencesRefactoringAction,
32-
ReplacePrivateUDTMemberReferencesRefactoringAction replaceUDTMemberReferencesRefactoringAction,
3325
ReplaceDeclarationIdentifierRefactoringAction replaceDeclarationIdentifierRefactoringAction,
3426
ModifyUserDefinedTypeRefactoringAction modifyUserDefinedTypeRefactoringAction,
3527
EncapsulateFieldInsertNewCodeRefactoringAction encapsulateFieldInsertNewCodeRefactoringAction)
3628
{
37-
_replaceReferences = replaceReferencesRefactoringAction;
38-
_replaceUDTMemberReferencesRefactoringAction = replaceUDTMemberReferencesRefactoringAction;
3929
_replaceDeclarationIdentifiers = replaceDeclarationIdentifierRefactoringAction;
4030
_modifyUDTRefactoringAction = modifyUserDefinedTypeRefactoringAction;
4131
_encapsulateFieldInsertNewCodeRefactoringAction = encapsulateFieldInsertNewCodeRefactoringAction;
4232
}
4333

44-
public ICodeOnlyRefactoringAction<ReplaceReferencesModel> ReplaceReferences
45-
=> _replaceReferences;
46-
4734
public ICodeOnlyRefactoringAction<ReplaceDeclarationIdentifierModel> ReplaceDeclarationIdentifiers
4835
=> _replaceDeclarationIdentifiers;
4936

50-
public ICodeOnlyRefactoringAction<ReplacePrivateUDTMemberReferencesModel> ReplaceUDTMemberReferences
51-
=> _replaceUDTMemberReferencesRefactoringAction;
52-
5337
public ICodeOnlyRefactoringAction<ModifyUserDefinedTypeModel> ModifyUserDefinedType
5438
=> _modifyUDTRefactoringAction;
5539

Lines changed: 180 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,180 @@
1+
using Antlr4.Runtime;
2+
using Rubberduck.Parsing;
3+
using Rubberduck.Parsing.Grammar;
4+
using Rubberduck.Parsing.Rewriter;
5+
using Rubberduck.Parsing.Symbols;
6+
using Rubberduck.Parsing.VBA;
7+
using System.Collections.Generic;
8+
using System.Linq;
9+
10+
namespace Rubberduck.Refactorings.EncapsulateField
11+
{
12+
public interface IEncapsulateFieldReferenceReplacer
13+
{
14+
void ReplaceReferences<T>(IEnumerable<T> selectedCandidates,
15+
IRewriteSession rewriteSession) where T : IEncapsulateFieldCandidate;
16+
}
17+
/// <summary>
18+
/// EncapsulateFieldReferenceReplacer determines the replacement expressions for existing references
19+
/// of encapsulated fields. It supports both direct encapsulation and encapsulation after wrapping the
20+
/// target field in a Private UserDefinedType
21+
/// </summary>
22+
public class EncapsulateFieldReferenceReplacer : IEncapsulateFieldReferenceReplacer
23+
{
24+
private readonly IDeclarationFinderProvider _declarationFinderProvider;
25+
private readonly IPropertyAttributeSetsGenerator _propertyAttributeSetsGenerator;
26+
private readonly IUDTMemberReferenceProvider _udtMemberReferenceProvider;
27+
private readonly Dictionary<IdentifierReference, (ParserRuleContext, string)> _identifierReplacements = new Dictionary<IdentifierReference, (ParserRuleContext, string)>();
28+
29+
public EncapsulateFieldReferenceReplacer(IDeclarationFinderProvider declarationFinderProvider,
30+
IPropertyAttributeSetsGenerator propertyAttributeSetsGenerator,
31+
IUDTMemberReferenceProvider udtMemberReferenceProvider)
32+
{
33+
_declarationFinderProvider = declarationFinderProvider;
34+
_propertyAttributeSetsGenerator = propertyAttributeSetsGenerator;
35+
_udtMemberReferenceProvider = udtMemberReferenceProvider;
36+
}
37+
38+
public void ReplaceReferences<T>(IEnumerable<T> selectedCandidates, IRewriteSession rewriteSession) where T : IEncapsulateFieldCandidate
39+
{
40+
if (!selectedCandidates.Any())
41+
{
42+
return;
43+
}
44+
45+
ResolveReferenceContextReplacements(selectedCandidates);
46+
47+
foreach (var kvPair in _identifierReplacements)
48+
{
49+
var rewriter = rewriteSession.CheckOutModuleRewriter(kvPair.Key.QualifiedModuleName);
50+
(ParserRuleContext Context, string Text) = kvPair.Value;
51+
rewriter.Replace(Context, Text);
52+
}
53+
}
54+
55+
private void ResolveReferenceContextReplacements<T>(IEnumerable<T> selectedCandidates ) where T : IEncapsulateFieldCandidate
56+
{
57+
var selectedVariableDeclarations = selectedCandidates.Select(sc => sc.Declaration).Cast<VariableDeclaration>();
58+
59+
var udtFieldToMemberReferences = _udtMemberReferenceProvider.UdtFieldToMemberReferences(_declarationFinderProvider, selectedVariableDeclarations);
60+
61+
foreach (var field in selectedCandidates)
62+
{
63+
if (IsInstanceOfPrivateUDT(field))
64+
{
65+
if (udtFieldToMemberReferences.TryGetValue(field.Declaration, out var relevantReferences))
66+
{
67+
ResolvePrivateUDTMemberReferenceReplacements(field, relevantReferences);
68+
}
69+
continue;
70+
}
71+
72+
ResolveNonPrivateUDTFieldReferenceReplacements(field);
73+
}
74+
}
75+
76+
private void ResolvePrivateUDTMemberReferenceReplacements<T>(T field, IEnumerable<IdentifierReference> udtMemberReferencesToChange) where T: IEncapsulateFieldCandidate
77+
{
78+
if (field is IEncapsulateFieldAsUDTMemberCandidate wrappedField)
79+
{
80+
var wrappedField_WithStmtContexts = wrappedField.Declaration.References
81+
.Where(rf => rf.Context.Parent.Parent is VBAParser.WithStmtContext)
82+
.Select(rf => (rf, rf.Context));
83+
84+
foreach ((IdentifierReference idRef, ParserRuleContext prCtxt) in wrappedField_WithStmtContexts)
85+
{
86+
AddIdentifierReplacement(idRef, prCtxt, $"{wrappedField.ObjectStateUDT.FieldIdentifier}.{wrappedField.PropertyIdentifier}");
87+
}
88+
}
89+
90+
foreach (var paSet in _propertyAttributeSetsGenerator.GeneratePropertyAttributeSets(field))
91+
{
92+
foreach (var rf in paSet.Declaration.References.Where(idRef => udtMemberReferencesToChange.Contains(idRef)))
93+
{
94+
(ParserRuleContext context, string expression) = GenerateUDTMemberReplacementTuple(field, rf, paSet);
95+
AddIdentifierReplacement(rf, context, expression);
96+
}
97+
}
98+
}
99+
100+
private void ResolveNonPrivateUDTFieldReferenceReplacements<T>(T field) where T: IEncapsulateFieldCandidate
101+
{
102+
foreach (var idRef in field.Declaration.References.Where(rf => !(rf.IsArrayAccess || rf.IsDefaultMemberAccess)))
103+
{
104+
var replacementExpression = MustAccessUsingBackingField(idRef, field)
105+
? GetBackingIdentifier(field)
106+
: field.PropertyIdentifier;
107+
108+
if (RequiresModuleQualification(field, idRef, _declarationFinderProvider))
109+
{
110+
replacementExpression = $"{field.QualifiedModuleName.ComponentName}.{replacementExpression}";
111+
}
112+
113+
AddIdentifierReplacement(idRef, idRef.Context, replacementExpression);
114+
}
115+
}
116+
117+
private static (ParserRuleContext, string) GenerateUDTMemberReplacementTuple<T>(T field, IdentifierReference rf, PropertyAttributeSet paSet) where T : IEncapsulateFieldCandidate
118+
{
119+
var replacementToken = paSet.PropertyName;
120+
if (rf.IsAssignment && field.IsReadOnly)
121+
{
122+
replacementToken = paSet.BackingField;
123+
}
124+
125+
switch (rf.Context.Parent)
126+
{
127+
case VBAParser.WithMemberAccessExprContext wmaec:
128+
return (wmaec, rf.IsAssignment && field.IsReadOnly ? $".{paSet.PropertyName}" : paSet.PropertyName);
129+
case VBAParser.MemberAccessExprContext maec:
130+
return (maec, rf.IsAssignment && field.IsReadOnly ? replacementToken : paSet.PropertyName);
131+
default:
132+
return (rf.Context, replacementToken);
133+
}
134+
}
135+
136+
private static bool RequiresModuleQualification<T>(T field, IdentifierReference idRef, IDeclarationFinderProvider declarationFinderProvider) where T: IEncapsulateFieldCandidate
137+
{
138+
if (idRef.QualifiedModuleName == field.QualifiedModuleName)
139+
{
140+
return false;
141+
}
142+
143+
var isUDTField = field.Declaration.AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.UserDefinedType) ?? false;
144+
145+
return (isUDTField && !EncapsulateFieldUtilities.IsModuleQualifiedExternalReferenceOfUDTField(declarationFinderProvider, idRef, field.QualifiedModuleName))
146+
|| !(idRef.Context.IsDescendentOf<VBAParser.MemberAccessExprContext>() || idRef.Context.IsDescendentOf<VBAParser.WithMemberAccessExprContext>());
147+
}
148+
149+
private static bool IsInstanceOfPrivateUDT<T>(T field) where T: IEncapsulateFieldCandidate
150+
{
151+
bool IsPrivateUDT(IUserDefinedTypeCandidate u) => u.Declaration.AsTypeDeclaration.Accessibility == Accessibility.Private;
152+
153+
return field is IEncapsulateFieldAsUDTMemberCandidate wrappedField
154+
? wrappedField.WrappedCandidate is IUserDefinedTypeCandidate wrappedUDT && IsPrivateUDT(wrappedUDT)
155+
: field is IUserDefinedTypeCandidate udt && IsPrivateUDT(udt);
156+
}
157+
158+
private static bool MustAccessUsingBackingField(IdentifierReference rf, IEncapsulateFieldCandidate field)
159+
=> rf.QualifiedModuleName == field.QualifiedModuleName
160+
&& ((rf.IsAssignment && field.IsReadOnly) || field.Declaration.IsArray);
161+
162+
private static string GetBackingIdentifier(IEncapsulateFieldCandidate field)
163+
{
164+
var objStateUDT = field is IEncapsulateFieldAsUDTMemberCandidate udtM ? udtM.ObjectStateUDT : null;
165+
return objStateUDT is null
166+
? field.BackingIdentifier
167+
: $"{objStateUDT.FieldIdentifier}.{field.BackingIdentifier}";
168+
}
169+
170+
private void AddIdentifierReplacement(IdentifierReference idRef, ParserRuleContext context, string replacementText)
171+
{
172+
if (_identifierReplacements.ContainsKey(idRef))
173+
{
174+
_identifierReplacements[idRef] = (context, replacementText);
175+
return;
176+
}
177+
_identifierReplacements.Add(idRef, (context, replacementText));
178+
}
179+
}
180+
}
Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,31 @@
1+
using Rubberduck.Parsing.VBA;
2+
using Rubberduck.Refactorings.EncapsulateField;
3+
4+
namespace Rubberduck.Refactorings
5+
{
6+
public interface IEncapsulateFieldReferenceReplacerFactory
7+
{
8+
IEncapsulateFieldReferenceReplacer Create();
9+
}
10+
public class EncapsulateFieldReferenceReplacerFactory : IEncapsulateFieldReferenceReplacerFactory
11+
{
12+
private readonly IDeclarationFinderProvider _declarationFinderProvider;
13+
private readonly IPropertyAttributeSetsGenerator _propertyAttributeSetsGenerator;
14+
private IUDTMemberReferenceProvider _userDefinedTypeInstanceProvider;
15+
public EncapsulateFieldReferenceReplacerFactory(IDeclarationFinderProvider declarationFinderProvider,
16+
IPropertyAttributeSetsGenerator propertyAttributeSetsGenerator,
17+
IUDTMemberReferenceProvider userDefinedTypeInstanceProvider)
18+
{
19+
_declarationFinderProvider = declarationFinderProvider;
20+
_propertyAttributeSetsGenerator = propertyAttributeSetsGenerator;
21+
_userDefinedTypeInstanceProvider = userDefinedTypeInstanceProvider;
22+
}
23+
24+
public IEncapsulateFieldReferenceReplacer Create()
25+
{
26+
return new EncapsulateFieldReferenceReplacer(_declarationFinderProvider,
27+
_propertyAttributeSetsGenerator,
28+
_userDefinedTypeInstanceProvider);
29+
}
30+
}
31+
}

0 commit comments

Comments
 (0)