64bit VM latest

Tim Rowledge tim at rowledge.org
Mon May 23 23:27:24 UTC 2005


After much hacking I have a new alpha of VMMaker for 64 bit clean code.

I found a quite long list of changes neccessary, some of which might be
controversial. Before I release this widely I'd like to see if we can all agree
with the changes.

Image fileins:
I've cut down all the 'normal' image changes to a bare minimum for release into
the 3.8 update stream. See attached VMM38-64bit-imageUpdates/1/cs. I have _not_
done anything with any of the image code that is not directly related to making
VMMaker work. SystemTracer etc were left alone. I also made a 'remove all
leftover VMM code' file to get the few remaining vmm related methods out of the
main image. See RemoveLeftoverVMMbits-38b4/1/cs.

VMMaker changes:

Added GCInstrumentJMMImprovementsAR64bit.3.cs
- needs several int->sqInt changes
- adds several prims using named-in-no-module approach
- removes a couple of instvars and classvars
- alters prim table to correct a couple of missed obsoletes

Clean out new gc & instrumentation code to changeset. SystemDictionary stuff to
new fileout for update stream (VMM38-gc-instrument-image).

LowSpaceAndInterruptHandler-2-dtl needs to go into update stream. VMMLowSpace-
dtl-tpr-2 is corrected VM changes, included in VMM. 

Lowspace problem in initializeMemoryFirstFree: which steals memory just when we
are short of it. I recommend setting the lowspacethreshold to 3-4Mb instead of
200kb. We could do some tweaking in the VM code to help but when you're down to
200kb things are going to get ugly no matter what. Virtual memory might stay
execution a while but even that will run out sometime.

add fix for FloatArrat>primitiveDivFloatArray quick-0 test.
fix primVMParameters to merge GC changes and wordSize

revert #isIntegerValue: to use EOR trick - works for 32 & 64 bit machine, I
think. Explicit range check will not work for actual 64bits.

fix storeInteger:ofObject:withValue: to skip root oop check and many
storePointerUnchecked where SmallInt is used, save checking for young. (several
%speedup)

make pop:thenPushIntegerOf:, check sends of pop: and pushInteger:
add an instantiate but don't fill, used for small classes like points

and the one that will annoy Ian, macros for longAtput etc in sqMemoryAccess.h
This proved neccessary after John & I discovered a noticable drop in benchmark
results when using the inlined accessor functions. Examing the compiled code
for both ARM and PPC showed that the inlining was being done (quite neatly I
thought for ARM) but not quite neatly enough in some crucial cases. It was
causing a 20% or so overall hit and 40% for tinyBenchmarks, a bit less for OSX.

Still to do:
there are lots of places where potential signed/unsigned/oop comparisons are
done and might cause problems. 'oop < endOfMemory' is pretty common in the
interp.c file.

There is a stricly temporary .mcz file on my website that should be readable as
http://www.rowledge.org/tim/squeak/SqFiles/release/VMMaker-tpr.27.mcz  and I
should have the changed sqMemoryAccess.h file committed sometime today.
    

tim
--
Tim Rowledge, tim at rowledge.org, http://www.rowledge.org/tim
Useful Latin Phrases:- Romani quidem artem amatoriam invenerunt. = You know,
the Romans invented the art of love.
-------------- next part --------------
'From Squeak3.8gamma of ''24 November 2004'' [latest update: #6548] on 1 April 2005 at 1:24:17 pm'!
WordArray class removeSelector: #ccg:emitLoadFor:from:on:!
WordArray class removeSelector: #ccg:prolog:expr:index:!
WordArray class removeSelector: #ccgDeclareCForVar:!

!WordArray class reorganize!
('as yet unclassified' bobsTest)
!

String class removeSelector: #ccg:prolog:expr:index:!
String class removeSelector: #ccgDeclareCForVar:!

!String class reorganize!
('instance creation' correspondingSymbolClass fromByteArray: new:)
('examples')
('initialization')
('primitives' findFirstInString:inSet:startingAt: indexOfAscii:inString:startingAt: stringHash:initialHash: translate:from:to:table:)
('m17n' conv conv0 getDelimited:from:in: getDelimited:in: getTempMethodStringFrom:replaceVars:withVars: multiClasses pushUpMethods)
!

MultiString class removeSelector: #ccg:prolog:expr:index:!
MultiString class removeSelector: #ccgDeclareCForVar:!

