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

commits at source.squeak.org commits at source.squeak.org
Thu Aug 7 00:18:07 UTC 2014


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

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

Name: VMMaker.oscog-eem.844
Author: eem
Time: 6 August 2014, 5:15:34.309 pm
UUID: 4ea8ab78-c8f6-4cf2-a165-23eb85dd66aa
Ancestors: VMMaker.oscog-eem.843

Fix bad bug in interpreter to machine code frame conversion
on backward branch.  Old code would decrement branch
even if backward branch checked for events and did a
process switch, potentially converting frames at arbitrary
unmappable pcs, not just backward branches.  Neaten and
comment the code.  Neaten and update the pc mapping
tests for multiple bytecode sets and for sets with
extensions.  Change the default count to 40 from 10 to
reduce the number of startup methods jitted.

Implement genExtTrapIfNotInstanceOfBehaviorsBytecode
for SqeakV3.  And fix it and the interpreter's version to
pop the value from the stack.

Eliminate expensive asserts in Spur allObjects/alInstances
unnecessary in MarkObjectsForEnumerationPrimitives false
regime.

Simulator:
Make the DetailedInstructionPrinter multiple bytecode set
aware.

Fix bugs in the facades: don't rely on host image for compact
class indices, answer more classes through splObj:, implement
encoderClassForHeader:.

Comment the facade and proxy classes; they are confusing.

Nuke obsolete InterpreterForLongFormV3.

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

Item was changed:
  ----- Method: CoInterpreter class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  
  	super initializeMiscConstants.
  	COGVM := true.
  
+ 	MinBackwardJumpCountForCompile := 40.
- 	MinBackwardJumpCountForCompile := 10.
  
  	MaxNumArgs := 15.
  	PrimCallNeedsNewMethod := 1.
  	PrimCallNeedsPrimitiveFunction := 2.
  	PrimCallMayCallBack := 4.
  	PrimCallCollectsProfileSamples := 8.
  	CheckAllocationFillerAfterPrimCall := 16.
  	PrimCallDoNotJIT := 32.
  
  	ReturnToInterpreter := 1. "setjmp/longjmp code."
  
  	PrimTraceLogSize := 256. "Room for 256 selectors.  Must be 256 because we use a byte to hold the index"
  	TraceBufferSize := 256 * 3. "Room for 256 events"
  	TraceContextSwitch := self objectMemoryClass basicNew integerObjectOf: 1.
  	TraceBlockActivation := self objectMemoryClass basicNew integerObjectOf: 2.
  	TraceBlockCreation := self objectMemoryClass basicNew integerObjectOf: 3.
  	TraceIncrementalGC := self objectMemoryClass basicNew integerObjectOf: 4.
  	TraceFullGC := self objectMemoryClass basicNew integerObjectOf: 5.
  	TraceCodeCompaction := self objectMemoryClass basicNew integerObjectOf: 6.
  	TraceOwnVM := self objectMemoryClass basicNew integerObjectOf: 7.
  	TraceDisownVM := self objectMemoryClass basicNew integerObjectOf: 8.
  	TraceThreadSwitch := self objectMemoryClass basicNew integerObjectOf: 9.
  	TracePreemptDisowningThread := self objectMemoryClass basicNew integerObjectOf: 10.
  	TraceVMCallback := self objectMemoryClass basicNew integerObjectOf: 11.
  	TraceVMCallbackReturn := self objectMemoryClass basicNew integerObjectOf: 12.
  	TraceStackOverflow := self objectMemoryClass basicNew integerObjectOf: 13.
  
  	TraceIsFromMachineCode := 1.
  	TraceIsFromInterpreter := 2.
  	CSCallbackEnter := 3.
  	CSCallbackLeave := 4.
  	CSEnterCriticalSection := 5.
  	CSExitCriticalSection := 6.
  	CSResume := 7.
  	CSSignal := 8.
  	CSSuspend := 9.
  	CSWait := 10.
  	CSYield := 11.
  	CSCheckEvents := 12.
  	CSThreadSchedulingLoop := 13.
  	CSOwnVM := 14.
  	CSThreadBind := 15.
  	CSSwitchIfNeccessary := 16.
  
  	TraceSources := CArrayAccessor on: #('?' 'm' 'i' 'callbackEnter' 'callbackLeave' 'enterCritical' 'exitCritical' 'resume' 'signal'  'suspend' 'wait' 'yield' 'eventcheck' 'threadsched' 'ownVM' 'bindToThread' 'switchIfNecessary').
  
  	"this is simulation only"
  	RumpCStackSize := 4096!

Item was changed:
  ----- Method: CoInterpreter>>attemptToSwitchToMachineCode: (in category 'jump bytecodes') -----
  attemptToSwitchToMachineCode: bcpc
+ 	"Attempt to convert the current interpreted activation into a machine code
+ 	 activation, and if this is popssible, jump into machine code.  bcpc is the
+ 	 0-relative pc of the backward branch bytecode (not any preceeding extension)."
  	| cogMethod pc |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	(self methodHasCogMethod: method) ifFalse:
  		[cogit cog: method selector: objectMemory nilObject].
  	(self methodHasCogMethod: method) ifTrue:
  		[cogMethod := self cogMethodOf: method.
  		 pc := self convertToMachineCodeFrame: cogMethod bcpc: bcpc.
  		 self assertValidMachineCodeFrame: pc.
  		 self push: pc.
  		 self push: objectMemory nilObject.
  		 cogit ceEnterCogCodePopReceiverReg]!

Item was changed:
  ----- Method: CoInterpreter>>convertToMachineCodeFrame:bcpc: (in category 'frame access') -----
  convertToMachineCodeFrame: cogHomeMethod bcpc: bcpc
  	<var: #cogHomeMethod type: #'CogHomeMethod *'>
  	<returnTypeC: #usqInt>
  	"Convert the current interpreter frame into a machine code frame
  	 and answer the machine code pc matching bcpc."
  	| startBcpc methodField closure cogMethod pc |
  	<var: #cogMethod type: #'CogBlockMethod *'>
  	<var: #p type: #'char *'>
  	self assert: (self isMachineCodeFrame: framePointer) not.
  	"Update the return pc, perhaps saving it in the caller's iframeSavedIP."
  	(self isBaseFrame: framePointer)
  		ifTrue:
  			[stackPages
  				longAt: framePointer + FoxCallerSavedIP
  				put: cogit ceBaseFrameReturnPC]
  		ifFalse:
  			[(self isMachineCodeFrame: (self frameCallerFP: framePointer)) ifFalse:
  				[self iframeSavedIP: (self frameCallerFP: framePointer)
  					put: (self frameCallerSavedIP: framePointer) asInteger.
  				 stackPages
  					longAt: framePointer + FoxCallerSavedIP
  					put: cogit ceReturnToInterpreterPC]].
+ 	"Compute the cog method field"
- 	"Set the cog method field"
  	(self iframeIsBlockActivation: framePointer)
  		ifTrue:
  			[closure := self pushedReceiverOrClosureOfFrame: framePointer.
  			 startBcpc := self startPCOfClosure: closure.
  			 cogMethod := cogit
  								findMethodForStartBcpc: startBcpc
  								inHomeMethod: cogHomeMethod.
  			 methodField := cogMethod asInteger + MFMethodFlagIsBlockFlag]
  		ifFalse:
  			[startBcpc := self startPCOfMethodHeader: cogHomeMethod methodHeader.
  			 cogMethod := self cCoerceSimple: cogHomeMethod to: #'CogBlockMethod *'.
  			 methodField := cogHomeMethod asInteger].
+ 	"compute the pc before converting the frame to help with debugging."
+ 	pc := cogit mcPCForBackwardBranch: bcpc startBcpc: startBcpc in: cogMethod.
+ 	self assert: pc > (cogMethod asUnsignedInteger + cogit noCheckEntryOffset).
+ 	self assert: bcpc = (self bytecodePCFor: pc startBcpc: startBcpc in: cogMethod).
+ 	"now convert to a machine code frame"
  	stackPages
  		longAt: framePointer + FoxMethod
  		put: methodField
  			+ ((self iframeHasContext: framePointer)
  				ifTrue: [MFMethodFlagHasContextFlag]
  				ifFalse: [0]).
  	framePointer + FoxIFReceiver to: stackPointer by: BytesPerWord negated do:
  		[:p|
  		stackPages longAt: p + FoxMFReceiver - FoxIFReceiver put: (stackPages longAt: p)].
  	stackPointer := stackPointer + FoxMFReceiver - FoxIFReceiver.
