[Vm-dev] VM Maker: VMMaker.oscog-eem.834.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Jul 25 18:03:07 UTC 2014


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.834.mcz

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

Name: VMMaker.oscog-eem.834
Author: eem
Time: 25 July 2014, 8:00:25.579 am
UUID: 56c11930-453f-42ad-bc3f-d21b2ff16c86
Ancestors: VMMaker.oscog-eem.833

Sista:
Implement all of the missing SistaV1 bytecodes in the
StackInterpreter except the class trap bytecode.
Define the class trap selector's SOA index.
Make the undefined case error message more informative
and write it to the transcript.

=============== Diff against VMMaker.oscog-eem.833 ===============

Item was changed:
  ----- Method: ObjectMemory class>>initializeSpecialObjectIndices (in category 'initialization') -----
  initializeSpecialObjectIndices
  	"Initialize indices into specialObjects array."
  
  	NilObject := 0.
  	FalseObject := 1.
  	TrueObject := 2.
  	SchedulerAssociation := 3.
  	ClassBitmap := 4.
  	ClassSmallInteger := 5.
  	ClassByteString := ClassString := 6. "N.B.  Actually class ByteString"
  	ClassArray := 7.
  	"SmalltalkDictionary := 8."  "Do not delete!!"
  	ClassFloat := 9.
  	ClassMethodContext := 10.
  	ClassBlockContext := 11.
  	ClassPoint := 12.
  	ClassLargePositiveInteger := 13.
  	TheDisplay := 14.
  	ClassMessage := 15.
  	"ClassCompiledMethod := 16. unused by the VM"
  	TheLowSpaceSemaphore := 17.
  	ClassSemaphore := 18.
  	ClassCharacter := 19.
  	SelectorDoesNotUnderstand := 20.
  	SelectorCannotReturn := 21.
  	ProcessSignalingLowSpace := 22.	"was TheInputSemaphore"
  	SpecialSelectors := 23.
  	CharacterTable := 24.
  	SelectorMustBeBoolean := 25.
  	ClassByteArray := 26.
  	"ClassProcess := 27. unused"
  	CompactClasses := 28.
  	TheTimerSemaphore := 29.
  	TheInterruptSemaphore := 30.
  	SelectorCannotInterpret := 34.
  	"Was MethodContextProto := 35."
  	ClassBlockClosure := 36.
  	"Was BlockContextProto := 37."
  	ExternalObjectsArray := 38.
  	ClassMutex := 39.
  	"Was: ClassTranslatedMethod := 40."
  	ProcessInExternalCodeTag := 40.
  	TheFinalizationSemaphore := 41.
  	ClassLargeNegativeInteger := 42.
  
  	ClassExternalAddress := 43.
  	ClassExternalStructure := 44.
  	ClassExternalData := 45.
  	ClassExternalFunction := 46.
  	ClassExternalLibrary := 47.
  
  	SelectorAboutToReturn := 48.
  	SelectorRunWithIn := 49.
  
  	SelectorAttemptToAssign := 50.
  	"PrimErrTableIndex := 51. in VMClass class>>initializePrimitiveErrorCodes"
  	ClassAlien := 52.
  	SelectorInvokeCallback := 53.
  	ClassUnsafeAlien := 54.
  
  	ClassWeakFinalizer := 55.
  
  	ForeignCallbackProcess := 56.
  
  	SelectorUnknownBytecode := 57.
+ 	SelectorCounterTripped := 58.
+ 	SelectorClassTrap := 59
- 	SelectorCounterTripped := 58
  !

