[Cuis-dev] Improvement: Italic abstract classes and methods V2

Ernesto Ittig e.ittig at gmail.com
Thu Dec 4 21:36:22 PST 2025


Hey all!

  This is a follow-up on the change set I sent last Saturday.

  I've fixed a preëxisting bug in the Browser where, if a selected class
was deleted in a different browser, its methods would remain listed and
cause all sorts of issues. Thanks to Luciano Notarfrancesco for pointing
this out!

  I've also made some performance improvements. The method I was using
for determining if a class is abstract was quite inefficient, and by
caching the results I was able to reduce the time it took by 100x. This
enabled two interested possibilities:

  The class list is recomputed when a method is compiled. This way you
can see a class change from abstract to concrete and v.v. when editing
its methods.

  The caching approach requires storing which messages a class (or any
of its superclasses) responds with subclassResponsibilty. This enables
the existence of a "concrete class checklist", such that, when
subclassing an abstract class, you can see which methods you need to
override to make it concrete. This is an interesting line to follow in
the future.

  Hope you like it!

Cheers,
Ernesto Ittig
-------------- next part --------------
'From Cuis7.5 [latest update: #7739] on 5 December 2025 at 2:05:55 am'!
!classDefinition: #AbstractClassRecorder category: #'Kernel-Classes'!
Object subclass: #AbstractClassRecorder
	instanceVariableNames: 'abstractSelectorsPerClass'
	classVariableNames: 'UniqueInstance'
	poolDictionaries: ''
	category: 'Kernel-Classes'!

!AbstractClassRecorder methodsFor: 'abstract classes' stamp: 'EI 5/Dec/2025 00:39:33'!
abstractSelectorsFor: aClass

	^ abstractSelectorsPerClass at: aClass
		ifAbsent: [
			self generateAbstractSelectorsFor: aClass.
			^ abstractSelectorsPerClass at: aClass ]! !