- 	pc := cogit mcPCForBackwardBranch: bcpc startBcpc: startBcpc in: cogMethod.
- 	self assert: pc > (cogMethod asUnsignedInteger + cogit noCheckEntryOffset).
  	^pc!

Item was changed:
  ----- Method: CoInterpreter>>ifBackwardsCheckForEvents: (in category 'jump bytecodes') -----
  ifBackwardsCheckForEvents: offset
  	"Backward jump means we're in a loop.
  		- check for possible interrupts.
  		- check for long-running loops and JIT if appropriate."
  	| switched backwardJumpCountByte |
  	<inline: true>
+ 	offset >= 0 ifTrue:
+ 		[^self].
+ 
+ 	localSP < stackLimit ifTrue:
+ 		[self externalizeIPandSP.
+ 		 switched := self checkForEventsMayContextSwitch: true.
+ 		 self returnToExecutive: true postContextSwitch: switched.
+ 		 self browserPluginReturnIfNeeded.
+ 		 self internalizeIPandSP.
+ 		 switched ifTrue:
+ 			[^self]].
+ 
+ 	"We use the least significant byte of the flags word (which is marked as an immediate) and
+ 	 subtract two each time to avoid disturbing the least significant tag bit.  Since the byte is
+ 	 initialized to 1 (on frame build), on first decrement it will become -1.  Trip when it reaches 1 again."
+ 	backwardJumpCountByte := self iframeBackwardBranchByte: localFP.
+ 	(backwardJumpCountByte := backwardJumpCountByte - 2) = 1
+ 		ifTrue:
+ 			[(self methodWithHeaderShouldBeCogged: (self headerOf: method)) ifTrue:
+ 				[self externalizeIPandSP.
+ 				 self attemptToSwitchToMachineCode: (self oopForPointer: localIP) - offset - method - BaseHeaderSize - 1
+ 				 "If attemptToSwitchToMachineCode: returns the method could not be cogged, hence..."].
+ 			 "can't cog method; avoid asking to cog it again for the longest possible time."
+ 			 backwardJumpCountByte := 16r7F]
+ 		ifFalse:
+ 			[backwardJumpCountByte = -1 ifTrue: "initialize the count"
+ 				[self assert: minBackwardJumpCountForCompile <= 128.
+ 				 backwardJumpCountByte := minBackwardJumpCountForCompile - 1 << 1 + 1]].
+ 	self iframeBackwardBranchByte: localFP put: backwardJumpCountByte!
- 	offset < 0 ifTrue:
- 		[localSP < stackLimit ifTrue:
- 			[self externalizeIPandSP.
- 			 switched := self checkForEventsMayContextSwitch: true.
- 			 self returnToExecutive: true postContextSwitch: switched.
- 			 self browserPluginReturnIfNeeded.
- 			 self internalizeIPandSP].
- 		 "We use the least significant byte of the flags word (which is marked as an immediate) and subtract two each time
- 		  to avoid disturbing the least significant tag bit.  Since the byte is initialized to 1 (on frame build), on first decrement
- 		  it will become -1.  We trip when it becomes 1 again."
- 		 backwardJumpCountByte := stackPages byteAt: localFP + (VMBIGENDIAN ifTrue: [FoxIFrameFlags + BytesPerWord - 1] ifFalse: [FoxIFrameFlags]).
- 		 (backwardJumpCountByte := backwardJumpCountByte - 2) <= 1 ifTrue:
- 			[backwardJumpCountByte = -1
- 				ifTrue: "initialize the count"
- 					[self assert: minBackwardJumpCountForCompile <= 128.
- 					 backwardJumpCountByte := minBackwardJumpCountForCompile - 1 << 1 + 1]
- 				ifFalse:
- 					[(self methodWithHeaderShouldBeCogged: (self headerOf: method))
- 						ifTrue:
- 							[self externalizeFPandSP.
- 							 self attemptToSwitchToMachineCode: (self oopForPointer: localIP) - offset - method - BaseHeaderSize - 1]
- 						ifFalse: "avoid asking for as long as possible"
- 							[backwardJumpCountByte := 16rFF]]].
- 		 stackPages
- 			byteAt: localFP + (VMBIGENDIAN ifTrue: [FoxIFrameFlags + BytesPerWord - 1] ifFalse: [FoxIFrameFlags])
- 			put: backwardJumpCountByte]!

Item was added:
+ ----- Method: CoInterpreter>>iframeBackwardBranchByte: (in category 'frame access') -----
+ iframeBackwardBranchByte: theFP
+ 	"See encodeFrameFieldHasContext:numArgs: and ifBackwardsCheckForEvents:"
+ 	<inline: true>
+ 	<var: #theFP type: #'char *'>
+ 	^stackPages byteAt: theFP + (VMBIGENDIAN ifTrue: [FoxIFrameFlags + BytesPerWord - 1] ifFalse: [FoxIFrameFlags])!

Item was added:
+ ----- Method: CoInterpreter>>iframeBackwardBranchByte:put: (in category 'frame access') -----
+ iframeBackwardBranchByte: theFP put: aByte
+ 	"See encodeFrameFieldHasContext:numArgs: and ifBackwardsCheckForEvents:"
+ 	<inline: true>
+ 	<var: #theFP type: #'char *'>
+ 	stackPages
+ 		byteAt: theFP + (VMBIGENDIAN ifTrue: [FoxIFrameFlags + BytesPerWord - 1] ifFalse: [FoxIFrameFlags])
+ 		put: aByte!

Item was added:
+ ----- Method: CogObjectRepresentation>>branchIfInstanceOfBehavior:branches: (in category 'sista support') -----
+ branchIfInstanceOfBehavior: classObj branches: branches
+ 	"Generate a branch if ReceiverResultReg is an instance of classObj, otherwise fall-
+ 	 through. Store the branch in branches and answer the number of branches generated."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentation>>branchIfInstanceOfBehaviors:branches: (in category 'sista support') -----
+ branchIfInstanceOfBehaviors: arrayObj branches: branches
+ 	"Generate a branch if ReceiverResultReg is an instance of any of the classes in arrayObj,
+ 	 otherwise fall-through. Store the branch in branches and answer the number of branches
+ 	 generated."
+ 
+ 	self subclassResponsibility!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>branchIfInstanceOfBehavior:branches: (in category 'sista support') -----
  branchIfInstanceOfBehavior: classObj branches: branches
+ 	"Generate a branch if ReceiverResultReg is an instance of classObj, otherwise fall-
+ 	 through. Store the branch in branches and answer the number of branches generated."
  	<var: #branches type: #'AbstractInstruction *'>
  	| jmpImmediate compactClassIndex |
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	cogit MoveR: ReceiverResultReg R: TempReg.
  	jmpImmediate := self genJumpSmallIntegerInScratchReg: TempReg.
  	classObj = (objectMemory splObj: ClassSmallInteger) ifTrue:
  		[branches at: 0 put: jmpImmediate.
+ 		 ^1].
- 		 ^0].
  	(compactClassIndex := objectMemory compactClassIndexOfClass: classObj) ~= 0
  		ifTrue:
  			[self genGetCompactClassIndexNonImmOf: ReceiverResultReg into: TempReg.
  			 cogit CmpCq: compactClassIndex R: TempReg]
  		ifFalse:
  			[self genGetClassObjectOfNonCompact: ReceiverResultReg into: TempReg.
  			 cogit
  				annotate: (cogit CmpCw: classObj R: TempReg)
  				objRef: classObj].
  	branches at: 0 put: (cogit JumpZero: 0).