!MultiString class reorganize!
('enumeration' allMethodsWithEncodingTag: allMultiStringMethods allNonAsciiMethods string:hasEncoding:)
('primitives' findFirstInMultiString:inSet:startingAt: findFirstInString:inSet:startingAt: indexOfAscii:inMultiString:startingAt: indexOfAscii:inString:startingAt: multiStringHash:initialHash: stringHash:initialHash: translate:from:to:table: translateMultiString:from:to:table:)
('instance creation' correspondingSymbolClass from: fromByteArray: fromISO2022JPString: fromPacked: fromString: value:)
!

IntegerArray class removeSelector: #ccg:emitLoadFor:from:on:!
IntegerArray class removeSelector: #ccg:prolog:expr:index:!
IntegerArray class removeSelector: #ccgDeclareCForVar:!

!IntegerArray class reorganize!
('as yet unclassified')
!

FloatArray class removeSelector: #ccg:emitLoadFor:from:on:!
FloatArray class removeSelector: #ccg:prolog:expr:index:!
FloatArray class removeSelector: #ccgDeclareCForVar:!

!FloatArray class reorganize!
('as yet unclassified')
!

Float class removeSelector: #ccg:emitLoadFor:from:on:!
Float class removeSelector: #ccg:generateCoerceToOopFrom:on:!
Float class removeSelector: #ccg:generateCoerceToValueFrom:on:!
Float class removeSelector: #ccg:prolog:expr:index:!
Float class removeSelector: #ccgCanConvertFrom:!
Float class removeSelector: #ccgDeclareCForVar:!

!Float class reorganize!
('class initialization' initialize)
('instance creation' fromIEEE32Bit: readFrom:)
('constants' e halfPi infinity nan negativeZero one pi)
!

ByteArray class removeSelector: #ccg:emitLoadFor:from:on:!
ByteArray class removeSelector: #ccg:prolog:expr:index:!
ByteArray class removeSelector: #ccgDeclareCForVar:!

!ByteArray class reorganize!
('byte based hash' hashBytes:startingWith:)
!

Array class removeSelector: #ccg:emitLoadFor:from:on:!
Array class removeSelector: #ccg:prolog:expr:index:!
Array class removeSelector: #ccgDeclareCForVar:!

!Array class reorganize!
('brace support' braceStream: braceWith: braceWith:with: braceWith:with:with: braceWith:with:with:with: braceWithNone)
('instance creation' new:)
!

Object class removeSelector: #ccg:emitLoadFor:from:on:!
Object class removeSelector: #ccg:generateCoerceToOopFrom:on:!
Object class removeSelector: #ccg:generateCoerceToValueFrom:on:!
Object class removeSelector: #ccg:prolog:expr:index:!
Object class removeSelector: #ccgCanConvertFrom:!
Object class removeSelector: #ccgDeclareCForVar:!

!Object class reorganize!
('instance creation' categoryForUniclasses chooseUniqueClassName initialInstance initializedInstance instanceOfUniqueClass instanceOfUniqueClassWithInstVarString:andClassInstVarString: isUniClass newFrom: newUniqueClassInstVars:classInstVars: newUserInstance readCarefullyFrom: readFrom:)
('documentation' howToModifyPrimitives whatIsAPrimitive)
('private' releaseExternalSettings)
('objects from disk' createFrom:size:version:)
('class initialization' flushDependents flushEvents initialize initializeDependentsFields reInitializeDependentsFields)
('window color' windowColorSpecification)
('file list services' fileReaderServicesForDirectory: fileReaderServicesForFile:suffix:)
!

-------------- next part --------------
'From Squeak3.8gamma of ''24 November 2004'' [latest update: #6599] on 27 April 2005 at 11:08:01 am'!
"Change Set:		VMM38-64bit-imageUpdates
Date:			2005-04-27
Author:			tim at rowledge.org, derived from original by ian.piumarta at squeakland.org and johnmci at smalltalkconsultants.com

Changes relative to 3.8g-6548 that add some initial 64-bit support to the image. Needs to go into the update stream asap"!


