[squeak-dev] The Trunk: System.spur-dtl.685.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Sep 27 20:31:03 UTC 2014


Eliot Miranda uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System.spur-dtl.685.mcz

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

Name: System.spur-dtl.685
Author: eem
Time: 27 September 2014, 1:17:02.073 pm
UUID: b1dd4f4e-0266-4130-9183-4349427d2843
Ancestors: System-dtl.685

System-dtl.685 patched for Spur by SpurBootstrapMonticelloPackagePatcher Cog-eem.208

Smalltalk isRunningCog should answer false for an interpreter VM

=============== Diff against System-dtl.685 ===============

Item was changed:
  ----- Method: SmalltalkImage>>compactClassesArray (in category 'special objects') -----
  compactClassesArray
  	"Smalltalk compactClassesArray"
+ 	"Backward-compatibility support.  Spur does not have compact classes."
+ 	^{}!
- 	"Return the array of 31 classes whose instances may be
- 	represented compactly"
- 	^ self specialObjectsArray at: 29!

Item was added:
+ ----- Method: SmalltalkImage>>growMemoryByAtLeast: (in category 'memory space') -----
+ growMemoryByAtLeast: numBytes
+ 	"Grow memory by at least the requested number of bytes.
+ 	 Primitive.  Essential. Fail if no memory is available."
+ 	<primitive: 180>
+ 	(numBytes isInteger and: [numBytes > 0]) ifTrue:
+ 		[OutOfMemory signal].
+ 	^self primitiveFailed!

Item was added:
+ ----- Method: SmalltalkImage>>maxIdentityHash (in category 'system attributes') -----
+ maxIdentityHash
+ 	"Answer the maximum identityHash value supported by the VM."
+ 	<primitive: 176>
+ 	^self primitiveFailed!

Item was changed:
  ----- Method: SmalltalkImage>>recreateSpecialObjectsArray (in category 'special objects') -----
  recreateSpecialObjectsArray
  	"Smalltalk recreateSpecialObjectsArray"
  	
  	"To external package developers:
  	**** DO NOT OVERRIDE THIS METHOD.  *****
  	If you are writing a plugin and need additional special object(s) for your own use, 
  	use addGCRoot() function and use own, separate special objects registry "
  	
  	"The Special Objects Array is an array of objects used by the Squeak virtual machine.
  	 Its contents are critical and accesses to it by the VM are unchecked, so don't even
  	 think of playing here unless you know what you are doing."
  	| newArray |
+ 	newArray := Array new: 60.
- 	newArray := Array new: 58.
  	"Nil false and true get used throughout the interpreter"
  	newArray at: 1 put: nil.
  	newArray at: 2 put: false.
  	newArray at: 3 put: true.
  	"This association holds the active process (a ProcessScheduler)"
  	newArray at: 4 put: (self specialObjectsArray at: 4) "(self bindingOf: #Processor) but it answers an Alias".
  	"Numerous classes below used for type checking and instantiation"
  	newArray at: 5 put: Bitmap.
  	newArray at: 6 put: SmallInteger.
  	newArray at: 7 put: ByteString.
  	newArray at: 8 put: Array.
  	newArray at: 9 put: Smalltalk.
  	newArray at: 10 put: Float.
