Skip to content

Commit 58703bb

Browse files
committed
Merge branch 'parserIssues' of https://github.com/Hosch250/Rubberduck
2 parents 476d961 + 6d3af79 commit 58703bb

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

41 files changed

+6250
-3930
lines changed

RetailCoder.VBE/Refactorings/ExtractMethod/ExtractMethodExtraction.cs

Lines changed: 4 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -15,8 +15,7 @@ public void apply(ICodeModuleWrapper codeModule, IExtractMethodModel model, Sele
1515
var newMethodCall = model.Method.NewMethodCall();
1616
var positionToInsertNewMethod = model.PositionForNewMethod;
1717
var positionForMethodCall = model.PositionForMethodCall;
18-
var selectionToRemove = model.SelectionToRemove;
19-
18+
var selectionToRemove = model.RowsToRemove;
2019
// The next 4 lines are dependent on the positions of the various parts,
2120
// so have to be applied in the correct order.
2221
var newMethod = constructLinesOfProc(codeModule, model);
@@ -27,46 +26,40 @@ public void apply(ICodeModuleWrapper codeModule, IExtractMethodModel model, Sele
2726

2827
public virtual void removeSelection(ICodeModuleWrapper codeModule, IEnumerable<Selection> selection)
2928
{
30-
foreach (var item in selection)
29+
foreach (var item in selection.OrderBy(x => -x.StartLine))
3130
{
3231
var start = item.StartLine;
3332
var end = item.EndLine;
3433
var lineCount = end - start + 1;
35-
3634
codeModule.DeleteLines(start,lineCount);
37-
3835
}
3936
}
37+
4038
public virtual string constructLinesOfProc(ICodeModuleWrapper codeModule, IExtractMethodModel model)
4139
{
4240

4341
var newLine = Environment.NewLine;
4442
var method = model.Method;
4543
var keyword = Tokens.Sub;
4644
var asTypeClause = string.Empty;
47-
var selection = model.SelectionToRemove;
48-
45+
var selection = model.RowsToRemove;
4946

5047
var access = method.Accessibility.ToString();
5148
var extractedParams = method.Parameters.Select(p => ExtractedParameter.PassedBy.ByRef + " " + p.Name + " " + Tokens.As + " " + p.TypeName);
5249
var parameters = "(" + string.Join(", ", extractedParams) + ")";
53-
5450
//method signature
5551
var result = access + ' ' + keyword + ' ' + method.MethodName + parameters + ' ' + asTypeClause + newLine;
56-
5752
// method body
5853
string textToMove = "";
5954
foreach (var item in selection)
6055
{
6156
textToMove += codeModule.get_Lines(item.StartLine, item.EndLine - item.StartLine + 1);
6257
textToMove += Environment.NewLine;
6358
}
64-
6559
// method end;
6660
result += textToMove;
6761
result += Tokens.End + " " + Tokens.Sub;
6862
return result;
6963
}
70-
7164
}
7265
}

RetailCoder.VBE/Refactorings/ExtractMethod/ExtractMethodModel.cs

Lines changed: 100 additions & 76 deletions
Original file line numberDiff line numberDiff line change
@@ -7,105 +7,128 @@
77
using Rubberduck.Parsing.Symbols;
88
using Rubberduck.VBEditor;
99