!SmalltalkImage methodsFor: 'vm parameters' stamp: 'tpr 4/27/2005 11:03'!
vmParameterAt: parameterIndex
	"parameterIndex is a positive integer corresponding to one of the VM's internal
	parameter/metric registers.  Answer with the current value of that register.
	Fail if parameterIndex has no corresponding register.
	VM parameters are numbered as follows:
		1	end of old-space (0-based, read-only)
		2	end of young-space (read-only)
		3	end of memory (read-only)
		4	allocationCount (read-only)
		5	allocations between GCs (read-write)
		6	survivor count tenuring threshold (read-write)
		7	full GCs since startup (read-only)
		8	total milliseconds in full GCs since startup (read-only)
		9	incremental GCs since startup (read-only)
		10	total milliseconds in incremental GCs since startup (read-only)
		11	tenures of surving objects since startup (read-only)
		12-20 specific to the translating VM
		21	root table size (read-only)
		22	root table overflows since startup (read-only)
		23	bytes of extra memory to reserve for VM buffers, plugins, etc.

		24	memory threshold above which shrinking object memory (rw)
		25	memory headroom when growing object memory (rw)
		26  interruptChecksEveryNms - force an ioProcessEvents every N milliseconds, in case the image  is not calling getNextEvent often (rw)
		27	number of times mark loop iterated for current IGC/FGC (read-only) includes ALL marking
		28	number of times sweep loop iterated  for current IGC/FGC (read-only)
		29	number of times make forward loop iterated for current IGC/FGC (read-only)
		30	number of times compact move loop iterated for current IGC/FGC (read-only)
		31	number of grow memory requests (read-only)
		32	number of shrink memory requests (read-only)
		33	number of root table entries used for current IGC/FGC (read-only)
		34	number of allocations done before current IGC/FGC (read-only)
		35	number of survivor objects after current IGC/FGC (read-only)
		36  millisecond clock when current IGC/FGC completed (read-only)
		37  number of marked objects for Roots of the world, not including Root Table entries for current IGC/FGC (read-only)
		38  milliseconds taken by current IGC  (read-only)
		39  Number of finalization signals for Weak Objects pending when current IGC/FGC completed (read-only)
		40  VM word size - 4 or 8 (read-only)"

	<primitive: 254>
	self primitiveFailed! !


!SystemDictionary methodsFor: 'sources, change log' stamp: 'JMM 4/13/2005 20:35'!
wordSize
	"Answer the size (in bytes) of an object pointer."
	"Smalltalk wordSize"

	^[SmalltalkImage current vmParameterAt: 40] on: Error do: [4]! !

!SystemDictionary methodsFor: 'deprecated' stamp: 'tpr 4/27/2005 11:04'!
vmParameterAt: parameterIndex
	"See comment for SmalltalkImage>vmParameterAt:"

	^ self deprecated: 'Use SmalltalkImage current vmParameterAt:'
		block: [SmalltalkImage current vmParameterAt: parameterIndex]
	! !

-------------- next part --------------
'From Squeak3.8gamma of ''24 November 2004'' [latest update: #6599] on 27 April 2005 at 11:14:55 am'!
"Change Set:		VMM38-gc-instrument-image
Date:			27 April 2005
Author:			tim at rowledge.org derived from original by johnmci at smalltalkconsulting.com and andreas.raab at gmx.de

Image side methods to support revised GC handling of weak pointers and GC instrumentation. See SystemDictionary>forceTenure, isYoung: etc.

Needs to go into update stream asap"!


!SystemDictionary methodsFor: 'memory space' stamp: 'JMM 1/27/2005 13:23'!
forceTenure
	"Primitive. Tell the GC logic to force a tenure on the next increment GC."
	<primitive: 'primitiveForceTenure'>
	^self primitiveFailed! !

!SystemDictionary methodsFor: 'memory space' stamp: 'ar 1/18/2005 16:46'!
isRoot: oop
	"Primitive. Answer whether the object is currently a root for youngSpace."
	<primitive: 'primitiveIsRoot'>
	^self primitiveFailed! !

!SystemDictionary methodsFor: 'memory space' stamp: 'ar 1/18/2005 16:47'!
isYoung: oop
	"Primitive. Answer whether the object currently resides in youngSpace."
	<primitive: 'primitiveIsYoung'>
	^self primitiveFailed! !

!SystemDictionary methodsFor: 'memory space' stamp: 'ar 1/18/2005 16:48'!
rootTable
	"Primitive. Answer a snapshot of the VMs root table. 
	Keep in mind that the primitive may itself cause GC."
	<primitive: 'primitiveRootTable'>
	^self primitiveFailed! !

!SystemDictionary methodsFor: 'memory space' stamp: 'ar 1/18/2005 16:49'!
rootTableAt: index
	"Primitive. Answer the nth element of the VMs root table"
	<primitive: 'primitiveRootTableAt'>
	^nil! !

