Skip to content

Commit 734ca5b

Browse files
committed
Merge branch 'rubberduck-vba/next' into next
2 parents 0da217d + a64fc33 commit 734ca5b

35 files changed

+632
-431
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingModuleAnnotationInspection.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
1717
/// do not have a Rubberduck annotation corresponding to the hidden VB attribute.
1818
/// </why>
1919
/// <example hasResult="true">
20-
/// <module name="MyModule" type="Class Module">
20+
/// <module name="MyModule" type="Predeclared Class">
2121
/// <![CDATA[
2222
/// Attribute VB_PredeclaredId = True
2323
/// Option Explicit
@@ -26,7 +26,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
2626
/// </module>
2727
/// </example>
2828
/// <example hasResult="false">
29-
/// <module name="MyModule" type="Class Module">
29+
/// <module name="MyModule" type="Predeclared Class">
3030
/// <![CDATA[
3131
/// Attribute VB_PredeclaredId = True
3232
/// '@PredeclaredId
@@ -92,4 +92,4 @@ protected override string ResultDescription(Declaration declaration, (string Att
9292
string.Join(", ", properties.AttributeValues));
9393
}
9494
}
95-
}
95+
}

Rubberduck.Refactorings/Common/CodeBuilder.cs

Lines changed: 16 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
using Rubberduck.Parsing.Grammar;
1+
using Rubberduck.Common;
2+
using Rubberduck.Parsing.Grammar;
23
using Rubberduck.Parsing.Symbols;
34
using System;
45
using System.Collections.Generic;
@@ -11,19 +12,13 @@ public interface ICodeBuilder
1112
/// <summary>
1213
/// Returns ModuleBodyElementDeclaration signature with an ImprovedArgument list
1314
/// </summary>
14-
/// <param name="declaration"></param>
15-
/// <returns></returns>
1615
string ImprovedFullMemberSignature(ModuleBodyElementDeclaration declaration);
1716