+ 	^1!
- 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>branchIfInstanceOfBehaviors:branches: (in category 'sista support') -----
+ branchIfInstanceOfBehaviors: arrayObj branches: branches
+ 	"Generate a branch if ReceiverResultReg is an instance of any of the classes in arrayObj,
+ 	 otherwise fall-through. Store the branch in branches and answer the number of branches
+ 	 generated."
+ 
+ 	<var: #branches type: #'AbstractInstruction *'>
+ 	| anImmediate allCompact noneCompact classObj jmpImmediate jmpCompact branchIndex |
+ 	<var: #jmpCompact type: #'AbstractInstruction *'>
+ 	<var: #jmpImmediate type: #'AbstractInstruction *'>
+ 	"let me tell you all about it, let me falsify"
+ 	anImmediate := false. allCompact := true. noneCompact := true.
+ 	0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
+ 		[:i|
+ 		 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
+ 		 classObj = (objectMemory splObj: ClassSmallInteger)
+ 			ifTrue:
+ 				[anImmediate := true]
+ 			ifFalse:
+ 				[(objectMemory compactClassIndexOfClass: classObj) = 0
+ 					ifTrue: [allCompact := false]
+ 					ifFalse: [noneCompact := false]]].
+ 	cogit MoveR: ReceiverResultReg R: TempReg.
+ 	branchIndex := 0.
+ 	jmpImmediate := self genJumpSmallIntegerInScratchReg: TempReg.
+ 	self genGetCompactClassIndexNonImmOf: ReceiverResultReg into: TempReg.
+ 	noneCompact
+ 		ifTrue:
+ 			[cogit CmpCq: 0 R: TempReg.
+ 			 jmpCompact := cogit JumpNonZero: 0]
+ 		ifFalse:
+ 			[0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
+ 				[:i| | compactClassIndex |
+ 				 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
+ 				 (classObj ~= (objectMemory splObj: ClassSmallInteger)
+ 				  and: [(compactClassIndex := objectMemory compactClassIndexOfClass: classObj) ~= 0]) ifTrue:
+ 					[cogit CmpCq: compactClassIndex R: TempReg.
+ 					 branches at: branchIndex put: (cogit JumpZero: 0).
+ 					 branchIndex := branchIndex + 1]]].
+ 	allCompact ifFalse:
+ 		[self genGetClassObjectOfNonCompact: ReceiverResultReg into: TempReg.
+ 		 0 to: (objectMemory numSlotsOf: arrayObj) - 1 do:
+ 			[:i|
+ 			 classObj := objectMemory fetchPointer: i ofObject: arrayObj.
+ 			 (classObj ~= (objectMemory splObj: ClassSmallInteger)
+ 			  and: [(objectMemory compactClassIndexOfClass: classObj) = 0]) ifTrue:
+ 				[cogit
+ 					annotate: (cogit CmpCw: classObj R: TempReg)
+ 					objRef: classObj.
+ 				 branches at: branchIndex put: (cogit JumpZero: 0).
+ 				 branchIndex := branchIndex + 1]]].
+ 	"Either succeed or fail on the immediate test."
+ 	anImmediate
+ 		ifTrue: [branches at: branchIndex put: jmpImmediate.
+ 				branchIndex := branchIndex + 1]
+ 		ifFalse: [jmpImmediate jmpTarget: cogit Label].
+ 	noneCompact ifTrue:
+ 		[jmpCompact jmpTarget: cogit Label].
+ 	self assert: branchIndex = (objectMemory numSlotsOf: arrayObj).
+ 	^branchIndex!

Item was changed:
  ----- Method: CogVMSimulator>>convertToMachineCodeFrame:bcpc: (in category 'frame access') -----
  convertToMachineCodeFrame: cogHomeMethod bcpc: bcpc
+ 	"bytecodeSetSelector ~= 0 ifTrue: ["self halt"]".
- 	"(minBackwardJumpCountForCompile ~= MinBackwardJumpCountForCompile
- 	 and: [(self stringOf: (self penultimateLiteralOf: cogHomeMethod methodObject)) = #repeat]) ifTrue:
- 		[self printExternalHeadFrame.
- 		self print: bcpc; cr.
- 		self halt]."
  	^super convertToMachineCodeFrame: cogHomeMethod bcpc: bcpc!

Item was changed:
  ----- Method: Cogit class>>testPCMappingFor:options: (in category 'tests') -----
  testPCMappingFor: aCompiledMethod options: optionsDictionaryOrArray
  	| tuple |
  	tuple := self cog: aCompiledMethod selector: aCompiledMethod selector options: optionsDictionaryOrArray.
+ 	tuple second testPCMappingForCompiledMethod: aCompiledMethod cogMethod: tuple last!
- 	tuple second testPCMappingForMethod: tuple last!

Item was changed:
  ----- Method: Cogit class>>testPCMappingSelect:options: (in category 'tests') -----
  testPCMappingSelect: aBlock options: optionsDictionaryOrArray
+ 	"Test pc mapping both ways using a selection of the methods in the current image."
- 	"Test pc mapping both ways using the methods in the current image"
  	| cogit coInterpreter |
  	self initializeWithOptions: (self asOptionsDictionary: optionsDictionaryOrArray).
  	cogit := self new.
  	coInterpreter := CurrentImageCoInterpreterFacade new cogit: cogit; yourself.
  	[cogit
  			setInterpreter: coInterpreter;
  			singleStep: true;
  			initializeCodeZoneFrom: 1024 upTo: coInterpreter memory size]
  		on: Notification
  		do: [:ex|
  			(ex messageText beginsWith: 'cannot find receiver for') ifTrue:
  				[ex resume: coInterpreter]].
  	SystemNavigation new allSelect:
  		[:m| | cm |
  		(m isQuick not
  		 and: [aBlock value: m]) ifTrue:
  			[Transcript nextPut: $.; flush.
  			 [cm := cogit
  						cog: (coInterpreter oopForObject: m)
  						selector: (coInterpreter oopForObject: m selector).
  			   cm isNil and: [coInterpreter isCogCompiledCodeCompactionCalledFor]] whileTrue:
  				[cogit methodZone clearCogCompiledCode.
  				 coInterpreter clearCogCompiledCodeCompactionCalledFor.
  				 coInterpreter initializeObjectMap].
+ 			 cogit testPCMappingForCompiledMethod: m cogMethod: cm].
- 			 cogit testPCMappingForMethod: cm].
  		 false]!

Item was added:
+ ----- Method: Cogit>>bcpcsAndDescriptorsFor:bsOffset:do: (in category 'tests-method map') -----
+ bcpcsAndDescriptorsFor: aMethod bsOffset: bsOffset do: quaternaryBlock
+ 	"Evaluate quaternaryBlock with the pc, byte, descriptor and numExtensions for
+ 	 all the bytecodes in aMethod.  Evaluate with byte, descriptor and numExtensions
+ 	 nil for the initialPC of the mehtod and any blocks within it."
+ 	<doNotGenerate>
+ 	| nExts byte descriptor endpc latestContinuation pc primIdx |
+ 	((primIdx := coInterpreter primitiveIndexOf: aMethod) > 0
+ 	and: [coInterpreter isQuickPrimitiveIndex: primIdx]) ifTrue:
+ 		[^self].
+ 	latestContinuation := pc := coInterpreter startPCOfMethod: aMethod.
+ 	quaternaryBlock value: pc value: nil value: nil value: 0. "stackCheck/entry pc"
+ 	nExts := 0.
+ 	endpc := objectMemory numBytesOf: aMethod.
+ 	[pc <= endpc] whileTrue:
+ 		[byte := objectMemory fetchByte: pc ofObject: aMethod.
+ 		descriptor := self generatorAt: byte + bsOffset.
+ 		descriptor isExtension ifFalse:
+ 			[quaternaryBlock value: pc value: byte value: descriptor value: nExts].
+ 		(descriptor isReturn
+ 		 and: [pc >= latestContinuation]) ifTrue:
+ 			[endpc := pc].
+ 		(descriptor isBranch
+ 		 or: [descriptor isBlockCreation]) ifTrue:
+ 			[| targetPC |
+ 			 descriptor isBlockCreation ifTrue:
+ 				[quaternaryBlock value: pc + descriptor numBytes value: nil value: nil value: 0]. "stackCheck/entry pc"
+ 			 targetPC := self latestContinuationPCFor: descriptor at: pc exts: nExts in: aMethod.
+ 			 self assert: targetPC < endpc.
+ 			 latestContinuation := latestContinuation max: targetPC].
+ 		pc := pc + descriptor numBytes.
+ 		nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]]!

