| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752 | 
							- Smalltalk current createPackage: 'Kernel-Classes'!
 
- Object subclass: #Behavior
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Classes'!
 
- !Behavior commentStamp!
 
- Behavior is the superclass of all class objects. 
 
- It defines the protocol for creating instances of a class with `#basicNew` and `#new` (see `boot.js` for class constructors details).
 
- Instances know about the subclass/superclass relationships between classes, contain the description that instances are created from, 
 
- and hold the method dictionary that's associated with each class.
 
- Behavior also  provides methods for compiling methods, examining the method dictionary, and iterating over the class hierarchy.!
 
- !Behavior methodsFor: 'accessing'!
 
- allInstanceVariableNames
 
- 	| result |
 
- 	result := self instanceVariableNames copy.
 
- 	self superclass ifNotNil: [
 
- 	    result addAll: self superclass allInstanceVariableNames].
 
- 	^result
 
- !
 
- allSelectors
 
- 	^self allSuperclasses
 
- 		inject: self selectors
 
- 		into: [ :soFar :aBehavior | soFar addAll: aBehavior selectors; yourself ]
 
- !
 
- allSubclasses
 
- 	| result |
 
- 	result := self subclasses.
 
- 	self subclasses do: [:each |
 
- 	    result addAll: each allSubclasses].
 
- 	^result
 
- !
 
- allSuperclasses
 
- 	
 
