123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467 |
- Smalltalk current createPackage: 'Kernel-Classes' properties: #{}!
- 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
- !
- allSubclasses
- | result |
- result := self subclasses.
- self subclasses do: [:each |
- result addAll: each allSubclasses].
- ^result
- !
- comment
- ^(self basicAt: 'comment') ifNil: ['']
- !
- comment: aString
- self basicAt: 'comment' put: aString
- !
- commentStamp
- ^ClassCommentReader new
- class: self;
- yourself
- !
- commentStamp: aStamp prior: prior
- ^self commentStamp
- !
- instanceVariableNames
- <return self.iVarNames>
- !
- methodAt: aString
- <return smalltalk.methods(self)[aString]>
- !
- methodDictionary
- <var dict = smalltalk.HashedCollection._new();
- var methods = self.fn.prototype.methods;
- for(var i in methods) {
- if(methods[i].selector) {
- dict._at_put_(methods[i].selector, methods[i]);
- }
- };
- return dict>
- !
- methodsFor: aString
- ^ClassCategoryReader new
- class: self category: aString;
- yourself
- !
- methodsFor: aString stamp: aStamp
- "Added for compatibility, right now ignores stamp."
- ^self methodsFor: aString
- !
- name
- <return self.className || nil>
- !
- protocols
- | protocols |
- protocols := Array new.
- self methodDictionary do: [:each |
- (protocols includes: each category) ifFalse: [
- protocols add: each category]].
- ^protocols sort
- !
- 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>
- !
- subclasses
- <return smalltalk.subclasses(self)>
- !
- superclass
- <return self.superclass || nil>
- !
- withAllSubclasses
- ^(Array with: self) addAll: self allSubclasses; yourself
- ! !
- !Behavior methodsFor: 'compiling'!
- addCompiledMethod: aMethod
- <smalltalk.addMethod(aMethod.selector._asSelector(), aMethod, self)>
- !
- compile: aString
- self compile: aString category: ''
- !
- compile: aString category: anotherString
- | method |
- method := Compiler new load: aString forClass: self.
- method category: anotherString.
- self addCompiledMethod: method
- !
- removeCompiledMethod: aMethod
- <delete self.fn.prototype[aMethod.selector._asSelector()];
- delete self.fn.prototype.methods[aMethod.selector];
- smalltalk.init(self);>
- ! !
- !Behavior methodsFor: 'instance creation'!
- basicNew
- <return new self.fn()>
- !
- new
- ^self basicNew initialize
- ! !
- !Behavior methodsFor: 'testing'!
- canUnderstand: aSelector
- ^(self methodDictionary keys includes: aSelector asString) or: [
- self superclass notNil and: [self superclass canUnderstand: aSelector]]
- !
- 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]
- !
- package
- <return self.pkg>
- !
- package: aPackage
- <self.pkg = aPackage>
- !
- rename: aString
- <
- smalltalk[aString] = self;
- delete smalltalk[self.className];
- self.className = 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: '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'!
- instanceClass
- <return self.instanceClass>
- !
- instanceVariableNames: aCollection
- ClassBuilder new
- class: self instanceVariableNames: aCollection
- ! !
- !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: 'class creation'!
- class: aClass instanceVariableNames: aString
- aClass isMetaclass ifFalse: [self error: aClass name, ' is not a metaclass'].
- aClass basicAt: 'iVarNames' put: (self instanceVariableNamesFor: aString).
- self setupClass: aClass
- !
- 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.
- ^newClass
- ! !
- !ClassBuilder methodsFor: 'private'!
- addSubclassOf: aClass named: aString instanceVariableNames: aCollection
- <smalltalk.addClass(aString, aClass, aCollection);
- return smalltalk[aString]>
- !
- addSubclassOf: aClass named: aString instanceVariableNames: aCollection package: packageName
- <smalltalk.addClass(aString, aClass, aCollection, packageName);
- return smalltalk[aString]>
- !
- copyClass: aClass named: aString
- | newClass |
- newClass := self
- addSubclassOf: aClass superclass
- named: aString
- instanceVariableNames: aClass instanceVariableNames
- package: aClass package name.
- self setupClass: newClass.
- aClass methodDictionary values do: [:each |
- newClass addCompiledMethod: (Compiler new load: each source forClass: newClass).
- (newClass methodDictionary at: each selector) category: each category].
- aClass class methodDictionary values do: [:each |
- newClass class addCompiledMethod: (Compiler new load: each source forClass: newClass class).
- (newClass class methodDictionary at: each selector) category: each category].
- self setupClass: newClass.
- ^newClass
- !
- instanceVariableNamesFor: aString
- ^(aString tokenize: ' ') reject: [:each | each isEmpty]
- !
- setupClass: aClass
- <smalltalk.init(aClass);>
- ! !
- Object subclass: #ClassCategoryReader
- instanceVariableNames: 'class category chunkParser'
- 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]
- ! !
- !ClassCategoryReader methodsFor: 'initialization'!
- initialize
- super initialize.
- chunkParser := ChunkParser new.
- ! !
- !ClassCategoryReader methodsFor: 'private'!
- compileMethod: aString
- | method compiler |
- method := (compiler := Compiler new) load: aString forClass: class.
- method category: category.
- class addCompiledMethod: method.
- compiler setupClass: class.
- ! !
- Object subclass: #ClassCommentReader
- instanceVariableNames: 'class chunkParser'
- package: 'Kernel-Classes'!
- !ClassCommentReader commentStamp!
- ClassCommentReader represents a mechanism for retrieving class descriptions 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.
- chunkParser := ChunkParser new.
- ! !
- !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
- ! !
|