1817
/// <summary>
1918
/// Returns a ModuleBodyElementDeclaration block
2019
/// with an ImprovedArgument List
2120
/// </summary>
22-
/// <param name="declaration"></param>
2321
/// <param name="content">Main body content/logic of the member</param>
24-
/// <param name="accessibility"></param>
25-
/// <param name="newIdentifier"></param>
26-
/// <returns></returns>
2722
string BuildMemberBlockFromPrototype(ModuleBodyElementDeclaration declaration,
2823
string content = null,
2924
string accessibility = null,
@@ -34,19 +29,14 @@ string BuildMemberBlockFromPrototype(ModuleBodyElementDeclaration declaration,
3429
/// 1. Explicitly declares Property Let\Set value parameter as ByVal
3530
/// 2. Ensures UserDefined Type parameters are declared either explicitly or implicitly as ByRef
3631
/// </summary>
37-
/// <param name="declaration"></param>
38-
/// <returns></returns>
3932
string ImprovedArgumentList(ModuleBodyElementDeclaration declaration);
4033

4134
/// <summary>
4235
/// Generates a Property Get codeblock based on the prototype declaration
4336
/// </summary>
4437
/// <param name="prototype">VariableDeclaration or UserDefinedTypeMember</param>
45-
/// <param name="propertyIdentifier"></param>
46-
/// <param name="accessibility"></param>
4738
/// <param name="content">Member body content. Formatting is the responsibility of the caller</param>
48-
/// <param name="parameterIdentifier">Defaults to 'value' unless otherwise specified</param>
49-
/// <returns></returns>
39+
/// <param name="parameterIdentifier">Defaults to '<paramref name="propertyIdentifier"/>Value' unless otherwise specified</param>
5040
bool TryBuildPropertyGetCodeBlock(Declaration prototype,
5141
string propertyIdentifier,
5242
out string codeBlock,
@@ -57,11 +47,8 @@ bool TryBuildPropertyGetCodeBlock(Declaration prototype,
5747
/// Generates a Property Let codeblock based on the prototype declaration
5848
/// </summary>
5949
/// <param name="prototype">VariableDeclaration or UserDefinedTypeMember</param>
60-
/// <param name="propertyIdentifier"></param>
61-
/// <param name="accessibility"></param>
62-
/// <param name="content">Membmer body content. Formatting is the responsibility of the caller</param>
63-
/// <param name="parameterIdentifier">Defaults to 'value' unless otherwise specified</param>
64-
/// <returns></returns>
50+
/// <param name="content">Member body content. Formatting is the responsibility of the caller</param>
51+
/// <param name="parameterIdentifier">Defaults to '<paramref name="propertyIdentifier"/>Value' unless otherwise specified</param>
6552
bool TryBuildPropertyLetCodeBlock(Declaration prototype,
6653
string propertyIdentifier,
6754
out string codeBlock,
@@ -73,21 +60,26 @@ bool TryBuildPropertyLetCodeBlock(Declaration prototype,
7360
/// Generates a Property Set codeblock based on the prototype declaration
7461
/// </summary>
7562
/// <param name="prototype">VariableDeclaration or UserDefinedTypeMember</param>
76-
/// <param name="propertyIdentifier"></param>
77-
/// <param name="accessibility"></param>
78-
/// <param name="content">Membmer body content. Formatting is the responsibility of the caller</param>
79-
/// <param name="parameterIdentifier">Defaults to 'value' unless otherwise specified</param>
80-
/// <returns></returns>
63+
/// <param name="content">Member body content. Formatting is the responsibility of the caller</param>
64+
/// <param name="parameterIdentifier">Defaults to '<paramref name="propertyIdentifier"/>Value' unless otherwise specified</param>
8165
bool TryBuildPropertySetCodeBlock(Declaration prototype,
8266
string propertyIdentifier,
8367
out string codeBlock,
8468
string accessibility = null,
8569
string content = null,
8670
string parameterIdentifier = null);
71+
/// <summary>
72+
/// Generates a default RHS property parameter IdentifierName
73+
/// </summary>
74+
/// <param name="propertyIdentifier">Let/Set Property IdentifierName</param>
75+
string BuildPropertyRhsParameterName(string propertyIdentifier);
8776
}
8877

8978
public class CodeBuilder : ICodeBuilder
9079
{
80+
public string BuildPropertyRhsParameterName(string propertyIdentifier)
81+
=> string.Format(Resources.Refactorings.Refactorings.CodeBuilder_DefaultPropertyRHSParamFormat, propertyIdentifier.ToLowerCaseFirstLetter());
82+
9183
public string BuildMemberBlockFromPrototype(ModuleBodyElementDeclaration declaration,
9284
string content = null,
9385
string accessibility = null,
@@ -127,7 +119,7 @@ private bool TryBuildPropertyBlockFromTarget<T>(T prototype, DeclarationType let
127119
return false;
128120
}
129121

130-
var propertyValueParam = parameterIdentifier ?? Resources.RubberduckUI.EncapsulateField_DefaultPropertyParameter;
122+
var propertyValueParam = parameterIdentifier ?? BuildPropertyRhsParameterName(propertyIdentifier);
131123

132124
var asType = prototype.IsArray
133125
? $"{Tokens.Variant}"
Lines changed: 108 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,108 @@
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 System;
7+
using System.Collections.Generic;
8+
using System.Linq;
9+
10+
namespace Rubberduck.Refactorings.Common
11+
{
12+
public static class IModuleRewriterExtensions
13+
{
14+
/// <summary>
15+
/// Removes variable declaration and subsequent <c>VBAParser.EndOfStatementContext</c>
16+
/// depending on the <paramref name="removeEndOfStmtContext"/> flag.
17+
/// This function is intended to be called only once per rewriter within a given <c>ModuleRewriteSession</c>.
18+
/// </summary>
19+
/// <remarks>
20+
/// Calling this function with <paramref name="removeEndOfStmtContext"/> defaulted to <c>true</c>
21+
/// avoids leaving residual newlines between the deleted declaration and the next declaration.
22+
/// The one-time call constraint is required for scenarios where variables to delete are declared in a list. Specifically,
23+
/// the use case where all the variables in the list are to be removed.
24+
/// If the variables to remove are not declared in a list, then this function can be called multiple times.
25+
/// </remarks>
26+
public static void RemoveVariables(this IModuleRewriter rewriter, IEnumerable<VariableDeclaration> toRemove, bool removeEndOfStmtContext = true)
27+
{
28+
if (!toRemove.Any())
29+
{
30+
return;
31+
}
32+
33+
var fieldsToDeleteByListContext = toRemove.Distinct()
34+
.ToLookup(f => f.Context.GetAncestor<VBAParser.VariableListStmtContext>());
35+
36+
foreach (var fieldsToDelete in fieldsToDeleteByListContext)
37+
{
38+
var variableList = fieldsToDelete.Key.children.OfType<VBAParser.VariableSubStmtContext>();
39+
40+
if (variableList.Count() == fieldsToDelete.Count())
41+
{
42+
if (fieldsToDelete.First().ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
43+
{
44+
rewriter.RemoveDeclarationContext<VBAParser.ModuleDeclarationsElementContext>(fieldsToDelete.First(), removeEndOfStmtContext);
45+
}
46+
else
47+
{
48+
rewriter.RemoveDeclarationContext<VBAParser.BlockStmtContext>(fieldsToDelete.First(), removeEndOfStmtContext);
49+
}
50+
continue;
51+
}
52+
53+
foreach (var target in fieldsToDelete)
54+
{
55+
rewriter.Remove(target);
56+
}
57+
}
58+
}
59+
60+
/// <summary>
61+
/// Removes a member declaration and subsequent <c>VBAParser.EndOfStatementContext</c>
62+
/// depending on the <paramref name="removeEndOfStmtContext"/> flag.
63+
/// </summary>
64+
/// <remarks>
65+
/// Calling this function with <paramref name="removeEndOfStmtContext"/> defaulted to <c>true</c>
66+
/// avoids leaving residual newlines between the deleted declaration and the next declaration.
67+
/// </remarks>
68+
public static void RemoveMember(this IModuleRewriter rewriter, ModuleBodyElementDeclaration target, bool removeEndOfStmtContext = true)
69+
{
70+
RemoveMembers(rewriter, new ModuleBodyElementDeclaration[] { target }, removeEndOfStmtContext);
71+
}
72+
73+
/// <summary>
74+
/// Removes member declarations and subsequent <c>VBAParser.EndOfStatementContext</c>
75+
/// depending on the <paramref name="removeEndOfStmtContext"/> flag.
76+
/// </summary>
77+
/// <remarks>
78+
/// Calling this function with <paramref name="removeEndOfStmtContext"/> defaulted to <c>true</c>
79+
/// avoids leaving residual newlines between the deleted declaration and the next declaration.
80+
/// </remarks>
81+
public static void RemoveMembers(this IModuleRewriter rewriter, IEnumerable<ModuleBodyElementDeclaration> toRemove, bool removeEndOfStmtContext = true)
82+
{
83+
if (!toRemove.Any())
84+
{
85+
return;
86+
}
87+
88+
foreach (var member in toRemove)
89+
{
90+
rewriter.RemoveDeclarationContext<VBAParser.ModuleBodyElementContext>(member, removeEndOfStmtContext);
91+
}
92+
}
93+
94+
private static void RemoveDeclarationContext<T>(this IModuleRewriter rewriter, Declaration declaration, bool removeEndOfStmtContext = true) where T : ParserRuleContext
95+
{
96+
if (!declaration.Context.TryGetAncestor<T>(out var elementContext))
97+
{
98+
throw new ArgumentException();
99+
}
100+
101+
rewriter.Remove(elementContext);
102+
if (removeEndOfStmtContext && elementContext.TryGetFollowingContext<VBAParser.EndOfStatementContext>(out var nextContext))
103+
{
104+
rewriter.Remove(nextContext);
105+
}
106+
}
107+
}
108+
}

Rubberduck.Refactorings/EncapsulateField/EncapsulateFieldElementsBuilder.cs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
using Rubberduck.Parsing.Symbols;
33
using Rubberduck.Parsing.VBA;
44
using Rubberduck.Refactorings.Common;
5-
using Rubberduck.Refactorings.EncapsulateField.Extensions;
65
using Rubberduck.VBEditor;
76
using System;
87
using System.Collections.Generic;
@@ -16,12 +15,14 @@ public class EncapsulateFieldElementsBuilder
1615
private readonly IDeclarationFinderProvider _declarationFinderProvider;
1716
private QualifiedModuleName _targetQMN;
1817
private string _defaultObjectStateUDTTypeName;
18+
private ICodeBuilder _codeBuilder;
1919

2020
public EncapsulateFieldElementsBuilder(IDeclarationFinderProvider declarationFinderProvider, QualifiedModuleName targetQMN)
2121
{
2222
_declarationFinderProvider = declarationFinderProvider;
2323
_targetQMN = targetQMN;
2424
_defaultObjectStateUDTTypeName = $"T{_targetQMN.ComponentName}";
25+
_codeBuilder = new CodeBuilder();
2526
CreateRefactoringElements();
2627
}
2728

@@ -110,7 +111,7 @@ private IEncapsulateFieldCandidate CreateCandidate(Declaration target, IValidate
110111
if (target.IsUserDefinedType())
111112
{
112113
var udtValidator = EncapsulateFieldValidationsProvider.NameOnlyValidator(NameValidators.UserDefinedType);
113-
var udtField = new UserDefinedTypeCandidate(target, udtValidator) as IUserDefinedTypeCandidate;
114+
var udtField = new UserDefinedTypeCandidate(target, udtValidator, _codeBuilder.BuildPropertyRhsParameterName) as IUserDefinedTypeCandidate;
114115

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

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

130131
udtField.AddMember(candidateUDTMember);
131132
}
@@ -141,10 +142,10 @@ private IEncapsulateFieldCandidate CreateCandidate(Declaration target, IValidate
141142
}
142143
else if (target.IsArray)
143144
{
144-
return new ArrayCandidate(target, validator);
145+
return new ArrayCandidate(target, validator, _codeBuilder.BuildPropertyRhsParameterName);
145146
}
146147

147-
var candidate = new EncapsulateFieldCandidate(target, validator);
148+
var candidate = new EncapsulateFieldCandidate(target, validator, _codeBuilder.BuildPropertyRhsParameterName);
148149
return candidate;
149150
}
150151

Rubberduck.Refactorings/EncapsulateField/EncapsulateFieldRefactoring.cs

Lines changed: 8 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,6 @@
66
using Rubberduck.VBEditor;
77
using Rubberduck.SmartIndenter;
88
using Rubberduck.VBEditor.Utility;
9-
using System;
109

1110
namespace Rubberduck.Refactorings.EncapsulateField
1211
{
@@ -91,26 +90,25 @@ protected override EncapsulateFieldModel InitializeModel(Declaration target)
9190

9291
protected override void RefactorImpl(EncapsulateFieldModel model)
9392
{
94-
var refactorRewriteSession = new EncapsulateFieldRewriteSession(_rewritingManager.CheckOutCodePaneSession()) as IEncapsulateFieldRewriteSession;
93+
var executableRewriteSession = _rewritingManager.CheckOutCodePaneSession();
9594

96-
refactorRewriteSession = RefactorRewrite(model, refactorRewriteSession);
95+
RefactorRewrite(model, executableRewriteSession);
9796

98-
if (!refactorRewriteSession.TryRewrite())
97+
if (!executableRewriteSession.TryRewrite())
9998
{
100-
throw new RewriteFailedException(refactorRewriteSession.RewriteSession);
99+
throw new RewriteFailedException(executableRewriteSession);
101100
}
102101
}
103102

104103
private string PreviewRewrite(EncapsulateFieldModel model)
105104
{
106-
var previewSession = new EncapsulateFieldRewriteSession(_rewritingManager.CheckOutCodePaneSession()) as IEncapsulateFieldRewriteSession; ;
105+
var previewSession = RefactorRewrite(model, _rewritingManager.CheckOutCodePaneSession(), true);
107106

108-
previewSession = RefactorRewrite(model, previewSession, true);
109-
110-
return previewSession.CreatePreview(model.QualifiedModuleName);
107+
return previewSession.CheckOutModuleRewriter(model.QualifiedModuleName)
108+
.GetText();
111109
}
112110

113-
private IEncapsulateFieldRewriteSession RefactorRewrite(EncapsulateFieldModel model, IEncapsulateFieldRewriteSession refactorRewriteSession, bool asPreview = false)
111+
private IRewriteSession RefactorRewrite(EncapsulateFieldModel model, IRewriteSession refactorRewriteSession, bool asPreview = false)
114112
{
115113
if (!model.SelectedFieldCandidates.Any()) { return refactorRewriteSession; }
116114

0 commit comments

Comments
 (0)