[squeak-dev] The Inbox: Tools-jmg.426.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Nov 3 02:29:49 UTC 2012


A new version of Tools was added to project The Inbox:
http://source.squeak.org/inbox/Tools-jmg.426.mcz

==================== Summary ====================

Name: Tools-jmg.426
Author: jmg
Time: 2 November 2012, 8:29:30.822 pm
UUID: daaf005c-5185-49b4-ba46-b6b9e68ecbc3
Ancestors: Tools-ul.425

When changing or adding categories I was frustrated by the fact that the categories shown in the list weren't sorted alphabetically, which made it hard for me to quickly scan the list to see if there was a category similar to the one I was thinking of (ie: I am drawing in a morph, so I want a category related to drawing).  I could use the search bar but sometimes I just wanted to scan the list.  I changed the methods presenting the list so that the categories were shown alphabetically, while preserving the special convenience categories at the start of the list (ie: new..., and the categories in the current morph).

=============== Diff against Tools-ul.425 ===============

Item was changed:
  ----- Method: Browser>>addCategory (in category 'message category functions') -----
  addCategory
+ 	"Present a choice of categories or prompt for a new category name
+ 	and add it before the current selection, or at the end if no current
+ 	selection"
- 	"Present a choice of categories or prompt for a new category name and add it before the current selection, or at the end if no current selection"
  	| labels reject lines menuIndex newName oldCategory |
+ 	self okToChange
+ 		ifFalse: [^ self].
+ 	self hasClassSelected
+ 		ifFalse: [^ self].
+ 	labels := OrderedCollection new.
- 	self okToChange ifFalse: [^ self].
- 	self hasClassSelected ifFalse: [^ self].
- 	labels := OrderedCollection with: 'new...'.
  	reject := Set new.
+ 	reject addAll: self selectedClassOrMetaClass organization categories;
+ 		 add: ClassOrganizer nullCategory;
+ 		 add: ClassOrganizer default.
- 	reject
- 		addAll: self selectedClassOrMetaClass organization categories;
- 		add: ClassOrganizer nullCategory;
- 		add: ClassOrganizer default.
  	lines := OrderedCollection new.
+ 	self selectedClassOrMetaClass allSuperclasses
+ 		do: [:cls | | cats | cls = Object
+ 				ifFalse: [cats := cls organization categories
+ 								reject: [:cat | reject includes: cat].
+ 					cats isEmpty
+ 						ifFalse: [lines add: labels size.
+ 							labels addAll: cats.
+ 							reject addAll: cats]]].
+ 	labels sort.
+ 	labels addFirst: 'new...'.  
+ 	newName := (labels size = 1
+ 					or: [menuIndex := UIManager default
+ 									chooseFrom: labels
+ 									lines: lines
+ 									title: 'Add Category'.
+ 						menuIndex = 0
+ 							ifTrue: [^ self].
+ 						menuIndex = 1])
+ 				ifTrue: [self request: 'Please type new category name' initialAnswer: 'category name']
+ 				ifFalse: [labels at: menuIndex].
- 	self selectedClassOrMetaClass allSuperclasses do: [:cls | | cats |
- 		cls = Object ifFalse: [
- 			cats := cls organization categories reject:
- 				 [:cat | reject includes: cat].
- 			cats isEmpty ifFalse: [
- 				lines add: labels size.
- 				labels addAll: cats asSortedCollection.
- 				reject addAll: cats]]].
- 	newName := (labels size = 1 or: [
- 		menuIndex := (UIManager default chooseFrom: labels lines: lines title: 'Add Category').
- 		menuIndex = 0 ifTrue: [^ self].
- 		menuIndex = 1])
- 			ifTrue: [
- 				self request: 'Please type new category name'
- 					initialAnswer: 'category name']
- 			ifFalse: [
- 				labels at: menuIndex].
  	oldCategory := self selectedMessageCategoryName.
  	newName isEmpty
  		ifTrue: [^ self]
  		ifFalse: [newName := newName asSymbol].
  	self classOrMetaClassOrganizer
  		addCategory: newName
  		before: (self hasMessageCategorySelected
- 				ifFalse: [nil]
  				ifTrue: [self selectedMessageCategoryName]).
  	self changed: #messageCategoryList.
+ 	self
+ 		selectMessageCategoryNamed: (oldCategory isNil
+ 				ifTrue: [self classOrMetaClassOrganizer categories last]
+ 				ifFalse: [oldCategory]).
+ 	self changed: #messageCategoryList!
- 	self selectMessageCategoryNamed:
- 		(oldCategory isNil
- 			ifTrue: [self classOrMetaClassOrganizer categories last]
- 			ifFalse: [oldCategory]).
- 	self changed: #messageCategoryList.
- !

Item was changed:
  ----- Method: CodeHolder>>categoryFromUserWithPrompt:for: (in category 'categories') -----
  categoryFromUserWithPrompt: aPrompt for: aClass
  	"self new categoryFromUserWithPrompt: 'testing' for: SystemDictionary"
  
  	|  labels myCategories reject lines newName menuIndex | 
+ 	labels := OrderedCollection new.
+ 	myCategories := aClass organization categories asSortedCollection:
+ 		[:a :b | a asLowercase < b asLowercase].
- 	labels := OrderedCollection with: 'new...'.
- 	labels addAll: (myCategories := aClass organization categories asSortedCollection:
- 		[:a :b | a asLowercase < b asLowercase]).
  	reject := myCategories asSet.
  	reject
  		add: ClassOrganizer nullCategory;
  		add: ClassOrganizer default.
  	lines := OrderedCollection with: 1 with: (myCategories size + 1).
  
  	aClass allSuperclasses do:
  		[:cls |
  			| cats |
  			cats := cls organization categories reject:
  				 [:cat | reject includes: cat].
  			cats isEmpty ifFalse:
  				[lines add: labels size.
  				labels addAll: (cats asSortedCollection:
  					[:a :b | a asLowercase < b asLowercase]).
  				reject addAll: cats]].
+ 	labels sort.
+ 	labels addAllFirst: (myCategories).
+ 	labels addFirst: 'new...'.
- 
  	newName := (labels size = 1 or:
  		[menuIndex := (UIManager default chooseFrom: labels lines: lines title: aPrompt).
  		menuIndex = 0 ifTrue: [^ nil].
  		menuIndex = 1])
  			ifTrue:
  				[UIManager default request: 'Please type new category name'
  					initialAnswer: 'category name']
  			ifFalse: 
  				[labels at: menuIndex].
  	^ newName ifNotNil: [newName asSymbol]!



More information about the Squeak-dev mailing list