+ 	newArray at: 11 put: (self globals at: #MethodContext ifAbsent: [self globals at: #Context]).
+ 	newArray at: 12 put: nil. "was BlockContext."
- 	newArray at: 11 put: MethodContext.
- 	newArray at: 12 put: BlockContext.
  	newArray at: 13 put: Point.
  	newArray at: 14 put: LargePositiveInteger.
  	newArray at: 15 put: Display.
  	newArray at: 16 put: Message.
  	newArray at: 17 put: CompiledMethod.
+ 	newArray at: 18 put: ((self specialObjectsArray at: 18) ifNil: [Semaphore new]). "low space Semaphore"
- 	newArray at: 18 put: (self specialObjectsArray at: 18).
- 	"(low space Semaphore)"
  	newArray at: 19 put: Semaphore.
  	newArray at: 20 put: Character.
  	newArray at: 21 put: #doesNotUnderstand:.
  	newArray at: 22 put: #cannotReturn:.
  	newArray at: 23 put: nil. "This is the process signalling low space."
  	"An array of the 32 selectors that are compiled as special bytecodes,
  	 paired alternately with the number of arguments each takes."
  	newArray at: 24 put: #(	#+ 1 #- 1 #< 1 #> 1 #<= 1 #>= 1 #= 1 #~= 1
  							#* 1 #/ 1 #\\ 1 #@ 1 #bitShift: 1 #// 1 #bitAnd: 1 #bitOr: 1
  							#at: 1 #at:put: 2 #size 0 #next 0 #nextPut: 1 #atEnd 0 #== 1 #class 0
  							#blockCopy: 1 #value 0 #value: 1 #do: 1 #new 0 #new: 1 #x 0 #y 0 ).
  	"An array of the 255 Characters in ascii order.
+ 	 Cog inlines table into machine code at: prim so do not regenerate it.
+ 	 This is nil in Spur, which has immediate Characters."
- 	 Cog inlines table into machine code at: prim so do not regenerate it."
  	newArray at: 25 put: (self specialObjectsArray at: 25).
  	newArray at: 26 put: #mustBeBoolean.
  	newArray at: 27 put: ByteArray.
  	newArray at: 28 put: Process.
+ 	"An array of up to 31 classes whose instances will have compact headers; an empty array in Spur"
- 	"An array of up to 31 classes whose instances will have compact headers"
  	newArray at: 29 put: self compactClassesArray.
+ 	newArray at: 30 put: ((self specialObjectsArray at: 30) ifNil: [Semaphore new]). "delay Semaphore"
+ 	newArray at: 31 put: ((self specialObjectsArray at: 31) ifNil: [Semaphore new]). "user interrupt Semaphore"
- 	newArray at: 30 put: (self specialObjectsArray at: 30). "(delay Semaphore)"
- 	newArray at: 31 put: (self specialObjectsArray at: 31). "(user interrupt Semaphore)"
  	"Entries 32 - 34 unreferenced. Previously these contained prototype instances to be copied for fast initialization"
+ 	newArray at: 32 put: nil. "was the prototype Float"
+ 	newArray at: 33 put: nil. "was the prototype 4-byte LargePositiveInteger"
+ 	newArray at: 34 put: nil. "was the prototype Point"
- 	newArray at: 32 put: nil. "was (Float new: 2)"
- 	newArray at: 33 put: nil. "was (LargePositiveInteger new: 4)"
- 	newArray at: 34 put: nil. "was Point new"
  	newArray at: 35 put: #cannotInterpret:.
+ 	newArray at: 36 put: nil. "was the prototype MethodContext"
- 	"Note: This must be fixed once we start using context prototypes (yeah, right)"
- 	"(MethodContext new: CompiledMethod fullFrameSize)."
- 	newArray at: 36 put: (self specialObjectsArray at: 36). "Is the prototype MethodContext (unused by the VM)"
  	newArray at: 37 put: BlockClosure.
+ 	newArray at: 38 put: nil. "was the prototype BlockContext"
- 	"(BlockContext new: CompiledMethod fullFrameSize)."
- 	newArray at: 38 put: (self specialObjectsArray at: 38). "Is the prototype BlockContext (unused by the VM)"
  	"array of objects referred to by external code"
+ 	newArray at: 39 put: (self specialObjectsArray at: 39).	"external semaphores"
- 	newArray at: 39 put: (self specialObjectsArray at: 39).	"preserve external semaphores"
  	newArray at: 40 put: nil. "Reserved for Mutex in Cog VMs"
+ 	newArray at: 41 put: ((self specialObjectsArray at: 41) ifNil: [LinkedList new]). "Reserved for a LinkedList instance for overlapped calls in CogMT"
+ 	newArray at: 42 put: ((self specialObjectsArray at: 42) ifNil: [Semaphore new]). "finalization Semaphore"
- 	newArray at: 41 put: nil. "Reserved for a LinkedList instance for overlapped calls in CogMT"
- 	"finalization Semaphore"
- 	newArray at: 42 put: ((self specialObjectsArray at: 42) ifNil: [Semaphore new]).
  	newArray at: 43 put: LargeNegativeInteger.
  	"External objects for callout.
  	 Note: Written so that one can actually completely remove the FFI."
  	newArray at: 44 put: (self at: #ExternalAddress ifAbsent: []).
  	newArray at: 45 put: (self at: #ExternalStructure ifAbsent: []).
  	newArray at: 46 put: (self at: #ExternalData ifAbsent: []).
  	newArray at: 47 put: (self at: #ExternalFunction ifAbsent: []).
  	newArray at: 48 put: (self at: #ExternalLibrary ifAbsent: []).
  	newArray at: 49 put: #aboutToReturn:through:.
  	newArray at: 50 put: #run:with:in:.
  	"51 reserved for immutability message"
+ 	newArray at: 51 put: #attemptToAssign:withIndex:.
- 	"newArray at: 51 put: #attemptToAssign:withIndex:."
- 	newArray at: 51 put: (self specialObjectsArray at: 51 ifAbsent: []).
  	newArray at: 52 put: #(nil "nil => generic error" #'bad receiver'
  							#'bad argument' #'bad index'
  							#'bad number of arguments'
  							#'inappropriate operation'  #'unsupported operation'
  							#'no modification' #'insufficient object memory'
  							#'insufficient C memory' #'not found' #'bad method'
  							#'internal error in named primitive machinery'
  							#'object may move' #'resource limit exceeded'
+ 							#'object is pinned' #'primitive write beyond end of object').
- 							#'object is pinned').
  	"53 to 55 are for Alien"
  	newArray at: 53 put: (self at: #Alien ifAbsent: []).
+ 	newArray at: 54 put: #invokeCallbackContext:. "use invokeCallback:stack:registers:jmpbuf: for old Alien callbacks."
- 	newArray at: 54 put: #invokeCallbackContext::. "use invokeCallback:stack:registers:jmpbuf: for old Alien callbacks."
  	newArray at: 55 put: (self at: #UnsafeAlien ifAbsent: []).
  
+ 	"Used to be WeakFinalizationList for WeakFinalizationList hasNewFinalization, obsoleted by ephemeron support."
+ 	newArray at: 56 put: nil.
- 	"Weak reference finalization"
- 	newArray at: 56 put: (self at: #WeakFinalizationList ifAbsent: []).
  
  	"reserved for foreign callback process"
  	newArray at: 57 put: (self specialObjectsArray at: 57 ifAbsent: []).
  
  	newArray at: 58 put: #unusedBytecode.
+ 	"59 reserved for Sista counter tripped message"
+ 	newArray at: 59 put: #conditionalBranchCounterTrippedOn:.
+ 	"60 reserved for Sista class trap message"
+ 	newArray at: 60 put: #classTrapFor:.
  
  	"Now replace the interpreter's reference in one atomic operation"
+ 	self specialObjectsArray becomeForward: newArray!
- 	self specialObjectsArray becomeForward: newArray
- 	!

Item was changed:
  ----- Method: SmalltalkImage>>setGCParameters (in category 'snapshot and quit') -----
  setGCParameters
+ 	"Adjust the VM's default GC parameters to avoid too much tenuring.
+ 	 Maybe this should be left to the VM?"
- 	"Adjust the VM's default GC parameters to avoid premature tenuring."
  
+ 	| proportion edenSize survivorSize averageObjectSize numObjects |
+ 	proportion := 0.9. "tenure when 90% of pastSpace is full"
+ 	edenSize := SmalltalkImage current vmParameterAt: 44.
+ 	survivorSize := edenSize / 5.0. "David's paper uses 140Kb eden + 2 x 28kb survivor spaces; Spur uses the same ratios :-)"
+ 	averageObjectSize := 8 * self wordSize. "a good approximation"
+ 	numObjects := (proportion * survivorSize / averageObjectSize) rounded.
+ 	SmalltalkImage current vmParameterAt: 6 put: numObjects  "tenure when more than this many objects survive the GC"!
- 	self vmParameterAt: 5 put: 4000.  "do an incremental GC after this many allocations"
- 	self vmParameterAt: 6 put: 2000.  "tenure when more than this many objects survive the GC"
- !

Item was changed:
  ----- Method: SpaceTally>>spaceForInstancesOf: (in category 'instance size') -----
  spaceForInstancesOf: aClass
+ 	"Answer a pair of the number of bytes consumed by all instances of the
+ 	 given class, including their object headers, and the number of instances."
- 	"Answer the number of bytes consumed by all instances of the given class, including their object headers and the number of instances."
  
+ 	| instances total |
+ 	instances := aClass allInstances.
+ 	instances isEmpty ifTrue: [^#(0 0)].
- 	| smallHeaderSize instVarBytes isVariable bytesPerElement  total lastInstance instance instanceCount |
- 	instance := aClass someInstance ifNil: [ ^#(0 0) ].	
- 	smallHeaderSize := aClass isCompact ifTrue: [ 4 ] ifFalse: [ 8 ].
- 	instVarBytes := aClass instSize * 4.
- 	isVariable := aClass isVariable.
- 	bytesPerElement := isVariable
- 		ifFalse: [ 0 ]
- 		ifTrue: [ aClass isBytes ifTrue: [ 1 ] ifFalse: [ 4 ] ].
  	total := 0.
+ 	aClass isVariable
+ 		ifTrue:
+ 			[instances do:
+ 				[:i| total := total + (aClass byteSizeOfInstanceOfSize: i basicSize)]]
+ 		ifFalse:
+ 			[total := instances size * aClass byteSizeOfInstance].
+ 	^{ total. instances size }!
- 	instanceCount := 0.
- 	"A modified version of #allInstancesDo: is inlined here. It avoids an infinite loop when another process is creating new instances of aClass."
- 	self flag: #allInstancesDo:.
- 	lastInstance :=
- 		aClass == CompiledMethod "CompiledMethod has special format, see its class comment"
- 			ifTrue: [aClass new]
- 			ifFalse: [aClass basicNew].
- 	[ instance == lastInstance ] whileFalse: [
- 		| contentBytes headerBytes |
- 		contentBytes := instVarBytes + (isVariable
- 			ifFalse: [ 0 ]
- 			ifTrue: [ instance basicSize * bytesPerElement ]).
- 		headerBytes := contentBytes > 255
- 			ifTrue: [ 12 ]
- 			ifFalse: [ smallHeaderSize ].
- 		total := total + headerBytes + (contentBytes roundUpTo: 4).
- 		instanceCount := instanceCount + 1.
- 		instance := instance nextInstance ].
- 	^{ total. instanceCount }!

Item was added:
+ ----- Method: SystemDictionary>>growMemoryByAtLeast: (in category 'memory space') -----
+ growMemoryByAtLeast: numBytes
+ 	"Grow memory by at least the requested number of bytes.
+ 	 Primitive.  Fail if no memory is available.  Essential."
+ 	<primitive: 180>
+ 	^(numBytes isInteger and: [numBytes > 0])
+ 		ifTrue: [OutOfMemory signal]
+ 		ifFalse: [self primitiveFailed]!

Item was added:
+ ----- Method: SystemDictionary>>maxIdentityHash (in category 'system attributes') -----
+ maxIdentityHash
+ 	"Answer the maximum identityHash value supported by the VM."
+ 	<primitive: 176>
+ 	^self primitiveFailed!

Item was added:
+ ----- Method: SystemDictionary>>setGCParameters (in category 'snapshot and quit') -----
+ setGCParameters
+ 	"Adjust the VM's default GC parameters to avoid too much tenuring.
+ 	 Maybe this should be left to the VM?"
+ 
+ 	| proportion edenSize survivorSize averageObjectSize numObjects |
+ 	proportion := 0.9. "tenure when 90% of pastSpace is full"
+ 	edenSize := SmalltalkImage current vmParameterAt: 44.
+ 	survivorSize := edenSize / 5.0. "David's paper uses 140Kb eden + 2 x 28kb survivor spaces; Spur uses the same ratios :-)"
+ 	averageObjectSize := 8 * self wordSize. "a good approximation"
+ 	numObjects := (proportion * survivorSize / averageObjectSize) rounded.
+ 	SmalltalkImage current vmParameterAt: 6 put: numObjects  "tenure when more than this many objects survive the GC"!

Item was added:
+ ----- Method: SystemNavigation>>allObjects (in category 'query') -----
+ allObjects
+ 	"Answer an Array of all objects in the system.  Fail if
+ 	 there isn't enough memory to instantiate the result."
+ 	<primitive: 178>
+ 	^self primitiveFailed!

Item was changed:
  ----- Method: SystemNavigation>>allObjectsDo: (in category 'query') -----
  allObjectsDo: aBlock 
+ 	"Evaluate the argument, aBlock, for each object in the system, excluding immediates
+ 	 such as SmallInteger and Character."
+ 	self allObjectsOrNil
+ 		ifNotNil: [:allObjects| allObjects do: aBlock]
+ 		ifNil:
+ 			["Fall back on the old single object primitive code.  With closures, this needs
+ 			  to use an end marker (lastObject) since activation of the block will create
+ 			  new contexts and cause an infinite loop.  The lastObject must be created
+ 			  before calling someObject, so that the VM can settle the enumeration (e.g.
+ 			  by flushing new space) as a side effect of  someObject"
+ 			| object lastObject |
+ 			lastObject := Object new.
+ 			object := self someObject.
+ 			[lastObject == object or: [0 == object]] whileFalse:
+ 				[aBlock value: object.
+ 				 object := object nextObject]]!
- 	"Evaluate the argument, aBlock, for each object in the system 
- 	excluding SmallIntegers. With closures, this needs to use an end
- 	marker (lastObject) since activation of the block will create new 
- 	contexts and cause an infinite loop."
- 	| object lastObject |
- 	object := self someObject.
- 	lastObject := Object new.
- 	[lastObject == object or: [0 == object]]
- 		whileFalse: [aBlock value: object.
- 			object := object nextObject]!

Item was added:
+ ----- Method: SystemNavigation>>allObjectsOrNil (in category 'query') -----
+ allObjectsOrNil
+ 	"Answer an Array of all objects in the system.  Fail if there isn't
+ 	 enough memory to instantiate the result and answer nil."
+ 	<primitive: 178>
+ 	^nil!



More information about the Squeak-dev mailing list