Item was removed:
- ----- Method: Cogit>>bcpcsAndDescriptorsFor:do: (in category 'tests-method map') -----
- bcpcsAndDescriptorsFor: aMethod do: trinaryBlock
- 	<doNotGenerate>
- 	| bsOffset nExts byte descriptor endpc latestContinuation pc primIdx |
- 	((primIdx := coInterpreter primitiveIndexOf: aMethod) > 0
- 	and: [coInterpreter isQuickPrimitiveIndex: primIdx]) ifTrue:
- 		[^self].
- 	latestContinuation := pc := coInterpreter startPCOfMethod: aMethod.
- 	trinaryBlock value: pc value: nil value: nil. "stackCheck/entry pc"
- 	bsOffset := self bytecodeSetOffsetFor: aMethod.
- 	nExts := 0.
- 	endpc := objectMemory numBytesOf: aMethod.
- 	[pc <= endpc] whileTrue:
- 		[byte := objectMemory fetchByte: pc ofObject: aMethod.
- 		descriptor := self generatorAt: byte + bsOffset.
- 		trinaryBlock value: pc value: byte value: descriptor.
- 		(descriptor isReturn
- 		 and: [pc >= latestContinuation]) ifTrue:
- 			[endpc := pc].
- 		(descriptor isBranch
- 		 or: [descriptor isBlockCreation]) ifTrue:
- 			[| targetPC |
- 			 descriptor isBlockCreation ifTrue:
- 				[trinaryBlock value: pc + descriptor numBytes value: nil value: nil]. "stackCheck/entry pc"
- 			 targetPC := self latestContinuationPCFor: descriptor at: pc exts: nExts in: aMethod.
- 			 self assert: targetPC < endpc.
- 			 latestContinuation := latestContinuation max: targetPC].
- 		pc := pc + descriptor numBytes.
- 		 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]]!

Item was changed:
  ----- Method: Cogit>>cCoerceSimple:to: (in category 'translation support') -----
  cCoerceSimple: value to: cTypeString
  	<doNotGenerate>
  	cTypeString == #'CogMethod *' ifTrue:
  		[^(value isInteger and: [value < 0])
  			ifTrue: [value] "it's an error code; leave it be"
  			ifFalse: [self cogMethodSurrogateAt: value asUnsignedInteger]].
  	cTypeString == #'CogBlockMethod *' ifTrue:
  		[^self cogBlockMethodSurrogateAt: value asUnsignedInteger].
+ 	(cTypeString == #'AbstractInstruction *'
+ 	 and: [value isBehavior]) ifTrue:
+ 		[^processor abstractInstructionCompilerClass].
  	^super cCoerceSimple: value to: cTypeString!

Item was removed:
- ----- Method: Cogit>>nExtensionsFor:in: (in category 'simulation only') -----
- nExtensionsFor: bcpc in: aMethodObj
- 	(coInterpreter methodUsesAlternateBytecodeSet: aMethodObj) ifFalse:
- 		[^0].
- 	^(InstructionStream on: (VMCompiledMethodProxy new
- 								for: aMethodObj
- 								coInterpreter: coInterpreter
- 								objectMemory: objectMemory))
- 		extensionsForBytecodeAt: bcpc + 1
- 		into: [:extAValue :extBValue| (extAValue ~= 0 ifTrue: [1] ifFalse: [0]) + (extBValue ~= 0 ifTrue: [1] ifFalse: [0])]!

Item was added:
+ ----- Method: Cogit>>testBcToMcPcMappingForCompiledMethod:cogMethod: (in category 'tests-method map') -----
+ testBcToMcPcMappingForCompiledMethod: aCompiledMethod cogMethod: cogMethod
+ 	<doNotGenerate>
+ 	"self disassembleMethod: cogMethod"
+ 	"self printPCMapPairsFor: cogMethod on: Transcript"
+ 	| aMethodObj currentSubMethod subMethods bsOffset |
+ 	aMethodObj := cogMethod methodObject.
+ 	subMethods := self subMethodsAsRangesFor: cogMethod.
+ 	currentSubMethod := subMethods first.
+ 	currentSubMethod endPC: (self endPCOf: aMethodObj).
+ 	bsOffset := self bytecodeSetOffsetFor: aMethodObj.
+ 	self bcpcsAndDescriptorsFor: aMethodObj bsOffset: bsOffset do:
+ 		[:bcpc :byte :desc :nExts| | subMethod |
+ 		(desc notNil and: [desc isBlockCreation]) ifTrue:
+ 			[subMethod := subMethods detect: [:sm| sm startpc = (bcpc + desc numBytes)].
+ 			 subMethod endPC: bcpc + desc numBytes + (self spanFor: desc at: bcpc exts: -1 in: aMethodObj) - 1]].
+ 	subMethods allButFirst do:
+ 		[:blockSubMethod| | cogBlockMethod |
+ 		cogBlockMethod := self
+ 								findMethodForStartBcpc: blockSubMethod startpc
+ 								inHomeMethod: cogMethod.
+ 		self assert: cogBlockMethod address = (blockSubMethod first - (self sizeof: CogBlockMethod))].
+ 	self bcpcsAndDescriptorsFor: aMethodObj bsOffset: bsOffset do:
+ 		[:bcpc :byte :desc :nExts| | absMcpc mappedBcpc |
+ 		currentSubMethod := self innermostSubMethodFor: bcpc in: subMethods startingAt: 1.
+ 		(currentSubMethod cogMethod stackCheckOffset > 0
+ 		 and: [desc isNil or: [desc isMapped]]) ifTrue:
+ 			["The first bytecode and backward branch bytecodes are mapped to their pc.
+ 			  Other bytecodes map to their following pc."
+ 			 absMcpc := (desc notNil
+ 						   and: [desc isBranch
+ 						   and: [self isBackwardBranch: desc at: bcpc exts: nExts in: aMethodObj]])
+ 							ifTrue: "Backward branches have a special mapper"
+ 								[mappedBcpc := bcpc.
+ 								 self
+ 									mcPCForBackwardBranch: mappedBcpc
+ 									startBcpc: currentSubMethod startpc
+ 									in: currentSubMethod cogMethod]
+ 							ifFalse: "All others use the generic mapper"
+ 								[mappedBcpc := desc ifNil: [bcpc] ifNotNil: [bcpc + desc numBytes].
+ 								 self
+ 									mcPCFor: mappedBcpc
+ 									startBcpc: currentSubMethod startpc
+ 									in: currentSubMethod cogMethod].
+ 			 self assert: absMcpc > (currentSubMethod cogMethod asInteger + self noCheckEntryOffset).
+ 			 self assert: (self
+ 							bytecodePCFor: absMcpc
+ 							startBcpc: currentSubMethod startpc
+ 							in: currentSubMethod cogMethod) = mappedBcpc]]!

