|
1 |
| -using Rubberduck.Parsing.Grammar; |
2 |
| -using Rubberduck.Parsing.Rewriter; |
| 1 | +using Rubberduck.Parsing.Rewriter; |
3 | 2 | using Rubberduck.Parsing.Symbols;
|
4 | 3 | using Rubberduck.Parsing.VBA;
|
5 | 4 | using Rubberduck.Refactorings.Common;
|
6 | 5 | using Rubberduck.Resources;
|
7 |
| -using Rubberduck.Refactorings.CodeBlockInsert; |
8 | 6 | using System;
|
9 | 7 | using System.Diagnostics;
|
10 | 8 | using System.Linq;
|
11 | 9 | using Rubberduck.Refactorings.EncapsulateField;
|
| 10 | +using System.Collections.Generic; |
12 | 11 |
|
13 | 12 | namespace Rubberduck.Refactorings.EncapsulateFieldInsertNewCode
|
14 | 13 | {
|
15 | 14 | public class EncapsulateFieldInsertNewCodeRefactoringAction : CodeOnlyRefactoringActionBase<EncapsulateFieldInsertNewCodeModel>
|
16 | 15 | {
|
17 |
| - private const string FourSpaces = " "; |
18 |
| - |
| 16 | + private readonly static string _doubleSpace = $"{Environment.NewLine}{Environment.NewLine}"; |
| 17 | + private int? _codeSectionStartIndex; |
19 | 18 | private readonly IDeclarationFinderProvider _declarationFinderProvider;
|
20 |
| - private readonly IRewritingManager _rewritingManager; |
21 |
| - private readonly ICodeBuilder _codeBuilder; |
22 |
| - private readonly ICodeOnlyRefactoringAction<CodeBlockInsertModel> _codeBlockInsertRefactoringAction; |
| 19 | + private readonly IEncapsulateFieldCodeBuilderFactory _encapsulateFieldCodeBuilderFactory; |
23 | 20 | public EncapsulateFieldInsertNewCodeRefactoringAction(
|
24 |
| - CodeBlockInsertRefactoringAction codeBlockInsertRefactoringAction, |
25 | 21 | IDeclarationFinderProvider declarationFinderProvider,
|
26 |
| - IRewritingManager rewritingManager, |
27 |
| - ICodeBuilder codeBuilder) |
| 22 | + IRewritingManager rewritingManager, |
| 23 | + IEncapsulateFieldCodeBuilderFactory encapsulateFieldCodeBuilderFactory) |
28 | 24 | : base(rewritingManager)
|
29 | 25 | {
|
30 | 26 | _declarationFinderProvider = declarationFinderProvider;
|
31 |
| - _rewritingManager = rewritingManager; |
32 |
| - _codeBuilder = codeBuilder; |
33 |
| - _codeBlockInsertRefactoringAction = codeBlockInsertRefactoringAction; |
| 27 | + _encapsulateFieldCodeBuilderFactory = encapsulateFieldCodeBuilderFactory; |
34 | 28 | }
|
35 | 29 |
|
36 | 30 | public override void Refactor(EncapsulateFieldInsertNewCodeModel model, IRewriteSession rewriteSession)
|
37 | 31 | {
|
38 |
| - var codeSectionStartIndex = _declarationFinderProvider.DeclarationFinder |
| 32 | + _codeSectionStartIndex = _declarationFinderProvider.DeclarationFinder |
39 | 33 | .Members(model.QualifiedModuleName).Where(m => m.IsMember())
|
40 | 34 | .OrderBy(c => c.Selection)
|
41 | 35 | .FirstOrDefault()?.Context.Start.TokenIndex;
|
42 | 36 |
|
43 |
| - var codeBlockInsertModel = new CodeBlockInsertModel() |
44 |
| - { |
45 |
| - QualifiedModuleName = model.QualifiedModuleName, |
46 |
| - SelectedFieldCandidates = model.SelectedFieldCandidates, |
47 |
| - NewContent = model.NewContent, |
48 |
| - CodeSectionStartIndex = codeSectionStartIndex, |
49 |
| - IncludeComments = model.IncludeNewContentMarker |
50 |
| - }; |
| 37 | + LoadNewPropertyBlocks(model, rewriteSession); |
51 | 38 |
|
52 |
| - LoadNewPropertyBlocks(codeBlockInsertModel, _codeBuilder, rewriteSession); |
| 39 | + InsertBlocks(model, rewriteSession); |
53 | 40 |
|
54 |
| - _codeBlockInsertRefactoringAction.Refactor(codeBlockInsertModel, rewriteSession); |
| 41 | + model.NewContentAggregator = null; |
55 | 42 | }
|
56 | 43 |
|
57 |
| - public void LoadNewPropertyBlocks(CodeBlockInsertModel model, ICodeBuilder codeBuilder, IRewriteSession rewriteSession) |
| 44 | + public void LoadNewPropertyBlocks(EncapsulateFieldInsertNewCodeModel model, IRewriteSession rewriteSession) |
58 | 45 | {
|
59 |
| - if (model.IncludeComments) |
60 |
| - { |
61 |
| - model.AddContentBlock(NewContentType.PostContentMessage, RubberduckUI.EncapsulateField_PreviewMarker); |
62 |
| - } |
63 |
| - |
| 46 | + var builder = _encapsulateFieldCodeBuilderFactory.Create(); |
64 | 47 | foreach (var propertyAttributes in model.SelectedFieldCandidates.SelectMany(f => f.PropertyAttributeSets))
|
65 | 48 | {
|
66 | 49 | Debug.Assert(propertyAttributes.Declaration.DeclarationType.HasFlag(DeclarationType.Variable) || propertyAttributes.Declaration.DeclarationType.HasFlag(DeclarationType.UserDefinedTypeMember));
|
67 | 50 |
|
68 |
| - LoadPropertyGetCodeBlock(model, propertyAttributes, codeBuilder); |
69 |
| - |
70 |
| - if (propertyAttributes.GenerateLetter) |
71 |
| - { |
72 |
| - LoadPropertyLetCodeBlock(model, propertyAttributes, codeBuilder); |
73 |
| - } |
| 51 | + var (Get, Let, Set) = builder.BuildPropertyBlocks(propertyAttributes); |
74 | 52 |
|
75 |
| - if (propertyAttributes.GenerateSetter) |
76 |
| - { |
77 |
| - LoadPropertySetCodeBlock(model, propertyAttributes, codeBuilder); |
78 |
| - } |
| 53 | + var blocks = new List<string>() { Get, Let, Set }; |
| 54 | + blocks.ForEach(s => model.NewContentAggregator.AddNewContent(NewContentType.CodeSectionBlock, s)); |
79 | 55 | }
|
80 | 56 | }
|
81 | 57 |
|
82 |
| - private static void LoadPropertyLetCodeBlock(CodeBlockInsertModel model, PropertyAttributeSet propertyAttributes, ICodeBuilder codeBuilder) |
| 58 | + private void InsertBlocks(EncapsulateFieldInsertNewCodeModel model, IRewriteSession rewriteSession) |
83 | 59 | {
|
84 |
| - var letterContent = $"{FourSpaces}{propertyAttributes.BackingField} = {propertyAttributes.ParameterName}"; |
85 |
| - if (!codeBuilder.TryBuildPropertyLetCodeBlock(propertyAttributes.Declaration, propertyAttributes.PropertyName, out var propertyLet, content: letterContent)) |
| 60 | + var newDeclarationSectionBlock = model.NewContentAggregator.RetrieveBlock(NewContentType.UserDefinedTypeDeclaration, NewContentType.DeclarationBlock, NewContentType.CodeSectionBlock); |
| 61 | + if (string.IsNullOrEmpty(newDeclarationSectionBlock)) |
86 | 62 | {
|
87 |
| - throw new ArgumentException(); |
| 63 | + return; |
88 | 64 | }
|
89 |
| - model.AddContentBlock(NewContentType.CodeSectionBlock, propertyLet); |
90 |
| - } |
91 | 65 |
|
92 |
| - private static void LoadPropertySetCodeBlock(CodeBlockInsertModel model, PropertyAttributeSet propertyAttributes, ICodeBuilder codeBuilder) |
93 |
| - { |
94 |
| - var setterContent = $"{FourSpaces}{Tokens.Set} {propertyAttributes.BackingField} = {propertyAttributes.ParameterName}"; |
95 |
| - if (!codeBuilder.TryBuildPropertySetCodeBlock(propertyAttributes.Declaration, propertyAttributes.PropertyName, out var propertySet, content: setterContent)) |
| 66 | + var allNewContent = string.Join(_doubleSpace, new string[] { newDeclarationSectionBlock }); |
| 67 | + |
| 68 | + var previewMarker = model.NewContentAggregator.RetrieveBlock(RubberduckUI.EncapsulateField_PreviewMarker); |
| 69 | + if (!string.IsNullOrEmpty(previewMarker)) |
96 | 70 | {
|
97 |
| - throw new ArgumentException(); |
| 71 | + allNewContent = $"{allNewContent}{Environment.NewLine}{previewMarker}"; |
98 | 72 | }
|
99 |
| - model.AddContentBlock(NewContentType.CodeSectionBlock, propertySet); |
| 73 | + |
| 74 | + var rewriter = rewriteSession.CheckOutModuleRewriter(model.QualifiedModuleName); |
| 75 | + |
| 76 | + InsertBlock(allNewContent, _codeSectionStartIndex, rewriter); |
100 | 77 | }
|
101 | 78 |
|
102 |
| - private static void LoadPropertyGetCodeBlock(CodeBlockInsertModel model, PropertyAttributeSet propertyAttributes, ICodeBuilder codeBuilder) |
| 79 | + private static void InsertBlock(string content, int? insertionIndex, IModuleRewriter rewriter) |
103 | 80 | {
|
104 |
| - var getterContent = $"{propertyAttributes.PropertyName} = {propertyAttributes.BackingField}"; |
105 |
| - if (propertyAttributes.UsesSetAssignment) |
| 81 | + if (string.IsNullOrEmpty(content)) |
106 | 82 | {
|
107 |
| - getterContent = $"{Tokens.Set} {getterContent}"; |
| 83 | + return; |
108 | 84 | }
|
109 | 85 |
|
110 |
| - if (propertyAttributes.AsTypeName.Equals(Tokens.Variant) && !propertyAttributes.Declaration.IsArray) |
| 86 | + if (insertionIndex.HasValue) |
111 | 87 | {
|
112 |
| - getterContent = string.Join(Environment.NewLine, |
113 |
| - $"{Tokens.If} IsObject({propertyAttributes.BackingField}) {Tokens.Then}", |
114 |
| - $"{FourSpaces}{Tokens.Set} {propertyAttributes.PropertyName} = {propertyAttributes.BackingField}", |
115 |
| - Tokens.Else, |
116 |
| - $"{FourSpaces}{propertyAttributes.PropertyName} = {propertyAttributes.BackingField}", |
117 |
| - $"{Tokens.End} {Tokens.If}", |
118 |
| - Environment.NewLine); |
| 88 | + rewriter.InsertBefore(insertionIndex.Value, $"{content}{_doubleSpace}"); |
| 89 | + return; |
119 | 90 | }
|
120 |
| - |
121 |
| - if (!codeBuilder.TryBuildPropertyGetCodeBlock(propertyAttributes.Declaration, propertyAttributes.PropertyName, out var propertyGet, content: $"{FourSpaces}{getterContent}")) |
122 |
| - { |
123 |
| - throw new ArgumentException(); |
124 |
| - } |
125 |
| - |
126 |
| - model.AddContentBlock(NewContentType.CodeSectionBlock, propertyGet); |
| 91 | + rewriter.InsertBefore(rewriter.TokenStream.Size - 1, $"{_doubleSpace}{content}"); |
127 | 92 | }
|
128 | 93 | }
|
129 | 94 | }
|
0 commit comments