Item was changed:
  ----- Method: SpurMemoryManager class>>initializeSpecialObjectIndices (in category 'class initialization') -----
  initializeSpecialObjectIndices
  	"Initialize indices into specialObjects array."
  
  	NilObject := 0.
  	FalseObject := 1.
  	TrueObject := 2.
  	SchedulerAssociation := 3.
  	ClassBitmap := 4.
  	ClassSmallInteger := 5.
  	ClassByteString := ClassString := 6. "N.B.  Actually class ByteString"
  	ClassArray := 7.
  	"SmalltalkDictionary := 8."  "Do not delete!!"
  	ClassFloat := 9.
  	ClassMethodContext := 10.
  	"ClassBlockContext := 11. unused by the VM"
  	ClassPoint := 12.
  	ClassLargePositiveInteger := 13.
  	TheDisplay := 14.
  	ClassMessage := 15.
  	"ClassCompiledMethod := 16. unused by the VM"
  	TheLowSpaceSemaphore := 17.
  	ClassSemaphore := 18.
  	ClassCharacter := 19.
  	SelectorDoesNotUnderstand := 20.
  	SelectorCannotReturn := 21.
  	ProcessSignalingLowSpace := 22.	"was TheInputSemaphore"
  	SpecialSelectors := 23.
  	CharacterTable := nil.	"Must be unused by the VM"
  	SelectorMustBeBoolean := 25.
  	ClassByteArray := 26.
  	"ClassProcess := 27. unused"
  	CompactClasses := 28.
  	TheTimerSemaphore := 29.
  	TheInterruptSemaphore := 30.
  	SelectorCannotInterpret := 34.
  	"Was MethodContextProto := 35."
  	ClassBlockClosure := 36.
  	"Was BlockContextProto := 37."
  	ExternalObjectsArray := 38.
  	ClassMutex := 39.
  	"Was: ClassTranslatedMethod := 40."
  	ProcessInExternalCodeTag := 40.
  	TheFinalizationSemaphore := 41.
  	ClassLargeNegativeInteger := 42.
  
  	ClassExternalAddress := 43.
  	ClassExternalStructure := 44.
  	ClassExternalData := 45.
  	ClassExternalFunction := 46.
  	ClassExternalLibrary := 47.
  
  	SelectorAboutToReturn := 48.
  	SelectorRunWithIn := 49.
  
  	SelectorAttemptToAssign := 50.
  	"PrimErrTableIndex := 51. in VMClass class>>initializePrimitiveErrorCodes"
  	ClassAlien := 52.
  	SelectorInvokeCallback := 53.
  	ClassUnsafeAlien := 54.
  
  	ClassWeakFinalizer := 55.
  
  	ForeignCallbackProcess := 56.
  
  	SelectorUnknownBytecode := 57.
+ 	SelectorCounterTripped := 58.
+ 	SelectorClassTrap := 59!
- 	SelectorCounterTripped := 58!

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForSistaV1 (in category 'initialization') -----
  initializeBytecodeTableForSistaV1
  	"See e.g. the cass comment for EncoderForSistaV1"
  	"StackInterpreter initializeBytecodeTableForSistaV1"
  	"Note: This table will be used to generate a C switch statement."
  
  	BytecodeTable := Array new: 256.
  	self table: BytecodeTable from:
  	#(	"1 byte bytecodes"
  		(   0  15 pushReceiverVariableBytecode)
  		( 16  31 pushLiteralVariable16CasesBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  75 pushTemporaryVariableBytecode)
  		( 76	 pushReceiverBytecode)
  		( 77	 pushConstantTrueBytecode)
  		( 78	 pushConstantFalseBytecode)
  		( 79	 pushConstantNilBytecode)
  		( 80	 pushConstantZeroBytecode)
  		( 81	 pushConstantOneBytecode)
  		( 82	 extPushPseudoVariable)
  		( 83	 duplicateTopBytecode)
  	
  		( 84 87	unknownBytecode)
  		( 88	returnReceiver)
  		( 89	returnTrue)
  		( 90	returnFalse)
  		( 91	returnNil)
  		( 92	returnTopFromMethod)
  		( 93	returnNilFromBlock)
  		( 94	returnTopFromBlock)
