Skip to content

Commit 1143a56

Browse files
grleachmanretailcoder
authored andcommitted
Changes for #1225 ExtractMethodRefactoring (#1564)
* Wrap CodeModule. Add RD Interface * Run AutoFormatter over file * fix xml comments * Add a method for ParseString for a module. * Heavy refactoring of ExtractMethodRefactoring #1225. Provisionally remove GUI interaction as it's not required. Add stubs for tests. * Marker for needing to validate the MEthodName and increment. * #1225 : Add checking for Multiple NewMethod signatures. Start work on ExtractMethodSelectionValidation, aka CanExecute * prep for next stage of ExtractMethodRefactor * Validate selection is within a single method * Validate selection procEndLine only needs ParserRuleContext to validate * #1225 : Removed Obsolete Call on method siganture * #1225 modify tests for new spec on Method Call. change from underscore nomenclature * #1225 prep for local variable only used within selection * completed logic for ExtractMethodModel ByVal, ByRef, MoveIn * Adjust the method for determining byval, byref and movein * Extract methods and pull together with surrounding code. * Break down the Extraction and Testing a little deeper * Working through requirements now. Specifications almost complete. UI interfacing needs refactoring. Some nasty bits here and there * Why was that left out ??. commit interface for ExtractMethodRule! * End of my exploration into ExtractMethodRefactoring. Maybe I'll come back to this. * Final refactorings, now only need to apply the blackbox testing * final implementation of this version. Haven't implemented line lable moves * #1225 added check for moving an internally declared dim. Now need to resolve if that dim is used externally * add NCrunch to git ignore
1 parent e6e991d commit 1143a56

35 files changed

+2245
-433
lines changed

.gitignore

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -83,6 +83,7 @@ _TeamCity*
8383
# NCrunch
8484
*.ncrunch*
8585
.*crunch*.local.xml
86+
_Ncrunch*
8687

8788
# Installshield output folder
8889
[Ee]xpress/

RetailCoder.VBE/Common/DeclarationExtensions.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -231,8 +231,8 @@ public static IEnumerable<Declaration> FindBuiltInEventHandlers(this IEnumerable
231231
}
232232

233233
/// <summary>
234-
/// Gets the <see cref="Declaration"/> of the specified <see cref="type"/>,
235-
/// at the specified <see cref="selection"/>.
234+
/// Gets the <see cref="Declaration"/> of the specified <see cref="DeclarationType"/>,
235+
/// at the specified <see cref="QualifiedSelection"/>.
236236
/// Returns the declaration if selection is on an identifier reference.
237237
/// </summary>
238238
public static Declaration FindSelectedDeclaration(this IEnumerable<Declaration> declarations, QualifiedSelection selection, DeclarationType type, Func<Declaration, Selection> selector = null)
@@ -241,8 +241,8 @@ public static Declaration FindSelectedDeclaration(this IEnumerable<Declaration>
241241
}
242242