Item was removed:
- ----- Method: Cogit>>testBcToMcPcMappingForMethod: (in category 'tests-method map') -----
- testBcToMcPcMappingForMethod: cogMethod
- 	<doNotGenerate>
- 	"self disassembleMethod: cogMethod"
- 	"self printPCMapPairsFor: cogMethod on: Transcript"
- 	| aMethodObj currentSubMethod subMethods |
- 	aMethodObj := cogMethod methodObject.
- 	subMethods := self subMethodsAsRangesFor: cogMethod.
- 	currentSubMethod := subMethods first.
- 	currentSubMethod endPC: (self endPCOf: aMethodObj).
- 	self bcpcsAndDescriptorsFor: aMethodObj do:
- 		[:bcpc :byte :desc| | subMethod |
- 		(desc notNil and: [desc isBlockCreation]) ifTrue:
- 			[subMethod := subMethods detect: [:sm| sm startpc = (bcpc + desc numBytes)].
- 			 subMethod endPC: bcpc + desc numBytes + (self spanFor: desc at: bcpc exts: -1 in: aMethodObj) - 1]].
- 	subMethods allButFirst do:
- 		[:blockSubMethod| | cogBlockMethod |
- 		cogBlockMethod := self
- 								findMethodForStartBcpc: blockSubMethod startpc
- 								inHomeMethod: cogMethod.
- 		self assert: cogBlockMethod address = (blockSubMethod first - (self sizeof: CogBlockMethod))].
- 	self bcpcsAndDescriptorsFor: aMethodObj do:
- 		[:bcpc :byte :desc| | absMcpc mappedBcpc |
- 		currentSubMethod := self innermostSubMethodFor: bcpc in: subMethods startingAt: 1.
- 		(currentSubMethod cogMethod stackCheckOffset > 0
- 		 and: [desc isNil or: [desc isMapped]]) ifTrue:
- 			["The first bytecode and backward branch bytecodes are mapped to their pc.
- 			  Other bytecodes map to their following pc."
- 			mappedBcpc := (desc isNil
- 							   or: [desc isBranch
- 								   and: [(self isBackwardBranch: desc at: bcpc exts: (self nExtensionsFor: bcpc in: aMethodObj) in: aMethodObj)]])
- 								ifTrue: [bcpc]
- 								ifFalse: [bcpc + desc numBytes].
- 			 absMcpc := self
- 							mcPCFor: mappedBcpc
- 							startBcpc: currentSubMethod startpc
- 							in: currentSubMethod cogMethod.
- 			 self assert: absMcpc > (currentSubMethod cogMethod asInteger + self noCheckEntryOffset).
- 			 self assert: (self
- 							bytecodePCFor: absMcpc
- 							startBcpc: currentSubMethod startpc
- 							in: currentSubMethod cogMethod) = mappedBcpc]]!

Item was added:
+ ----- Method: Cogit>>testMcToBcPcMappingForCompiledMethod:cogMethod: (in category 'tests-method map') -----
+ testMcToBcPcMappingForCompiledMethod: aCompiledMethod cogMethod: cogMethod
+ 	<doNotGenerate>
+ 	| bcMethod subMethods prevMcpc isAltInstSet |
+ 	"self disassembleMethod: cogMethod"
+ 	"coInterpreter symbolicMethod: cogMethod methodObject"
+ 	"coInterpreter printOop: cogMethod methodObject"
+ 	"self printPCMapPairsFor: cogMethod on: Transcript"
+ 	cogMethod stackCheckOffset = 0 ifTrue: "frameless"
+ 		[^self].
+ 	bcMethod := coInterpreter isCurrentImageFacade
+ 					ifTrue: [coInterpreter objectForOop: cogMethod methodObject]
+ 					ifFalse: [VMCompiledMethodProxy new
+ 								for: cogMethod methodObject
+ 								coInterpreter: coInterpreter
+ 								objectMemory: objectMemory].
+ 	subMethods := self subMethodsAsRangesFor: cogMethod.
+ 	isAltInstSet := coInterpreter headerIndicatesAlternateBytecodeSet: cogMethod methodHeader.
+ 	self mapFor: cogMethod do:
+ 		[:annotation :mcpc| | subMethod bcpc mappedpc |
+ 		(self isPCMappedAnnotation: annotation alternateInstructionSet: isAltInstSet) ifTrue:
+ 			[subMethod := subMethods
+ 								detect: [:range| range includes: mcpc]
+ 								ifNone: ["a trailing call ceNonLocalReturnTrampoline's following
+ 										 pc is the start of a following block or the end of the map"
+ 										subMethods detect: [:range| range includes: mcpc - 1]].
+ 			mcpc > subMethod first ifTrue:
+ 				[bcpc := self
+ 							bytecodePCFor: mcpc
+ 							startBcpc: subMethod startpc
+ 							in: subMethod cogMethod.
+ 				self assert: bcpc ~= 0.
+ 				mappedpc := self mcPCFor: bcpc startBcpc: subMethod startpc in: subMethod cogMethod.
+ 				self assert: mappedpc > (subMethod cogMethod address + self noCheckEntryOffset).
+ 				"mcpc = mappedpc is obviously what we want and expect.  prevMcpc = mappedpc hacks
+ 				 around frame building accessors where the first bytecode is mapped twice, once for the
+ 				 stack check and once for the context inst var access.  The bytecode pc can only map
+ 				 back to a single mcpc, the first, so the second map entry will fail without this hack."
+ 				self assert: (mcpc = mappedpc or: [prevMcpc = mappedpc]).
+ 				(self isSendAnnotation: annotation) ifTrue:
+ 					[| mcSelector bcSelector |
+ 					mcSelector := self selectorForSendAt: mcpc annotation: annotation.
+ 					"sends map to the following pc.  need to find the selector for the previous pc"
+ 					bcSelector := self selectorForSendBefore: bcpc in: bcMethod.
+ 					self assert: mcSelector = bcSelector]].
+ 			 prevMcpc := mcpc].
+ 		 false "keep scanning"]!

Item was removed:
- ----- Method: Cogit>>testMcToBcPcMappingForMethod: (in category 'tests-method map') -----
- testMcToBcPcMappingForMethod: cogMethod
- 	<doNotGenerate>
- 	| bcMethod subMethods prevMcpc isAltInstSet |
- 	"self disassembleMethod: cogMethod"
- 	"coInterpreter symbolicMethod: cogMethod methodObject"
- 	"coInterpreter printOop: cogMethod methodObject"
- 	"self printPCMapPairsFor: cogMethod on: Transcript"
- 	cogMethod stackCheckOffset = 0 ifTrue: "frameless"
- 		[^self].
- 	bcMethod := coInterpreter isCurrentImageFacade
- 					ifTrue: [coInterpreter objectForOop: cogMethod methodObject]
- 					ifFalse: [VMCompiledMethodProxy new
- 								for: cogMethod methodObject
- 								coInterpreter: coInterpreter
- 								objectMemory: objectMemory].
- 	subMethods := self subMethodsAsRangesFor: cogMethod.
- 	isAltInstSet := coInterpreter headerIndicatesAlternateBytecodeSet: cogMethod methodHeader.
- 	self mapFor: cogMethod do:
- 		[:annotation :mcpc| | subMethod bcpc mappedpc |
- 		(self isPCMappedAnnotation: annotation alternateInstructionSet: isAltInstSet) ifTrue:
- 			[subMethod := subMethods
- 								detect: [:range| range includes: mcpc]
- 								ifNone: ["a trailing call ceNonLocalReturnTrampoline's following
- 										 pc is the start of a following block or the end of the map"
- 										subMethods detect: [:range| range includes: mcpc - 1]].
- 			mcpc > subMethod first ifTrue:
- 				[bcpc := self
- 							bytecodePCFor: mcpc
- 							startBcpc: subMethod startpc
- 							in: subMethod cogMethod.
- 				self assert: bcpc ~= 0.
- 				mappedpc := self mcPCFor: bcpc startBcpc: subMethod startpc in: subMethod cogMethod.
- 				self assert: mappedpc > (subMethod cogMethod address + self noCheckEntryOffset).
- 				"mcpc = mappedpc is obviously what we want and expect.  PrevMcpc = mappedpc hacks
- 				 around frame building accessors where the first bytecode is mapped twice, once for the
- 				 stack check and once for the context inst var access.  The bytecode pc can only map
- 				 back to a single mcpc, the first, so the second map entry will fail without this hack."
- 				self assert: (mcpc = mappedpc or: [prevMcpc = mappedpc]).
- 				"IsNSSendCall is used only for pushImplicitReceiver:.  This isn't a send bytecode.
- 				 So filter-out these annotations."
- 				((self isSendAnnotation: annotation) and: [annotation ~= IsNSSendCall]) ifTrue:
- 					[| mcSelector bcSelector |
- 					mcSelector := self selectorForSendAt: mcpc annotation: annotation.
- 					"sends map to the following pc.  need to find the selector for the previous pc"
- 					bcSelector := self selectorForSendBefore: bcpc in: bcMethod.
- 					self assert: mcSelector = bcSelector]].
- 			 prevMcpc := mcpc].
- 		 false "keep scanning"]!

