[Pkg] The Trunk: Kernel.spur-eem.861.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Aug 6 00:28:23 UTC 2014


Eliot Miranda uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel.spur-eem.861.mcz

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

Name: Kernel.spur-eem.861
Author: eem
Time: 5 August 2014, 5:27:24.372 pm
UUID: d83077cc-0fd1-4a3b-b4f9-3e4447dd472d
Ancestors: Kernel-eem.861

Kernel-eem.861 patched for Spur by SpurBootstrapMonticelloPackagePatcher Cog-eem.179

Slightly more efficient ProtoObject>>become:.
Eliminate isKindOf:'s in InstructionPrinter>>pushConstant:.
Provide CompiledMethod>>protocol to answer its selector's
category^H^H^H^H^H^H^H^Hprotocol.

=============== Diff against Kernel-eem.861 ===============

Item was changed:
  ----- Method: Behavior>>allInstances (in category 'accessing instances and variables') -----
+ allInstances
+ 	"Answer all instances of the receiver."
+ 	<primitive: 177>
+ 	"The primitive can fail because memory is low.  If so, fall back on the old
+ 	 enumeration code, which gives the system a chance to GC and/or grow.
+ 	 Because aBlock might change the class of inst (for example, using become:),
+ 	 it is essential to compute next before aBlock value: inst."
+ 	| inst insts next |
+ 	insts := WriteStream on: (Array new: 64).
+ 	inst := self someInstance.
+ 	[inst == nil] whileFalse:
+ 		[next := inst nextInstance.
+ 		 (inst == insts or: [inst == insts originalContents]) ifFalse: [insts nextPut: inst].
+ 		 inst := next].
+ 	^insts contents!
- allInstances 
- 	"Answer a collection of all current instances of the receiver."
- 
- 	| all |
- 	all := OrderedCollection new.
- 	self allInstancesDo: [:x | x == all ifFalse: [all add: x]].
- 	^ all asArray
- !

Item was changed:
  ----- Method: Behavior>>allInstancesDo: (in category 'enumerating') -----
+ allInstancesDo: aBlock
+ 	"Evaluate aBlock with each of the current instances of the receiver."
+ 	| instances inst next |
+ 	instances := self allInstancesOrNil.
+ 	instances ifNotNil:
+ 		[instances do: aBlock.
+ 		 ^self].
+ 	"allInstancesOrNil can fail because memory is low.  If so, fall back on the old
+ 	 enumeration code.  Because aBlock might change the class of inst (for example,
+ 	 using become:), it is essential to compute next before aBlock value: inst."
- allInstancesDo: aBlock 
- 	"Evaluate the argument, aBlock, for each of the current instances of the 
- 	receiver.
- 	
- 	Because aBlock might change the class of inst (for example, using become:),
- 	it is essential to compute next before aBlock value: inst."
- 	| inst next |
  	inst := self someInstance.
+ 	[inst == nil] whileFalse:
+ 		[next := inst nextInstance.
+ 		 aBlock value: inst.
+ 		 inst := next]!
- 	[inst == nil]
- 		whileFalse:
- 		[
- 		next := inst nextInstance.
- 		aBlock value: inst.
- 		inst := next]!

Item was added:
+ ----- Method: Behavior>>allInstancesOrNil (in category 'enumerating') -----
+ allInstancesOrNil
+ 	"Answer all instances of the receiver, or nil if the primitive
+ 	 fails, which it may be due to being out of memory."
+ 	<primitive: 177>
+ 	^nil!

Item was changed:
  ----- Method: Behavior>>basicNew (in category 'instance creation') -----
  basicNew
  	"Primitive. Answer an instance of the receiver (which is a class) with no 
+ 	 indexable variables. Fail if the class is indexable. Essential. See Object 
+ 	 documentation whatIsAPrimitive.
+ 	
+ 	 If the primitive fails because space is low then the scavenger
+ 	 will run before the method is activated.  Check arguments and
+ 	 retry via handleFailingBasicNew if they're OK."
- 	indexable variables. Fail if the class is indexable. Essential. See Object 
- 	documentation whatIsAPrimitive."
  
  	<primitive: 70>
+ 	self isVariable ifTrue: [^self basicNew: 0].
+ 	"space must have been low, and the scavenger must have run.
+ 	 retry after the scavenge."
+ 	^self handleFailingBasicNew!
- 	self isVariable ifTrue: [ ^ self basicNew: 0 ].
- 	"space must be low"
- 	OutOfMemory signal.
- 	^ self basicNew  "retry if user proceeds"
- !

Item was changed:
  ----- Method: Behavior>>basicNew: (in category 'instance creation') -----
  basicNew: sizeRequested 
+ 	"Primitive. Answer an instance of this class with the number of indexable
+ 	 variables specified by the argument, sizeRequested.  Fail if this class is not
+ 	 indexable or if the argument is not a positive Integer, or if there is not
+ 	 enough memory available. Essential. See Object documentation whatIsAPrimitive.
+ 	
+ 	 If the primitive fails because space is low then the scavenger will run before the
+ 	 method is activated.  Check args and retry via handleFailingBasicNew: if they're OK."
- 	"Primitive. Answer an instance of this class with the number
- 	of indexable variables specified by the argument, sizeRequested.
- 	Fail if this class is not indexable or if the argument is not a
- 	positive Integer, or if there is not enough memory available. 
- 	Essential. See Object documentation whatIsAPrimitive."
  
  	<primitive: 71>
  	self isVariable ifFalse:
  		[self error: self printString, ' cannot have variable sized instances'].
  	(sizeRequested isInteger and: [sizeRequested >= 0]) ifTrue:
+ 		["arg okay; space must have been low, and the scavenger must have run.
+ 		  retry after the scavenge"
+ 		^self handleFailingBasicNew: sizeRequested].
- 		["arg okay; space must be low."
- 		OutOfMemory signal.
- 		^ self basicNew: sizeRequested  "retry if user proceeds"].
  	self primitiveFailed!