243243
/// <summary>
244-
/// Gets the <see cref="Declaration"/> of the specified <see cref="types"/>,
245-
/// at the specified <see cref="selection"/>.
244+
/// Gets the <see cref="Declaration"/> of the specified <see cref="DeclarationType"/>,
245+
/// at the specified <see cref="QualifiedSelection"/>.
246246
/// Returns the declaration if selection is on an identifier reference.
247247
/// </summary>
248248
public static Declaration FindSelectedDeclaration(this IEnumerable<Declaration> declarations, QualifiedSelection selection, IEnumerable<DeclarationType> types, Func<Declaration, Selection> selector = null)
Lines changed: 73 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,73 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using System.Text;
5+
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.VBEditor;
7+
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodeModule;
8+
9+
namespace Rubberduck.Refactorings.ExtractMethod
10+
{
11+
public class ExtractMethodExtraction : IExtractMethodExtraction
12+
{
13+
14+
public void apply(ICodeModuleWrapper codeModule, IExtractMethodModel model, Selection selection)
15+
{
16+
var newMethodCall = model.Method.NewMethodCall();
17+
var positionToInsertNewMethod = model.PositionForNewMethod;
18+
var positionForMethodCall = model.PositionForMethodCall;
19+
var selectionToRemove = model.SelectionToRemove;
20+
21+
// The next 4 lines are dependent on the positions of the various parts,
22+
// so have to be applied in the correct order.
23+
var newMethod = constructLinesOfProc(codeModule, model);
24+
codeModule.InsertLines(positionToInsertNewMethod.StartLine, newMethod);
25+
removeSelection(codeModule, selectionToRemove);
26+
codeModule.InsertLines(selection.StartLine, newMethodCall);
27+
}
28+
29+
public virtual void removeSelection(ICodeModuleWrapper codeModule, IEnumerable<Selection> selection)
30+
{
31+
foreach (var item in selection)
32+
{
33+
var start = item.StartLine;
34+
var end = item.EndLine;
35+
var lineCount = end - start + 1;
36+
37+
codeModule.DeleteLines(start,lineCount);
38+
39+
}
40+
}
41+
public virtual string constructLinesOfProc(ICodeModuleWrapper codeModule, IExtractMethodModel model)
42+
{
43+
44+
var newLine = Environment.NewLine;
45+
var method = model.Method;
46+
var keyword = Tokens.Sub;
47+
var asTypeClause = string.Empty;
48+
var selection = model.SelectionToRemove;
49+
50+
51+
var access = method.Accessibility.ToString();
52+
var extractedParams = method.Parameters.Select(p => ExtractedParameter.PassedBy.ByRef + " " + p.Name + " " + Tokens.As + " " + p.TypeName);
53+
var parameters = "(" + string.Join(", ", extractedParams) + ")";
54+
55+
//method signature
56+
var result = access + ' ' + keyword + ' ' + method.MethodName + parameters + ' ' + asTypeClause + newLine;
57+
58+
// method body
59+
string textToMove = "";
60+
foreach (var item in selection)
61+
{
62+
textToMove += codeModule.get_Lines(item.StartLine, item.EndLine - item.StartLine + 1);
63+
textToMove += Environment.NewLine;
64+
}
65+
66+
// method end;
67+
result += textToMove;
68+
result += Tokens.End + " " + Tokens.Sub;
69+
return result;
70+
}
71+
72+
}
73+
}
Lines changed: 107 additions & 58 deletions
Original file line numberDiff line numberDiff line change
@@ -1,108 +1,157 @@
11
using System;
2+
using System.Collections;
23
using System.Collections.Generic;
4+
using System.Diagnostics;
35
using System.Linq;
46
using Antlr4.Runtime;
57
using Microsoft.Vbe.Interop;
68
using Rubberduck.Common;
79
using Rubberduck.Parsing;
10+
using Rubberduck.Parsing.Grammar;
811
using Rubberduck.Parsing.Symbols;
912
using Rubberduck.VBEditor;
1013
using Rubberduck.VBEditor.Extensions;
1114