Item was added:
+ ----- Method: Cogit>>testPCMappingForCompiledMethod:cogMethod: (in category 'tests-method map') -----
+ testPCMappingForCompiledMethod: aCompiledMethod cogMethod: cm
+ 	<doNotGenerate>
+ 	methodObj := nil.
+ 	self
+ 		testMcToBcPcMappingForCompiledMethod: aCompiledMethod cogMethod: cm;
+ 		testBcToMcPcMappingForCompiledMethod: aCompiledMethod cogMethod: cm!

Item was removed:
- ----- Method: Cogit>>testPCMappingForMethod: (in category 'tests-method map') -----
- testPCMappingForMethod: cm
- 	<doNotGenerate>
- 	methodObj := nil.
- 	self
- 		testMcToBcPcMappingForMethod: cm;
- 		testBcToMcPcMappingForMethod: cm!

Item was changed:
  CogClass subclass: #CurrentImageCoInterpreterFacade
  	instanceVariableNames: 'memory cogit coInterpreter objectMemory objectMap headerToMethodMap cachedObject cachedOop variables'
  	classVariableNames: ''
  	poolDictionaries: 'VMBasicConstants VMObjectIndices'
  	category: 'VMMaker-Support'!
+ 
+ !CurrentImageCoInterpreterFacade commentStamp: 'eem 8/6/2014 14:59' prior: 0!
+ A CurrentImageCoInterpreterFacade is a stand-in for an object memory (ObjectMemory, SpurMemoryManager, etc) that allows the Cogits to access image objects as if they were in the simulator VM's heap.  hence it allows the Cogits to generate code for methdos in the current image, for testing, etc.
+ 
+ Instance Variables
+ 	cachedObject:			<Object>
+ 	cachedOop:			<Integer>
+ 	coInterpreter:			<CoInterpreter>
+ 	cogit:					<Cogit>
+ 	headerToMethodMap:	<Dictionary>
+ 	memory:				<ByteArray>
+ 	objectMap:				<IdentityDictionary>
+ 	objectMemory:			<NewObjectMemory|SpurMemoryManager>
+ 	variables:				<Dictionary>
+ 
+ cachedObject
+ 	- the object matching cachedOop, to speed-up oop to obejct mapping
+ 
+ cachedOop
+ 	- the last used oop
+ 
+ coInterpreter
+ 	- the CoInterpreter simulator used by the cogit.
+ 
+ cogit
+ 	- the code egnerator in use
+ 
+ headerToMethodMap
+ 	- a map from header to CompiledMethod
+ 
+ memory
+ 	- a rump memory for holding various interpreter variables (e.g. stackLimit) that are accessed as memory locations by generated code
+ 
+ objectMap
+ 	- map from objects to their oops
+ 
+ objectMemory
+ 	- the object memory used to encode various values, answer queries, etc
+ 
+ variables
+ 	- a map from the names of variables to their addresses in memory
+ !

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>encoderClassForHeader: (in category 'accessing') -----
+ encoderClassForHeader: headerInteger
+ 	^coInterpreter encoderClassForHeader: headerInteger!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>fetchPointer:ofObject: (in category 'accessing') -----
  fetchPointer: index ofObject: anOop
  	| obj |
  	obj := (objectMap keyAtValue: anOop).
+ 	^self oopForObject: (obj isCompiledMethod
+ 							ifTrue: [obj objectAt: index + 1]
+ 							ifFalse: [obj instVarAt: index + 1])!
- 	^obj isCompiledMethod
- 		ifTrue: [obj objectAt: index + 1]
- 		ifFalse: [obj instVarAt: index + 1]!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>splObj: (in category 'accessing') -----
  splObj: splObjIndex
  	^splObjIndex caseOf: {
+ 		[ClassArray]					-> [self oopForObject: Array].
+ 		[ClassCharacter]				-> [self oopForObject: Character].
+ 		[ClassLargeNegativeInteger]	-> [self oopForObject: LargeNegativeInteger].
+ 		[ClassLargePositiveInteger]	-> [self oopForObject: LargePositiveInteger].
+ 		[ClassSmallInteger]				-> [self oopForObject: SmallInteger].
+ 		[CompactClasses]				-> [self oopForObject: Smalltalk compactClassesArray]
- 		[ClassArray]		-> [self oopForObject: Array].
- 		[CompactClasses]	-> [self oopForObject: Smalltalk compactClassesArray]
  		}!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSqueakV3ObjectRepresentation>>compactClassIndexOfClass: (in category 'accessing') -----
+ compactClassIndexOfClass: classOop
+ 	"Ugh, can't reply on the host.  Spur doesn't have compact classes"
+ 	| aClass |
+ 	aClass := self objectForOop: classOop.
+ 	^false
+ 		ifTrue: [aClass indexIfCompact]
+ 		ifFalse:
+ 			[aClass caseOf: {
+ 				[CompiledMethod]		->	[1].
+ 				[Array]					->	[3].
+ 				[LargeNegativeInteger]	->	[4].
+ 				[LargePositiveInteger]	->	[5].
+ 				[Float]					->	[6].
+ 				[Association]			->	[8].
+ 				[Point]					->	[9].
+ 				[Rectangle]				->	[10].
+ 				[ByteString]			->	[11].
+ 				[MethodContext]		->	[14].
+ 				[Bitmap]				->	[16]
+ 				}
+ 				otherwise: [0]]!

Item was changed:
  InstructionPrinter subclass: #DetailedInstructionPrinter
+ 	instanceVariableNames: 'stackHeightComputer encoderClass'
- 	instanceVariableNames: 'stackHeightComputer'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-Support'!

Item was added:
+ ----- Method: DetailedInstructionPrinter>>encoderClass (in category 'accessing') -----
+ encoderClass
+ 
+ 	^encoderClass!

Item was added:
+ ----- Method: DetailedInstructionPrinter>>encoderClass: (in category 'accessing') -----
+ encoderClass: anObject
+ 
+ 	encoderClass := anObject!

Item was added:
+ ----- Method: DetailedInstructionPrinter>>interpretNextInstructionFor: (in category 'decoding') -----
+ interpretNextInstructionFor: client
+ 	^encoderClass
+ 		ifNil: [super interpretNextInstructionFor: client]
+ 		ifNotNil: [encoderClass interpretNextInstructionFor: client in: self]!

Item was added:
+ ----- Method: DetailedInstructionPrinter>>printInstructionsOn: (in category 'printing') -----
+ printInstructionsOn: aStream
+ 	"Append to the stream, aStream, a description of each bytecode in the
+ 	 instruction stream."
+ 	
+ 	| end |
+ 	encoderClass ifNil:
+ 		[^super printInstructionsOn: aStream].
+ 	stackHeightComputer encoderClass: encoderClass.
+ 	stream := aStream.
+ 	scanner := InstructionStream on: method.
+ 	end := method endPC.
+ 	oldPC := scanner pc.
+ 	innerIndents := Array new: end withAll: 0.
+ 	[scanner pc <= end] whileTrue:
+ 		[encoderClass interpretNextInstructionFor: self in: scanner]!

Item was removed:
- Interpreter subclass: #InterpreterForLongFormV3
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-Interpreter'!
- 
- !InterpreterForLongFormV3 commentStamp: '<historical>' prior: 0!
- I interpret only the long-form bytecodes, making room for lots of additional bytecodes.
- 
- 
- 
- Misc notes:
-  I do not need to reimplement booleanCheat: to only check for long jumps since it only gets called by the inlined arithmetic primitives which I don't implement.!