+ 		( 95	extNopBytecode)
- 		( 95	extNop)
  
  		( 96	 bytecodePrimAdd)
  		( 97	 bytecodePrimSubtract)
  		( 98	 bytecodePrimLessThanSistaV1) "for booleanCheatSistaV1:"
  		( 99	 bytecodePrimGreaterThanSistaV1) "for booleanCheatSistaV1:"
  		(100	 bytecodePrimLessOrEqualSistaV1) "for booleanCheatSistaV1:"
  		(101	 bytecodePrimGreaterOrEqualSistaV1) "for booleanCheatSistaV1:"
  		(102	 bytecodePrimEqualSistaV1) "for booleanCheatSistaV1:"
  		(103	 bytecodePrimNotEqualSistaV1) "for booleanCheatSistaV1:"
  		(104	 bytecodePrimMultiply)
  		(105	 bytecodePrimDivide)
  		(106	 bytecodePrimMod)
  		(107	 bytecodePrimMakePoint)
  		(108	 bytecodePrimBitShift)
  		(109	 bytecodePrimDiv)
  		(110	 bytecodePrimBitAnd)
  		(111	 bytecodePrimBitOr)
  
  		(112	 bytecodePrimAt)
  		(113	 bytecodePrimAtPut)
  		(114	 bytecodePrimSize)
  		(115	 bytecodePrimNext)		 "i.e. a 0 arg special selector"
  		(116	 bytecodePrimNextPut)		 "i.e. a 1 arg special selector"
  		(117	 bytecodePrimAtEnd)
  		(118	 bytecodePrimIdenticalSistaV1) "for booleanCheatSistaV1:"
  		(119	 bytecodePrimClass)
  		(120	 bytecodePrimSpecialSelector24) "was blockCopy:"
  		(121	 bytecodePrimValue)
  		(122	 bytecodePrimValueWithArg)
  		(123	 bytecodePrimDo)			"i.e. a 1 arg special selector"
  		(124	 bytecodePrimNew)			"i.e. a 0 arg special selector"
  		(125	 bytecodePrimNewWithArg)	"i.e. a 1 arg special selector"
  		(126	 bytecodePrimPointX)		"i.e. a 0 arg special selector"
  		(127	 bytecodePrimPointY)		"i.e. a 0 arg special selector"
  
  		(128 143	sendLiteralSelector0ArgsBytecode)
  		(144 159	sendLiteralSelector1ArgBytecode)
  		(160 175	sendLiteralSelector2ArgsBytecode)
  
  		(176 183	shortUnconditionalJump)
  		(184 191	shortConditionalJumpTrue)
  		(192 199	shortConditionalJumpFalse)
  	
  		(200 207	storeAndPopReceiverVariableBytecode)
  		(208 215	storeAndPopTemporaryVariableBytecode)
  		(216		popStackBytecode)
  
  		(217 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(224		extABytecode)
  		(225		extBBytecode)
  
  		(226		extPushReceiverVariableBytecode)
  		(227		extPushLiteralVariableBytecode)
  		(228		extPushLiteralBytecode)
  		(229		longPushTemporaryVariableBytecode)
  		(230		pushClosureTempsBytecode)
  		(231		pushNewArrayBytecode)
  		(232		extPushIntegerBytecode)
  		(233		extPushCharacterBytecode)
  
  		(234		extSendBytecode)
  		(235		extSendSuperBytecode)
  
  		(236		extTrapOnBehaviorsBytecode)
  
  		(237		extUnconditionalJump)
  		(238		extJumpIfTrue)
  		(239		extJumpIfFalse)
  
  		(240		extStoreAndPopReceiverVariableBytecode)
  		(241		extStoreAndPopLiteralVariableBytecode)
  		(242		longStoreAndPopTemporaryVariableBytecode)
  
  		(243		extStoreReceiverVariableBytecode)
  		(244		extStoreLiteralVariableBytecode)
  		(245		longStoreTemporaryVariableBytecode)
  
  		(246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(248		callPrimitiveBytecode)
  		(249		unknownBytecode) "reserved for Push Float"
  
  		(250		extPushClosureBytecode)
  		(251		pushRemoteTempLongBytecode)
  		(252		storeRemoteTempLongBytecode)
  		(253		storeAndPopRemoteTempLongBytecode)
  
  		(254 255	unknownBytecode)
  	)!

Item was added:
+ ----- Method: StackInterpreter>>booleanCheatFalseSistaV1 (in category 'utilities') -----
+ booleanCheatFalseSistaV1
+ 	"cheat the interpreter out of the pleasure of handling the next bytecode IFF it is a jump-on-boolean. Which it is, often enough when the current bytecode is something like bytecodePrimEqual"
+ 	<sharedCodeNamed: 'booleanCheatFalseSistaV1' inCase: #bytecodePrimGreaterThanSistaV1>
+ 	| bytecode offset |
+ 
+ 	bytecode := self fetchByte.  "assume next bytecode is jumpIfFalse (99%)"
+ 	self internalPop: 2.
+ 	(bytecode < 199 and: [bytecode > 191]) ifTrue:  "short jumpIfFalse"
+ 		[^self jump: bytecode - 191].
+ 
+ 	bytecode = 239 ifTrue:  "long jumpIfFalse"
+ 		[offset := self fetchByte.
+ 		^self jump: offset].
+ 
+ 	"not followed by a jumpIfFalse; (un)do instruction fetch and push boolean result"
+ 	self cppIf: MULTIPLEBYTECODESETS
+ 		ifTrue: [currentBytecode := bytecode + bytecodeSetSelector]
+ 		ifFalse: [currentBytecode := bytecode].
+ 	self internalPush: objectMemory falseObject!

Item was added:
+ ----- Method: StackInterpreter>>booleanCheatSistaV1: (in category 'utilities') -----
+ booleanCheatSistaV1: cond
+ 	"cheat the interpreter out of the pleasure of handling the next bytecode IFF it is a jump-on-boolean. Which it is, often enough when the current bytecode is something like bytecodePrimEqual"
+ 	<inline: true>
+ 
+ 	cond
+ 		ifTrue: [self booleanCheatTrueSistaV1]
+ 		ifFalse: [self booleanCheatFalseSistaV1]!

Item was added:
+ ----- Method: StackInterpreter>>booleanCheatTrueSistaV1 (in category 'utilities') -----
+ booleanCheatTrueSistaV1
+ 	"cheat the interpreter out of the pleasure of handling the next bytecode IFF it is a jump-on-boolean. Which it is, often enough when the current bytecode is something like bytecodePrimEqual"
+ 	<sharedCodeNamed: 'booleanCheatTrueSistaV1' inCase: #bytecodePrimLessThanSistaV1>
+ 	| bytecode offset |
+ 
+ 	bytecode := self fetchByte.  "assume next bytecode is jumpIfFalse (99%)"
+ 	self internalPop: 2.
+ 	bytecode >= 192 ifTrue:
+ 		[bytecode <= 199 ifTrue: "short jumpIfFalse 192 - 199"
+ 			[^self fetchNextBytecode].
+ 		bytecode = 239 ifTrue: "long jumpIfFalse"
+ 			[self fetchByte.
+ 			^self fetchNextBytecode].
+ 		bytecode = 238 ifTrue: "long jumpIfTrue 238"
+ 			[offset := self fetchByte.
+ 			^self jump: offset]].
+ 
+ 	"not followed by a jumpIfFalse; (un)do instruction fetch and push boolean result"
+ 	self cppIf: MULTIPLEBYTECODESETS
+ 		ifTrue: [currentBytecode := bytecode + bytecodeSetSelector]
+ 		ifFalse: [currentBytecode := bytecode].
+ 	self internalPush: objectMemory trueObject!

Item was added:
+ ----- Method: StackInterpreter>>bytecodePrimEqualSistaV1 (in category 'common selector sends') -----
+ bytecodePrimEqualSistaV1
+ 	| rcvr arg aBool |
+ 	rcvr := self internalStackValue: 1.
+ 	arg := self internalStackValue: 0.
+ 	(self areIntegers: rcvr and: arg) ifTrue: [^self booleanCheatSistaV1: rcvr = arg].
+ 
+ 	self initPrimCall.
+ 	aBool := self primitiveFloatEqual: rcvr toArg: arg.
+ 	self successful ifTrue: [^self booleanCheatSistaV1: aBool].
+ 
+ 	messageSelector := self specialSelector: 6.
+ 	argumentCount := 1.
+ 	self normalSend!

Item was added:
+ ----- Method: StackInterpreter>>bytecodePrimGreaterOrEqualSistaV1 (in category 'common selector sends') -----
+ bytecodePrimGreaterOrEqualSistaV1
+ 	| rcvr arg aBool |
+ 	rcvr := self internalStackValue: 1.
+ 	arg := self internalStackValue: 0.
+ 	(self areIntegers: rcvr and: arg) ifTrue:
+ 		["The C code can avoid detagging since tagged integers are still signed.
+ 		 But this means the simulator must override to do detagging."
+ 		^self cCode: [self booleanCheatSistaV1: rcvr >= arg]
+ 			inSmalltalk: [self booleanCheatSistaV1: (objectMemory integerValueOf: rcvr) >= (objectMemory integerValueOf: arg)]].
+ 
+ 	self initPrimCall.
+ 	aBool := self primitiveFloatGreaterOrEqual: rcvr toArg: arg.
+ 	self successful ifTrue: [^self booleanCheatSistaV1: aBool].
+ 
+ 	messageSelector := self specialSelector: 5.
+ 	argumentCount := 1.
+ 	self normalSend!

Item was added:
+ ----- Method: StackInterpreter>>bytecodePrimGreaterThanSistaV1 (in category 'common selector sends') -----
+ bytecodePrimGreaterThanSistaV1
+ 	| rcvr arg aBool |
+ 	rcvr := self internalStackValue: 1.
+ 	arg := self internalStackValue: 0.
+ 	(self areIntegers: rcvr and: arg) ifTrue:
+ 		["The C code can avoid detagging since tagged integers are still signed.
+ 		 But this means the simulator must override to do detagging."
+ 		^self cCode: [self booleanCheatSistaV1: rcvr > arg]
+ 			inSmalltalk: [self booleanCheatSistaV1: (objectMemory integerValueOf: rcvr) > (objectMemory integerValueOf: arg)]].
+ 
+ 	self initPrimCall.
+ 	aBool := self primitiveFloatGreater: rcvr thanArg: arg.
+ 	self successful ifTrue: [^self booleanCheatSistaV1: aBool].
+ 
+ 	messageSelector := self specialSelector: 3.
+ 	argumentCount := 1.
+ 	self normalSend!

Item was added:
+ ----- Method: StackInterpreter>>bytecodePrimIdenticalSistaV1 (in category 'common selector sends') -----
+ bytecodePrimIdenticalSistaV1
+ 	| rcvr arg |
+ 	rcvr := self internalStackValue: 1.
+ 	arg := self internalStackValue: 0.
+ 	(objectMemory isOopForwarded: rcvr) ifTrue:
+ 		[rcvr := self handleSpecialSelectorSendFaultFor: rcvr].
+ 	(objectMemory isOopForwarded: arg) ifTrue:
+ 		[arg := self handleSpecialSelectorSendFaultFor: arg].
+ 	self booleanCheatSistaV1: rcvr = arg!

Item was added:
+ ----- Method: StackInterpreter>>bytecodePrimLessOrEqualSistaV1 (in category 'common selector sends') -----
+ bytecodePrimLessOrEqualSistaV1
+ 	| rcvr arg aBool |
+ 	rcvr := self internalStackValue: 1.
+ 	arg := self internalStackValue: 0.
+ 	(self areIntegers: rcvr and: arg) ifTrue:
+ 		["The C code can avoid detagging since tagged integers are still signed.
+ 		 But this means the simulator must override to do detagging."
+ 		^self cCode: [self booleanCheatSistaV1: rcvr <= arg]
+ 			inSmalltalk: [self booleanCheatSistaV1: (objectMemory integerValueOf: rcvr) <= (objectMemory integerValueOf: arg)]].
+ 
+ 	self initPrimCall.
+ 	aBool := self primitiveFloatLessOrEqual: rcvr toArg: arg.
+ 	self successful ifTrue: [^self booleanCheatSistaV1: aBool].
+ 
+ 	messageSelector := self specialSelector: 4.
+ 	argumentCount := 1.
+ 	self normalSend!

Item was added:
+ ----- Method: StackInterpreter>>bytecodePrimLessThanSistaV1 (in category 'common selector sends') -----
+ bytecodePrimLessThanSistaV1
+ 	| rcvr arg aBool |
+ 	rcvr := self internalStackValue: 1.
+ 	arg := self internalStackValue: 0.
+ 	(self areIntegers: rcvr and: arg) ifTrue:
+ 		["The C code can avoid detagging since tagged integers are still signed.
+ 		 But this means the simulator must override to do detagging."
+ 		^self cCode: [self booleanCheatSistaV1: rcvr < arg]
+ 			inSmalltalk: [self booleanCheatSistaV1: (objectMemory integerValueOf: rcvr) < (objectMemory integerValueOf: arg)]].
+ 
+ 	self initPrimCall.
+ 	aBool := self primitiveFloatLess: rcvr thanArg: arg.
+ 	self successful ifTrue: [^ self booleanCheatSistaV1: aBool].
+ 
+ 	messageSelector := self specialSelector: 2.
+ 	argumentCount := 1.
+ 	self normalSend!

Item was added:
+ ----- Method: StackInterpreter>>bytecodePrimNotEqualSistaV1 (in category 'common selector sends') -----
+ bytecodePrimNotEqualSistaV1
+ 	| rcvr arg aBool |
+ 	rcvr := self internalStackValue: 1.
+ 	arg := self internalStackValue: 0.
+ 	(self areIntegers: rcvr and: arg) ifTrue: [^self booleanCheatSistaV1: rcvr ~= arg].
+ 
+ 	self initPrimCall.
+ 	aBool := self primitiveFloatEqual: rcvr toArg: arg.
+ 	self successful ifTrue: [^self booleanCheatSistaV1: aBool not].
+ 
+ 	messageSelector := self specialSelector: 7.
+ 	argumentCount := 1.
+ 	self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>extNopBytecode (in category 'miscellaneous bytecodes') -----
  extNopBytecode
+ 	"SistaV1		94		01011111		Nop"
+ 	"NewspeakV4: 221		11011101		Nop"
+ 	self fetchNextBytecode.
- 	"221		11011101		Nop"
  	extA := extB := 0!

Item was added:
+ ----- Method: StackInterpreter>>extPushCharacterBytecode (in category 'stack bytecodes') -----
+ extPushCharacterBytecode
+ 	"SistaV1:	*	233		11101001	iiiiiiii		Push Character #iiiiiiii (+ Extend B * 256)"
+ 	| value |
+ 	value := self fetchByte + (extB << 8).
+ 	self fetchNextBytecode.
+ 	self internalPush: (objectMemory characterObjectOf: value).
+ 	extB := 0!

Item was added:
+ ----- Method: StackInterpreter>>extPushPseudoVariable (in category 'stack bytecodes') -----
+ extPushPseudoVariable
+ 	"SistaV1:	*	82			01010010			Push thisContext, (then e.g. Extend 1 = push thisProcess)"
+ 	extA
+ 		caseOf: {
+ 			[0]	->	[self pushActiveContextBytecode].
+ 			[1]	->	[self internalPush: self activeProcess] }
+ 		otherwise:
+ 			[self respondToUnknownBytecode].
+ 	self fetchNextBytecode.
+ 	extA := 0!

Item was added:
+ ----- Method: StackInterpreter>>pushClosureTempsBytecode (in category 'stack bytecodes') -----
+ pushClosureTempsBytecode
+ 	"SistaV1:	230		11100110	iiiiiiii		PushNClosureTemps iiiiiiii"
+ 	| nTemps |
+ 	nTemps := self fetchByte.
+ 	self fetchNextBytecode.
+ 	1 to: nTemps do:
+ 		[:i|
+ 		self internalPush: objectMemory nilObject]!

Item was added:
+ ----- Method: StackInterpreter>>returnNilFromBlock (in category 'return bytecodes') -----
+ returnNilFromBlock
+ 	"Return nil to the caller of the current block activation."
+ 	localReturnValue := objectMemory nilObject.
+ 	self commonCallerReturn!

Item was changed:
  ----- Method: StackInterpreter>>returnTopFromBlock (in category 'return bytecodes') -----
  returnTopFromBlock
+ 	"Return top-of-stack to the caller of the current block activation."
- 	"Return to the caller of the current block activation."
  	localReturnValue := self internalStackTop.
  	self commonCallerReturn!

Item was changed:
  ----- Method: TMethod>>buildCaseStmt:in: (in category 'transformations') -----
  buildCaseStmt: aSendNode in: aCodeGen
  	"Build a case statement node for the given send of dispatchOn:in:."
  	"Note: the first argument is the variable to be dispatched on. The second argument is a constant node holding an array of unary selectors, which will be turned into sends to self."
  
  	| unimplemented errorMessage |
  	((aSendNode args size >= 2) and:
  	 [aSendNode args second isConstant and:
  	 [aSendNode args second value class = Array]]) ifFalse:
  		[self error: 'wrong node structure for a case statement'].
  
  	unimplemented := aSendNode args second value reject: [:s| self definingClass includesSelector: s].
  	unimplemented isEmpty ifFalse:
+ 		[errorMessage := 'The following selectors in case statement "', (aSendNode printString copyUpTo: $#), '..." are unimplemented: ',
- 		[errorMessage := 'The following selectors are unimplemented: ',
  							(String streamContents: [:s| unimplemented do: [:sel| s crtab; store: sel]]).
+ 		 aCodeGen logger nextPutAll: errorMessage; cr; flush.
  		 (self confirm: errorMessage
  			orCancel: aCodeGen abortBlock) ifFalse:
  				[self halt]].
  
  	^TCaseStmtNode new
  		setExpression: aSendNode args first
  		selectors: aSendNode args second value
  		arguments: (aSendNode args copyFrom: 3 to: aSendNode args size)!

Item was changed:
  SharedPool subclass: #VMObjectIndices
  	instanceVariableNames: ''
+ 	classVariableNames: 'ActiveProcessIndex CharacterTable CharacterValueIndex ClassAlien ClassArray ClassBitmap ClassBlockClosure ClassBlockContext ClassByteArray ClassByteString ClassCharacter ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassMutex ClassPoint ClassSemaphore ClassSmallInteger ClassString ClassUnsafeAlien ClassWeakFinalizer ClosureCopiedValuesIndex ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLinkIndex LiteralStart MessageArgumentsIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MethodDictionaryIndex MethodIndex MyListIndex NextLinkIndex NilObject PrimErrTableIndex PriorityIndex ProcessInExternalCodeTag ProcessListsIndex ProcessSignalingLowSpace ReceiverIndex SchedulerAssociation SelectorAboutToReturn SelectorAttemptToAssign SelectorCannotInterpret SelectorCannotReturn SelectorClassTrap SelectorCounterTripped SelectorDoesNotUnderstand SelectorInvokeCallback SelectorMustBeBoolean SelectorRunWithIn SelectorStart SelectorUnknownBytecode SenderIndex SpecialSelectors StackPointerIndex StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject ValueIndex XIndex YIndex'
- 	classVariableNames: 'ActiveProcessIndex CharacterTable CharacterValueIndex ClassAlien ClassArray ClassBitmap ClassBlockClosure ClassBlockContext ClassByteArray ClassByteString ClassCharacter ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassLargeNegativeInteger ClassLargePositiveInteger ClassMessage ClassMethodContext ClassMutex ClassPoint ClassSemaphore ClassSmallInteger ClassString ClassUnsafeAlien ClassWeakFinalizer ClosureCopiedValuesIndex ClosureFirstCopiedValueIndex ClosureIndex ClosureNumArgsIndex ClosureOuterContextIndex ClosureStartPCIndex CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ExcessSignalsIndex ExternalObjectsArray FalseObject FirstLinkIndex ForeignCallbackProcess HeaderIndex InstanceSpecificationIndex InstructionPointerIndex KeyIndex LastLinkIndex LiteralStart MessageArgumentsIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MethodDictionaryIndex MethodIndex MyListIndex NextLinkIndex NilObject PrimErrTableIndex PriorityIndex ProcessInExternalCodeTag ProcessListsIndex ProcessSignalingLowSpace ReceiverIndex SchedulerAssociation SelectorAboutToReturn SelectorAttemptToAssign SelectorCannotInterpret SelectorCannotReturn SelectorCounterTripped SelectorDoesNotUnderstand SelectorInvokeCallback SelectorMustBeBoolean SelectorRunWithIn SelectorStart SelectorUnknownBytecode SenderIndex SpecialSelectors StackPointerIndex StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject ValueIndex XIndex YIndex'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !VMObjectIndices commentStamp: '<historical>' prior: 0!
  I am a shared pool for the constants that define object layout and well-known objects shared between the object memories (e.g. ObjectMemory, NewObjectMemory), the interpreters (e.g. StackInterpreter, CoInterpreter) and the object representations (e.g. ObjectRepresentationForSqueakV3).
  
  self classPool declare: #Foo from: StackInterpreter classPool
  
  (ObjectMemory classPool keys select: [:k| (k beginsWith: 'Class') and: [(k endsWith: 'Index') not]]) do:
  	[:k| self classPool declare: k from: ObjectMemory classPool]!



More information about the Vm-dev mailing list