-     self superclass ifNil: [ ^ #() ].
 
-     
 
- 	^ (OrderedCollection with: self superclass) 
 
-     	addAll: self superclass allSuperclasses;
 
-         yourself
 
- !
 
- comment
 
-     ^(self basicAt: 'comment') ifNil: ['']
 
- !
 
- comment: aString
 
-     self basicAt: 'comment' put: aString.
 
-     SystemAnnouncer current
 
-     	announce: (ClassCommentChanged new
 
-         	theClass: self;
 
-             yourself)
 
- !
 
- commentStamp
 
-     ^ClassCommentReader new
 
- 	class: self;
 
- 	yourself
 
- !
 
- commentStamp: aStamp prior: prior
 
-         ^self commentStamp
 
- !
 
- definition
 
- 	^ ''
 
- !
 
- instanceVariableNames
 
- 	<return self.iVarNames>
 
- !
 
- lookupSelector: selector
 
- 	"Look up the given selector in my methodDictionary.
 
- 	Return the corresponding method if found.
 
- 	Otherwise chase the superclass chain and try again.
 
- 	Return nil if no method is found."
 
-     
 
- 	| lookupClass |
 
-     
 
- 	lookupClass := self.
 
- 	[ lookupClass = nil ] whileFalse: [
 
-       	(lookupClass includesSelector: selector)
 
- 				ifTrue: [ ^ lookupClass methodAt: selector ].
 
- 			lookupClass := lookupClass superclass ].
 
- 	^ nil
 
- !
 
- methodAt: aSymbol
 
- 	^ self methodDictionary at: aSymbol asString
 
- !
 
- methodDictionary
 
- 	<var dict = smalltalk.HashedCollection._new();
 
- 	var methods = self.methods;
 
- 	for(var i in methods) {
 
- 		if(methods[i].selector) {
 
- 			dict._at_put_(methods[i].selector, methods[i]);
 
- 		}
 
- 	};
 
- 	return dict>
 
- !
 
- methods
 
- 	^ self methodDictionary values
 
- !
 
- methodsFor: aString
 
- 	^ClassCategoryReader new
 
- 	    class: self category: aString;
 
- 	    yourself
 
- !
 
- methodsFor: aString stamp: aStamp
 
- 	"Added for compatibility, right now ignores stamp."
 
- 	^self methodsFor: aString
 
- !
 
- methodsInProtocol: aString
 
- 	^ self methodDictionary values select: [ :each | each protocol = aString ]
 
- !
 
- name
 
- 	<return self.className || nil>
 
- !
 
- organization
 
- 	^ self basicAt: 'organization'
 
- !
 
- protocols
 
-    ^ self organization elements sorted
 
- !
 
- protocolsDo: aBlock
 
- 	"Execute aBlock for each method category with
 
- 	its collection of methods in the sort order of category name."
 
- 	| methodsByCategory |
 
- 	methodsByCategory := HashedCollection new.
 
- 	self methodDictionary values do: [:m |
 
- 		(methodsByCategory at: m category ifAbsentPut: [Array new])
 
-  			add: m]. 
 
- 	self protocols do: [:category |
 
- 		aBlock value: category value: (methodsByCategory at: category)]
 
- !
 
- prototype
 
- 	<return self.fn.prototype>
 
- !
 
- selectors
 
- 	^ self methodDictionary keys
 
- !
 
- subclasses
 
- 	<return smalltalk.subclasses(self)>
 
- !
 
- superclass
 
- 	<return self.superclass || nil>
 
- !
 
- theMetaClass
 
- 	^ self class
 
- !
 
- theNonMetaClass
 
- 	^ self
 
- !
 
- withAllSubclasses
 
- 	^(Array with: self) addAll: self allSubclasses; yourself
 
- ! !
 
- !Behavior methodsFor: 'compiling'!
 
- addCompiledMethod: aMethod
 
- 	| oldMethod announcement |
 
-     
 
- 	oldMethod := self methodDictionary 
 
-     	at: aMethod selector 
 
-         ifAbsent: [ nil ].
 
-     
 
-    (self protocols includes: aMethod protocol)
 
-    		ifFalse: [ self organization addElement: aMethod protocol ].
 
-    
 
- 	self basicAddCompiledMethod: aMethod.
 
-     
 
-     announcement := oldMethod 
 
-     	ifNil: [
 
- 		    MethodAdded new
 
- 		            method: aMethod;
 
-        			    yourself ]
 
-     	ifNotNil: [
 
-           	MethodModified new
 
-                     oldMethod: oldMethod; 
 
- 		            method: aMethod;
 
-        			    yourself ].
 
-                     
 
-                     
 
- 	SystemAnnouncer current
 
- 		   		announce: announcement
 
- !
 
- compile: aString
 
- 	self compile: aString category: ''
 
- !
 
- compile: aString category: anotherString
 
- 	Compiler new
 
- 		install: aString 
 
-         forClass: self 
 
-         category: anotherString
 
- !
 
- removeCompiledMethod: aMethod
 
- 	self basicRemoveCompiledMethod: aMethod.
 
-     
 
-     self methods 
 
-     	detect: [ :each | each protocol = aMethod protocol ]
 
-   		ifNone: [ self organization removeElement: aMethod protocol ].
 
-     
 
-     SystemAnnouncer current
 
-    		announce: (MethodRemoved new
 
-             method: aMethod;
 
-             yourself)
 
- ! !
 
- !Behavior methodsFor: 'instance creation'!
 
- basicNew
 
- 	<return new self.fn()>
 
- !
 
- new
 
- 	^self basicNew initialize
 
- ! !
 
- !Behavior methodsFor: 'private'!
 
- basicAddCompiledMethod: aMethod
 
- 	<smalltalk.addMethod(aMethod.selector._asSelector(), aMethod, self)>
 
- !
 
- basicRemoveCompiledMethod: aMethod
 
- 	<
 
-     	smalltalk.removeMethod(aMethod)
 
- 		smalltalk.init(self);
 
-     >
 
- ! !
 
- !Behavior methodsFor: 'testing'!
 
- canUnderstand: aSelector
 
- 	^(self methodDictionary keys includes: aSelector asString) or: [
 
- 		self superclass notNil and: [self superclass canUnderstand: aSelector]]
 
- !
 
- includesSelector: aSymbol
 
- 	^ self methodDictionary includesKey: aSymbol asString
 
- !
 
- inheritsFrom: aClass
 
- 	^aClass allSubclasses includes: self
 
- ! !
 
- Behavior subclass: #Class
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Classes'!
 
- !Class commentStamp!
 
- Class is __the__ class object. 
 
- Instances are the classes of the system.
 
- Class creation is done throught a `ClassBuilder`!
 
- !Class methodsFor: 'accessing'!
 
- category
 
- 	^self package ifNil: ['Unclassified'] ifNotNil: [self package name]
 
- !
 
- definition
 
- 	^ String streamContents: [ :stream |
 
- 		stream 
 
- 	    	nextPutAll: self superclass asString;
 
- 	    	nextPutAll: ' subclass: #';
 
- 	    	nextPutAll: self name;
 
- 	    	nextPutAll: String lf, String tab;
 
- 	    	nextPutAll: 'instanceVariableNames: '''.
 
- 		self instanceVariableNames 
 
-           	do: [ :each | stream nextPutAll: each ] 
 
- 	    	separatedBy: [ stream nextPutAll: ' ' ].
 
- 		stream
 
- 	    	nextPutAll: '''', String lf, String tab;
 
- 	    	nextPutAll: 'package: ''';
 
- 	    	nextPutAll: self category;
 
- 	    	nextPutAll: '''' ]
 
- !
 
- package
 
- 	<return self.pkg>
 
- !
 
- package: aPackage
 
- 	<self.pkg = aPackage>
 
- !
 
- rename: aString
 
- 	ClassBuilder new renameClass: self to: aString
 
- ! !
 
- !Class methodsFor: 'class creation'!
 
- subclass: aString instanceVariableNames: anotherString
 
- 	"Kept for compatibility."
 
- 	^self subclass: aString instanceVariableNames: anotherString package: nil
 
- !
 
- subclass: aString instanceVariableNames: aString2 category: aString3
 
- 	"Kept for compatibility."
 
- 	self deprecatedAPI.
 
- 	^self subclass: aString instanceVariableNames: aString2 package: aString3
 
- !
 
- subclass: aString instanceVariableNames: aString2 classVariableNames: classVars poolDictionaries: pools category: aString3
 
- 	"Just ignore class variables and pools. Added for compatibility."
 
- 	^self subclass: aString instanceVariableNames: aString2 package: aString3
 
- !
 
- subclass: aString instanceVariableNames: aString2 package: aString3
 
- 	^ClassBuilder new
 
- 	    superclass: self subclass: aString asString instanceVariableNames: aString2 package: aString3
 
- ! !
 
- !Class methodsFor: 'converting'!
 
- asJavascript
 
- 	^ 'smalltalk.', self name
 
- ! !
 
- !Class methodsFor: 'printing'!
 
- printString
 
- 	^self name
 
- ! !
 
- !Class methodsFor: 'testing'!
 
- isClass
 
- 	^true
 
- ! !
 
- Behavior subclass: #Metaclass
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Classes'!
 
- !Metaclass commentStamp!
 
- Metaclass is the root of the class hierarchy.
 
- Metaclass instances are metaclasses, one for each real class. 
 
- Metaclass instances have a single instance, which they hold onto, which is the class that they are the metaclass of.!
 
- !Metaclass methodsFor: 'accessing'!
 
- definition
 
- 	^ String streamContents: [ :stream |
 
- 		stream 
 
- 	   	 	nextPutAll: self asString;
 
- 	    	nextPutAll: ' class ';
 
- 	    	nextPutAll: 'instanceVariableNames: '''.
 
- 		self instanceVariableNames
 
- 	    	do: [ :each | stream nextPutAll: each ]
 
- 	    	separatedBy: [ stream nextPutAll: ' ' ].
 
- 		stream nextPutAll: '''' ]
 
- !
 
- instanceClass
 
- 	<return self.instanceClass>
 
- !
 
- instanceVariableNames: aCollection
 
- 	ClassBuilder new
 
- 	    class: self instanceVariableNames: aCollection
 
- !
 
- theMetaClass
 
- 	^ self
 
- !
 
- theNonMetaClass
 
- 	^ self instanceClass
 
- ! !
 
- !Metaclass methodsFor: 'converting'!
 
- asJavascript
 
- 	^ 'smalltalk.', self instanceClass name, '.klass'
 
- ! !
 
- !Metaclass methodsFor: 'printing'!
 
- printString
 
- 	^self instanceClass name, ' class'
 
- ! !
 
- !Metaclass methodsFor: 'testing'!
 
- isMetaclass
 
- 	^true
 
- ! !
 
- Object subclass: #ClassBuilder
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Classes'!
 
- !ClassBuilder commentStamp!
 
- ClassBuilder is responsible for compiling new classes or modifying existing classes in the system.
 
- Rather than using ClassBuilder directly to compile a class, use `Class >> subclass:instanceVariableNames:package:`.!
 
- !ClassBuilder methodsFor: 'accessing'!
 
- instanceVariableNamesFor: aString
 
- 	^(aString tokenize: ' ') reject: [ :each | each isEmpty ]
 
- ! !
 
- !ClassBuilder methodsFor: 'class definition'!
 
- addSubclassOf: aClass named: aString instanceVariableNames: aCollection package: packageName
 
-     | theClass |
 
-     
 
-     theClass := Smalltalk current at: aString.
 
-     
 
-    	theClass ifNotNil: [ 
 
-     	theClass superclass == aClass ifFalse: [
 
-     		^ self 
 
-         		migrateClassNamed: aString 
 
-            	 	superclass: aClass 
 
-            	 	instanceVariableNames: aCollection 
 
-             	package: packageName ] ].
 
- 	^ self 
 
-     	basicAddSubclassOf: aClass 
 
-         named: aString 
 
-         instanceVariableNames: aCollection 
 
-         package: packageName
 
- !
 
- class: aClass instanceVariableNames: aString
 
- 	self basicClass: aClass instanceVariableNames: aString.
 
-     self setupClass: aClass.
 
-     
 
-     SystemAnnouncer current
 
-     	announce: (ClassDefinitionChanged new
 
-         	theClass: aClass;
 
-             yourself)
 
- !
 
- superclass: aClass subclass: aString
 
- 	^self superclass: aClass subclass: aString instanceVariableNames: '' package: nil
 
- !
 
- superclass: aClass subclass: aString instanceVariableNames: aString2 package: aString3
 
- 	| newClass |
 
- 	
 
-     newClass := self addSubclassOf: aClass
 
- 		named: aString instanceVariableNames: (self instanceVariableNamesFor: aString2)
 
- 		package: (aString3 ifNil: ['unclassified']).
 
- 	self setupClass: newClass.
 
-     
 
-     SystemAnnouncer current 
 
-     	announce: (ClassAdded new
 
-         	theClass: newClass;
 
-             yourself).
 
-     
 
- 	^newClass
 
- ! !
 
- !ClassBuilder methodsFor: 'class migration'!
 
- migrateClass: aClass superclass: anotherClass
 
- 	console log: aClass name.
 
- 	self 
 
-     	migrateClassNamed: aClass name
 
-         superclass: anotherClass
 
-         instanceVariableNames: aClass instanceVariableNames
 
-         package: aClass package name
 
- !
 
- migrateClassNamed: aString superclass: aClass instanceVariableNames: aCollection package: packageName
 
- 	| oldClass newClass tmp |
 
-     
 
-     tmp := 'new*', aString.
 
-     oldClass := Smalltalk current at: aString.
 
-     
 
-     newClass := self 
 
- 		addSubclassOf: aClass
 
- 		named: tmp
 
- 		instanceVariableNames: aCollection
 
- 		package: packageName.
 
- 	self basicSwapClassNames: oldClass with: newClass.
 
- 	[ self copyClass: oldClass to: newClass ]
 
- 		on: Error
 
- 		do: [ :exception |
 
- 			self
 
-             	basicSwapClassNames: oldClass with: newClass;
 
-             	basicRemoveClass: newClass.
 
-             exception signal ].
 
- 	self
 
- 		rawRenameClass: oldClass to: tmp;
 
-         rawRenameClass: newClass to: aString.
 
- 	oldClass subclasses do: [ :each |
 
-     	self migrateClass: each superclass: newClass ].
 
-     self basicRemoveClass: oldClass.
 
- 	^newClass
 
- !
 
- renameClass: aClass to: aString
 
- 	self basicRenameClass: aClass to: aString.
 
-     
 
-     SystemAnnouncer current
 
-     	announce: (ClassRenamed new
 
-         	theClass: aClass;
 
-             yourself)
 
- ! !
 
- !ClassBuilder methodsFor: 'copying'!
 
- copyClass: aClass named: aString
 
- 	| newClass |
 
- 	newClass := self 
 
- 		addSubclassOf: aClass superclass
 
- 		named: aString 
 
- 		instanceVariableNames: aClass instanceVariableNames 
 
- 		package: aClass package name.
 
- 	self copyClass: aClass to: newClass.
 
-     
 
- 	^newClass
 
- !
 
- copyClass: aClass to: anotherClass
 
- 	anotherClass comment: aClass comment.
 
- 	aClass methodDictionary values do: [ :each |
 
- 		Compiler new install: each source forClass: anotherClass category: each category ].
 
- 	self basicClass: anotherClass class instanceVariables: aClass class instanceVariableNames.
 
- 	aClass class methodDictionary values do: [ :each |
 
- 		Compiler new install: each source forClass: anotherClass class category: each category ].
 
- 	self setupClass: anotherClass
 
- ! !
 
- !ClassBuilder methodsFor: 'method definition'!
 
- installMethod: aCompiledMethod forClass: aBehavior category: aString
 
- 	aCompiledMethod category: aString.
 
- 	aBehavior addCompiledMethod: aCompiledMethod.
 
-     self setupClass: aBehavior.
 
- 	^aCompiledMethod
 
- ! !
 
- !ClassBuilder methodsFor: 'private'!
 
- basicAddSubclassOf: aClass named: aString instanceVariableNames: aCollection package: packageName
 
- 	<
 
- 		smalltalk.addClass(aString, aClass, aCollection, packageName);
 
- 		return smalltalk[aString]
 
- 	>
 
- !
 
- basicClass: aClass instanceVariableNames: aString
 
- 	self basicClass: aClass instanceVariables: (self instanceVariableNamesFor: aString)
 
- !
 
- basicClass: aClass instanceVariables: aCollection
 
- 	aClass isMetaclass ifFalse: [self error: aClass name, ' is not a metaclass'].
 
- 	aClass basicAt: 'iVarNames' put: aCollection
 
- !
 
- basicRemoveClass: aClass
 
- 	<smalltalk.removeClass(aClass)>
 
- !
 
- basicRenameClass: aClass to: aString
 
- 	<
 
- 		smalltalk[aString] = aClass;
 
- 		delete smalltalk[aClass.className];
 
- 		aClass.className = aString;
 
- 	>
 
- !
 
- basicSwapClassNames: aClass with: anotherClass
 
- 	<
 
- 		var tmp = aClass.className;
 
- 		aClass.className = anotherClass.className;
 
-         anotherClass.className = tmp;
 
- 	>
 
- !
 
- rawRenameClass: aClass to: aString
 
- 	<
 
- 		smalltalk[aString] = aClass;
 
- 	>
 
- ! !
 
- !ClassBuilder methodsFor: 'public'!
 
- setupClass: aClass
 
- 	<smalltalk.init(aClass);>
 
- ! !
 
- Object subclass: #ClassCategoryReader
 
- 	instanceVariableNames: 'class category'
 
- 	package: 'Kernel-Classes'!
 
- !ClassCategoryReader commentStamp!
 
- ClassCategoryReader represents a mechanism for retrieving class descriptions stored on a file.!
 
- !ClassCategoryReader methodsFor: 'accessing'!
 
- class: aClass category: aString
 
- 	class := aClass.
 
- 	category := aString
 
- ! !
 
- !ClassCategoryReader methodsFor: 'fileIn'!
 
- scanFrom: aChunkParser
 
- 	| chunk |
 
- 	[chunk := aChunkParser nextChunk.
 
- 	chunk isEmpty] whileFalse: [
 
- 	    self compileMethod: chunk].
 
- 	ClassBuilder new setupClass: class
 
- ! !
 
- !ClassCategoryReader methodsFor: 'initialization'!
 
- initialize
 
- 	super initialize.
 
- ! !
 
- !ClassCategoryReader methodsFor: 'private'!
 
- compileMethod: aString
 
- 	Compiler new install: aString forClass: class category: category
 
- ! !
 
- Object subclass: #ClassCommentReader
 
- 	instanceVariableNames: 'class'
 
- 	package: 'Kernel-Classes'!
 
- !ClassCommentReader commentStamp!
 
- ClassCommentReader represents a mechanism for retrieving class comments stored on a file.
 
- See `ClassCategoryReader` too.!
 
- !ClassCommentReader methodsFor: 'accessing'!
 
- class: aClass
 
- 	class := aClass
 
- ! !
 
- !ClassCommentReader methodsFor: 'fileIn'!
 
- scanFrom: aChunkParser
 
- 	| chunk |
 
- 	chunk := aChunkParser nextChunk.
 
- 	chunk isEmpty ifFalse: [
 
- 	    self setComment: chunk].
 
- ! !
 
- !ClassCommentReader methodsFor: 'initialization'!
 
- initialize
 
- 	super initialize.
 
- ! !
 
- !ClassCommentReader methodsFor: 'private'!
 
- setComment: aString
 
-     class comment: aString
 
- ! !
 
- Object subclass: #ClassSorterNode
 
- 	instanceVariableNames: 'theClass level nodes'
 
- 	package: 'Kernel-Classes'!
 
- !ClassSorterNode methodsFor: 'accessing'!
 
- getNodesFrom: aCollection
 
- 	| children others |
 
- 	children := #().
 
- 	others := #().
 
- 	aCollection do: [:each |
 
- 		(each superclass = self theClass)
 
- 			ifTrue: [children add: each]
 
- 			ifFalse: [others add: each]].
 
- 	nodes:= children collect: [:each |
 
- 		ClassSorterNode on: each classes: others level: self level + 1]
 
- !
 
- level
 
- 	^level
 
- !
 
- level: anInteger
 
- 	level := anInteger
 
- !
 
- nodes
 
- 	^nodes
 
- !
 
- theClass
 
- 	^theClass
 
- !
 
- theClass: aClass
 
- 	theClass := aClass
 
- ! !
 
- !ClassSorterNode methodsFor: 'visiting'!
 
- traverseClassesWith: aCollection
 
- 	"sort classes alphabetically Issue #143"
 
- 	aCollection add: self theClass.
 
- 	(self nodes sorted: [:a :b | a theClass name <= b theClass name ]) do: [:aNode |
 
- 		aNode traverseClassesWith: aCollection ].
 
- ! !
 
- !ClassSorterNode class methodsFor: 'instance creation'!
 
- on: aClass classes: aCollection level: anInteger
 
- 	^self new
 
- 		theClass: aClass;
 
- 		level: anInteger;
 
- 		getNodesFrom: aCollection;
 
- 		yourself
 
- ! !
 
 
  |