!SystemDictionary methodsFor: 'memory space' stamp: 'JMM 1/27/2005 13:12'!
setGCBiasToGrow: aNumber
	"Primitive. Indicate that the GC logic should be bias to grow"
	<primitive: 'primitiveSetGCBiasToGrow'>
	^self primitiveFailed
"Example:
	Smalltalk setGCBiasToGrowGCLimit: 16*1024*1024.
	Smalltalk setGCBiasToGrow: 1.
"! !

!SystemDictionary methodsFor: 'memory space' stamp: 'JMM 1/27/2005 12:27'!
setGCBiasToGrowGCLimit: aNumber
	"Primitive. Indicate that the bias to grow logic should do a GC after aNumber Bytes"
	<primitive: 'primitiveSetGCBiasToGrowGCLimit'>
	^self primitiveFailed
"Example:
	Smalltalk setGCBiasToGrowGCLimit: 16*1024*1024.
"! !

!SystemDictionary methodsFor: 'memory space' stamp: 'ar 1/18/2005 16:54'!
setGCSemaphore: semaIndex
	"Primitive. Indicate the GC semaphore index to be signaled on GC occurance."
	<primitive: 'primitiveSetGCSemaphore'>
	^self primitiveFailed
"Example:

	| index sema process |
	sema := Semaphore new.
	index := Smalltalk registerExternalObject: sema.
	Smalltalk setGCSemaphore: index.
	process := [
		[[true] whileTrue:[
			sema wait.
			Smalltalk beep.
		]] ensure:[
			Smalltalk setGCSemaphore: 0.
			Smalltalk unregisterExternalObject: sema.
		].
	] fork.
	process inspect.
"! !