Item was removed:
- ----- Method: InterpreterForLongFormV3 class>>initializeBytecodeTable (in category 'initialization') -----
- initializeBytecodeTable
- 	"Interpreter initializeBytecodeTable"
- 	"Note: This table will be used to generate a C switch statement."
- 
- 	BytecodeTable := Array new: 256.
- 	self table: BytecodeTable from:
- 	#(
- 		(  0  111 unknownBytecode)
- 
- 		(112 pushReceiverBytecode)
- 		(113 pushConstantTrueBytecode)
- 		(114 pushConstantFalseBytecode)
- 		(115 pushConstantNilBytecode)
- 		(116 pushConstantMinusOneBytecode)
- 		(117 pushConstantZeroBytecode)
- 		(118 pushConstantOneBytecode)
- 		(119 pushConstantTwoBytecode)
- 		(120 returnReceiver)
- 		(121 returnTrue)
- 		(122 returnFalse)
- 		(123 returnNil)
- 		(124 returnTopFromMethod)
- 		(125 returnTopFromBlock)
- 
- 		(126 127 unknownBytecode)
- 
- 		(128 extendedPushBytecode)
- 		(129 extendedStoreBytecode)
- 		(130 extendedStoreAndPopBytecode)
- 		(131 singleExtendedSendBytecode)
- 		(132 doubleExtendedDoAnythingBytecode)
- 		(133 singleExtendedSuperBytecode)
- 		(134 secondExtendedSendBytecode)
- 		(135 popStackBytecode)
- 		(136 duplicateTopBytecode)
- 
- 		(137 pushActiveContextBytecode)
- 		(138 pushNewArrayBytecode)
- 		(139 unknownBytecode)
- 		(140 pushRemoteTempLongBytecode)
- 		(141 storeRemoteTempLongBytecode)
- 		(142 storeAndPopRemoteTempLongBytecode)
- 		(143 pushClosureCopyCopiedValuesBytecode)
- 
- 		(144 159 unknownBytecode)
- 
- 		(160 167 longUnconditionalJump)
- 		(168 171 longJumpIfTrue)
- 		(172 175 longJumpIfFalse)
- 
- 		"176-255 were send bytecodes"
- 		(176 255 unknownBytecode)
- 	).!

Item was removed:
- ----- Method: InterpreterForLongFormV3 class>>sourceFileName (in category 'accessing') -----
- sourceFileName
- 	"Answer the filename for the core interpreter"
- 
- 	^'interp-lfv3.c'!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genExtTrapIfNotInstanceOfBehaviorsBytecode (in category 'bytecode generators') -----
  genExtTrapIfNotInstanceOfBehaviorsBytecode
  	"SistaV1: *	236		11101100	iiiiiiii		Trap If Not Instance Of Behavior/Array Of Behavior #iiiiiiii (+ Extend A * 256, where Extend A >= 0)"
+ 	| reg litIndex literal branches label numBranches |
- 	| litIndex literal branches label numBranches |
  	<var: #branches type: #'AbstractInstruction **'>
+ 	reg := self ssStorePop: true toPreferredReg: ReceiverResultReg.
+ 	reg ~= ReceiverResultReg ifTrue:
+ 		[self MoveR: reg R: ReceiverResultReg].
+ 	optStatus isReceiverResultRegLive: false.
- 	self ssStorePop: false toPreferredReg: ReceiverResultReg.
  	litIndex := extA * 256 + byte1.
  	extA := 0.
  	literal := self getLiteral: litIndex.
+ 	"Allow an extra branch for Spur, which may have two tag patterns for SmallInteger"
  	numBranches := (objectMemory isArrayNonImm: literal)