1215
namespace Rubberduck.Refactorings.ExtractMethod
1316
{
14-
public class ExtractMethodModel
17+
18+
public class ExtractMethodModel : IExtractMethodModel
1519
{
16-
public ExtractMethodModel(VBE vbe, IEnumerable<Declaration> declarations, QualifiedSelection selection)
20+
private const string NEW_METHOD = "NewMethod";
21+
22+
public ExtractMethodModel(List<IExtractMethodRule> emRules, IExtractedMethod extractedMethod)
1723
{
18-
var items = declarations.ToList();
24+
_rules = emRules;
25+
_extractedMethod = extractedMethod;
26+
}
1927

20-
_sourceMember = items.FindSelectedDeclaration(selection, DeclarationExtensions.ProcedureTypes, d => ((ParserRuleContext)d.Context.Parent).GetSelection());
21-
if (_sourceMember == null)
28+
29+
public void extract(IEnumerable<Declaration> declarations, QualifiedSelection selection, string selectedCode)
30+
{
31+
var items = declarations.ToList();
32+
var sourceMember = items.FindSelectedDeclaration(selection, DeclarationExtensions.ProcedureTypes, d => ((ParserRuleContext)d.Context.Parent).GetSelection());
33+
if (sourceMember == null)
2234
{
2335
throw new InvalidOperationException("Invalid selection.");
2436
}
2537

38+
var inScopeDeclarations = items.Where(item => item.ParentScope == sourceMember.Scope).ToList();
39+
40+
_byref = new List<Declaration>();
41+
_byval = new List<Declaration>();
42+
_declarationsToMove = new List<Declaration>();
43+
2644
_extractedMethod = new ExtractedMethod();
45+
2746

28-
_selection = selection;
29-
_selectedCode = vbe.ActiveCodePane.CodeModule.GetLines(selection.Selection);
47+
var selectionToRemove = new List<Selection>();
48+
var selectionStartLine = selection.Selection.StartLine;
49+
var selectionEndLine = selection.Selection.EndLine;
3050

31-
var inScopeDeclarations = items.Where(item => item.ParentScope == _sourceMember.Scope).ToList();
51+
var methodInsertLine = sourceMember.Context.Stop.Line + 1;
52+
_positionForNewMethod = new Selection(methodInsertLine, 1, methodInsertLine, 1);
3253

33-
var inSelection = inScopeDeclarations.SelectMany(item => item.References)
34-
.Where(item => selection.Selection.Contains(item.Selection))
35-
.ToList();
54+
// https://github.com/rubberduck-vba/Rubberduck/wiki/Extract-Method-Refactoring-%3A-Workings---Determining-what-params-to-move
55+
foreach (var item in inScopeDeclarations)
56+
{
57+
var flags = new Byte();
58+
59+
foreach (var oRef in item.References)
60+
{
61+
foreach (var rule in _rules)
62+
{
63+
rule.setValidFlag(ref flags, oRef, selection.Selection);
64+
}
65+
}
66+
67+
//TODO: extract this to seperate class.
68+
if (flags < 4) { /*ignore the variable*/ }
69+
else if (flags < 12)
70+
_byref.Add(item);
71+
else if (flags == 12)
72+
_declarationsToMove.Add(item);
73+
else if (flags > 12)
74+
_byval.Add(item);
3675

37-
var usedInSelection = new HashSet<Declaration>(inScopeDeclarations.Where(item =>
38-
selection.Selection.Contains(item.Selection) ||
39-
item.References.Any(reference => inSelection.Contains(reference))));
76+
}
4077

41-
var usedBeforeSelection = new HashSet<Declaration>(inScopeDeclarations.Where(item =>
42-
item.Selection.StartLine < selection.Selection.StartLine ||
43-
item.References.Any(reference => reference.Selection.StartLine < selection.Selection.StartLine)));
78+
_declarationsToMove.ForEach(d => selectionToRemove.Add(d.Selection));
79+
selectionToRemove.Add(selection.Selection);
4480

45-
var usedAfterSelection = new HashSet<Declaration>(inScopeDeclarations.Where(item =>
46-
item.Selection.StartLine > selection.Selection.StartLine ||
47-
item.References.Any(reference => reference.Selection.StartLine > selection.Selection.EndLine)));
81+
var methodCallPositionStartLine = selectionStartLine - selectionToRemove.Count(s => s.StartLine < selectionStartLine);
82+
_positionForMethodCall = new Selection(methodCallPositionStartLine, 1, methodCallPositionStartLine, 1);
4883

49-
// identifiers used inside selection and before selection (or if it's a parameter) are candidates for parameters:
50-
var input = inScopeDeclarations.Where(item =>
51-
usedInSelection.Contains(item) && (usedBeforeSelection.Contains(item) || item.DeclarationType == DeclarationType.Parameter)).ToList();
84+
var methodParams = _byref.Select(dec => new ExtractedParameter(dec.AsTypeName, ExtractedParameter.PassedBy.ByRef, dec.IdentifierName))
85+
.Union(_byval.Select(dec => new ExtractedParameter(dec.AsTypeName, ExtractedParameter.PassedBy.ByVal, dec.IdentifierName)));
5286

53-
// identifiers used inside selection and after selection are candidates for return values:
54-
var output = inScopeDeclarations.Where(item =>
55-
usedInSelection.Contains(item) && usedAfterSelection.Contains(item))
56-
.ToList();
87+
// iterate until we have a non-clashing method name.
88+
var newMethodName = NEW_METHOD;
5789

58-
// identifiers used only inside and/or after selection are candidates for locals:
59-
_locals = inScopeDeclarations.Where(item => item.DeclarationType != DeclarationType.Parameter && (
60-
item.References.All(reference => inSelection.Contains(reference))
61-
|| (usedAfterSelection.Contains(item) && (!usedBeforeSelection.Contains(item)))))
62-
.ToList();
90+
var newMethodInc = 0;
91+
while (declarations.FirstOrDefault(d =>
92+
DeclarationExtensions.ProcedureTypes.Contains(d.DeclarationType)
93+
&& d.IdentifierName.Equals(newMethodName)) != null)
94+
{
95+
newMethodInc++;
96+
newMethodName = NEW_METHOD + newMethodInc;
97+
}
6398

64-
// locals that are only used in selection are candidates for being moved into the new method:
65-
_declarationsToMove = _locals.Where(item => !usedAfterSelection.Contains(item)).ToList();
99+
_extractedMethod.MethodName = newMethodName;
100+
_extractedMethod.ReturnValue = null;
101+
_extractedMethod.Accessibility = Accessibility.Private;
102+
_extractedMethod.SetReturnValue = false;
103+
_extractedMethod.Parameters = methodParams.ToList();
66104

67-
_output = output.Select(declaration =>
68-
new ExtractedParameter(declaration.AsTypeName, ExtractedParameter.PassedBy.ByRef, declaration.IdentifierName));
105+
_selection = selection;
106+
_selectedCode = selectedCode;
107+
_selectionToRemove = selectionToRemove.ToList();
69108

70-
_input = input.Where(declaration => !output.Contains(declaration))
71-
.Select(declaration =>
72-
new ExtractedParameter(declaration.AsTypeName, ExtractedParameter.PassedBy.ByVal, declaration.IdentifierName));
73109
}
74110

75-
private readonly Declaration _sourceMember;
111+
private List<Declaration> _byref;
112+
private List<Declaration> _byval;
113+
private List<Declaration> _moveIn;
114+
115+
private Declaration _sourceMember;
76116
public Declaration SourceMember { get { return _sourceMember; } }
77117

78-
private readonly QualifiedSelection _selection;
118+
private QualifiedSelection _selection;
79119
public QualifiedSelection Selection { get { return _selection; } }
80120

81-
private readonly string _selectedCode;
121+
private string _selectedCode;
82122
public string SelectedCode { get { return _selectedCode; } }
83123

84-
private readonly List<Declaration> _locals;
85-
public IEnumerable<Declaration> Locals { get {return _locals;} }
124+
private List<Declaration> _locals;
125+
public IEnumerable<Declaration> Locals { get { return _locals; } }
86126

87-
private readonly IEnumerable<ExtractedParameter> _input;
127+
private IEnumerable<ExtractedParameter> _input;
88128
public IEnumerable<ExtractedParameter> Inputs { get { return _input; } }
89129

90-
private readonly IEnumerable<ExtractedParameter> _output;
91-
public IEnumerable<ExtractedParameter> Outputs { get {return _output; } }
130+
private IEnumerable<ExtractedParameter> _output;
131+
public IEnumerable<ExtractedParameter> Outputs { get { return _output; } }
92132

93-
private readonly List<Declaration> _declarationsToMove;
133+
private List<Declaration> _declarationsToMove;
94134
public IEnumerable<Declaration> DeclarationsToMove { get { return _declarationsToMove; } }
95135

96-
private readonly ExtractedMethod _extractedMethod;
97-
public ExtractedMethod Method { get { return _extractedMethod; } }
136+
private IExtractedMethod _extractedMethod;
137+
138+
private IEnumerable<IExtractMethodRule> _rules;
139+
140+
public IExtractedMethod Method { get { return _extractedMethod; } }
141+
142+
143+
private Selection _positionForMethodCall;
144+
public Selection PositionForMethodCall { get { return _positionForMethodCall; } }
145+
146+
public string NewMethodCall { get { return _extractedMethod.NewMethodCall(); } }
147+
148+
private Selection _positionForNewMethod;
149+
public Selection PositionForNewMethod { get { return _positionForNewMethod; } }
150+
IEnumerable<Selection> _selectionToRemove;
151+
private List<IExtractMethodRule> emRules;
152+
153+
public IEnumerable<Selection> SelectionToRemove { get { return _selectionToRemove; } }
154+
98155

99-
public class ExtractedMethod
100-
{
101-
public string MethodName { get; set; }
102-
public Accessibility Accessibility { get; set; }
103-
public bool SetReturnValue { get; set; }
104-
public ExtractedParameter ReturnValue { get; set; }
105-
public IEnumerable<ExtractedParameter> Parameters { get; set; }
106-
}
107156
}
108157
}

0 commit comments

Comments
 (0)