!SystemDictionary methodsFor: 'special objects' stamp: 'JMM 1/27/2005 12:17'!
recreateSpecialObjectsArray    "Smalltalk recreateSpecialObjectsArray"
	"The Special Objects Array is an array of object pointers used by the
	Squeak virtual machine.  Its contents are critical and unchecked,
	so don't even think of playing here unless you know what you are doing."
	| newArray |
	newArray _ Array new: 50.
	"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: (Smalltalk associationAt: #Processor).
	"Numerous classes below used for type checking and instantiation"
	newArray at: 5 put: Bitmap.
	newArray at: 6 put: SmallInteger.
	newArray at: 7 put: String.
	newArray at: 8 put: Array.
	newArray at: 9 put: Smalltalk. 
	newArray at: 10 put: Float.
	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)  "(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.  "*unused*"
	"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."
	newArray at: 25 put: ((0 to: 255) collect: [:ascii | Character value: ascii]).
	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"
	newArray at: 29 put: self compactClassesArray.
	newArray at: 30 put: (self specialObjectsArray at: 30)   "(delay Semaphore)".
	newArray at: 31 put: (self specialObjectsArray at: 31)   "(user interrupt Semaphore)".
	newArray at: 32 put: nil. 
	newArray at: 33 put: nil.
	newArray at: 34 put: nil.
	newArray at: 35 put: #cannotInterpret:.
	"Note: This must be fixed once we start using context prototypes"
	newArray at: 36 put: (self specialObjectsArray at: 36). 
						"(MethodContext new: CompiledMethod fullFrameSize)."
	newArray at: 37 put: nil.
	newArray at: 38 put: (self specialObjectsArray at: 38). 
						"(BlockContext new: CompiledMethod fullFrameSize)."

	newArray at: 39 put: Array new.  "array of objects referred to by external code"

	newArray at: 40 put: PseudoContext.
	newArray at: 41 put: TranslatedMethod.

	"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: (Smalltalk at: #ExternalAddress ifAbsent:[nil]).
	newArray at: 45 put: (Smalltalk at: #ExternalStructure ifAbsent:[nil]).
	newArray at: 46 put: (Smalltalk at: #ExternalData ifAbsent:[nil]).
	newArray at: 47 put: (Smalltalk at: #ExternalFunction ifAbsent:[nil]).
	newArray at: 48 put: (Smalltalk at: #ExternalLibrary ifAbsent:[nil]).

	newArray at: 49 put: #aboutToReturn:through:.
	newArray at: 50 put: #run:with:in:.

	"Now replace the interpreter's reference in one atomic operation"
	self specialObjectsArray become: newArray! !

-------------- next part --------------
'From Squeak3.7 of ''4 September 2004'' [latest update: #5989] on 16 April 2005 at 3:25:11 am'!
"Change Set:		LowSpaceAndInterruptHandler-2-dtl
Date:			16 April 2005
Author:			David T. Lewis

Alternate version of low space handler fix, using Tim's approach of passing the process causing low space back through the special objects array. Includes both Morphic and MVC updates. The low space watcher is restarted in the postscript.

LowSpaceAndInterruptHandler-2-dtl
VMMLowSpaceAndInterruptHandler-2-dtl

"!


!ControlManager methodsFor: 'scheduling' stamp: 'dtl 4/4/2005 06:42'!
interruptName: labelString
	"Create a Notifier on the active scheduling process with the given label. Make the Notifier the active controller."

	^ self interruptName: labelString preemptedProcess: nil
! !

!ControlManager methodsFor: 'scheduling' stamp: 'dtl 4/6/2005 23:20'!
interruptName: labelString preemptedProcess: theInterruptedProcess
	"Create a Notifier on the active scheduling process with the given label. Make the Notifier the active controller."
	| suspendingList newActiveController preemptedProcess |

	preemptedProcess _ theInterruptedProcess ifNil: [Processor preemptedProcess].
	preemptedProcess == activeControllerProcess
		ifFalse: [(suspendingList _ preemptedProcess suspendingList) == nil
				ifTrue: [preemptedProcess suspend]
				ifFalse: [suspendingList remove: preemptedProcess.
						preemptedProcess offList]].

	(suspendingList _ activeControllerProcess suspendingList) == nil
		ifTrue: [activeControllerProcess == Processor activeProcess
					ifTrue: [activeControllerProcess suspend]]
		ifFalse: [suspendingList remove: activeControllerProcess ifAbsent:[].
				activeControllerProcess offList].

	activeController ~~ nil ifTrue: [
		"Carefully de-emphasis the current window."
		activeController view topView deEmphasizeForDebugger].

	newActiveController _
		(Debugger
			openInterrupt: labelString
			onProcess: preemptedProcess) controller.
	newActiveController centerCursorInView.
	self activeController: newActiveController.
! !


!CurrentProjectRefactoring class methodsFor: 'revectoring to current' stamp: 'dtl 4/3/2005 14:14'!
currentInterruptName: aString preemptedProcess: theInterruptedProcess

	^ Project interruptName: aString preemptedProcess: theInterruptedProcess! !


!Project class methodsFor: 'utilities' stamp: 'dtl 4/3/2005 14:02'!
interruptName: labelString
	"Create a Notifier on the active scheduling process with the given label."

	^ self interruptName: labelString preemptedProcess: nil
! !

!Project class methodsFor: 'utilities' stamp: 'dtl 4/3/2005 16:27'!
interruptName: labelString preemptedProcess: theInterruptedProcess
	"Create a Notifier on the active scheduling process with the given label."
	| preemptedProcess projectProcess suspendingList |
	Smalltalk isMorphic ifFalse:
		[^ ScheduledControllers interruptName: labelString].
	ActiveHand ifNotNil:[ActiveHand interrupted].
	ActiveWorld _ World. "reinstall active globals"
	ActiveHand _ World primaryHand.
	ActiveHand interrupted. "make sure this one's interrupted too"
	ActiveEvent _ nil.

	projectProcess _ self uiProcess.	"we still need the accessor for a while"
	preemptedProcess _ theInterruptedProcess ifNil: [Processor preemptedProcess].
	"Only debug preempted process if its priority is >= projectProcess' priority"
	preemptedProcess priority < projectProcess priority ifTrue:[
		(suspendingList _ projectProcess suspendingList) == nil
			ifTrue: [projectProcess == Processor activeProcess
						ifTrue: [projectProcess suspend]]
			ifFalse: [suspendingList remove: projectProcess ifAbsent: [].
					projectProcess offList].
		preemptedProcess _ projectProcess.
	] ifFalse:[
		preemptedProcess suspend offList.
	].
	Debugger openInterrupt: labelString onProcess: preemptedProcess
! !


!SystemDictionary methodsFor: 'memory space' stamp: 'dtl 4/16/2005 01:06'!
lowSpaceWatcher
	"Wait until the low space semaphore is signalled, then take appropriate actions."

	| free preemptedProcess |
	self garbageCollectMost <= self lowSpaceThreshold ifTrue: [
		self garbageCollect <= self lowSpaceThreshold ifTrue: [
			"free space must be above threshold before starting low space watcher"
			^ Beeper beep]].

	Smalltalk specialObjectsArray at: 23 put: nil.  "process causing low space will be saved here"
	LowSpaceSemaphore _ Semaphore new.
	self primLowSpaceSemaphore: LowSpaceSemaphore.
	self primSignalAtBytesLeft: self lowSpaceThreshold.  "enable low space interrupts"

	LowSpaceSemaphore wait.  "wait for a low space condition..."

	self primSignalAtBytesLeft: 0.  "disable low space interrupts"
	self primLowSpaceSemaphore: nil.
	LowSpaceProcess _ nil.

	"The process that was active at the time of the low space interrupt."
	preemptedProcess _ Smalltalk specialObjectsArray at: 23.
	Smalltalk specialObjectsArray at: 23 put: nil.

	"Note: user now unprotected until the low space watcher is re-installed"

	self memoryHogs isEmpty ifFalse: [
		free := self bytesLeft.
		self memoryHogs do: [ :hog | hog freeSomeSpace ].
		self bytesLeft > free ifTrue: [ ^ self installLowSpaceWatcher ]].
	Smalltalk isMorphic
			ifTrue: [CurrentProjectRefactoring
						currentInterruptName: 'Space is low'
						preemptedProcess: preemptedProcess]
			ifFalse: [ScheduledControllers
						interruptName: 'Space is low'
						preemptedProcess: preemptedProcess]! !

!SystemDictionary methodsFor: 'special objects' stamp: 'dtl 4/16/2005 00:57'!
recreateSpecialObjectsArray    "Smalltalk recreateSpecialObjectsArray"
	"The Special Objects Array is an array of object pointers used by the
	Squeak virtual machine.  Its contents are critical and unchecked,
	so don't even think of playing here unless you know what you are doing."
	| newArray |
	newArray _ Array new: 50.
	"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: (Smalltalk associationAt: #Processor).
	"Numerous classes below used for type checking and instantiation"
	newArray at: 5 put: Bitmap.
	newArray at: 6 put: SmallInteger.
	newArray at: 7 put: String.
	newArray at: 8 put: Array.
	newArray at: 9 put: Smalltalk. 
	newArray at: 10 put: Float.
	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)  "(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.  "process that signaled the low space semaphore"
	"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."
	newArray at: 25 put: ((0 to: 255) collect: [:ascii | Character value: ascii]).
	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"
	newArray at: 29 put: self compactClassesArray.
	newArray at: 30 put: (self specialObjectsArray at: 30)   "(delay Semaphore)".
	newArray at: 31 put: (self specialObjectsArray at: 31)   "(user interrupt Semaphore)".

	"Prototype instances that can be copied for fast initialization"
	newArray at: 32 put: (Float new: 2).
	newArray at: 33 put: (LargePositiveInteger new: 4).
	newArray at: 34 put: Point new.
	newArray at: 35 put: #cannotInterpret:.
	"Note: This must be fixed once we start using context prototypes"
	newArray at: 36 put: (self specialObjectsArray at: 36). 
						"(MethodContext new: CompiledMethod fullFrameSize)."
	newArray at: 37 put: nil.
	newArray at: 38 put: (self specialObjectsArray at: 38). 
						"(BlockContext new: CompiledMethod fullFrameSize)."

	newArray at: 39 put: Array new.  "array of objects referred to by external code"

	newArray at: 40 put: PseudoContext.
	newArray at: 41 put: TranslatedMethod.

	"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: (Smalltalk at: #ExternalAddress ifAbsent:[nil]).
	newArray at: 45 put: (Smalltalk at: #ExternalStructure ifAbsent:[nil]).
	newArray at: 46 put: (Smalltalk at: #ExternalData ifAbsent:[nil]).
	newArray at: 47 put: (Smalltalk at: #ExternalFunction ifAbsent:[nil]).
	newArray at: 48 put: (Smalltalk at: #ExternalLibrary ifAbsent:[nil]).

	newArray at: 49 put: #aboutToReturn:through:.
	newArray at: 50 put: #run:with:in:.

	"Now replace the interpreter's reference in one atomic operation"
	self specialObjectsArray become: newArray! !

"Postscript:

Restart the low space watcher to activate the new version."

Smalltalk installLowSpaceWatcher.

!



More information about the Vm-dev mailing list