!AbstractClassRecorder methodsFor: 'abstract classes' stamp: 'EI 5/Dec/2025 00:40:07'!
generateAbstractSelectorsFor: aClass

	| abstractMethods |
	
	abstractMethods := OrderedCollection new.
	aClass methodsDo: [:method | method isAbstract ifTrue: [abstractMethods add: method selector]].
	
	(aClass superclass
		ifNotNil: [:superclass | self abstractSelectorsFor: superclass]
		ifNil: [#()]) do: [:selector |
			(aClass includesSelector: selector) ifFalse: [abstractMethods add: selector]].
	
	abstractSelectorsPerClass at: aClass put: abstractMethods
		
		
	! !

!AbstractClassRecorder methodsFor: 'abstract classes' stamp: 'EI 5/Dec/2025 01:25:13'!
isAbstractClass: aClass

	^ (self abstractSelectorsFor: aClass) isEmpty not! !

!AbstractClassRecorder methodsFor: 'events' stamp: 'EI 5/Dec/2025 01:00:55'!
classRemoved: aClass

	aClass withAllSubclasses do: [ :class |
		abstractSelectorsPerClass removeKey: class ifAbsent: []]! !

!AbstractClassRecorder methodsFor: 'events' stamp: 'EI 5/Dec/2025 01:02:09'!
methodChanged: aCompiledMethod

	self classRemoved: aCompiledMethod methodClass! !

!AbstractClassRecorder methodsFor: 'events' stamp: 'EI 5/Dec/2025 01:37:34'!
methodChangedFrom: aCompiledMethod1 to: aCompiledMethod2

	aCompiledMethod1 isAbstract ~= aCompiledMethod2 isAbstract ifTrue: [
		self classRemoved: aCompiledMethod2 methodClass ]! !

!AbstractClassRecorder methodsFor: 'initialization' stamp: 'EI 5/Dec/2025 01:15:02'!
initialize

	abstractSelectorsPerClass := Dictionary new.
	
	SystemChangeNotifier uniqueInstance
		removeActionsWithReceiver: self;
		when: #classRemoved send: #classRemoved: to: self;
		when: #methodAddedInProtocolTimeStamp send: #methodChanged: to: self;
		when: #methodChanged send: #methodChangedFrom:to: to: self;
		when: #methodRemoved send: #methodChanged: to: self! !


!AbstractClassRecorder class methodsFor: 'instance creation' stamp: 'EI 4/Dec/2025 23:31:12'!
uniqueInstance 

	UniqueInstance ifNil: [ UniqueInstance := self new ].
	
	^ UniqueInstance! !


!ClassDescription methodsFor: 'testing' stamp: 'EI 5/Dec/2025 01:16:33'!
isAbstract

	^ AbstractClassRecorder uniqueInstance isAbstractClass: self! !


!Class methodsFor: 'testing' stamp: 'EI 4/Dec/2025 21:13:05'!
isAbstract

	^ super isAbstract or: [ self class isAbstract ]! !


!Browser methodsFor: 'class list' stamp: 'EI 29/Nov/2025 12:53:25'!
styleAbstractMethodOrClass: aMethodOrClass withName: aClassName
	| styledName |
	
	styledName := aClassName asText.
	
	aMethodOrClass isAbstract ifTrue: [
		styledName addAttribute: TextEmphasis italic ].
	
	^ styledName! !

!Browser methodsFor: 'class list' stamp: 'EI 28/Nov/2025 17:12:39'!
unstyledClassList

	^ listClassesHierarchically
		ifTrue: [self hierarchicalClassList]
		ifFalse: [self basicClassList].! !

!Browser methodsFor: 'message list' stamp: 'EI 28/Nov/2025 17:32:42'!
unstyledMessageList
	"Answer an Array of the message selectors of the currently selected message category, provided that the messageCategoryListIndex is in proper range.  Otherwise, answer an empty Array  If messageCategoryListIndex is found to be larger than the number of categories (it happens!!), it is reset to zero."
	| classOrMetaClassOrganizer answer |
	classOrMetaClassOrganizer := self classOrMetaClassOrganizer.
	classOrMetaClassOrganizer isNil ifTrue: [ ^#() ].
	answer := (selectedMessageCategory isNil or: [ selectedMessageCategory == ClassOrganizer allCategory ])
		ifTrue: [classOrMetaClassOrganizer allMethodSelectors]
		ifFalse: [classOrMetaClassOrganizer listAtCategoryNamed: selectedMessageCategory].	
	answer isNil ifTrue: [
		selectedMessageCategory := nil.
		answer := #() ].
	^answer! !


!HierarchyBrowser methodsFor: 'class list' stamp: 'EI 28/Nov/2025 17:12:39'!
unstyledClassList

	classList := classList select: [:each | Smalltalk includesKey: each withoutLeadingBlanks asSymbol].
	^ classList! !


!CodeFileBrowser methodsFor: 'class list' stamp: 'EI 28/Nov/2025 17:12:39'!
unstyledClassList
	"Answer a collection of the class names of the selected category. Answer an 
	empty array if no selection exists."

	(selectedSystemCategory isNil or: [ caseCodeSource isNil ])
		ifTrue: [ ^#() ].

	^ listClassesHierarchically
		ifTrue: [self hierarchicalClassList]
		ifFalse: [(caseCodeSource classes collect: [:ea| ea name]) sort].! !


!SinglePackageBrowser methodsFor: 'lists' stamp: 'EI 28/Nov/2025 17:32:42'!
unstyledMessageList
	"Answer an Array of the message selectors of the currently selected message category, provided that the messageCategoryListIndex is in proper range.  Otherwise, answer an empty Array  If messageCategoryListIndex is found to be larger than the number of categories (it happens!!) (??), it is reset to zero."

	| answer |
	answer := selectedMessageCategory
		ifNil: [ #() ]
		ifNotNil: [
			(self classOrMetaClassOrganizer listAtCategoryNamed: selectedMessageCategory) ifNil: [
				selectedMessageCategory := nil.
				#() ]].
	selectedMessage ifNil: [
		answer isEmpty ifFalse: [
			(package includesSystemCategory: selectedSystemCategory) ifFalse: [
				selectedMessage := answer first.
				self editSelection: #editMessage ]]].
	^answer! !


!Browser methodsFor: 'class list' stamp: 'EI 29/Nov/2025 12:54:49'!
classList

	(Preferences at: #italicAbstractClassesAndMethods)
		ifFalse: [ ^ self unstyledClassList ].

	^ self unstyledClassList collect: [ :className |
		Smalltalk at: (className withoutLeadingBlanks asSymbol)
			ifPresent: [ :class | self styleAbstractMethodOrClass: class withName: className ]
			ifAbsent: [ className asText ]
		 ]! !

!Browser methodsFor: 'class list' stamp: 'EI 28/Nov/2025 17:12:39'!
classListIndex: anInteger
	"Set anInteger to be the index of the current class selection."

	| className recent canSelectClass classList prevSelectedClassName prevSelectedMessage |
	classList := self unstyledClassList.
	canSelectClass := classList isInBounds: anInteger.
	prevSelectedClassName := selectedClassName.
	selectedClassName := canSelectClass ifTrue: [
		| newClassName |
		newClassName := classList at: anInteger ifAbsent: nil.
		newClassName := newClassName ifNotNil: [newClassName withoutLeadingBlanks asSymbol].
		newClassName ].
	self setClassOrganizer.
	prevSelectedMessage := selectedMessage.
	selectedMessage := nil.

	self classCommentIndicated ifFalse: [
		self editSelection: (canSelectClass
			ifTrue: [#editClass]
			ifFalse: [ metaClassIndicated | selectedSystemCategory isNil
				ifTrue: [#none]
				ifFalse: [#newClass]])].

	self selectedClass ifNotNil: [
		recent := self class recentClasses.
		className := self selectedClass name.
		(recent includes: className) ifTrue: [recent remove: className].
		recent addFirst: className.
		recent size > 16 ifTrue: [recent removeLast]].

	"Clear selectedMessageCategory if there is no match in the new list of categories"
	(self messageCategoryList indexOf: selectedMessageCategory) = 0 ifTrue: [
		selectedMessageCategory := nil].

	self changed: #classSelectionChanged.
	self changed: #classCommentText.
	self changed: #classListIndex.	"update my selection"
	self changed: #messageCategoryList.
	self changed: #messageList.
	self changed: #relabel.
	self acceptedContentsChanged.
	prevSelectedClassName = selectedClassName ifFalse: [
		"If clicked on already selected class, deselect selector, so class definition is shown"
		self setSelector: prevSelectedMessage ].! !

!Browser methodsFor: 'class list' stamp: 'EI 28/Nov/2025 17:12:39'!
classListIndexOf: classNameToFind

	"Answer the index of the aClassName selection."

	classNameToFind ifNil: [ ^0 ].
	^self unstyledClassList findFirst: [ :displayed | | start |
		"Works regardless of currently showing hierarchically or alphabetically."
		start := displayed firstNonSeparator.
		start-1 + classNameToFind size		 = 		displayed size and: [
			displayed is: classNameToFind substringAt: start ]]! !

!Browser methodsFor: 'message category functions' stamp: 'EI 28/Nov/2025 17:32:42'!
removeMessageCategory
	"If a message category is selected, create a Confirmer so the user can 
	verify that the currently selected message category should be removed
 	from the system. If so, remove it."

	| messageCategoryName |
	selectedMessageCategory ifNil: [^ self].
	messageCategoryName := self selectedMessageCategoryName.
	(self unstyledMessageList isEmpty
		or: [self confirm: 'Are you sure you want to
remove this method category 
and all its methods?'])
		ifTrue: [
			self selectedClassOrMetaClass removeCategory: messageCategoryName.
			self messageCategoryListIndex: 0.
			self changed: #classSelectionChanged].
	self changed: #messageCategoryList.
! !

!Browser methodsFor: 'message category list' stamp: 'EI 4/Dec/2025 20:49:12'!
rawMessageCategoryList

	^ self selectedClass 
		ifNil: [ #() ]
		ifNotNil: [ self classOrMetaClassOrganizer categories ]! !

!Browser methodsFor: 'message functions' stamp: 'EI 4/Dec/2025 22:46:10'!
defineMessageFrom: aString notifying: aRequestor
	"Compile the expressions in aString. Notify aRequestor if a syntax error occurs. Install the compiled method in the selected class classified under  the currently selected message category name. Answer the selector obtained if compilation succeeds, nil otherwise."
	| selectedMessageName selector category oldMessageList scarySelector |
	selectedMessageName := self selectedMessageName.
	oldMessageList := self unstyledMessageList.
	 self metaClassIndicated ifTrue: [
		scarySelector := self selectedClassOrMetaClass parserClass selectorFrom: aString.
		((self selectedClassOrMetaClass includesSelector: scarySelector) not
			and: [Metaclass isScarySelector: scarySelector])
			ifTrue: ["A frist-time definition overlaps the protocol of Metaclasses"
					(self confirm: (scarySelector bold, ' is used in the existing class system.
Overriding it could cause serious problems.
Is this really what you want to do?'))
					ifFalse: [^nil]]].
	category := self selectedMessageCategoryName ifNotNil: [ :n | n asSymbol ].
	category == ClassOrganizer allCategory ifTrue: [
		"Current category for existing methods or if a method was selected,
		nil for new methods when no previous method was selected."
		category := self categoryOfCurrentMethod ].
	selector := self selectedClassOrMetaClass
				compile: aString
				classified: category
				notifying: aRequestor.
	selector
		ifNil: [^ nil].
	self changed: #messageList. "In case abstract/concrete status changed"
	self changed: #classList.
	self setClassOrganizer.
	selector ~~ selectedMessageName
		ifTrue: [
			self setClassOrganizer.  "In case organization not cached".
			self messageListIndex: (self unstyledMessageList indexOf: selector) ].
	^ selector! !

!Browser methodsFor: 'message functions' stamp: 'EI 4/Dec/2025 21:09:11'!
removeMessage
	"If a message is selected, create a Confirmer so the user can verify that  
	the currently selected message should be removed from the system. If 
	so,  
	remove it. If the Preference 'confirmMethodRemoves' is set to false, the 
	confirmer is bypassed."
	| messageName confirmation |
	selectedMessage ifNil: [ ^self ].
	messageName := self selectedMessageName.
	confirmation := Smalltalk confirmRemovalOf: messageName on: self selectedClassOrMetaClass.
	confirmation = 3
		ifTrue: [^ self].
	self selectedClassOrMetaClass removeSelector: self selectedMessageName.
	self reformulateList.
	self changed: #messageList.
	self changed: #classList. "In case it made the class concrete"
	self setClassOrganizer.
	"In case organization not cached"
	confirmation = 2
		ifTrue: [Smalltalk browseAllCallsOn: messageName]! !

!Browser methodsFor: 'message functions' stamp: 'EI 4/Dec/2025 21:09:00'!
removeMessageInHierarchy
	"If a message is selected, create a Confirmer so the user can verify that  
	the currently selected message should be removed from the system. If so,  
	remove it. If the Preference 'confirmMethodRemoves' is set to false, the 
	confirmer is bypassed."
	
	| messageName confirmation selectedClass |
	selectedMessage ifNil: [ ^self ].
	
	messageName := self selectedMessageName.
	selectedClass := self selectedClassOrMetaClass.
	confirmation := Smalltalk confirmRemovalOf: messageName on: selectedClass andSubclasses: true.
	confirmation = 3
		ifTrue: [^ self].

	selectedClass withAllSubclassesDo: [ :eachClass | eachClass removeSelector: messageName ].
	
	self reformulateList.
	self changed: #messageList.
	self changed: #classList. "In case it made the class concrete"
	self setClassOrganizer.
	confirmation = 2
		ifTrue: [Smalltalk browseAllCallsOn: messageName]! !

!Browser methodsFor: 'message list' stamp: 'EI 4/Dec/2025 20:31:24'!
messageList
	
	(Preferences at: #italicAbstractClassesAndMethods)
		ifFalse: [ ^ self unstyledMessageList ].

	^ self unstyledMessageList collect: [ :messageName |
			self selectedClassOrMetaClass compiledMethodAt: messageName
				ifPresent: [ :method | self styleAbstractMethodOrClass: method withName: messageName ]
				ifAbsent: [ messageName ]
		]! !

!Browser methodsFor: 'message list' stamp: 'EI 28/Nov/2025 17:32:42'!
messageListIndex
	"Answer the index of the selected message selector into the currently 
	selected message category."

	selectedMessage ifNil: [ ^0 ].
	^self unstyledMessageList indexOf: selectedMessage! !

!Browser methodsFor: 'message list' stamp: 'EI 28/Nov/2025 17:32:42'!
messageListIndex: anInteger
	"Set the selected message selector to be the one indexed by anInteger."
	
	| index messageList |
	
	messageList := self unstyledMessageList.
	index := messageList ifInBounds: anInteger ifNot: 0.

	selectedMessage := index = 0 ifFalse: [ (messageList at: index) string ].
	self editSelection: (index > 0
		ifTrue: [#editMessage]
		ifFalse: [self messageCategoryListIndex > 0
			ifTrue: [#newMessage]
			ifFalse: [self classListIndex > 0
				ifTrue: [#editClass]
				ifFalse: [#newClass]]]).
	self changed: #messageListIndex. "update my selection"
	self changed: #relabel.
	self acceptedContentsChanged! !

!Browser methodsFor: 'message list' stamp: 'EI 28/Nov/2025 17:32:42'!
selectedMessageName: aSelector
	"Make the given selector be the selected message name"

	| anIndex |
	anIndex := self unstyledMessageList indexOf: aSelector.
	anIndex > 0 ifTrue:
		[self messageListIndex: anIndex]! !

!Browser methodsFor: 'metaclass' stamp: 'EI 4/Dec/2025 21:16:03'!
classOrMetaClassOrganizer
	"Answer the class organizer for the metaclass or class, depending on 
	which (instance or class) is indicated."
	
	self selectedClass ifNil: [ self setClassOrganizer ].

	self metaClassIndicated
		ifTrue: [^metaClassOrganizer]
		ifFalse: [^classOrganizer]! !

!Browser methodsFor: 'system category functions' stamp: 'EI 28/Nov/2025 17:12:39'!
moveAllToOtherSystemCategory
	"If a class category is selected, prompt user for category to move to,
	create a Confirmer so the user can verify that all the classes in current category
 	should be moved to the selected category."
	| newSystemCategory |
	selectedSystemCategory ifNil: [ ^ self ].
	newSystemCategory := Smalltalk systemCategoryFromUserWithPrompt: 'Move classes to System Category...'.
	(newSystemCategory notNil and: [
		self unstyledClassList notEmpty and: [ self confirm: 'Are you sure you want to
move classes from ' , selectedSystemCategory , ' 
to ' , newSystemCategory , '?' ]]) ifTrue: [
		"Safer this way (#classList will be a collection of strings with spaces and who knows what in the future.  So let's just get the classes we need directly)"
		(SystemOrganization classesAt: selectedSystemCategory) do: [ :eaClass |
			eaClass category: newSystemCategory ].
		self changed: #systemCategoryRoots ].! !

!Browser methodsFor: 'system category functions' stamp: 'EI 28/Nov/2025 17:12:39'!
removeSystemCategory
	"If a class category is selected, create a Confirmer so the user can 
	verify that the currently selected class category and all of its classes
 	should be removed from the system. If so, remove it."

	selectedSystemCategory ifNil: [^ self].
	(self unstyledClassList isEmpty
		or: [self confirm: 'Are you sure you want to
remove this system category 
and all its classes?'])
		ifTrue: [
			systemOrganizer removeSystemCategory: selectedSystemCategory.
			self setSelectedSystemCategory: nil.
			self changed: #systemCategoryRoots ]! !

!Browser methodsFor: 'refactorings - category' stamp: 'EI 28/Nov/2025 17:32:42'!
addCategoryAsSubclassResponsibilitySelectors


	| methodsOfCategory |
			
	methodsOfCategory := self unstyledMessageList.
	
	methodsOfCategory do: [ :selectedSelector | selectedSelector ifNotNil: 
			[(AddAsSubclassResponsibilityApplier on: self for: self selectedClassOrMetaClass>>selectedSelector) value ]
		].! !

!Browser methodsFor: 'refactorings - category' stamp: 'EI 28/Nov/2025 17:32:42'!
pushDownCategorySelectorsToOneSubclass
	
	self unstyledMessageList do: [ :selectedSelector | selectedSelector ifNotNil: 
		[(PushDownMethodToOneSubclassApplier on: self for: self selectedClassOrMetaClass>>selectedSelector) value ]
	].
	
	self removeMessageCategory.! !

!Browser methodsFor: 'refactorings - category' stamp: 'EI 28/Nov/2025 17:32:42'!
pushDownCategorySelectorsToSubclasses
	
		self unstyledMessageList do: [ :selectedSelector | selectedSelector ifNotNil: 
			[(PushDownMethodToSubclassesApplier on: self for: self selectedClassOrMetaClass>>selectedSelector) value] 
		].
	
		self removeMessageCategory.
! !

!Browser methodsFor: 'refactorings - category' stamp: 'EI 28/Nov/2025 17:32:42'!
pushUpCategorySelectors

	| methodsOfCategory |

	methodsOfCategory := self unstyledMessageList.
	
	methodsOfCategory do: [:selectedSelector |  (PushUpMethodApplier on: self for: self selectedClassOrMetaClass>>selectedSelector) value ].
	
	self removeMessageCategory 
! !


!HierarchyBrowser methodsFor: 'initialization' stamp: 'EI 28/Nov/2025 17:12:39'!
potentialClassNames
	
	"Answer the names of all the classes that could be viewed in this browser"
	
	^ self unstyledClassList collect: [:aName | aName withoutLeadingBlanks ]! !


!CodeFileBrowser methodsFor: 'class list' stamp: 'EI 28/Nov/2025 17:41:58'!
classList
	
	^ self unstyledClassList! !

!CodeFileBrowser methodsFor: 'message list' stamp: 'EI 28/Nov/2025 17:42:42'!
messageList
	"Colorize messages as needed"
	^ super unstyledMessageList collect: [ :eaListItem | | useAttr |
		useAttr := (self classOrMetaClassOrganizer isRemoved: eaListItem)
			ifTrue: [ TextColor red ]
			ifFalse: [ | baseSrc |
				baseSrc := self pvtBaseSelectedMessageSourceCodeFor: eaListItem.
				baseSrc
					ifNil: [ TextColor green ]
					ifNotNil: [ | caseSrc |
						caseSrc := self pvtCaseSelectedMessageSourceCodeFor: eaListItem.
						baseSrc = caseSrc ifFalse: [ TextColor blue ]]].
		useAttr
			ifNil: [ eaListItem ]
			ifNotNil: [ :attr |
				Text
					string: eaListItem
					attribute: attr ]].! !

!CodeFileBrowser methodsFor: 'removing' stamp: 'EI 28/Nov/2025 17:32:42'!
removeMessageCategory
	"If a message category is selected, create a Confirmer so the user can 
	verify that the currently selected message category should be removed
 	from the system. If so, remove it."

	| messageCategoryName |
	selectedMessageCategory ifNil: [ ^self ].
	messageCategoryName := self selectedMessageCategoryName.
	(self unstyledMessageList isEmpty
		or: [self confirm: 'Are you sure you want to
remove this method category 
and all its methods?']) ifFalse: [^ self].
	self selectedClassOrMetaClass removeCategory: messageCategoryName.
	self messageCategoryListIndex: 0.
	self changed: #messageCategoryList.! !


!SinglePackageBrowser methodsFor: 'lists' stamp: 'EI 28/Nov/2025 17:45:29'!
messageList
	
	^ self unstyledMessageList! !


!PreferenceSet class methodsFor: 'sys data' stamp: 'EI 29/Nov/2025 12:39:30'!
prefProgramming
	^ #(
		#(atMinusDigitMeaning st80 #(st80 ansiSmalltalk disabled) )
		#(allowBlockArgumentAssignment false )
		#(allowNonBooleanReceiversOfBooleanMessages false )
		#(alternativeBrowseIt false )
		#(browseWithPrettyPrint false )
		#(debugHaloHandle true )
		#(debugLogTimestamp true )
		#(debugShowDamage false )
		#(decorateBrowserButtons true )
		#(diffsInChangeList true )
		#(diffsWithPrettyPrint false )
		#(extraDebuggerButtons true )
		#(fullPrintItInWorkspaces false )
		#(highlightBlockNesting true )
		#(italicsInShout true)
		#(listClassesHierarchically true )
		#(logDebuggerStackToFile false )
		#(prettyPrintRectangularBlocks false )
		#(shiftClickShowsImplementors false )
		#(shoutInWorkspaces true )
		#(showAnnotations true )
		#(showLinesInHierarchyViews true )
		#(stylingWithEmphasisInWorkspaces false )
		#(systemCategoryAnnotations #(classCount instanceMethodsCount classMethodsCount "linesOfCode" messageSendsCount) )
		#(classAnnotations #(instanceMethodsCount classMethodsCount "linesOfCode" messageSendsCount) )
		#(messageCategoryAnnotations #(messagesCount messageSendsCount) )
		#(methodAnnotations #(timeStamp "linesOfCode" messageSendsCount messageCategory implementorsCount sendersCount packages library changeSets) )	
		#(syntaxHighlightingAsYouType true )
		#(showAssignmentAsLeftArrow false )
		#(usePreDebugWindow false)
		#(clearPackagePathsOnImageMove true)
		#(italicAbstractClassesAndMethods false)
	)! !

!methodRemoval: HierarchyBrowser #classList stamp: 'EI 4/Dec/2025 20:54:22'!
HierarchyBrowser removeSelector: #classList!
!methodRemoval: AbstractClassRecorder #abstractSelectorFor: stamp: 'EI 5/Dec/2025 00:24:04'!
AbstractClassRecorder removeSelector: #abstractSelectorFor:!

!AbstractClassRecorder reorganize!
('abstract classes' abstractSelectorsFor: generateAbstractSelectorsFor: isAbstractClass:)
('events' classRemoved: methodChanged: methodChangedFrom:to:)
('initialization' initialize)
!


!AbstractClassRecorder class reorganize!
('instance creation' uniqueInstance)
!

PreferenceSet installDefault: #(italicAbstractClassesAndMethods true) in: #programming!


More information about the Cuis-dev mailing list