Skip to content

Commit

Permalink
60448
Browse files Browse the repository at this point in the history
19856 FileReference { #spotterPreviewItemsIn: . #spotterPreviewZipItemsIn: }  relies on #doesNotUnderstand:
	https://pharo.fogbugz.com/f/cases/19856

19854 Rename refactoring from source code by cmd r should support all kind of ast nodes
	https://pharo.fogbugz.com/f/cases/19854

19850 OrderedCollection Inspector indexes not right for similar items 
	https://pharo.fogbugz.com/f/cases/19850

http://files.pharo.org/image/60/60448.zip
  • Loading branch information
Jenkins Build Server authored and ci committed Mar 20, 2017
1 parent 3cb2c06 commit 508a5ac
Show file tree
Hide file tree
Showing 34 changed files with 105 additions and 45 deletions.
Expand Up @@ -2,7 +2,6 @@ gtInspectorItemsIn: composite
<gtInspectorPresentationOrder: 0>
^ (composite fastList)
title: 'Items';
useCache;
display: [
"The FastTable renderer needs to access elements by index so we transform
the collection to an OrderedCollection. Subclasses can override the #display
Expand Down
@@ -1,7 +1,6 @@
gtInspectorItemsIn: composite
^ (composite fastTable)
title: 'Items';
useCache;
display: [ self associations ];
"children: [ :each |
(each value isDictionary)
Expand Down
Expand Up @@ -3,5 +3,4 @@ gtInspectorKeysIn: composite

^ composite fastList
title: 'Keys';
useCache;
display: [ self keys ]
@@ -1,7 +1,6 @@
gtInspectorItemsIn: composite
^ (composite fastTable)
title: 'Items';
useCache;
display: [ self associations ];
"children: [ :each |
(each value isDictionary)
Expand Down
Expand Up @@ -2,7 +2,6 @@ gtInspectorItemsIn: composite
^ composite fastTable
title: 'Items';
display: [ self ];
useCache;
beMultiple;
enableElementIndex;
wantsAutomaticRefresh: true;
Expand Down
Expand Up @@ -2,6 +2,5 @@ gtInspectorItemsIn: composite
<gtInspectorPresentationOrder: 0>
composite fastList
title: 'Items';
useCache;
display: [ items copy ];
format: [ :each | each gtDisplayString ]
@@ -1,7 +1,6 @@
gtInspectorItemsIn: composite
^ (composite fastTable)
title: 'Items';
useCache;
display: [ self associations ];
"children: [ :each |
(each value isDictionary)
Expand Down
Expand Up @@ -6,11 +6,14 @@ spotterPreviewItemsIn: aComposite
title: [ self gtDisplayString ];
display: #yourself;
format: [ :folder |
|iconName |
iconName := folder isDirectory
ifTrue: [ #glamorousFolder ]
ifFalse: [ #glamorousBrowse ].

GTSpotterItemBrick new
text: folder basename;
icon: (folder isDirectory
ifTrue: [Smalltalk ui theme icons glamorousFolder]
ifFalse: [Smalltalk ui theme icons glamorousBrowse] );
icon: (self iconNamed: iconName);
disable;
yourself ];
styled: [ :brick | brick ];
Expand Down
Expand Up @@ -8,11 +8,14 @@ spotterPreviewZipItemsIn: aComposite
title: [ self gtDisplayString ];
display: #yourself;
format: [ :folder |
|iconName |
iconName := folder isDirectory
ifTrue: [ #glamorousFolder ]
ifFalse: [ #glamorousBrowse ].

GTSpotterItemBrick new
text: folder basename;
icon: (folder isDirectory
ifTrue: [Smalltalk ui theme icons glamorousFolder]
ifFalse: [Smalltalk ui theme icons glamorousBrowse] );
icon: (self iconNamed: iconName);
disable;
yourself ];
styled: [ :brick | brick ];
Expand Down
@@ -0,0 +1,4 @@
renameMessageFor: aMethodOrMessageNode
model okToChange ifFalse: [ ^ self ].
aMethodOrMessageNode ifNil: [ ^ self ].
self performRefactoringFor: #privateRenameMessageFor: with: aMethodOrMessageNode
@@ -1,5 +1,5 @@
privateAddClassVarFrom: aClass
^ RBAddClassVariableRefactoring
model: environment
variable: (self request: 'Enter the new variable name:' initialAnswer: 'Var')
variable: (self request: self newVariableRequestText initialAnswer: 'Var')
class: aClass theNonMetaClass
@@ -1,9 +1,9 @@
privateRenameClassVarFrom: aClass
^ self
class: aClass
andClassVariable: [ :class :variable |

^ self class: aClass andClassVariable: [ :class :variable |
RBRenameClassVariableRefactoring
model: environment
rename: variable
to: (self request: 'Enter the new variable name :' initialAnswer: variable) asSymbol
in: class ]
to: (self request: self newVariableRequestText initialAnswer: variable) asSymbol
in: class
]
@@ -1,6 +1,7 @@
privateRenameClassVarNamed: variable from: aClass

^ RBRenameClassVariableRefactoring
model: environment
rename: variable
to: (self request: 'Enter the new variable name :' initialAnswer: variable) asSymbol
to: (self request: self newVariableRequestText initialAnswer: variable) asSymbol
in: aClass
@@ -1,5 +1,5 @@
privateAddInstVarFrom: aClass
^ RBAddInstanceVariableRefactoring
model: environment
variable: (self request: 'Enter the new variable name:' initialAnswer: 'inst')
variable: (self request: self newVariableRequestText initialAnswer: 'inst')
class: aClass theNonMetaClass
@@ -1,9 +1,9 @@
privateRenameInstVarFrom: aClass
^ self
class: aClass
andInstVariable: [ :class :variable |
RBRenameInstanceVariableRefactoring
model: environment
rename: variable
to: (self request: 'Enter the new variable name :' initialAnswer: variable) asSymbol
in: class ]

^ self class: aClass andInstVariable: [ :class :variable |
RBRenameInstanceVariableRefactoring
model: environment
rename: variable
to: (self request: self newVariableRequestText initialAnswer: variable) asSymbol
in: class
]
@@ -1,6 +1,7 @@
privateRenameInstVarNamed: variable from: aClass

^ RBRenameInstanceVariableRefactoring
model: environment
rename: variable
to: (self request: 'Enter the new variable name :' initialAnswer: variable) asSymbol
to: (self request: self newVariableRequestText initialAnswer: variable) asSymbol
in: aClass
@@ -0,0 +1,13 @@
privateRenameMessageFor: aMethodOrMessageNode
| newMethodName oldMethodName selector oldArguments argumentPermutation |
selector := aMethodOrMessageNode selector.
oldArguments := aMethodOrMessageNode arguments collect: #name.
oldMethodName := RBMethodName selector: selector arguments: oldArguments.
(newMethodName := self requestMethodNameFor: oldMethodName) ifNil: [ RefactoringAborted signal ].
argumentPermutation := newMethodName arguments collect: [ :each | oldArguments indexOf: each ].
^ RBRenameMethodRefactoring
model: environment
renameMethod: selector
in: aMethodOrMessageNode methodNode methodClass
to: newMethodName selector
permutation: argumentPermutation
@@ -1,7 +1,8 @@
privateExtractToTemporaryBetween: anInterval from: aMethod

^ RBExtractToTemporaryRefactoring
model: environment
extract: anInterval
to: (self request: 'Enter the new variable name:')
to: (self request: self newVariableRequestText)
from: aMethod selector
in: aMethod methodClass
@@ -1,7 +1,8 @@
privateRenameTemporaryNamed: oldname Between: anInterval from: aMethod

^ RBRenameTemporaryRefactoring
model: environment
renameTemporaryFrom: anInterval
to: (self request: 'Enter the new variable name:' initialAnswer: oldname)
to: (self request: self newVariableRequestText initialAnswer: oldname)
in: aMethod methodClass
selector: aMethod selector
@@ -0,0 +1,3 @@
newVariableRequestText

^ 'Enter the new variable name:'
Expand Up @@ -5,4 +5,4 @@ renameTextSelectionForMethod
selectedInterval first = 1
ifTrue: [ ^ self renameMethodFor: method ].
tempNode := (method ast bestNodeFor: selectedInterval).
self renameTemporaryNamed: tempNode asString Between: (tempNode start to: tempNode stop) from: method
tempNode executeRenameRefactoringBy: self
@@ -0,0 +1,2 @@
executeRenameRefactoringBy: aNautilusRefactoring inClass: aClass
aNautilusRefactoring renameClassVarNamed: self name from: aClass
@@ -0,0 +1,2 @@
executeRenameRefactoringBy: aNautilusRefactoring inClass: aClass
aNautilusRefactoring renameClass: value
@@ -0,0 +1,3 @@
executeRenameRefactoringBy: aNautilusRefactoring

aNautilusRefactoring renameTemporaryNamed: self name asString Between: (self start to: self stop) from: self methodNode
@@ -0,0 +1,3 @@
executeRenameRefactoringBy: aNautilusRefactoring

self binding variable executeRenameRefactoringBy: aNautilusRefactoring inClass: self methodNode methodClass
@@ -0,0 +1,3 @@
executeRenameRefactoringBy: aNautilusRefactoring

aNautilusRefactoring renameInstVarNamed: self name asString from: self methodNode methodClass
@@ -0,0 +1,3 @@
executeRenameRefactoringBy: aNautilusRefactoring

aNautilusRefactoring renameMessageFor: self
@@ -0,0 +1,3 @@
executeRenameRefactoringBy: aNautilusRefactoring

aNautilusRefactoring renameMessageFor: self
@@ -0,0 +1,3 @@
executeRenameRefactoringBy: aNautilusRefactoring

self inform: self class name, ' not supports rename'
@@ -0,0 +1,3 @@
executeRenameRefactoringBy: aNautilusRefactoring

aNautilusRefactoring renameTemporaryNamed: self name asString Between: (self start to: self stop) from: self methodNode
@@ -1,4 +1,4 @@
script60447
script60448

^ 'AST-Core-TheIntegrator.492.mcz
AST-Tests-Core-TheIntegrator.134.mcz
Expand Down Expand Up @@ -97,12 +97,12 @@ GT-Debugger-AndreiChis.379.mcz
GT-EventRecorder-AndreiChis.80.mcz
GT-EventRecorder-Tests-TheIntegrator.40.mcz
GT-Inspector-AndreiChis.465.mcz
GT-InspectorExtensions-Core-AndreiChis.256.mcz
GT-InspectorExtensions-Core-TheIntegrator.258.mcz
GT-Playground-AndreiChis.145.mcz
GT-SUnitDebugger-TudorGirba.39.mcz
GT-Spotter-TheIntegrator.411.mcz
GT-Spotter-EventRecorder-AndreiChis.114.mcz
GT-SpotterExtensions-Core-TheIntegrator.222.mcz
GT-SpotterExtensions-Core-TheIntegrator.224.mcz
GT-Tests-Debugger-AndreiChis.14.mcz
GT-Tests-Inspector-AndreiChis.60.mcz
GT-Tests-Playground-StefanReichhart.4.mcz
Expand Down Expand Up @@ -228,7 +228,7 @@ Nautilus-GroupManagerUI-TheIntegrator.44.mcz
Nautilus-Tests-TheIntegrator.52.mcz
NautilusCommon-TheIntegrator.327.mcz
NautilusGroupAutoBuilder-TheIntegrator.20.mcz
NautilusRefactoring-TheIntegrator.312.mcz
NautilusRefactoring-TheIntegrator.315.mcz
Network-Kernel-TheIntegrator.136.mcz
Network-MIME-TheIntegrator.73.mcz
Network-Mail-TheIntegrator.52.mcz
Expand Down

This file was deleted.

@@ -0,0 +1,12 @@
update60448
"self new update60448"
self withUpdateLog: '19856 FileReference { #spotterPreviewItemsIn: . #spotterPreviewZipItemsIn: } relies on #doesNotUnderstand:
https://pharo.fogbugz.com/f/cases/19856
19854 Rename refactoring from source code by cmd r should support all kind of ast nodes
https://pharo.fogbugz.com/f/cases/19854
19850 OrderedCollection Inspector indexes not right for similar items
https://pharo.fogbugz.com/f/cases/19850'.
self loadTogether: self script60448 merge: false.
self flushCaches.
@@ -1,3 +1,9 @@
commentForCurrentUpdate
^ '19847 removeLink: needs to invalidate
https://pharo.fogbugz.com/f/cases/19847'
^ '19856 FileReference { #spotterPreviewItemsIn: . #spotterPreviewZipItemsIn: } relies on #doesNotUnderstand:
https://pharo.fogbugz.com/f/cases/19856
19854 Rename refactoring from source code by cmd r should support all kind of ast nodes
https://pharo.fogbugz.com/f/cases/19854
19850 OrderedCollection Inspector indexes not right for similar items
https://pharo.fogbugz.com/f/cases/19850'

0 comments on commit 508a5ac

Please sign in to comment.