+ 						ifTrue: [(objectMemory numSlotsOf: literal) + 1]
+ 						ifFalse: [2].
- 						ifTrue: [objectMemory numSlotsOf: literal]
- 						ifFalse: [1].
  	branches := self alloca: numBranches type: (self cCoerceSimple: CogAbstractInstruction to: #'AbstractInstruction *').
+ 	numBranches := (objectMemory isArrayNonImm: literal)
+ 						ifTrue: [objectRepresentation branchIfInstanceOfBehaviors: literal branches: branches]
+ 						ifFalse: [objectRepresentation branchIfInstanceOfBehavior: literal branches: branches].
+ 	"Only flush the stack if the class trap traps.  Use ssFlushNoUpdateTo: so we continue compiling as if
+ 	 the stack had not been flushed.  Control does not return after the ceClassTrapTrampoline call."
- 	(objectMemory isArrayNonImm: literal)
- 		ifTrue: [objectRepresentation branchIfInstanceOfBehaviors: literal branches: branches]
- 		ifFalse: [objectRepresentation branchIfInstanceOfBehavior: literal branches: branches].
- 	"Only flush teh stack if the class trap traps.  Use ssFlushNoUpdateTo: so we continue compiling as if
- 	 the stack had not been fliushed.  Control does not return after the ceClassTrapTrampoline call."
  	self ssFlushNoUpdateTo: simStackPtr.
  	self CallRT: ceClassTrapTrampoline.
  	label := self Label.
  	0 to: numBranches - 1 do:
  		[:i|
  		(branches at: i) jmpTarget: label].
  	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>generateSistaRuntime (in category 'initialization') -----
  generateSistaRuntime
  	"Class trap sends class trap message to context with top of stack, so we on't need any arguments..."
+ 	ceClassTrapTrampoline := self genTrampolineFor: #ceClassTrap:
+ 									called: 'ceClassTrapTrampoline'
+ 									arg: ReceiverResultReg!
- 	ceClassTrapTrampoline := self genTrampolineFor: #ceClassTrap
- 									called: 'ceClassTrapTrampoline'!

Item was changed:
  ----- Method: SpurMemoryManager>>allInstancesOf: (in category 'primitive support') -----
  allInstancesOf: aClass
  	"Attempt to answer an array of all objects, excluding those that may
  	 be garbage collected as a side effect of allocating the result array.
  	 If no memory is available answer the number of instances as a SmallInteger.
  	 Since objects are at least 16 bytes big, and the largest SmallInteger covers
  	 1/4 of the address space, the count can never overflow."
  	| classIndex freeChunk ptr start limit count bytes |
  	classIndex := self rawHashBitsOf: aClass.
  	(classIndex = 0
  	 or: [aClass ~~ (self classOrNilAtIndex: classIndex)]) ifTrue:
  		[freeChunk := self allocateSlots: 0 format: self arrayFormat classIndex: ClassArrayCompactIndex.
  		 ^freeChunk].
  	MarkObjectsForEnumerationPrimitives ifTrue:
  		[self markObjects]. "may not want to revive objects unnecessarily; but marking is sloooow."
  	freeChunk := self allocateLargestFreeChunk.
  	ptr := start := freeChunk + self baseHeaderSize.
  	limit := self addressAfter: freeChunk.
  	count := 0.
  	self allHeapEntitiesDo:
  		[:obj| "continue enumerating even if no room so as to unmark all objects."
  		 (MarkObjectsForEnumerationPrimitives
  				ifTrue: [self isMarked: obj]
  				ifFalse: [true]) ifTrue:
  			[(self isNormalObject: obj)
  				ifTrue:
  					[MarkObjectsForEnumerationPrimitives ifTrue:
  						[self setIsMarkedOf: obj to: false].
  					 (self classIndexOf: obj) = classIndex ifTrue:
  					 	[count := count + 1.
  						 ptr < limit ifTrue:
  							[self longAt: ptr put: obj.
  							 ptr := ptr + self bytesPerSlot]]]
  				ifFalse:
  					[MarkObjectsForEnumerationPrimitives ifTrue:
  						[(self isSegmentBridge: obj) ifFalse:
  							[self setIsMarkedOf: obj to: false]]]]].
- 	self assert: self allObjectsUnmarked.
  	self assert: (self isEmptyObjStack: markStack).
  	MarkObjectsForEnumerationPrimitives
+ 		ifTrue:
+ 			[self assert: self allObjectsUnmarked.
+ 			 self emptyObjStack: weaklingStack]
+ 		ifFalse:
+ 			[self assert: (self isEmptyObjStack: weaklingStack)].
- 		ifTrue: [self emptyObjStack: weaklingStack]
- 		ifFalse: [self assert: (self isEmptyObjStack: weaklingStack)].
  	(count > (ptr - start / self bytesPerSlot) "not enough room"
  	 or: [limit ~= ptr and: [limit - ptr <= self allocationUnit]]) ifTrue: "can't split a single word"
  		[self freeObject: freeChunk.
  		 ^self integerObjectOf: count].
  	count < self numSlotsMask ifTrue:
  		[| smallObj |
  		 smallObj := self allocateSlots: count format: self arrayFormat classIndex: ClassArrayCompactIndex.
  		 0 to: count - 1 do:
  			[:i|
  			self storePointerUnchecked: i ofObject: smallObj withValue: (self fetchPointer: i ofFreeChunk: freeChunk)].
  		 self freeChunkWithBytes: (self bytesInObject: freeChunk) at: (self startOfObject: freeChunk).
  		 self beRootIfOld: smallObj.
  		 self checkFreeSpace.
  		 ^smallObj].
  	bytes := self largeObjectBytesForSlots: count.
  	start := self startOfObject: freeChunk.
  	self freeChunkWithBytes: limit - start - bytes at: start + bytes.
  	totalFreeOldSpace := totalFreeOldSpace - bytes.
  	self setOverflowNumSlotsOf: freeChunk to: count.
  	self set: freeChunk classIndexTo: ClassArrayCompactIndex formatTo: self arrayFormat.
  	self possibleRootStoreInto: freeChunk.
  	self checkFreeSpace.
  	self runLeakCheckerForFullGC: false.
  	^freeChunk
  	
  	!

Item was changed:
  ----- Method: SpurMemoryManager>>allObjects (in category 'primitive support') -----
  allObjects
  	"Attempt to answer an array of all objects, excluding those that may
  	 be garbage collected as a side effect of allocating the result array.
  	 If no memory is available answer the number of objects as a SmallInteger.
  	 Since objects are at least 16 bytes big, and the largest SmallInteger covers
  	 1/4 of the address space, the count can never overflow."
  	| freeChunk ptr start limit count bytes |
  	MarkObjectsForEnumerationPrimitives ifTrue:
  		[self markObjects]. "may not want to revive objects unnecessarily; but marking is sloooow."
  	freeChunk := self allocateLargestFreeChunk.
  	ptr := start := freeChunk + self baseHeaderSize.
  	limit := self addressAfter: freeChunk.
  	count := 0.
  	self allHeapEntitiesDo:
  		[:obj| "continue enumerating even if no room so as to unmark all objects."
  		 (MarkObjectsForEnumerationPrimitives
  				ifTrue: [self isMarked: obj]
  				ifFalse: [true]) ifTrue:
  			[(self isNormalObject: obj)
  				ifTrue:
  					[MarkObjectsForEnumerationPrimitives ifTrue:
  						[self setIsMarkedOf: obj to: false].
  					 count := count + 1.
  					 ptr < limit ifTrue:
  						[self longAt: ptr put: obj.
  						 ptr := ptr + self bytesPerSlot]]
  				ifFalse:
  					[MarkObjectsForEnumerationPrimitives ifTrue:
  						[(self isSegmentBridge: obj) ifFalse:
  							[self setIsMarkedOf: obj to: false]]]]].
- 	self assert: self allObjectsUnmarked.
  	self assert: (self isEmptyObjStack: markStack).
  	MarkObjectsForEnumerationPrimitives
+ 		ifTrue:
+ 			[self assert: self allObjectsUnmarked.
+ 			 self emptyObjStack: weaklingStack]
+ 		ifFalse:
+ 			[self assert: (self isEmptyObjStack: weaklingStack)].
- 		ifTrue: [self emptyObjStack: weaklingStack]
- 		ifFalse: [self assert: (self isEmptyObjStack: weaklingStack)].
  	self assert: count >= self numSlotsMask.
  	(count > (ptr - start / self bytesPerSlot) "not enough room"
  	 or: [limit ~= ptr and: [limit - ptr <= self allocationUnit]]) ifTrue: "can't split a single word"
  		[self freeChunkWithBytes: (self bytesInObject: freeChunk) at: (self startOfObject: freeChunk).
  		 self checkFreeSpace.
  		 ^self integerObjectOf: count].
  	bytes := self largeObjectBytesForSlots: count.
  	start := self startOfObject: freeChunk.
  	self freeChunkWithBytes: limit - start - bytes at: start + bytes.
  	totalFreeOldSpace := totalFreeOldSpace - bytes.
  	self setOverflowNumSlotsOf: freeChunk to: count.
  	self set: freeChunk classIndexTo: ClassArrayCompactIndex formatTo: self arrayFormat.
  	self possibleRootStoreInto: freeChunk.
  	self checkFreeSpace.
  	self runLeakCheckerForFullGC: false.
  	^freeChunk
  	
  	!

Item was changed:
  ----- Method: StackInterpreter>>extTrapIfNotInstanceOfBehaviorsBytecode (in category 'sista bytecodes') -----
  extTrapIfNotInstanceOfBehaviorsBytecode
+ 	"SistaV1: *	236	11101100	iiiiiiii	Trap If Not Instance Of Behavior/Array Of Behavior #iiiiiiii (+ Extend A * 256, where Extend A >= 0)"
- 	"SistaV1: *	236		11101100	iiiiiiii		Trap If Not Instance Of Behavior/Array Of Behavior #iiiiiiii (+ Extend A * 256, where Extend A >= 0)"
  	| tos tosClassTag literal |
+ 	tos := self internalStackTop.
- 	tos := self stackTop.
  	tosClassTag := objectMemory fetchClassTagOf: tos.
  	literal := self literal: extA << 8 + self fetchByte.
  	extA := 0.
  	(objectMemory isArrayNonImm: literal)
  		ifTrue:
  			[| i |
  			 i := (objectMemory numSlotsOf: literal) asInteger.
  			 [(i := i -1) < 0
  			  or: [tosClassTag = (objectMemory rawClassTagForClass: (objectMemory fetchPointer: i ofObject: literal))]] whileTrue.
  			 i < 0 ifTrue:
  				[^self respondToClassTrap]]
  		ifFalse:
  			[tosClassTag ~= (objectMemory rawClassTagForClass: literal) ifTrue:
  				[^self respondToClassTrap]].
+ 	self internalPopStack.
  	self fetchNextBytecode!

Item was changed:
  ----- Method: StackInterpreter>>respondToClassTrap (in category 'sista bytecodes') -----
  respondToClassTrap
  	| ourContext tos |
  	<sharedCodeInCase: #extTrapIfNotInstanceOfBehaviorsBytecode>
  	messageSelector := objectMemory splObj: SelectorClassTrap.
+ 	tos := self internalPopStack.
- 	tos := self internalStackTop.
  	ourContext := self ensureFrameIsMarried: localFP SP: localSP.
  	messageSelector = objectMemory nilObject ifTrue:
  		[self error: 'class trap'].
  	self internalPush: ourContext.
  	self internalPush: tos.
  	argumentCount := 1.
  	self normalSend!

Item was changed:
  VMObjectProxy subclass: #VMCompiledMethodProxy
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-Support'!
+ 
+ !VMCompiledMethodProxy commentStamp: 'eem 8/6/2014 14:48' prior: 0!
+ A VMCompiledMethodProxy is a wrapper for the oop of a CompiledMethod object in the simulator VM's heap that provides accessd to the oop as if it were a CompiledMethod object.!

Item was removed:
- ----- Method: VMCompiledMethodProxy>>usesAlternateBytecodeSet (in category 'accessing') -----
- usesAlternateBytecodeSet
- 
- 	^coInterpreter headerIndicatesAlternateBytecodeSet: self header!

Item was changed:
  Object subclass: #VMObjectProxy
  	instanceVariableNames: 'coInterpreter oop objectMemory'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-Support'!
+ 
+ !VMObjectProxy commentStamp: 'eem 8/6/2014 14:46' prior: 0!
+ A VMObjectProxy is a wraper for an oop in the VM, that provides limited access to that oop as an object.
+ !



More information about the Vm-dev mailing list