7
7
using Rubberduck . Parsing . Symbols ;
8
8
using Rubberduck . VBEditor ;
9
9
10
- namespace Rubberduck . Refactorings . ExtractMethod
10
+
11
+ public static class IEnumerableExt
11
12
{
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 ;
12
33
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
+ {
13
64
public class ExtractMethodModel : IExtractMethodModel
14
65
{
15
- private const string NEW_METHOD = "NewMethod" ;
66
+ private List < Declaration > _extractDeclarations ;
67
+ private IExtractMethodParameterClassification _paramClassify ;
68
+ private IExtractedMethod _extractedMethod ;
16
69
17
- public ExtractMethodModel ( List < IExtractMethodRule > emRules , IExtractedMethod extractedMethod )
70
+ public ExtractMethodModel ( IExtractedMethod extractedMethod , IExtractMethodParameterClassification paramClassify )
18
71
{
19
- _rules = emRules ;
20
72
_extractedMethod = extractedMethod ;
73
+ _paramClassify = paramClassify ;
21
74
}
22
75
23
-
24
76
public void extract ( IEnumerable < Declaration > declarations , QualifiedSelection selection , string selectedCode )
25
77
{
26
78
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
+
28
88
if ( sourceMember == null )
29
89
{
30
90
throw new InvalidOperationException ( "Invalid selection." ) ;
31
91
}
32
92
33
93
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 > ( ) ;
43
94
var selectionStartLine = selection . Selection . StartLine ;
44
95
var selectionEndLine = selection . Selection . EndLine ;
45
-
46
96
var methodInsertLine = sourceMember . Context . Stop . Line + 1 ;
97
+
47
98
_positionForNewMethod = new Selection ( methodInsertLine , 1 , methodInsertLine , 1 ) ;
48
99
49
- // https://github.com/rubberduck-vba/Rubberduck/wiki/Extract-Method-Refactoring-%3A-Workings---Determining-what-params-to-move
50
100
foreach ( var item in inScopeDeclarations )
51
101
{
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 ) ;
71
103
}
104
+ _declarationsToMove = _paramClassify . DeclarationsToMove . ToList ( ) ;
72
105
73
- _declarationsToMove . ForEach ( d => selectionToRemove . Add ( d . Selection ) ) ;
74
- selectionToRemove . Add ( selection . Selection ) ;
106
+ _rowsToRemove = splitSelection ( selection . Selection , _declarationsToMove ) . ToList ( ) ;
75
107
76
- var methodCallPositionStartLine = selectionStartLine - selectionToRemove . Count ( s => s . StartLine < selectionStartLine ) ;
108
+ var methodCallPositionStartLine = selectionStartLine - _declarationsToMove . Count ( d => d . Selection . StartLine < selectionStartLine ) ;
77
109
_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 ;
95
110
_extractedMethod . ReturnValue = null ;
96
111
_extractedMethod . Accessibility = Accessibility . Private ;
97
112
_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 ( ) ;
103
114
104
115
}
105
116
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
+ }
109
132
110
133
private Declaration _sourceMember ;
111
134
public Declaration SourceMember { get { return _sourceMember ; } }
@@ -121,32 +144,33 @@ public void extract(IEnumerable<Declaration> declarations, QualifiedSelection se
121
144
122
145
private IEnumerable < ExtractedParameter > _input ;
123
146
public IEnumerable < ExtractedParameter > Inputs { get { return _input ; } }
124
-
125
147
private IEnumerable < ExtractedParameter > _output ;
126
148
public IEnumerable < ExtractedParameter > Outputs { get { return _output ; } }
127
149
128
150
private List < Declaration > _declarationsToMove ;
129
151
public IEnumerable < Declaration > DeclarationsToMove { get { return _declarationsToMove ; } }
130
152
131
- private IExtractedMethod _extractedMethod ;
132
-
133
- private IEnumerable < IExtractMethodRule > _rules ;
134
-
135
153
public IExtractedMethod Method { get { return _extractedMethod ; } }
136
154
137
-
138
155
private Selection _positionForMethodCall ;
139
156
public Selection PositionForMethodCall { get { return _positionForMethodCall ; } }
140
157
141
158
public string NewMethodCall { get { return _extractedMethod . NewMethodCall ( ) ; } }
142
159
143
160
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
+ }
150
170
171
+ public IEnumerable < Declaration > DeclarationsToExtract
172
+ {
173
+ get { return _extractDeclarations ; }
174
+ }
151
175
}
152
176
}
0 commit comments