10-
namespace Rubberduck.Refactorings.ExtractMethod
10+
11+
public static class IEnumerableExt
1112
{
13+
/// <summary>
14+
/// Yields an Enumeration of selector Type,
15+
/// by checking for gaps between elements
16+
/// using the supplied increment function to work out the next value
17+
/// </summary>
18+
/// <typeparam name="T"></typeparam>
19+
/// <typeparam name="U"></typeparam>
20+
/// <param name="inputs"></param>
21+
/// <param name="getIncr"></param>
22+
/// <param name="selector"></param>
23+
/// <param name="comparisonFunc"></param>
24+
/// <returns></returns>
25+
public static IEnumerable<U> GroupByMissing<T, U>(this IEnumerable<T> inputs, Func<T, T> getIncr, Func<T, T, U> selector, Func<T, T, int> comparisonFunc)
26+
{
27+
28+
var initialized = false;
29+
T first = default(T);
30+
T last = default(T);
31+
T next = default(T);
32+
Tuple<T, T> tuple = null;
1233

34+
foreach (var input in inputs)
35+
{
36+
if (!initialized)
37+
{
38+
first = input;
39+
last = input;
40+
initialized = true;
41+
continue;
42+
}
43+
if (comparisonFunc(last, input) < 0)
44+
{
45+
throw new ArgumentException(string.Format("Values are not monotonically increasing. {0} should be less than {1}", last, input));
46+
}
47+
var inc = getIncr(last);
48+
if (!input.Equals(inc))
49+
{
50+
yield return selector(first, last);
51+
first = input;
52+
}
53+
last = input;
54+
}
55+
if (initialized)
56+
{
57+
yield return selector(first, last);
58+
}
59+
}
60+
}
61+
62+
namespace Rubberduck.Refactorings.ExtractMethod
63+
{
1364
public class ExtractMethodModel : IExtractMethodModel
1465
{
15-
private const string NEW_METHOD = "NewMethod";
66+
private List<Declaration> _extractDeclarations;
67+
private IExtractMethodParameterClassification _paramClassify;
68+
private IExtractedMethod _extractedMethod;
1669

17-
public ExtractMethodModel(List<IExtractMethodRule> emRules, IExtractedMethod extractedMethod)
70+
public ExtractMethodModel(IExtractedMethod extractedMethod, IExtractMethodParameterClassification paramClassify)
1871
{
19-
_rules = emRules;
2072
_extractedMethod = extractedMethod;
73+
_paramClassify = paramClassify;
2174
}
2275

23-
2476
public void extract(IEnumerable<Declaration> declarations, QualifiedSelection selection, string selectedCode)
2577
{
2678
var items = declarations.ToList();
27-
var sourceMember = items.FindSelectedDeclaration(selection, DeclarationExtensions.ProcedureTypes, d => ((ParserRuleContext)d.Context.Parent).GetSelection());
79+
_selection = selection;
80+
_selectedCode = selectedCode;
81+
_rowsToRemove = new List<Selection>();
82+
83+
var sourceMember = items.FindSelectedDeclaration(
84+
selection,
85+
DeclarationExtensions.ProcedureTypes,
86+
d => ((ParserRuleContext)d.Context.Parent).GetSelection());
87+
2888
if (sourceMember == null)
2989
{
3090
throw new InvalidOperationException("Invalid selection.");
3191
}
3292

3393
var inScopeDeclarations = items.Where(item => item.ParentScope == sourceMember.Scope).ToList();
34-
35-
_byref = new List<Declaration>();
36-
_byval = new List<Declaration>();
37-
_declarationsToMove = new List<Declaration>();
38-
39-
_extractedMethod = new ExtractedMethod();
40-
41-
42-
var selectionToRemove = new List<Selection>();
4394
var selectionStartLine = selection.Selection.StartLine;
4495
var selectionEndLine = selection.Selection.EndLine;
45-
4696
var methodInsertLine = sourceMember.Context.Stop.Line + 1;
97+
4798
_positionForNewMethod = new Selection(methodInsertLine, 1, methodInsertLine, 1);
4899

49-
// https://github.com/rubberduck-vba/Rubberduck/wiki/Extract-Method-Refactoring-%3A-Workings---Determining-what-params-to-move
50100
foreach (var item in inScopeDeclarations)
51101
{
52-
var flags = new Byte();
53-
54-
foreach (var oRef in item.References)
55-
{
56-
foreach (var rule in _rules)
57-
{
58-
rule.setValidFlag(ref flags, oRef, selection.Selection);
59-
}
60-
}
61-
62-
//TODO: extract this to seperate class.
63-
if (flags < 4) { /*ignore the variable*/ }
64-
else if (flags < 12)
65-
_byref.Add(item);
66-
else if (flags == 12)
67-
_declarationsToMove.Add(item);
68-
else if (flags > 12)
69-
_byval.Add(item);
70-
102+
_paramClassify.classifyDeclarations(selection, item);
71103
}
104+
_declarationsToMove = _paramClassify.DeclarationsToMove.ToList();
72105

73-
_declarationsToMove.ForEach(d => selectionToRemove.Add(d.Selection));
74-
selectionToRemove.Add(selection.Selection);
106+
_rowsToRemove = splitSelection(selection.Selection, _declarationsToMove).ToList();
75107

76-
var methodCallPositionStartLine = selectionStartLine - selectionToRemove.Count(s => s.StartLine < selectionStartLine);
108+
var methodCallPositionStartLine = selectionStartLine - _declarationsToMove.Count(d => d.Selection.StartLine < selectionStartLine);
77109
_positionForMethodCall = new Selection(methodCallPositionStartLine, 1, methodCallPositionStartLine, 1);
78-
79-
var methodParams = _byref.Select(dec => new ExtractedParameter(dec.AsTypeName, ExtractedParameter.PassedBy.ByRef, dec.IdentifierName))
80-
.Union(_byval.Select(dec => new ExtractedParameter(dec.AsTypeName, ExtractedParameter.PassedBy.ByVal, dec.IdentifierName)));
81-
82-
// iterate until we have a non-clashing method name.
83-
var newMethodName = NEW_METHOD;
84-
85-
var newMethodInc = 0;
86-
while (declarations.FirstOrDefault(d =>
87-
DeclarationExtensions.ProcedureTypes.Contains(d.DeclarationType)
88-
&& d.IdentifierName.Equals(newMethodName)) != null)
89-
{
90-
newMethodInc++;
91-
newMethodName = NEW_METHOD + newMethodInc;
92-
}
93-
94-
_extractedMethod.MethodName = newMethodName;
95110
_extractedMethod.ReturnValue = null;
96111
_extractedMethod.Accessibility = Accessibility.Private;
97112
_extractedMethod.SetReturnValue = false;
98-
_extractedMethod.Parameters = methodParams.ToList();
99-
100-
_selection = selection;
101-
_selectedCode = selectedCode;
102-
_selectionToRemove = selectionToRemove.ToList();
113+
_extractedMethod.Parameters = _paramClassify.ExtractedParameters.ToList();
103114

104115
}
105116

106-
private List<Declaration> _byref;
107-
private List<Declaration> _byval;
108-
private List<Declaration> _moveIn;
117+
public IEnumerable<Selection> splitSelection(Selection selection, IEnumerable<Declaration> declarations)
118+
{
119+
var tupleList = new List<Tuple<int, int>>();
120+
var declarationRows = declarations
121+
.Where(decl =>
122+
selection.StartLine <= decl.Selection.StartLine &&
123+
decl.Selection.StartLine <= selection.EndLine)
124+
.Select(decl => decl.Selection.StartLine)
125+
.OrderBy(x => x)
126+
.ToList();
127+
128+
var gappedSelectionRows = Enumerable.Range(selection.StartLine, selection.EndLine - selection.StartLine + 1).Except(declarationRows).ToList();
129+
var returnList = gappedSelectionRows.GroupByMissing(x => (x + 1), (x, y) => new Selection(x, 1, y, 1), (x, y) => y - x);
130+
return returnList;
131+
}
109132

110133
private Declaration _sourceMember;
111134
public Declaration SourceMember { get { return _sourceMember; } }
@@ -121,32 +144,33 @@ public void extract(IEnumerable<Declaration> declarations, QualifiedSelection se
121144

122145
private IEnumerable<ExtractedParameter> _input;
123146
public IEnumerable<ExtractedParameter> Inputs { get { return _input; } }
124-
125147
private IEnumerable<ExtractedParameter> _output;
126148
public IEnumerable<ExtractedParameter> Outputs { get { return _output; } }
127149

128150
private List<Declaration> _declarationsToMove;
129151
public IEnumerable<Declaration> DeclarationsToMove { get { return _declarationsToMove; } }
130152

131-
private IExtractedMethod _extractedMethod;
132-
133-
private IEnumerable<IExtractMethodRule> _rules;
134-
135153
public IExtractedMethod Method { get { return _extractedMethod; } }
136154

137-
138155
private Selection _positionForMethodCall;
139156
public Selection PositionForMethodCall { get { return _positionForMethodCall; } }
140157

141158
public string NewMethodCall { get { return _extractedMethod.NewMethodCall(); } }
142159

143160
private Selection _positionForNewMethod;
144-
public Selection PositionForNewMethod { get { return _positionForNewMethod; } }
145-
IEnumerable<Selection> _selectionToRemove;
146-
private List<IExtractMethodRule> emRules;
147-
148-
public IEnumerable<Selection> SelectionToRemove { get { return _selectionToRemove; } }
149-
161+
public Selection PositionForNewMethod { get { return _positionForNewMethod; } }
162+
IList<Selection> _rowsToRemove;
163+
public IEnumerable<Selection> RowsToRemove
164+
{
165+
// we need to split selectionToRemove around any declarations that
166+
// are within the selection.
167+
get { return _declarationsToMove.Select(decl => decl.Selection).Union(_rowsToRemove)
168+
.Select( x => new Selection(x.StartLine,1,x.EndLine,1)) ; }
169+
}
150170

171+
public IEnumerable<Declaration> DeclarationsToExtract
172+
{
173+
get { return _extractDeclarations; }
174+
}
151175
}
152176
}
Lines changed: 69 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,69 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using System.Text;
5+
using System.Threading.Tasks;
6+
using Rubberduck.Parsing.Symbols;
7+
using Rubberduck.VBEditor;
8+
9+
namespace Rubberduck.Refactorings.ExtractMethod
10+
{
11+
public class ExtractMethodParameterClassification : IExtractMethodParameterClassification
12+
{
13+
// https://github.com/rubberduck-vba/Rubberduck/wiki/Extract-Method-Refactoring-%3A-Workings---Determining-what-params-to-move
14+
private readonly IEnumerable<IExtractMethodRule> _emRules;
15+
private List<Declaration> _byref;
16+
private List<Declaration> _byval;
17+
private List<Declaration> _declarationsToMove;
18+
private List<Declaration> _extractDeclarations;
19+
20+
public ExtractMethodParameterClassification(IEnumerable<IExtractMethodRule> emRules)
21+
{
22+
_emRules = emRules;
23+
_byref = new List<Declaration>();
24+
_byval = new List<Declaration>();
25+
_declarationsToMove = new List<Declaration>();
26+
_extractDeclarations = new List<Declaration>();
27+
}
28+
29+
public void classifyDeclarations(QualifiedSelection selection, Declaration item)
30+
{
31+
32+
byte flags = new Byte();
33+
foreach (var oRef in item.References)
34+
{
35+
foreach (var rule in _emRules)
36+
{
37+
var byteFlag = rule.setValidFlag(oRef, selection.Selection);
38+
flags = (byte)(flags | (byte)byteFlag);
39+
40+
}
41+
}
42+
43+
if (flags < 4) { /*ignore the variable*/ }
44+
else if (flags < 12)
45+
_byref.Add(item);
46+
else if (flags == 12)
47+
_declarationsToMove.Add(item);
48+
else if (flags > 12)
49+
_byval.Add(item);
50+
51+
if (flags >= 18)
52+
{
53+
_extractDeclarations.Add(item);
54+
}
55+
}
56+
57+
public IEnumerable<ExtractedParameter> ExtractedParameters
58+
{
59+
get {
60+
return _byref.Select(dec => new ExtractedParameter(dec.AsTypeName, ExtractedParameter.PassedBy.ByRef, dec.IdentifierName)).
61+
Union(_byval.Select(dec => new ExtractedParameter(dec.AsTypeName, ExtractedParameter.PassedBy.ByVal, dec.IdentifierName)));
62+
}
63+
}
64+
65+
public IEnumerable<Declaration> DeclarationsToMove { get { return _declarationsToMove; } }
66+
public IEnumerable<Declaration> ExtractedDeclarations { get { return _extractDeclarations; } }
67+
68+
}
69+
}

0 commit comments

Comments
 (0)