Item was added:
+ ----- Method: Behavior>>byteSizeOfInstance (in category 'accessing instances and variables') -----
+ byteSizeOfInstance
+ 	"Answer the total memory size of an instance of the receiver."
+ 
+ 	<primitive: 181 error: ec>
+ 	self isVariable ifTrue:
+ 		[^self byteSizeOfInstanceOfSize: 0].
+ 	self primitiveFailed!

Item was added:
+ ----- Method: Behavior>>byteSizeOfInstanceOfSize: (in category 'accessing instances and variables') -----
+ byteSizeOfInstanceOfSize: basicSize
+ 	"Answer the total memory size of an instance of the receiver
+ 	 with the given number of indexable instance variables."
+ 
+ 	<primitive: 181 error: ec>
+ 	self isVariable
+ 		ifTrue: "If the primitive overflowed answer a close approximation"
+ 			[(basicSize isInteger
+ 			  and: [basicSize >= 16r1000000]) ifTrue:
+ 				[^2 * (self byteSizeOfInstanceOfSize: basicSize + 1 // 2)
+ 				   - (self byteSizeOfInstanceOfSize: 0)]]
+ 		ifFalse:
+ 			[basicSize = 0 ifTrue:
+ 				[^self byteSizeOfInstance]].
+ 	self primitiveFailed!

Item was added:
+ ----- Method: Behavior>>elementSize (in category 'accessing instances and variables') -----
+ elementSize
+ 	"Answer the size in bytes of an element in the receiver.  The formats are
+ 			0	= 0 sized objects (UndefinedObject True False et al)
+ 			1	= non-indexable objects with inst vars (Point et al)
+ 			2	= indexable objects with no inst vars (Array et al)
+ 			3	= indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 			4	= weak indexable objects with inst vars (WeakArray et al)
+ 			5	= weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 			6	= unused
+ 			7	= immediates (SmallInteger, Character)
+ 			8	= unused
+ 			9	= 64-bit indexable
+ 		10-11	= 32-bit indexable (Bitmap)
+ 		12-15	= 16-bit indexable
+ 		16-23	= 8-bit indexable
+ 		24-31	= compiled methods (CompiledMethod)"
+ 	| instSpec |
+ 	instSpec := self instSpec.
+ 	instSpec < 9 ifTrue: [^Smalltalk wordSize].
+ 	instSpec >= 16 ifTrue: [^1].
+ 	instSpec >= 12 ifTrue: [^2].
+ 	instSpec >= 10 ifTrue: [^4].
+ 	^8!

Item was added:
+ ----- Method: Behavior>>handleFailingBasicNew (in category 'private') -----
+ handleFailingBasicNew
+ 	"handleFailingBasicNew gets sent after basicNew has failed and allowed
+ 	 a scavenging garbage collection to occur.  The scavenging collection
+ 	 will have happened as the VM is activating the (failing) basicNew.  If
+ 	 handleFailingBasicNew fails then the scavenge failed to reclaim sufficient
+ 	 space and a global garbage collection is required.  Retry after garbage
+ 	 collecting and growing memory if necessary.
+ 
+ 	 Primitive. Answer an instance of this class with the number of indexable
+ 	 variables specified by the argument, sizeRequested.  Fail if this class is not
+ 	 indexable or if the argument is not a positive Integer, or if there is not
+ 	 enough memory available. Essential. See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 70>
+ 	Smalltalk garbageCollect < 1048576 ifTrue:
+ 		[Smalltalk growMemoryByAtLeast: 1048576].
+ 	^self handleFailingFailingBasicNew "retry after global garbage collect"!

Item was added:
+ ----- Method: Behavior>>handleFailingBasicNew: (in category 'private') -----
+ handleFailingBasicNew: sizeRequested
+ 	"handleFailingBasicNew: gets sent after basicNew: has failed and allowed
+ 	 a scavenging garbage collection to occur.  The scavenging collection
+ 	 will have happened as the VM is activating the (failing) basicNew:.  If
+ 	 handleFailingBasicNew: fails then the scavenge failed to reclaim sufficient
+ 	 space and a global garbage collection is required.  Retry after garbage
+ 	 collecting and growing memory if necessary.
+ 
+ 	 Primitive. Answer an instance of this class with the number of indexable
+ 	 variables specified by the argument, sizeRequested.  Fail if this class is not
+ 	 indexable or if the argument is not a positive Integer, or if there is not
+ 	 enough memory available. Essential. See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 71>
+ 	| bytesRequested |
+ 	bytesRequested := self byteSizeOfInstanceOfSize: sizeRequested.
+ 	Smalltalk garbageCollect < bytesRequested ifTrue:
+ 		[Smalltalk growMemoryByAtLeast: bytesRequested].
+ 	"retry after global garbage collect and possible grow"
+ 	^self handleFailingFailingBasicNew: sizeRequested!

Item was added:
+ ----- Method: Behavior>>handleFailingFailingBasicNew (in category 'private') -----
+ handleFailingFailingBasicNew
+ 	"This basicNew gets sent after handleFailingBasicNew: has done a full
+ 	 garbage collection and possibly grown memory.  If this basicNew fails
+ 	 then the system really is low on space, so raise the OutOfMemory signal.
+ 
+ 	 Primitive. Answer an instance of this class with the number of indexable
+ 	 variables specified by the argument, sizeRequested.  Fail if this class is not
+ 	 indexable or if the argument is not a positive Integer, or if there is not
+ 	 enough memory available. Essential. See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 70>
+ 	"space must be low"
+ 	OutOfMemory signal.
+ 	^self basicNew  "retry if user proceeds"!

Item was added:
+ ----- Method: Behavior>>handleFailingFailingBasicNew: (in category 'private') -----
+ handleFailingFailingBasicNew: sizeRequested
+ 	"This basicNew: gets sent after handleFailingBasicNew: has done a full
+ 	 garbage collection and possibly grown memory.  If this basicNew: fails
+ 	 then the system really is low on space, so raise the OutOfMemory signal.
+ 
+ 	 Primitive. Answer an instance of this class with the number of indexable
+ 	 variables specified by the argument, sizeRequested.  Fail if this class is not
+ 	 indexable or if the argument is not a positive Integer, or if there is not
+ 	 enough memory available. Essential. See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 71>
+ 	"space must be low."
+ 	OutOfMemory signal.
+ 	^self basicNew: sizeRequested  "retry if user proceeds"!

Item was added:
+ ----- Method: Behavior>>identityHash (in category 'comparing') -----
+ identityHash
+ 	"Answer a SmallInteger whose value is related to the receiver's identity.
+ 	 Behavior implements identityHash to allow the VM to use an object representation which
+ 	 does not include a direct reference to an object's class in an object.  If the VM is using
+ 	 this implementation then classes are held in a class table and instances contain the index
+ 	 of their class in the table.  A class's class table index is its identityHash so that an instance
+ 	 can be created without searching the table for a class's index.  The VM uses this primitive
+ 	 to enter the class into the class table, assigning its identityHash with an as yet unused
+ 	 class table index. If this primitive fails it means that the class table is full.  In Spur as of
+ 	 2014 there are 22 bits of classTable index and 22 bits of identityHash per object.
+ 
+ 	 Primitive. Essential. Do not override. See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 175>
+ 	self primitiveFailed!

Item was changed:
  ----- Method: Behavior>>indexIfCompact (in category 'private') -----
  indexIfCompact
+ 	"Backward compatibility with the Squeak V3 object format.
+ 	 Spur does not have a distinction between compact and non-compact classes."
+ 	^0!
- 	"If these 5 bits are non-zero, then instances of this class
- 	will be compact.  It is crucial that there be an entry in
- 	Smalltalk compactClassesArray for any class so optimized.
- 	See the msgs becomeCompact and becomeUncompact."
- 	^ (format bitShift: -11) bitAnd: 16r1F
- "
- Smalltalk compactClassesArray doWithIndex: 
- 	[:c :i | c == nil ifFalse:
- 		[c indexIfCompact = i ifFalse: [self halt]]]
- "!

Item was changed:
  ----- Method: Behavior>>instSize (in category 'testing') -----
  instSize
  	"Answer the number of named instance variables
+ 	(as opposed to indexed variables) of the receiver.
+ 	 Above Cog Spur the class format is
+ 		<5 bits inst spec><16 bits inst size>"
+ 	^format bitAnd: 16rFFFF!
- 	(as opposed to indexed variables) of the receiver."
- 
- 	self flag: #instSizeChange.  "Smalltalk browseAllCallsOn: #instSizeChange"
- "
- 	NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
- 	When we revise the image format, it should become...
- 	^ ((format bitShift: -1) bitAnd: 16rFF) - 1
- 	Note also that every other method in this category will require
- 	2 bits more of right shift after the change.
- "
- 	^ ((format bitShift: -10) bitAnd: 16rC0) + ((format bitShift: -1) bitAnd: 16r3F) - 1!

Item was changed:
  ----- Method: Behavior>>instSpec (in category 'testing') -----
  instSpec
+ 	"Answer the instance specification part of the format that defines what kind of object
+ 	 an instance of the receiver is.  The formats are
+ 			0	= 0 sized objects (UndefinedObject True False et al)
+ 			1	= non-indexable objects with inst vars (Point et al)
+ 			2	= indexable objects with no inst vars (Array et al)
+ 			3	= indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 			4	= weak indexable objects with inst vars (WeakArray et al)
+ 			5	= weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 			6	= unused
+ 			7	= immediates (SmallInteger, Character)
+ 			8	= unused
+ 			9	= 64-bit indexable
+ 		10-11	= 32-bit indexable (Bitmap)
+ 		12-15	= 16-bit indexable
+ 		16-23	= 8-bit indexable
+ 		24-31	= compiled methods (CompiledMethod)"
+ 	^(format bitShift: -16) bitAnd: 16r1F!
- 	^ (format bitShift: -7) bitAnd: 16rF!

Item was changed:
  ----- Method: Behavior>>isBits (in category 'testing') -----
  isBits
+ 	"Answer whether the receiver contains just bits (not pointers).
+ 	 Above Cog Spur the class format is
+ 		<5 bits inst spec><16 bits inst size>
+ 	 where the 5-bit inst spec is
+ 			0	= 0 sized objects (UndefinedObject True False et al)
+ 			1	= non-indexable objects with inst vars (Point et al)
+ 			2	= indexable objects with no inst vars (Array et al)
+ 			3	= indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 			4	= weak indexable objects with inst vars (WeakArray et al)
+ 			5	= weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 			6	= unused
+ 			7	= immediates (SmallInteger, Character)
+ 			8	= unused
+ 			9	= 64-bit indexable
+ 		10-11	= 32-bit indexable (Bitmap)
+ 		12-15	= 16-bit indexable
+ 		16-23	= 8-bit indexable
+ 		24-31	= compiled methods (CompiledMethod)"
+ 	^self instSpec >= 7!
- 	"Answer whether the receiver contains just bits (not pointers)."
- 
- 	^ self instSpec >= 6!

Item was changed:
  ----- Method: Behavior>>isBytes (in category 'testing') -----
  isBytes
+ 	"Answer whether the receiver has 8-bit instance variables.
+ 	 Above Cog Spur the class format is
+ 		<5 bits inst spec><16 bits inst size>
+ 	 where the 5-bit inst spec is
+ 			0	= 0 sized objects (UndefinedObject True False et al)
+ 			1	= non-indexable objects with inst vars (Point et al)
+ 			2	= indexable objects with no inst vars (Array et al)
+ 			3	= indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 			4	= weak indexable objects with inst vars (WeakArray et al)
+ 			5	= weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 			6	= unused
+ 			7	= immediates (SmallInteger, Character)
+ 			8	= unused
+ 			9	= 64-bit indexable
+ 		10-11	= 32-bit indexable (Bitmap)
+ 		12-15	= 16-bit indexable
+ 		16-23	= 8-bit indexable
+ 		24-31	= compiled methods (CompiledMethod)"
+ 	^self instSpec >= 16!
- 	"Answer whether the receiver has 8-bit instance variables."
- 
- 	^ self instSpec >= 8!

Item was added:
+ ----- Method: Behavior>>isEphemeronClass (in category 'testing') -----
+ isEphemeronClass
+ 	"Answer whether the receiver has ephemeral instance variables.  The garbage collector will
+ 	 fire (queue for finalization) any ephemeron whose first instance variable is not referenced
+ 	 other than from the transitive closure of references from ephemerons. Hence referring to
+ 	 an object from the first inst var of an ephemeron will cause the ephemeron to fire when
+ 	 the rest of the system does not refer to the object and that object is ready to be collected.
+ 	 Since references from the remaining inst vars of an ephemeron will not prevent the ephemeron
+ 	 from firing, ephemerons may act as the associations in weak dictionaries such that the value
+ 	 (e.g. properties attached to the key) will not prevent firing when the key is no longer referenced
+ 	 other than from ephemerons.  Ephemerons can therefore be used to implement instance-based
+ 	 pre-mortem finalization."
+ 	^self instSpec = 5!

Item was added:
+ ----- Method: Behavior>>isImmediateClass (in category 'testing') -----
+ isImmediateClass
+ 	"Answer whether the receiver has immediate instances.  Immediate instances
+ 	 store their value in their object pointer, not in an object body.  Hence immediates
+ 	 take no space and are immutable.  The immediates are distinguished by tag bits
+ 	 in the pointer. They include SmallIntegers and Characters.  Hence in the 32-bit
+ 	 system SmallIntegers are 31-bit signed integers and Characters are 30-bit
+ 	 unsigned character codes."
+ 	^self instSpec = 7!

Item was changed:
  ----- Method: Behavior>>isVariable (in category 'testing') -----
  isVariable
+ 	"Answer whether the receiver has indexable variables.
+ 	 Above Cog Spur the class format is
+ 		<5 bits inst spec><16 bits inst size>
+ 	 where the 5-bit inst spec is
+ 			0	= 0 sized objects (UndefinedObject True False et al)
+ 			1	= non-indexable objects with inst vars (Point et al)
+ 			2	= indexable objects with no inst vars (Array et al)
+ 			3	= indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 			4	= weak indexable objects with inst vars (WeakArray et al)
+ 			5	= weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 			6	= unused
+ 			7	= immediates (SmallInteger, Character)
+ 			8	= unused
+ 			9	= 64-bit indexable
+ 		10-11	= 32-bit indexable (Bitmap)
+ 		12-15	= 16-bit indexable
+ 		16-23	= 8-bit indexable
+ 		24-31	= compiled methods (CompiledMethod)"
+ 	| instSpec |
+ 	instSpec := self instSpec.
+ 	^instSpec >= 2 and: [instSpec <= 4 or: [instSpec >= 9]]!
- 	"Answer whether the receiver has indexable variables."
- 
- 	^ self instSpec >= 2!

Item was changed:
  ----- Method: Behavior>>kindOfSubclass (in category 'testing class hierarchy') -----
  kindOfSubclass
+ 	"Answer a String that is the keyword that describes the receiver's kind of subclass,
+ 	 either a regular subclass, a variableSubclass, a variableByteSubclass,
+ 	 a variableWordSubclass, a weakSubclass, an ephemeronSubclass or an immediateSubclass.
+ 	 c.f. typeOfClass"
+ 	^self isVariable
+ 		ifTrue:
+ 			[self isBits
+ 				ifTrue:
+ 					[self isBytes
+ 						ifTrue: [' variableByteSubclass: ']
+ 						ifFalse: [' variableWordSubclass: ']]
+ 				ifFalse:
+ 					[self isWeak
+ 						ifTrue: [' weakSubclass: ']
+ 						ifFalse: [' variableSubclass: ']]]
+ 		ifFalse:
+ 			[self isImmediateClass
+ 				ifTrue: [' immediateSubclass: ']
+ 				ifFalse:
+ 					[self isEphemeronClass
+ 						ifTrue: [' ephemeronSubclass: ']
+ 						ifFalse: [' subclass: ']]]!
- 	"Answer a String that is the keyword that describes the receiver's kind 
- 	of subclass, either a regular subclass, a variableSubclass, a  
- 	variableByteSubclass, a variableWordSubclass, or a weakSubclass."
- 	self isWeak
- 		ifTrue: [^ ' weakSubclass: '].
- 	^ self isVariable
- 		ifTrue: [self isBits
- 				ifTrue: [self isBytes
- 						ifTrue: [ ' variableByteSubclass: ']
- 						ifFalse: [ ' variableWordSubclass: ']]
- 				ifFalse: [ ' variableSubclass: ']]
- 		ifFalse: [ ' subclass: ']!

Item was changed:
  ----- Method: Behavior>>shouldNotBeRedefined (in category 'testing') -----
  shouldNotBeRedefined
+ 	"Answer if the receiver should not be redefined.
+ 	 The assumption is that classes in Smalltalk specialObjects and 
+ 	 instance-specific Behaviors should not be redefined"
- 	"Return true if the receiver should not be redefined.
- 	The assumption is that compact classes,
- 	classes in Smalltalk specialObjects and 
- 	Behaviors should not be redefined"
  
+ 	^(Smalltalk specialObjectsArray
+ 		identityIndexOf: self
+ 		ifAbsent: [(self isKindOf: self) ifTrue: [1] ifFalse: [0]]) ~= 0!
- 	^(Smalltalk compactClassesArray includes: self)
- 		or:[(Smalltalk specialObjectsArray includes: self)
- 			or:[self isKindOf: self]]!

Item was changed:
  ----- Method: Behavior>>typeOfClass (in category 'accessing') -----
  typeOfClass
+ 	"Answer a symbol uniquely describing the type of the receiver. c.f. kindOfSubclass"
+ 	self isBytes ifTrue:
+ 		[^self instSpec = CompiledMethod instSpec
+ 			ifTrue: [#compiledMethod] "Very special!!"
+ 			ifFalse: [#bytes]].
+ 	(self isWords and: [self isPointers not]) ifTrue:
+ 		[^self instSpec = SmallInteger instSpec
+ 			ifTrue: [#immediate] "Very special!!"
+ 			ifFalse: [#words]].
+ 	self isWeak ifTrue: [^#weak].
+ 	self isVariable ifTrue: [^#variable].
+ 	self isEphemeronClass ifTrue: [^#ephemeron].
+ 	^#normal!
- 	"Answer a symbol uniquely describing the type of the receiver"
- 	self instSpec = CompiledMethod instSpec ifTrue:[^#compiledMethod]. "Very special!!"
- 	self isBytes ifTrue:[^#bytes].
- 	(self isWords and:[self isPointers not]) ifTrue:[^#words].
- 	self isWeak ifTrue:[^#weak].
- 	self isVariable ifTrue:[^#variable].
- 	^#normal.!

Item was added:
+ ----- Method: Class>>immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'subclass creation') -----
+ immediateSubclass: t instanceVariableNames: f classVariableNames: d poolDictionaries: s category: cat 
+ 	"This is the standard initialization message for creating a new
+ 	 immediate class as a subclass of an existing class (the receiver)."
+ 	^ClassBuilder new
+ 		superclass: self
+ 		immediateSubclass: t
+ 		instanceVariableNames: f
+ 		classVariableNames: d
+ 		poolDictionaries: s
+ 		category: cat!

Item was changed:
  ----- Method: ClassBuilder>>computeFormat:instSize:forSuper:ccIndex: (in category 'class format') -----
  computeFormat: type instSize: newInstSize forSuper: newSuper ccIndex: ccIndex
  	"Compute the new format for making oldClass a subclass of newSuper.
+ 	 Answer the format or nil if there is any problem."
- 	Return the format or nil if there is any problem."
  	| instSize isVar isWords isPointers isWeak |
  	type == #compiledMethod ifTrue:
+ 		[newInstSize > 0 ifTrue:
+ 			[self error: 'A compiled method class cannot have named instance variables'.
+ 			^nil].
+ 		^CompiledMethod format].
- 		[^(CompiledMethod format
- 			bitClear: (16r1F bitShift: 11))
- 				bitOr: (ccIndex bitShift: 11)].
  	instSize := newInstSize + (newSuper ifNil:[0] ifNotNil:[newSuper instSize]).
+ 	instSize > 65535 ifTrue:
- 	instSize > 254 ifTrue:
  		[self error: 'Class has too many instance variables (', instSize printString,')'.
  		^nil].
  	type == #normal ifTrue:[isVar := isWeak := false. isWords := isPointers := true].
  	type == #bytes ifTrue:[isVar := true. isWords := isPointers := isWeak := false].
  	type == #words ifTrue:[isVar := isWords := true. isPointers := isWeak := false].
  	type == #variable ifTrue:[isVar := isPointers := isWords := true. isWeak := false].
  	type == #weak ifTrue:[isVar := isWeak := isWords := isPointers := true].
+ 	type == #ephemeron ifTrue:[isVar := false. isWeak := isWords := isPointers := true].
+ 	type == #immediate ifTrue:[isVar := isWeak := isPointers := false. isWords := true].
+ 	(isPointers not and: [instSize > 0]) ifTrue:
+ 		[self error: 'A non-pointer class cannot have named instance variables'.
- 	(isPointers not and:[instSize > 0]) ifTrue:
- 		[self error:'A non-pointer class cannot have instance variables'.
  		^nil].
+ 	^self format: instSize variable: isVar words: isWords pointers: isPointers weak: isWeak!
- 	^(self format: instSize 
- 		variable: isVar 
- 		words: isWords 
- 		pointers: isPointers 
- 		weak: isWeak) + (ccIndex bitShift: 11).!

Item was changed:
  ----- Method: ClassBuilder>>format:variable:words:pointers:weak: (in category 'class format') -----
  format: nInstVars variable: isVar words: isWords pointers: isPointers weak: isWeak
+ 	"Compute the format for the given instance specfication.
+ 	 Above Cog Spur the class format is
+ 		<5 bits inst spec><16 bits inst size>
+ 	 where the 5-bit inst spec is
+ 			0	= 0 sized objects (UndefinedObject True False et al)
+ 			1	= non-indexable objects with inst vars (Point et al)
+ 			2	= indexable objects with no inst vars (Array et al)
+ 			3	= indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 			4	= weak indexable objects with inst vars (WeakArray et al)
+ 			5	= weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 			6	= unused
+ 			7	= immediates (SmallInteger, Character)
+ 			8	= unused
+ 			9	= reserved for 64-bit indexable
+ 		10-11	= 32-bit indexable (Bitmap)
+ 		12-15	= 16-bit indexable
+ 		16-23	= 8-bit indexable
+ 		24-31	= compiled methods (CompiledMethod)"
+ 	| instSpec |
- 	"Compute the format for the given instance specfication."
- 	| cClass instSpec sizeHiBits fmt |
- 	self flag: #instSizeChange.
- "
- Smalltalk browseAllCallsOn: #instSizeChange.
- Smalltalk browseAllImplementorsOf: #fixedFieldsOf:.
- Smalltalk browseAllImplementorsOf: #instantiateClass:indexableSize:.
- "
- "
- 	NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
- 	For now the format word is...
- 		<2 bits=instSize//64><5 bits=cClass><4 bits=instSpec><6 bits=instSize\\64><1 bit=0>
- 	But when we revise the image format, it should become...
- 		<5 bits=cClass><4 bits=instSpec><8 bits=instSize><1 bit=0>
- "
- 	sizeHiBits := (nInstVars+1) // 64.
- 	cClass := 0.  "for now"
  	instSpec := isWeak
+ 					ifTrue:
+ 						[isVar
+ 							ifTrue: [4]
+ 							ifFalse: [5]]
+ 					ifFalse:
+ 						[isPointers
+ 							ifTrue:
+ 								[isVar
+ 									ifTrue: [nInstVars > 0 ifTrue: [3] ifFalse: [2]]
+ 									ifFalse: [nInstVars > 0 ifTrue: [1] ifFalse: [0]]]
+ 							ifFalse:
+ 								[isVar
+ 									ifTrue: [isWords ifTrue: [12] ifFalse: [16]]
+ 									ifFalse: [7]]].
+ 	^(instSpec bitShift: 16) + nInstVars!
- 		ifTrue:[4]
- 		ifFalse:[isPointers
- 				ifTrue: [isVar
- 						ifTrue: [nInstVars>0 ifTrue: [3] ifFalse: [2]]
- 						ifFalse: [nInstVars>0 ifTrue: [1] ifFalse: [0]]]
- 				ifFalse: [isWords ifTrue: [6] ifFalse: [8]]].
- 	fmt := sizeHiBits.
- 	fmt := (fmt bitShift: 5) + cClass.
- 	fmt := (fmt bitShift: 4) + instSpec.
- 	fmt := (fmt bitShift: 6) + ((nInstVars+1)\\64).  "+1 since prim size field includes header"
- 	fmt := (fmt bitShift: 1). "This shift plus integer bit lets wordSize work like byteSize"
- 	^fmt!

Item was added:
+ ----- Method: ClassBuilder>>superclass:immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'public') -----
+ superclass: aClass
+ 	immediateSubclass: t instanceVariableNames: f 
+ 	classVariableNames: d poolDictionaries: s category: cat
+ 	"This is the standard initialization message for creating a
+ 	 new immediate class as a subclass of an existing class."
+ 	| env |
+ 	aClass instSize > 0
+ 		ifTrue: [^self error: 'cannot make an immediate subclass of a class with named fields'].
+ 	aClass isVariable
+ 		ifTrue: [^self error: 'cannot make an immediate subclass of a class with indexed instance variables'].
+ 	aClass isPointers
+ 		ifFalse: [^self error: 'cannot make an immediate subclass of a class without pointer fields'].
+ 	"Cope with pre-environment and environment versions. Simplify asap."
+ 	env := (Smalltalk classNamed: #EnvironmentRequest)
+ 				ifNil: [aClass environment]
+ 				ifNotNil: [:erc| erc signal ifNil: [aClass environment]].
+ 	^self 
+ 		name: t
+ 		inEnvironment: env
+ 		subclassOf: aClass
+ 		type: #immediate
+ 		instanceVariableNames: f
+ 		classVariableNames: d
+ 		poolDictionaries: s
+ 		category: cat!

Item was changed:
  ----- Method: ClassBuilder>>update:to: (in category 'class mutation') -----
  update: oldClass to: newClass
+ 	"Convert oldClass, all its instances and possibly its meta class into newClass,
+ 	 instances of newClass and possibly its meta class. The process is surprisingly
+ 	 simple in its implementation and surprisingly complex in its nuances and potentially
+ 	 bad side effects.
+ 	 We can rely on two assumptions (which are critical):
+ 		#1: The method #updateInstancesFrom: will not create any lasting pointers to
+ 			 'old' instances ('old' is quote on quote since #updateInstancesFrom: will do
+ 			 a become of the old vs. the new instances and therefore it will not create
+ 			 pointers to *new* instances before the #become: which are *old* afterwards)
+ 		#2: The non-preemptive execution of the critical piece of code guarantees that
+ 			 nobody can get a hold by 'other means' (such as process interruption and
+ 			 reflection) on the old instances.
+ 	 Given the above two, we know that after #updateInstancesFrom: there are no pointers
+ 	 to any old instances. After the forwarding become there will be no pointers to the old
+ 	 class or meta class either.
+ 	 Andreas Raab, 2/27/2003 23:42"
- 	"Convert oldClass, all its instances and possibly its meta class into newClass, instances of newClass and possibly its meta class. The process is surprisingly simple in its implementation and surprisingly complex in its nuances and potentially bad side effects. 
- 	We can rely on two assumptions (which are critical):
- 		#1: The method #updateInstancesFrom: will not create any lasting pointers to 'old' instances ('old' is quote on quote since #updateInstancesFrom: will do a become of the old vs. the new instances and therefore it will not create pointers to *new* instances before the #become: which are *old* afterwards)
- 		#2: The non-preemptive execution of the critical piece of code guarantees that nobody can get a hold by 'other means' (such as process interruption and reflection) on the old instances.
- 	Given the above two, we know that after #updateInstancesFrom: there are no pointer to any old instances. After the forwarding become there will be no pointers to the old class or meta class either. Meaning that if we throw in a nice fat GC at the end of the critical block, everything will be gone (but see the comment right there). There's no need to worry.
- 	"
  	| meta |
  	meta := oldClass isMeta.
  	"Note: Everything from here on will run without the ability to get interrupted
  	to prevent any other process to create new instances of the old class."
+ 	["Note: The following removal may look somewhat obscure and needs an explanation.
+ 	  When we mutate the class hierarchy we create new classes for any existing subclass.
+ 	  So it may look as if we don't have to remove the old class from its superclass. However,
+ 	  at the top of the hierarchy (the first class we reshape) that superclass itself is not newly
+ 	  created so therefore it will hold both the oldClass and newClass in its (obsolete or not)
+ 	  subclasses. Since the #become: below will transparently replace the pointers to oldClass
+ 	  with newClass the superclass would have newClass in its subclasses TWICE. With rather
+ 	  unclear effects if we consider that we may convert the meta-class hierarchy itself (which
+ 	  is derived from the non-meta class hierarchy).
+ 	  Due to this problem ALL classes are removed from their superclass just prior to converting
+ 	  them. Here, breaking the superclass/subclass invariant really doesn't matter since we will
+ 	  effectively remove the oldClass (becomeForward:) just a few lines below."
- 	[
- 		"Note: The following removal may look somewhat obscure and needs an explanation. When we mutate the class hierarchy we create new classes for any existing subclass. So it may look as if we don't have to remove the old class from its superclass. However, at the top of the hierarchy (the first class we reshape) that superclass itself is not newly created so therefore it will hold both the oldClass and newClass in its (obsolete or not) subclasses. Since the #become: below will transparently replace the pointers to oldClass with newClass the superclass would have newClass in its subclasses TWICE. With rather unclear effects if we consider that we may convert the meta-class hierarchy itself (which is derived from the non-meta class hierarchy).
- 		Due to this problem ALL classes are removed from their superclass just prior to converting them. Here, breaking the superclass/subclass invariant really doesn't matter since we will effectively remove the oldClass (become+GC) just a few lines below."
  
  		oldClass superclass removeSubclass: oldClass.
  		oldClass superclass removeObsoleteSubclass: oldClass.
  
  		"make sure that the VM cache is clean"
  		oldClass methodDict do: [:cm | cm flushCache].
  		
  		"Convert the instances of oldClass into instances of newClass"
  		newClass updateInstancesFrom: oldClass.
  
  		meta
  			ifTrue:
  				[oldClass becomeForward: newClass.
  				 oldClass updateMethodBindingsTo: oldClass binding]
  			ifFalse:
  				[{oldClass. oldClass class} elementsForwardIdentityTo: {newClass. newClass class}.
  				 oldClass updateMethodBindingsTo: oldClass binding.
  				 oldClass class updateMethodBindingsTo: oldClass class binding].
  
+ 		"eem 5/31/2014 07:22 At this point there used to be a garbage collect whose purpose was
+ 		 to ensure no old instances existed after the becomeForward:.  Without the GC it was possible
+ 		 to resurrect old instances using e.g. allInstancesDo:.  This was because the becomeForward:
+ 		 updated references from the old objects to new objects but didn't destroy the old objects.
+ 		 But as of late 2013/early 2014 becomeForward: has been modified to free all the old objects."]
+ 			valueUnpreemptively!
- 		Smalltalk garbageCollect.
- 
- 		"Warning: Read this before you even think about removing the GC. Yes, it slows us down. Quite heavily if you have a large image. However, there's no good and simple alternative here, since unfortunately, #become: does change class pointers. What happens is that after the above become all of the instances of the old class will have a class pointer identifying them as instances of newClass. If we get our hands on any of these instances we will break immediately since their expected instance layout (that of its class, e.g., newClass) will not match their actual instance layout (that of oldClass). And getting your hands on any of those instances is really simple - just reshaping one class two times in rapid succession will do it. Reflection techniques, interrupts, etc. will only add to this problem. In the case of Metaclass things get even worse since when we recompile the entire class hierarchy we will recompile both, Metaclass and its instances (and some of its instances will have the old and some the new layout).
- 
- 		The only easy solution to this problem would be to 'fix up' the class pointers of the old instances to point to the old class (using primitiveChangeClassTo:). But this won't work either - as we do a one-way become we would have to search the entire object memory for the oldClass and couldn't even clearly identify it unless we give it some 'special token' which sounds quite error-prone. If you really need to get rid of the GC here are some alternatives:
- 
- 		On the image level, one could create a copy of the oldClass before becoming it into the new class and, after becoming it, 'fix up' the old instances. That would certainly work but it sounds quite complex, as we need to make sure we're not breaking any of the superclass/subclass meta/non-meta class variants.
- 
- 		Alternatively, fix up #becomeForward on the VM-level to 'dump the source objects' of #become. This would be quite doable (just 'convert' them into a well known special class such as bitmap) yet it has problems if (accidentally or not) one of the objects in #become: appears on 'both sides of the fence' (right now, this will work ... in a way ... even though the consequences are unclear).
- 
- 		Another alternative is to provide a dedicated primitive for this (instead of using it implicitly in become) which would allow us to dump all the existing instances right here. This is equivalent to a more general primitiveChangeClassTo: and might be worthwhile but it would likely have to keep in mind the differences between bits and pointer thingies etc.
- 
- 		Since all of the alternatives seem rather complex and magical compared to a straight-forward GC it seems best to stick with the GC solution for now. If someone has a real need to fix this problem, that person will likely be motivated enough to check out the alternatives. Personally I'd probably go for #1 (copy the old class and remap the instances to it) since it's a solution that could be easily reverted from within the image if there's any problem with it."
- 
- 	] valueUnpreemptively.
- !

Item was changed:
  ----- Method: Integer class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"Integer initialize"	
+ 	self initializeLowBitPerByteTable!
- initialize	"Integer initialize"
- 	"Ensure we have the right compact class index"
- 
- 	"LPI has been a compact class forever - just ensure basic correctness"
- 	(LargePositiveInteger indexIfCompact = 5) ifFalse:[
- 		(Smalltalk compactClassesArray at: 5)
- 			ifNil:[LargePositiveInteger becomeCompactSimplyAt: 5]
- 			ifNotNil:[self error: 'Unexpected compact class setup']].
- 
- 	"Cog requires LNI to be compact at 4 (replacing PseudoContext)"
- 	(LargeNegativeInteger indexIfCompact = 4) ifFalse:[
- 		"PseudoContext will likely get removed at some point so write this test
- 		without introducing a hard dependency"
- 		(Smalltalk compactClassesArray at: 4) name == #PseudoContext
- 			ifTrue:[Smalltalk compactClassesArray at: 4 put: nil].
- 		(Smalltalk compactClassesArray at: 4)
- 			ifNil:[LargeNegativeInteger becomeCompactSimplyAt: 4]
- 			ifNotNil:[self error: 'Unexpected compact class setup']].
- 		
- 	self initializeLowBitPerByteTable
- !

Item was added:
+ ----- Method: MethodContext class>>allInstances (in category 'enumerating') -----
+ allInstances
+ 	"Answer all instances of the receiver."
+ 	<primitive: 177>
+ 	"The primitive can fail because memory is low.  If so, fall back on the old
+ 	 enumeration code, which gives the system a chance to GC and/or grow.
+ 	 Because aBlock might change the class of inst (for example, using become:),
+ 	 it is essential to compute next before aBlock value: inst.
+ 	 Only count until thisContext since this context has been created only to
+ 	 compute the existing instances."
+ 	| inst insts next |
+ 	insts := WriteStream on: (Array new: 64).
+ 	inst := self someInstance.
+ 	[inst == thisContext or: [inst == nil]] whileFalse:
+ 		[next := inst nextInstance.
+ 		 insts nextPut: inst.
+ 		 inst := next].
+ 	^insts contents!

Item was changed:
  ----- Method: MethodContext class>>allInstancesDo: (in category 'private') -----
  allInstancesDo: aBlock
+ 	"Evaluate aBlock with each of the current instances of the receiver."
+ 	| instances inst next |
+ 	instances := self allInstancesOrNil.
+ 	instances ifNotNil:
+ 		[instances do: aBlock.
+ 		 ^self].
+ 	"allInstancesOrNil can fail because memory is low.  If so, fall back on the old
+ 	 enumeration code.  Because aBlock might change the class of inst (for example,
+ 	 using become:), it is essential to compute next before aBlock value: inst.
+ 	 Only count until thisContext since evaluation of aBlock will create new contexts."
- 	"Only count until thisContext since evaluation of aBlock will create new contexts."
- 	| inst next |
  	inst := self someInstance.
+ 	[inst == thisContext or: [inst == nil]] whileFalse:
+ 		[next := inst nextInstance.
+ 		 aBlock value: inst.
+ 		 inst := next]!
- 	[inst == thisContext] whileFalse:[
- 		next := inst nextInstance.
- 		aBlock value: inst.
- 		inst := next]
- !

Item was changed:
  ----- Method: ProtoObject>>scaledIdentityHash (in category 'comparing') -----
  scaledIdentityHash
  	"For identityHash values returned by primitive 75, answer
+ 	 such values times 2^8.  Otherwise, match the existing
+ 	 identityHash implementation"
- 	such values times 2^18.  Otherwise, match the existing
- 	identityHash implementation"
  
+ 	^self identityHash * 256 "bitShift: 8"!
- 	^self identityHash * 262144 "bitShift: 18"!

Item was changed:
==== ERROR ===

Error: Unrecognized class type

6 August 2014 12:28:23.253 am

VM: unix - a SmalltalkImage
Image: Squeak3.11alpha [latest update: #8824]

SecurityManager state:
Restricted: false
FileAccess: true
SocketAccess: true
Working Dir /home/squeaksource
Trusted Dir /home/squeaksource/secure
Untrusted Dir /home/squeaksource/My Squeak

MCClassDefinition(Object)>>error:
	Receiver: a MCClassDefinition(SmallInteger)
	Arguments and temporary variables: 
		aString: 	'Unrecognized class type'
	Receiver's instance variables: 
		name: 	#SmallInteger
		superclassName: 	#Integer
		variables: 	an OrderedCollection()
		category: 	#'Kernel-Numbers'
		type: 	#immediate
		comment: 	'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
		commentStamp: 	'<historical>'
		traitComposition: 	nil
		classTraitComposition: 	nil

MCClassDefinition>>kindOfSubclass
	Receiver: a MCClassDefinition(SmallInteger)
	Arguments and temporary variables: 

	Receiver's instance variables: 
		name: 	#SmallInteger
		superclassName: 	#Integer
		variables: 	an OrderedCollection()
		category: 	#'Kernel-Numbers'
		type: 	#immediate
		comment: 	'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
		commentStamp: 	'<historical>'
		traitComposition: 	nil
		classTraitComposition: 	nil

MCClassDefinition>>printDefinitionOn:
	Receiver: a MCClassDefinition(SmallInteger)
	Arguments and temporary variables: 
		stream: 	a WriteStream
	Receiver's instance variables: 
		name: 	#SmallInteger
		superclassName: 	#Integer
		variables: 	an OrderedCollection()
		category: 	#'Kernel-Numbers'
		type: 	#immediate
		comment: 	'My instances are 31-bit numbers, stored in twos complement form. The ...etc...
		commentStamp: 	'<historical>'
		traitComposition: 	nil
		classTraitComposition: 	nil

[] in MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
	Receiver: a MCDiffyTextWriter
	Arguments and temporary variables: 
		definition: 	a WriteStream
		s: 	a MCClassDefinition(SmallInteger)
	Receiver's instance variables: 
		stream: 	a WriteStream
		initStream: 	nil


--- The full stack ---
MCClassDefinition(Object)>>error:
MCClassDefinition>>kindOfSubclass
MCClassDefinition>>printDefinitionOn:
[] in MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
String class(SequenceableCollection class)>>new:streamContents:
String class(SequenceableCollection class)>>streamContents:
MCDiffyTextWriter(MCTextWriter)>>chunkContents:
MCDiffyTextWriter(MCStWriter)>>writeClassDefinition:
MCDiffyTextWriter(MCStWriter)>>visitClassDefinition:
MCClassDefinition>>accept:
[] in MCDiffyTextWriter(MCTextWriter)>>visitInFork:
String class(SequenceableCollection class)>>new:streamContents:
String class(SequenceableCollection class)>>streamContents:
MCDiffyTextWriter(MCTextWriter)>>visitInFork:
MCDiffyTextWriter>>writePatchFrom:to:
MCDiffyTextWriter>>writeModification:
[] in MCDiffyTextWriter>>writePatch:
SortedCollection(OrderedCollection)>>do:
MCDiffyTextWriter>>writePatch:
SSDiffyTextWriter>>writePatch:
[] in SSDiffyTextWriter>>writeVersion:for:
BlockClosure>>on:do:
SSDiffyTextWriter>>writeVersion:for:
[] in SSEMailSubscription>>versionAdded:to:
BlockClosure>>on:do:
SSEMailSubscription>>versionAdded:to:
[] in [] in SSProject>>versionAdded:
[] in BlockClosure>>newProcess


More information about the Packages mailing list