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

commits at source.squeak.org commits at source.squeak.org
Sat Mar 2 01:13:10 UTC 2013


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

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

Name: VMMaker.oscog-eem.270
Author: eem
Time: 1 March 2013, 5:10:47.701 pm
UUID: 014f0153-bb02-49b7-b544-d8f3ac2deef6
Ancestors: VMMaker.oscog-eem.269

Fix the become issue where methods that are identical are failing
the code test because their penultimate literals are different objects.
Add a flag "cmUsesPenultimateLit" to jitted methods, stealing bits
from stackCheckOffset (which was way larger than needed).
Shrink stackCheckOffset to 12 bits (still an order of magnitude larger
than needed) and add an error check on assigning it.
Also add a check for max method size (2^16-1 bytes) and refuse to
jit a method that generates too much code.
When comparing code, use the cmUsesPenultimateLit flag to decide
if comparison includes penultimate lit or not.

This is mildly insane, but the VM really doesn't know about the
penultimate literal and it shouldn't depend on knowing it can be
ignored.  Note that the CoInterpreter knows about the last literal;
it uses this in supersends.  With this hack, Pharo's condenseSources
works.

Fix simulation of primitiveMillisecondClockMask.

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

Item was changed:
  VMStructType subclass: #CogBlockMethod
+ 	instanceVariableNames: 'objectHeader homeOffset startpc padToWord cmNumArgs cmType cmRefersToYoung cpicHasMNUCase cmUsageCount cmUsesPenultimateLit cmUnusedFlags stackCheckOffset'
- 	instanceVariableNames: 'objectHeader homeOffset startpc padToWord cmNumArgs cmType cmRefersToYoung cpicHasMNUCase cmUsageCount stackCheckOffset'
  	classVariableNames: ''
  	poolDictionaries: 'CogMethodConstants VMBasicConstants'
  	category: 'VMMaker-JIT'!
  
  !CogBlockMethod commentStamp: 'eem 1/9/2011 08:41' prior: 0!
  I am the rump method header for a block method embedded in a full CogMethod.  I am the superclass of CogMethod, which is a Cog method header proper.  Instances of both classes have the same second word.  The homeOffset abd startpc fields are overlaid on the objectHeader in a CogMethod.  In C I look like
  
  	typedef struct {
  		unsigned short	homeOffset;
  		unsigned short	startpc;
  
  		unsigned		cmNumArgs : 8;
  		unsigned		cmType : 3;
  		unsigned		cmRefersToYoung : 1;
  		unsigned		cmIsUnlinked : 1;
  		unsigned		cmUsageCount : 3;
  		unsigned		stackCheckOffset : 16;
  	} CogBlockMethod;
  
  My instances are not actually used.  The methods exist only as input to Slang.  The simulator uses my surrogates (CogBlockMethodSurrogate32 and CogBlockMethodSurrogate64.!

Item was changed:
  ----- Method: CogBlockMethod class>>initialize (in category 'class initialization') -----
  initialize
  	"CogBlockMethod initialize"
  	"CogBlockMethod initialize. CogMethod initialize"
  	(Smalltalk classNamed: #CogBlockMethodSurrogate32) ifNotNil:
  		[:cbms32|
  		self checkGenerateSurrogate: cbms32 bytesPerWord: 4].
  	(Smalltalk classNamed: #CogBlockMethodSurrogate64) ifNotNil:
  		[:cbms64|
  		self checkGenerateSurrogate: cbms64 bytesPerWord: 8].
  
+ 	"see instVarNamesAndTypesForTranslationDo:"
+ 	CMMaxUsageCount		:= (2 raisedTo: 3) - 1.
+ 	MaxStackCheckOffset	:= (2 raisedTo: 12) - 1.
+ 	MaxMethodSize		:= (2 raisedTo: 16) - 1
- 	CMMaxUsageCount := 7 "see instVarNamesAndTypesForTranslationDo:"
  
  	"{ CogBlockMethodSurrogate32 selectors reject: [:s| CogBlockMethod includesSelector: s].
  	    CogBlockMethodSurrogate64 selectors reject: [:s| CogBlockMethod includesSelector: s].
  	    CogMethodSurrogate32 selectors reject: [:s| CogMethod includesSelector: s].
  	    CogMethodSurrogate64 selectors reject: [:s| CogMethod includesSelector: s]. }"!

Item was changed:
  ----- Method: CogBlockMethod class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a CogMethod or CogBlockMethod struct."
  
  	self allInstVarNames do:
  		[:ivn|
  		"Notionally objectHeader is in a union with homeOffset and startpc but
  		 we don't have any convenient support for unions.  So hack, hack, hack, hack."
  		((self == CogBlockMethod
  			ifTrue: [#('objectHeader')]
  			ifFalse: [#('homeOffset' 'startpc' 'padToWord')]) includes: ivn) ifFalse:
  				[aBinaryBlock
  					value: ivn
  					value: (ivn caseOf: {
+ 								['cmNumArgs']				-> [#(unsigned ' : 8')]. "SqueakV3 needs only 5 bits"
+ 								['cmType']					-> [#(unsigned ' : 3')].
+ 								['cmRefersToYoung']		-> [#(unsigned #Boolean ' : 1')].
+ 								['cpicHasMNUCase']		-> [#(unsigned #Boolean ' : 1')].
+ 								['cmUsageCount']			-> [#(unsigned ' : 3')]. "see CMMaxUsageCount in initialize"
+ 								['cmUsesPenultimateLit']	-> [#(unsigned #Boolean ' : 1')].
+ 								['cmUnusedFlags']			-> [#(unsigned ' : 3')].
+ 								['stackCheckOffset']		-> [#(unsigned ' : 12')]. "See MaxStackCheckOffset in initialize. a.k.a. cPICNumCases"
+ 								['blockSize']				-> [#'unsigned short']. "See MaxMethodSize in initialize"
+ 								['blockEntryOffset']			-> [#'unsigned short'].
+ 								['homeOffset']				-> [#'unsigned short'].
+ 								['startpc']					-> [#'unsigned short'].
+ 								['padToWord']				-> [#(#BytesPerWord 8 'unsigned int')]}
- 								['cmNumArgs']			-> [#(unsigned ' : 8')]. "SqueakV3 needs only 5 bits"
- 								['cmType']				-> [#(unsigned ' : 3')].
- 								['cmRefersToYoung']	-> [#(unsigned #Boolean ' : 1')].
- 								['cpicHasMNUCase']	-> [#(unsigned #Boolean ' : 1')].
- 								['cmUsageCount']		-> [#(unsigned ' : 3')]. "see CMMaxUsageCount in initialize"
- 								['stackCheckOffset']	-> [#(unsigned ' : 16')]. "a.k.a. cPICNumCases"
- 								['blockSize']			-> [#'unsigned short'].
- 								['blockEntryOffset']		-> [#'unsigned short'].
- 								['homeOffset']			-> [#'unsigned short'].
- 								['startpc']				-> [#'unsigned short'].
- 								['padToWord']			-> [#(#BytesPerWord 8 'unsigned int')]}
  							otherwise:
  								[#sqInt])]]!

Item was added:
+ ----- Method: CogBlockMethod>>cmUsesPenultimateLit (in category 'accessing') -----
+ cmUsesPenultimateLit
+ 	"Answer the value of cmUsesPenultimateLit"
+ 
+ 	^cmUsesPenultimateLit!

Item was added:
+ ----- Method: CogBlockMethod>>cmUsesPenultimateLit: (in category 'accessing') -----
+ cmUsesPenultimateLit: anObject
+ 	"Set the value of cmUsesPenultimateLit"
+ 
+ 	^cmUsesPenultimateLit := anObject!

Item was added:
+ ----- Method: CogBlockMethodSurrogate32>>cmUsesPenultimateLit (in category 'accessing') -----
+ cmUsesPenultimateLit
+ 	^((memory unsignedByteAt: address + 7) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- Method: CogBlockMethodSurrogate32>>cmUsesPenultimateLit: (in category 'accessing') -----
+ cmUsesPenultimateLit: aValue
+ 	memory
+ 		unsignedByteAt: address + 7
+ 		put: (((memory unsignedByteAt: address + 7) bitAnd: 16rFE) + (aValue ifTrue: [1] ifFalse: [0])).
+ 	^aValue!

Item was changed:
  ----- Method: CogBlockMethodSurrogate32>>stackCheckOffset (in category 'accessing') -----
  stackCheckOffset
+ 	^((memory unsignedShortAt: address + 7) bitShift: -4) bitAnd: 16rFFF!
- 	^memory unsignedShortAt: address + 7!

Item was changed:
  ----- Method: CogBlockMethodSurrogate32>>stackCheckOffset: (in category 'accessing') -----
  stackCheckOffset: aValue
+ 	self assert: (aValue between: 0 and: 16rFFF).
+ 	memory
- 	^memory
  		unsignedShortAt: address + 7
+ 		put: ((memory unsignedShortAt: address + 7) bitAnd: 16rF) + (aValue bitShift: 4).
+ 	^aValue!
- 		put: aValue!

Item was added:
+ ----- Method: CogBlockMethodSurrogate64>>cmUsesPenultimateLit (in category 'accessing') -----
+ cmUsesPenultimateLit
+ 	^((memory unsignedByteAt: address + 11) bitAnd: 16r1) ~= 0!

Item was added:
+ ----- Method: CogBlockMethodSurrogate64>>cmUsesPenultimateLit: (in category 'accessing') -----
+ cmUsesPenultimateLit: aValue
+ 	memory
+ 		unsignedByteAt: address + 11
+ 		put: (((memory unsignedByteAt: address + 11) bitAnd: 16rFE) + (aValue ifTrue: [1] ifFalse: [0])).
+ 	^aValue!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>stackCheckOffset (in category 'accessing') -----
  stackCheckOffset
+ 	^((memory unsignedShortAt: address + 11) bitShift: -4) bitAnd: 16rFFF!
- 	^memory unsignedShortAt: address + 11!

Item was changed:
  ----- Method: CogBlockMethodSurrogate64>>stackCheckOffset: (in category 'accessing') -----
  stackCheckOffset: aValue
+ 	self assert: (aValue between: 0 and: 16rFFF).
+ 	memory
- 	^memory
  		unsignedShortAt: address + 11
+ 		put: ((memory unsignedShortAt: address + 11) bitAnd: 16rF) + (aValue bitShift: 4).
+ 	^aValue!
- 		put: aValue!

Item was changed:
  SharedPool subclass: #CogMethodConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'CMBlock CMClosedPIC CMFree CMMaxUsageCount CMMethod CMOpenPIC MaxLiteralCountForCompile MaxMethodSize MaxNumArgs MaxStackCheckOffset PrimCallCollectsProfileSamples PrimCallMayCallBack PrimCallNeedsNewMethod PrimCallNeedsPrimitiveFunction'
- 	classVariableNames: 'CMBlock CMClosedPIC CMFree CMMaxUsageCount CMMethod CMOpenPIC MaxLiteralCountForCompile MaxNumArgs PrimCallCollectsProfileSamples PrimCallMayCallBack PrimCallNeedsNewMethod PrimCallNeedsPrimitiveFunction'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!

Item was changed:
  CogClass subclass: #Cogit
+ 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMissCall missOffset entryPointMask checkedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxMethodBefore maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceStoreCheckTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceClosureCopyTrampoline ceCreateNewArrayTrampoline ceEnterCogCodePopReceiverReg ceEnterCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceActiveContextTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline cePositive32BitIntegerTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB'
+ 	classVariableNames: 'AltBlockCreationBytecodeSize AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration EncounteredUnknownBytecode FirstAnnotation HasBytecodePC InsufficientCodeSpace IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxNegativeErrorCode MaxUnitDisplacement MaxUnreportableError MaxX2NDisplacement MethodTooBig NotFullyInitialized NumObjRefsInRuntime NumSendTrampolines NumTrampolines ProcessorClass YoungSelectorInPIC'
- 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMissCall missOffset entryPointMask checkedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxMethodBefore ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceStoreCheckTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceClosureCopyTrampoline ceCreateNewArrayTrampoline ceEnterCogCodePopReceiverReg ceEnterCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceActiveContextTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline cePositive32BitIntegerTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB'
- 	classVariableNames: 'AltBlockCreationBytecodeSize AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration EncounteredUnknownBytecode FirstAnnotation HasBytecodePC InsufficientCodeSpace IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxNegativeErrorCode MaxUnitDisplacement MaxUnreportableError MaxX2NDisplacement NotFullyInitialized NumObjRefsInRuntime NumSendTrampolines NumTrampolines ProcessorClass YoungSelectorInPIC'
  	poolDictionaries: 'CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 2/13/2013 15:37' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	StackToRegisterMappingCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixup shas one element per byte in methodObj's bytecode
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventuakly teh total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was changed:
  ----- Method: Cogit class>>initializeErrorCodes (in category 'class initialization') -----
  initializeErrorCodes
  	self flag: 'these should be positive quantities and the check for error code should be a comparison against minCogMethodAddress/methodZoneBase'.
  	NotFullyInitialized := -1.
  	InsufficientCodeSpace := -2.
+ 	MethodTooBig := -4.
+ 	YoungSelectorInPIC := -5.
- 	YoungSelectorInPIC := -3.
  	MaxUnreportableError := YoungSelectorInPIC.
+ 	EncounteredUnknownBytecode := -6.
- 	EncounteredUnknownBytecode := -4.
  	MaxNegativeErrorCode := EncounteredUnknownBytecode!

Item was changed:
  ----- Method: Cogit>>compileCogMethod: (in category 'compile abstract instructions') -----
  compileCogMethod: selector
  	<returnTypeC: #'CogMethod *'>
  	| numBytecodes numBlocks result extra |
  	hasYoungReferent := (objectMemory isYoung: methodObj)
  						  or: [objectMemory isYoung: selector].
  	methodOrBlockNumArgs := coInterpreter argumentCountOf: methodObj.
  	inBlock := false.
  	primInvokeLabel := nil.
  	postCompileHook := nil.
+ 	maxLitIndex := -1.
  	extra := ((primitiveIndex := coInterpreter primitiveIndexOf: methodObj) > 0
  			and: [(coInterpreter isQuickPrimitiveIndex: primitiveIndex) not])
  				ifTrue: [30]
  				ifFalse: [10].
  	initialPC := coInterpreter startPCOfMethod: methodObj.
  	"initial estimate.  Actual endPC is determined in scanMethod."
  	endPC := (coInterpreter isQuickPrimitiveIndex: primitiveIndex)
  					ifTrue: [initialPC - 1]
  					ifFalse: [objectMemory byteLengthOf: methodObj].
  	numBytecodes := endPC - initialPC + 1.
  	self allocateOpcodes: (numBytecodes + extra) * 10 bytecodes: numBytecodes.
  	(numBlocks := self scanMethod) < 0 ifTrue:
  		[^coInterpreter cCoerceSimple: numBlocks to: #'CogMethod *'].
  	self allocateBlockStarts: numBlocks.
  	blockEntryLabel := nil.
  	methodLabel dependent: nil.
  	(result := self compileEntireMethod) < 0 ifTrue:
  		[^coInterpreter cCoerceSimple: result to: #'CogMethod *'].
  	^self generateCogMethod: selector!

Item was changed:
  ----- Method: Cogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
  	<returnTypeC: #'CogMethod *'>
  	<var: #method type: #'CogMethod *'>
  	<var: #originalMethod type: #'CogMethod *'>
  	| methodHeader originalMethod |
  	method cmType: CMMethod.
  	method objectHeader: objectMemory nullHeaderForMachineCodeMethod.
  	method blockSize: size.
  	method methodObject: methodObj.
  	methodHeader := coInterpreter rawHeaderOf: methodObj.
  	"If the method has already been cogged (e.g. Newspeak accessors) then
  	 leave the original method attached to its cog method, but get the right header."
  	(coInterpreter isCogMethodReference: methodHeader)
  		ifTrue:
  			[originalMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  			self assert: originalMethod blockSize = size.
  			methodHeader := originalMethod methodHeader]
  		ifFalse:
  			[coInterpreter rawHeaderOf: methodObj put: method asInteger].
  	method methodHeader: methodHeader.
  	method selector: selector.
  	method cmNumArgs: (coInterpreter argumentCountOfMethodHeader: methodHeader).
  	(method cmRefersToYoung: hasYoungReferent) ifTrue:
  		[methodZone addToYoungReferrers: method].
  	method cmUsageCount: self initialMethodUsageCount.
  	method cpicHasMNUCase: false.
+ 	method cmUsesPenultimateLit: maxLitIndex >= ((coInterpreter literalCountOfHeader: methodHeader) - 2).
  	method blockEntryOffset: (blockEntryLabel notNil
  								ifTrue: [blockEntryLabel address - method asInteger]
  								ifFalse: [0]).
+ 	"This can be an error check since a large stackCheckOffset is caused by compiling
+ 	 a machine-code primitive, and hence depends on the Cogit, not the input method."
+ 	needsFrame ifTrue:
+ 		[stackCheckLabel address - method asInteger <= MaxStackCheckOffset ifFalse:
+ 			[self error: 'too much code for stack check offset']].
  	method stackCheckOffset: (needsFrame
  								ifTrue: [stackCheckLabel address - method asInteger]
  								ifFalse: [0]).
+ 	self assert: (backEnd callTargetFromReturnAddress: method asInteger + missOffset)
+ 				= (self methodAbortTrampolineFor: method cmNumArgs).
- 	self assert: (backEnd callTargetFromReturnAddress: method asInteger + missOffset) = (self methodAbortTrampolineFor: method cmNumArgs).
  	self assert: size = (methodZone roundUpLength: size).
  	^method!

Item was changed:
  ----- Method: Cogit>>generateCogMethod: (in category 'generate machine code') -----
  generateCogMethod: selector
  	"We handle jump sizing simply.  First we make a pass that asks each
  	 instruction to compute its maximum size.  Then we make a pass that
  	 sizes jumps based on the maxmimum sizes.  Then we make a pass
  	 that fixes up jumps.  When fixing up a jump the jump is not allowed to
  	 choose a smaller offset but must stick to the size set in the second pass."
  	| codeSize headerSize mapSize totalSize startAddress result method |
  	<var: #method type: #'CogMethod *'>
  	<var: #blockStart type: #'BlockStart *'>
  	<var: #headerReference type: #'AbstractInstruction *'>
  	<returnTypeC: #'CogMethod *'>
  	headerSize := self sizeof: CogMethod.
  	methodLabel address: headerSize negated.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: methodZone freeStart.
  	codeSize := self generateInstructionsAt: methodLabel address + headerSize.
  	mapSize := self generateMapAt: 0 start: methodLabel address + cmNoCheckEntryOffset.
  	totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize.
+ 	totalSize > MaxMethodSize ifTrue:
+ 		[^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  	startAddress := methodZone allocate: totalSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: startAddress + cmNoCheckEntryOffset = noCheckEntry address.
  	result := self outputInstructionsAt: startAddress + headerSize.
  	self assert: startAddress + headerSize + codeSize = result.
  	backEnd padIfPossibleWithNopsFrom: result to: startAddress + totalSize - mapSize.
  	self generateMapAt: startAddress + totalSize - 1 start: startAddress + cmNoCheckEntryOffset.
  	self fillInBlockHeadersAt: startAddress.
  	method := self fillInMethodHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  					size: totalSize
  					selector: selector.
  	postCompileHook notNil ifTrue:
  		[self perform: postCompileHook with: method with: primInvokeLabel.
  		 postCompileHook := nil].
  	processor flushICacheFrom: startAddress to: startAddress + headerSize + codeSize.
  	^method!

Item was added:
+ ----- Method: Cogit>>getLiteral: (in category 'compile abstract instructions') -----
+ getLiteral: litIndex
+ 	maxLitIndex < litIndex ifTrue:
+ 		[maxLitIndex := litIndex].
+ 	^coInterpreter literal: litIndex ofMethod: methodObj!

Item was changed:
  ----- Method: Cogit>>mapObjectReferencesInMachineCodeForBecome (in category 'garbage collection') -----
  mapObjectReferencesInMachineCodeForBecome
  	"Update all references to objects in machine code for a become.
  	 Unlike incrementalGC or fullGC a method that does not refer to young may
  	 refer to young as a result of the become operation.  Unlike incrementalGC
  	 or fullGC the reference from a Cog method to its methodObject *must not*
  	 change since the two are two halves of the same object."
  	| cogMethod hasYoungObj hasYoungObjPtr freedPIC |
  	<var: #cogMethod type: #'CogMethod *'>
  	hasYoungObj := false.
  	hasYoungObjPtr := self cCode: [(self addressOf: hasYoungObj) asInteger]
  							inSmalltalk: [CPluggableAccessor new
  											setObject: nil;
  											atBlock: [:obj :idx| hasYoungObj]
  											atPutBlock: [:obj :idx :val| hasYoungObj := val]].
  	codeModified := freedPIC := false.
  	self mapObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[self assert: hasYoungObj not.
  		 cogMethod cmType ~= CMFree ifTrue:
  			[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
  			 cogMethod selector: (objectRepresentation remapOop: cogMethod selector)..
  			 cogMethod cmType = CMClosedPIC
  				ifTrue:
  					[((objectMemory isYoung: cogMethod selector)
  					   or: [self mapObjectReferencesInClosedPIC: cogMethod]) ifTrue:
  						[freedPIC := true.
  						 methodZone freeMethod: cogMethod]]
  				ifFalse:
  					[(objectMemory isYoung: cogMethod selector) ifTrue:
  						[hasYoungObj := true].
  					 cogMethod cmType = CMMethod ifTrue:
  						[| remappedMethod |
  						 self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  						 self assert: ((coInterpreter rawHeaderOf: cogMethod methodObject) = cogMethod asInteger
  									or: [(self noAssertMethodClassAssociationOf: cogMethod methodObject)
  											= objectMemory nilObject]).
  						 remappedMethod := objectRepresentation remapOop: cogMethod methodObject.
  						 remappedMethod ~= cogMethod methodObject ifTrue:
  							[(coInterpreter methodHasCogMethod: remappedMethod) ifTrue:
  								[self error: 'attempt to become two cogged methods'].
  							 (objectMemory
  									withoutForwardingOn: cogMethod methodObject
  									and: remappedMethod
+ 									with: cogMethod cmUsesPenultimateLit
+ 									sendToCogit: #method:hasSameCodeAs:checkPenultimate:) ifFalse:
- 									sendToCogit: #method:hasSameCodeAs:) ifFalse:
  								[self error: 'attempt to become cogged method into different method'].
  							 coInterpreter
  								rawHeaderOf: cogMethod methodObject
  								put: cogMethod methodHeader.
  							 cogMethod
  								methodHeader: (coInterpreter rawHeaderOf: remappedMethod);
  								methodObject: remappedMethod.
  							 coInterpreter
  								rawHeaderOf: remappedMethod
  								put: cogMethod asInteger].
  						 (objectMemory isYoung: cogMethod methodObject) ifTrue:
  							[hasYoungObj := true]].
  					 self mapFor: cogMethod
  						 performUntil: (self cppIf: NewspeakVM
  											ifTrue: [#remapNSIfObjectRef:pc:hasYoung:]
  											ifFalse: [#remapIfObjectRef:pc:hasYoung:])
  						 arg: hasYoungObjPtr.
  					 hasYoungObj
  						ifTrue:
  							[cogMethod cmRefersToYoung ifFalse:
  								[cogMethod cmRefersToYoung: true.
  								 methodZone addToYoungReferrers: cogMethod].
  							hasYoungObj := false]
  						ifFalse: [cogMethod cmRefersToYoung: false]]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	methodZone pruneYoungReferrers.
  	freedPIC ifTrue:
  		[self unlinkSendsToFree.
  		 codeModified := true].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[processor flushICacheFrom: codeBase to: methodZone limitZony asInteger]!

Item was added:
+ ----- Method: Cogit>>method:hasSameCodeAs:checkPenultimate: (in category 'garbage collection') -----
+ method: methodA hasSameCodeAs: methodB checkPenultimate: comparePenultimateLiteral
+ 	"For the purposes of become: see if the two methods are similar, i.e. can be safely becommed.
+ 	 This is pretty strict.  All literals and bytecodes must be identical.  Only trailer bytes and header
+ 	  flags can differ."
+ 	<inline: false>
+ 	| headerA headerB numLitsA endPCA |
+ 	headerA := coInterpreter headerOf: methodA.
+ 	headerB := coInterpreter headerOf: methodB.
+ 	numLitsA := coInterpreter literalCountOfHeader: headerA.
+ 	endPCA := self endPCOf: methodA.
+ 	((coInterpreter argumentCountOfMethodHeader: headerA) ~= (coInterpreter argumentCountOfMethodHeader: headerB)
+ 	 or: [(coInterpreter temporaryCountOfMethodHeader: headerA) ~= (coInterpreter temporaryCountOfMethodHeader: headerB)
+ 	 or: [(coInterpreter primitiveIndexOfMethod: methodA header: headerA) ~= (coInterpreter primitiveIndexOfMethod: methodB header: headerB)
+ 	 or: [numLitsA ~= (coInterpreter literalCountOfHeader: headerB)
+ 	 or: [endPCA > (objectMemory byteLengthOf: methodB)]]]]) ifTrue:
+ 		[^false].
+ 	 1 to: numLitsA - 1 do:
+ 		[:li|
+ 		(objectMemory fetchPointer: li ofObject: methodA) ~= (objectMemory fetchPointer: li ofObject: methodB) ifTrue:
+ 			[(li < (numLitsA - 1) "If the method doesn't use the penultimate literal then don't fail the comparison."
+ 			  or: [comparePenultimateLiteral]) ifTrue:
+ 				[^false]]].
+ 	(coInterpreter startPCOfMethod: methodA) to: endPCA do:
+ 		[:bi|
+ 		(objectMemory fetchByte: bi ofObject: methodA) ~= (objectMemory fetchByte: bi ofObject: methodB) ifTrue:
+ 			[^false]].
+ 	^true!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>literalCountOfHeader: (in category 'accessing') -----
+ literalCountOfHeader: methodHeader
+ 	^(headerToMethodMap at: methodHeader) numLiterals!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveMillisecondClockMask (in category 'system control primitives') -----
  primitiveMillisecondClockMask
  	"Provide access to the millisecond clock mask to support calculation
  	of durations based on the millisecond clock value."
  
  	<export: true>
+ 	self pop: 1 thenPush: (objectMemory integerObjectOf: MillisecondClockMask)
- 	self pop: 1 thenPush: (self integerObjectOf: MillisecondClockMask)
  !

Item was added:
+ ----- Method: NewCoObjectMemory>>withoutForwardingOn:and:with:sendToCogit: (in category 'cog jit support') -----
+ withoutForwardingOn: obj1 and: obj2 with: aBool sendToCogit: selector
+ 	"For the purposes of become: send selector to the cogit with obj1 and obj2 and
+ 	 answer the result. Undo forwarding for the selector, but redo forwarding after since
+ 	 become:'s restoreHeadersAfter*Become* methods expect to be able to restore."
+ 	<api>
+ 	<var: #selector declareC: 'sqInt (*selector)(sqInt,sqInt,sqInt)'>
+ 	| savedHeaderA savedHeaderB result |
+ 	savedHeaderA := self baseHeader: obj1.
+ 	self baseHeader: obj1 put: (self headerWhileForwardingOf: obj1).
+ 	savedHeaderB := self baseHeader: obj2.
+ 	self baseHeader: obj2 put: (self headerWhileForwardingOf: obj2).
+ 
+ 	result := cogit perform: selector with: obj1 with: obj2 with: aBool.
+ 
+ 	self baseHeader: obj1 put: savedHeaderA.
+ 	self baseHeader: obj2 put: savedHeaderB.
+ 	^result!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>doubleExtendedDoAnythingBytecode (in category 'bytecode generators') -----
  doubleExtendedDoAnythingBytecode
  	"Replaces the Blue Book double-extended send [132], in which the first byte was wasted on 8 bits of argument count. 
  	Here we use 3 bits for the operation sub-type (opType),  and the remaining 5 bits for argument count where needed. 
  	The last byte give access to 256 instVars or literals. 
  	See also secondExtendedSendBytecode"
  	| opType |
  	opType := byte1 >> 5.
  	opType = 0 ifTrue:
+ 		[^self genSend: (self getLiteral: byte2) numArgs: (byte1 bitAnd: 31)].
- 		[^self genSend: (coInterpreter literal: byte2 ofMethod: methodObj) numArgs: (byte1 bitAnd: 31)].
  	opType = 1 ifTrue:
+ 		[^self genSendSuper: (self getLiteral: byte2) numArgs: (byte1 bitAnd: 31)].
- 		[^self genSendSuper: (coInterpreter literal: byte2 ofMethod: methodObj) numArgs: (byte1 bitAnd: 31)].
  	"We need a map entry for this bytecode for correct parsing.
  	 The sends will get an IsSend entry anyway.  The other cases need a
  	 fake one.  We could of course special case the scanning but that's silly."
  	opType caseOf: {
  			[2]	->	[byte2 <= StackPointerIndex
  						ifTrue: [self genPushMaybeContextReceiverVariable: byte2]
  						ifFalse: [self genPushReceiverVariable: byte2]].
  			[3]	->	[self genPushLiteralIndex: byte2].
  			[4]	->	[self genPushLiteralVariable: byte2].
  			[7]	->	[self genStorePop: false LiteralVariable: byte2] }
  		otherwise: "5 & 6"
  			[byte2 <= StackPointerIndex
  				ifTrue: [self genStorePop: opType = 6 MaybeContextReceiverVariable: byte2]
  				ifFalse: [self genStorePop: opType = 6 ReceiverVariable: byte2]].
  	"We need a map entry for this bytecode for correct parsing (if the method builds a frame).
  	 We could of course special case the scanning but that's silly."
  	needsFrame ifTrue:
  		[self annotateBytecode: self Label].
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genDynamicSuperSendBytecode (in category 'bytecode generators') -----
  genDynamicSuperSendBytecode
+ 	^self genSendDynamicSuper: (self getLiteral: byte2) numArgs: byte1!
- 	^self genSendDynamicSuper: (coInterpreter literal: byte2 ofMethod: methodObj) numArgs: byte1!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtSendAbsentDynamicSuperBytecode (in category 'bytecode generators') -----
  genExtSendAbsentDynamicSuperBytecode
  	"241		11110001	i i i i i j j j	Send To Absent Dynamic Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	| litIndex nArgs |
  	litIndex := (byte1 >> 3) + (extA << 5).
  	extA := 0.
  	nArgs := (byte1 bitAnd: 7) + (extB << 3).
  	extB := 0.
+ 	^self genSendAbsentDynamicSuper: (self getLiteral: litIndex) numArgs: nArgs!
- 	^self genSendAbsentDynamicSuper: (coInterpreter literal: litIndex ofMethod: methodObj) numArgs: nArgs!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtSendAbsentImplicitBytecode (in category 'bytecode generators') -----
  genExtSendAbsentImplicitBytecode
  	"240		11110000	i i i i i j j j	Send To Absent Implicit Receiver Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	| litIndex nArgs |
  	litIndex := (byte1 >> 3) + (extA << 5).
  	extA := 0.
  	nArgs := (byte1 bitAnd: 7) + (extB << 3).
  	extB := 0.
+ 	^self genSendAbsentImplicit: (self getLiteral: litIndex) numArgs: nArgs!
- 	^self genSendAbsentImplicit: (coInterpreter literal: litIndex ofMethod: methodObj) numArgs: nArgs!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtSendBytecode (in category 'bytecode generators') -----
  genExtSendBytecode
  	"238		11101110	i i i i i j j j	Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	| litIndex nArgs |
  	litIndex := (byte1 >> 3) + (extA << 5).
  	extA := 0.
  	nArgs := (byte1 bitAnd: 7) + (extB << 3).
  	extB := 0.
+ 	^self genSend: (self getLiteral: litIndex) numArgs: nArgs!
- 	^self genSend: (coInterpreter literal: litIndex ofMethod: methodObj) numArgs: nArgs!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtSendSuperBytecode (in category 'bytecode generators') -----
  genExtSendSuperBytecode
  	"239		11101111	i i i i i j j j	Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
  	| litIndex nArgs |
  	litIndex := (byte1 >> 3) + (extA << 5).
  	extA := 0.
  	nArgs := (byte1 bitAnd: 7) + (extB << 3).
  	extB := 0.
+ 	^self genSendSuper: (self getLiteral: litIndex) numArgs: nArgs!
- 	^self genSendSuper: (coInterpreter literal: litIndex ofMethod: methodObj) numArgs: nArgs!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtendedSendBytecode (in category 'bytecode generators') -----
  genExtendedSendBytecode
  	"Can use any of the first 32 literals for the selector and pass up to 7 arguments."
  
+ 	^self genSend: (self getLiteral: (byte1 bitAnd: 16r1F)) numArgs: byte1 >> 5!
- 	^self genSend: (coInterpreter literal: (byte1 bitAnd: 16r1F) ofMethod: methodObj) numArgs: byte1 >> 5!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtendedSuperBytecode (in category 'bytecode generators') -----
  genExtendedSuperBytecode
+ 	^self genSendSuper: (self getLiteral: (byte1 bitAnd: 16r1F)) numArgs: byte1 >> 5!
- 	^self genSendSuper: (coInterpreter literal: (byte1 bitAnd: 16r1F) ofMethod: methodObj) numArgs: byte1 >> 5!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPushExplicitOuterSendReceiverBytecode (in category 'bytecode generators') -----
  genPushExplicitOuterSendReceiverBytecode
  	"Uncached push explicit outer send receiver"
  	| levelOop |
+ 	levelOop := self getLiteral: byte1.
- 	levelOop := coInterpreter literal: byte1 ofMethod: methodObj.
  	self assert: (objectMemory isIntegerObject: levelOop).
  	^self genPushExplicitOuterSendReceiver: (objectMemory integerValueOf: levelOop)!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPushImplicitReceiverBytecode (in category 'bytecode generators') -----
  genPushImplicitReceiverBytecode
  	| result |
+ 	result := self genGetImplicitReceiverFor: (self getLiteral: byte1).
- 	result := self genGetImplicitReceiverFor: (coInterpreter literal: byte1 ofMethod: methodObj).
  	result ~= 0 ifTrue:
  		[^result].
  	self PushR: ReceiverResultReg.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPushLiteralIndex: (in category 'bytecode generators') -----
  genPushLiteralIndex: literalIndex "<SmallInteger>"
  	<inline: false>
  	| literal |
+ 	literal := self getLiteral: literalIndex.
- 	literal := coInterpreter literal: literalIndex ofMethod: methodObj.
  	^self genPushLiteral: literal!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPushLiteralVariable: (in category 'bytecode generators') -----
  genPushLiteralVariable: literalIndex
  	<inline: false>
  	| association |
+ 	association := self getLiteral: literalIndex.
- 	association := coInterpreter literal: literalIndex ofMethod: methodObj.
  	"N.B. Do _not_ use ReceiverResultReg to avoid overwriting receiver in assignment in frameless methods."
  	self annotate: (self MoveCw: association R: ClassReg) objRef: association.
  	objectRepresentation
  		genLoadSlot: ValueIndex
  		sourceReg: ClassReg
  		destReg: TempReg.
  	self PushR: TempReg.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSecondExtendedSendBytecode (in category 'bytecode generators') -----
  genSecondExtendedSendBytecode
  	"Can use any of the first 64 literals for the selector and pass up to 3 arguments."
  
+ 	^self genSend: (self getLiteral: (byte1 bitAnd: 16r3F)) numArgs: byte1 >> 6!
- 	^self genSend: (coInterpreter literal: (byte1 bitAnd: 16r3F) ofMethod: methodObj) numArgs: byte1 >> 6!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendAbsentImplicit0ArgsBytecode (in category 'bytecode generators') -----
  genSendAbsentImplicit0ArgsBytecode
  	"160-175	1010 i i i i		Send To Absent Implicit Receiver Literal Selector #iiii With 0 Arguments."
+ 	^self genSendAbsentImplicit: (self getLiteral: (byte0 bitAnd: 15)) numArgs: 0!
- 	^self genSendAbsentImplicit: (coInterpreter literal: (byte0 bitAnd: 15) ofMethod: methodObj) numArgs: 0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendLiteralSelector0ArgsBytecode (in category 'bytecode generators') -----
  genSendLiteralSelector0ArgsBytecode
+ 	^self genSend: (self getLiteral: (byte0 bitAnd: 15)) numArgs: 0!
- 	^self genSend: (coInterpreter literal: (byte0 bitAnd: 15) ofMethod: methodObj) numArgs: 0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendLiteralSelector1ArgBytecode (in category 'bytecode generators') -----
  genSendLiteralSelector1ArgBytecode
+ 	^self genSend: (self getLiteral: (byte0 bitAnd: 15)) numArgs: 1!
- 	^self genSend: (coInterpreter literal: (byte0 bitAnd: 15) ofMethod: methodObj) numArgs: 1!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genSendLiteralSelector2ArgsBytecode (in category 'bytecode generators') -----
  genSendLiteralSelector2ArgsBytecode
+ 	^self genSend: (self getLiteral: (byte0 bitAnd: 15)) numArgs: 2!
- 	^self genSend: (coInterpreter literal: (byte0 bitAnd: 15) ofMethod: methodObj) numArgs: 2!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genStorePop:LiteralVariable: (in category 'bytecode generators') -----
  genStorePop: popBoolean LiteralVariable: litVarIndex
  	<inline: false>
  	| association |
  	self assert: needsFrame.
+ 	association := self getLiteral: litVarIndex.
- 	association := coInterpreter literal: litVarIndex ofMethod: methodObj.
  	self annotate: (self MoveCw: association R: ReceiverResultReg) objRef: association.
  	popBoolean
  		ifTrue: [self PopR: ClassReg]
  		ifFalse: [self MoveMw: 0 r: SPReg R: ClassReg].
  	traceStores > 0 ifTrue:
  		[self CallRT: ceTraceStoreTrampoline].
  	^objectRepresentation
  		genStoreSourceReg: ClassReg
  		slotIndex: ValueIndex
  		destReg: ReceiverResultReg
  		scratchReg: TempReg!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>generateCogMethod: (in category 'generate machine code') -----
  generateCogMethod: selector
  	"We handle jump sizing simply.  First we make a pass that asks each
  	 instruction to compute its maximum size.  Then we make a pass that
  	 sizes jumps based on the maxmimum sizes.  Then we make a pass
  	 that fixes up jumps.  When fixing up a jump the jump is not allowed to
  	 choose a smaller offset but must stick to the size set in the second pass.
  
  	 Override to add counters"
  	| codeSize headerSize mapSize countersSize totalSize startAddress result method |
  	<var: #method type: #'CogMethod *'>
  	<var: #blockStart type: #'BlockStart *'>
  	<var: #headerReference type: #'AbstractInstruction *'>
  	<returnTypeC: #'CogMethod *'>
  	headerSize := self sizeof: CogMethod.
  	methodLabel address: headerSize negated.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: (methodZone allocate: 0).
  	codeSize := self generateInstructionsAt: methodLabel address + headerSize.
  	mapSize := self generateMapAt: 0 start: methodLabel address + cmNoCheckEntryOffset.
  	countersSize := counterIndex * CounterBytes.
  	totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize + countersSize.
+ 	totalSize > MaxMethodSize ifTrue:
+ 		[^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  	startAddress := methodZone allocate: totalSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: startAddress + cmNoCheckEntryOffset = noCheckEntry address.
  	self regenerateCounterReferences: startAddress + totalSize.
  	result := self outputInstructionsAt: startAddress + headerSize.
  	self assert: startAddress + headerSize + codeSize = result.
  	backEnd nopsFrom: result to: startAddress + totalSize - mapSize.
  	self generateMapAt: startAddress + totalSize - countersSize - 1 start: startAddress + cmNoCheckEntryOffset.
  	self fillInBlockHeadersAt: startAddress.
  	self fillInCounters: counterIndex atEndAddress: startAddress + totalSize.
  	method := self fillInMethodHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  					size: totalSize
  					selector: selector.
  	postCompileHook notNil ifTrue:
  		[self perform: postCompileHook with: method with: primInvokeLabel.
  		 postCompileHook := nil].
  	processor flushICacheFrom: startAddress to: startAddress + headerSize + codeSize.
  	^method!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>doubleExtendedDoAnythingBytecode (in category 'bytecode generators') -----
  doubleExtendedDoAnythingBytecode
  	"Replaces the Blue Book double-extended send [132], in which the first byte was wasted on 8 bits of argument count. 
  	Here we use 3 bits for the operation sub-type (opType),  and the remaining 5 bits for argument count where needed. 
  	The last byte give access to 256 instVars or literals. 
  	See also secondExtendedSendBytecode"
  	| opType |
  	opType := byte1 >> 5.
  	opType = 0 ifTrue:
+ 		[^self genSend: (self getLiteral: byte2) numArgs: (byte1 bitAnd: 31)].
- 		[^self genSend: (coInterpreter literal: byte2 ofMethod: methodObj) numArgs: (byte1 bitAnd: 31)].
  	opType = 1 ifTrue:
+ 		[^self genSendSuper: (self getLiteral: byte2) numArgs: (byte1 bitAnd: 31)].
- 		[^self genSendSuper: (coInterpreter literal: byte2 ofMethod: methodObj) numArgs: (byte1 bitAnd: 31)].
  	"We need a map entry for this bytecode for correct parsing.
  	 The sends will get an IsSend entry anyway.  The other cases need a
  	 fake one.  We could of course special case the scanning but that's silly."
  	opType caseOf: {
  			[2]	->	[byte2 <= StackPointerIndex
  						ifTrue: [self genPushMaybeContextReceiverVariable: byte2]
  						ifFalse: [self genPushReceiverVariable: byte2.
  								self ssTop annotateUse: true.
  								^0]].
  			[3]	->	[self genPushLiteralIndex: byte2.
  					 self ssTop annotateUse: true.
  					 ^0].
  			[4]	->	[self genPushLiteralVariable: byte2.].
  			[7]	->	[self genStorePop: false LiteralVariable: byte2] }
  		otherwise: "5 & 6"
  			[byte2 <= StackPointerIndex
  				ifTrue: [self genStorePop: opType = 6 MaybeContextReceiverVariable: byte2]
  				ifFalse: [self genStorePop: opType = 6 ReceiverVariable: byte2]].
  	"We need a map entry for this bytecode for correct parsing (if the method builds a frame).
  	 We could of course special case the scanning but that's silly (or is it?)."
  	self assert: needsFrame.
  	"genPushMaybeContextInstVar, pushListVar, store & storePop all generate code"
  	self assert: self prevInstIsPCAnnotated not.
  	self annotateBytecode: self Label.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPushImplicitReceiverBytecode (in category 'bytecode generators') -----
  genPushImplicitReceiverBytecode
  	| result |
+ 	result := self genGetImplicitReceiverFor: (self getLiteral: byte1).
- 	result := self genGetImplicitReceiverFor: (coInterpreter literal: byte1 ofMethod: methodObj).
  	result ~= 0 ifTrue:
  		[^result].
  	^self ssPushRegister: ReceiverResultReg!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPushLiteralVariable: (in category 'bytecode generators') -----
  genPushLiteralVariable: literalIndex
  	<inline: false>
  	| association freeReg |
  	freeReg := self ssAllocatePreferredReg: ClassReg.
+ 	association := self getLiteral: literalIndex.
- 	association := coInterpreter literal: literalIndex ofMethod: methodObj.
  	"N.B. Do _not_ use ReceiverResultReg to avoid overwriting receiver in assignment in frameless methods."
  	"So far descriptors are not rich enough to describe the entire dereference so generate the register
  	 load but don't push the result.  There is an order-or-evaluation issue if we defer the dereference."
  	self annotate: (self MoveCw: association R: TempReg) objRef: association.
  	objectRepresentation
  		genLoadSlot: ValueIndex
  		sourceReg: TempReg
  		destReg: freeReg.
  	self ssPushRegister: freeReg.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genStorePop:LiteralVariable: (in category 'bytecode generators') -----
  genStorePop: popBoolean LiteralVariable: litVarIndex
  	<inline: false>
  	| topReg valueReg association constVal |
  	self flag: 'with better register allocation this wouldn''t need a frame.  e.g. use SendNumArgs instead of ReceiverResultReg'.
  	self assert: needsFrame.
  	optStatus isReceiverResultRegLive: false.
  	"N.B.  No need to check the stack for references because we generate code for
  	 literal variable loads that stores the result in a register, deferring only the register push."
+ 	association := self getLiteral: litVarIndex.
- 	association := coInterpreter literal: litVarIndex ofMethod: methodObj.
  	constVal := self ssTop maybeConstant.
  	"Avoid store check for immediate values"
  	(self ssTop type = SSConstant
  	 and: [(objectRepresentation shouldAnnotateObjectReference: constVal) not]) ifTrue:
  		[self ssAllocateRequiredReg: ReceiverResultReg.
  		 self annotate: (self MoveCw: association R: ReceiverResultReg) objRef: association.
  		 self ssStorePop: popBoolean toPreferredReg: TempReg.
  		 traceStores > 0 ifTrue:
  			[self CallRT: ceTraceStoreTrampoline].
  		 ^objectRepresentation
  			genStoreImmediateInSourceReg: TempReg
  			slotIndex: ValueIndex
  			destReg: ReceiverResultReg].
  	((topReg := self ssTop registerOrNil) isNil
  	 or: [topReg = ReceiverResultReg]) ifTrue:
  		[topReg := ClassReg].
  	self ssPop: 1.
  	self ssAllocateCallReg: topReg. "for the ceStoreCheck call in genStoreSourceReg:... below"
  	self ssPush: 1.
  	valueReg := self ssStorePop: popBoolean toPreferredReg: topReg.
  	valueReg = ReceiverResultReg ifTrue:
  		[self MoveR: valueReg R: topReg].
  	self ssAllocateCallReg: ReceiverResultReg.
  	self annotate: (self MoveCw: association R: ReceiverResultReg) objRef: association.
  	 traceStores > 0 ifTrue:
  		[self MoveR: topReg R: TempReg.
  		 self CallRT: ceTraceStoreTrampoline].
  	^objectRepresentation
  		genStoreSourceReg: topReg
  		slotIndex: ValueIndex
  		destReg: ReceiverResultReg
  		scratchReg: TempReg!



More information about the Vm-dev mailing list