[ANN]: 3.9a 6704 update ready...

Lic. Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Fri Nov 11 09:09:05 UTC 2005


Giovanni Corriga puso en su mail :

> Also, I get a MessageNotUnderstood: SmallInteger>>startUp when trying to
> do this:
> 1. open class browser
> 2. browse Kernel-Classes>ClassDescription>accessing>classCommentBlank
> 3. click on the Senders button and selecting classCommentBlank
> 
> Giovanni
Giovanni:
This was fixed and another two bug too.
I attach the .cs , as I think all go in next release.

-------------- next part --------------
'From Squeak3.9alpha of 4 July 2005 [latest update: #6703] on 8 November 2005 at 11:09:14 am'!
"Change Set:		SystemNavigation-showMenuOfwithFirstItemifChosenDowithCaption
Date:			8 November 2005
Author:			Edgar J. De Cleene

This try to fix a walkback when you hit senders or implementors in buttons and menus"!


!SystemNavigation methodsFor: 'ui' stamp: 'edc 11/8/2005 10:58'!
showMenuOf: selectorCollection withFirstItem: firstItem ifChosenDo: choiceBlock withCaption: aCaption
	"Show a sorted menu of the given selectors, preceded by firstItem, and all abbreviated to 40 characters.  Use aCaption as the menu title, if it is not nil.  Evaluate choiceBlock if a message is chosen."

	| index menuLabels sortedList |
	sortedList _ selectorCollection asSortedCollection.
	menuLabels _ String streamContents: 
		[:strm | strm nextPutAll: (firstItem contractTo: 40).
		sortedList do: [:sel | strm cr; nextPutAll: (sel contractTo: 40)]].
	index _ UIManager default chooseFrom: (menuLabels substrings) lines: #(1).
	index = 1 ifTrue: [choiceBlock value: firstItem].
	index > 1 ifTrue: [choiceBlock value: (sortedList at: index - 1)]! !

-------------- next part --------------
'From Squeak3.9alpha of 4 July 2005 [latest update: #6703] on 8 November 2005 at 10:29:28 am'!
"Change Set:		SystemDictionary-unusedClassesAndMethodsWithout-fix for3.9
Date:			8 November 2005
Author:			Edgar J. De Cleene

fix for bring this useful method to 3.9 "!


!SystemDictionary methodsFor: 'shrinking' stamp: 'edc 11/8/2005 10:11'!
unusedClassesAndMethodsWithout: classesAndMessagesPair 
	"Accepts and returns a pair: {set of class names. set of selectors}. 
	It is expected these results will be diff'd with the normally unused 
	results. "
	| classRemovals messageRemovals nClasses nMessages |
	(classRemovals _ IdentitySet new) addAll: classesAndMessagesPair first.
	(messageRemovals _ IdentitySet new) addAll: classesAndMessagesPair second.
	nClasses _ nMessages _ -1.
	["As long as we keep making progress..."
	classRemovals size > nClasses
		or: [messageRemovals size > nMessages]]
		whileTrue: ["...keep trying for bigger sets of unused classes and selectors."
			nClasses _ classRemovals size.
			nMessages _ messageRemovals size.
			Utilities
				informUser: 'Iterating removals '
						, (classesAndMessagesPair first isEmpty
								ifTrue: ['for baseline...']
								ifFalse: ['for ' , classesAndMessagesPair first first , ' etc...']) , Character cr asString , nClasses printString , ' classes, ' , nMessages printString , ' messages.
|
|'
				during: ["spacers move menu off cursor"
					classRemovals
						addAll: (self systemNavigation allUnusedClassesWithout: {classRemovals. messageRemovals}).
					messageRemovals
						addAll: (self systemNavigation allUnSentMessagesWithout: {classRemovals. messageRemovals})]].
	^ {classRemovals. self systemNavigation allUnSentMessagesWithout: {classRemovals. messageRemovals}}! !

-------------- next part --------------
'From Squeak3.9alpha of 4 July 2005 [latest update: #6703] on 8 November 2005 at 11:57:23 am'!
"Change Set:		Browser>addCategory
Date:			8 November 2005
Author:			Edgar J. De Cleene

Fix a walkback when you try to assing a category to new method>"!


!Browser methodsFor: 'message category functions' stamp: 'edc 11/8/2005 11:51'!
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"
	| labels reject lines cats menuIndex oldIndex newName |
	self okToChange ifFalse: [^ self].
	classListIndex = 0 ifTrue: [^ self].
	labels _ OrderedCollection with: 'new...'.
	reject _ Set new.
	reject
		addAll: self selectedClassOrMetaClass organization categories;
		add: ClassOrganizer nullCategory;
		add: ClassOrganizer default.
	lines _ OrderedCollection new.
	self selectedClassOrMetaClass allSuperclasses do: [:cls |
		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].
	oldIndex _ messageCategoryListIndex.
	newName isEmpty
		ifTrue: [^ self]
		ifFalse: [newName _ newName asSymbol].
	self classOrMetaClassOrganizer
		addCategory: newName
		before: (messageCategoryListIndex = 0
				ifTrue: [nil]
				ifFalse: [self selectedMessageCategoryName]).
	self changed: #messageCategoryList.
	self messageCategoryListIndex:
		(oldIndex = 0
			ifTrue: [self classOrMetaClassOrganizer categories size + 1]
			ifFalse: [oldIndex]).
	self changed: #messageCategoryList.
! !



More information about the Squeak-dev mailing list