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

commits at source.squeak.org commits at source.squeak.org
Wed Sep 21 22:26:11 UTC 2011


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

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

Name: VMMaker.oscog-eem.125
Author: eem
Time: 21 September 2011, 3:24:21.37 pm
UUID: 539c10db-ab19-4fc7-ada1-4ffae6463ed1
Ancestors: VMMaker.oscog-eem.124

Cogit:
Add callsite link/relocate checks to catch the call 0x00000013 MNU
callsite relinking bug.

Reduce the size of the simStack to something proportional to
LargeContextSize.

CogMemoryManager:
Use a 5-bit format field to encode all of indexability, weak/ephemeron,
hence gaining a bit.

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

Item was added:
+ ----- Method: CoInterpreter>>interpretAddress (in category 'trampoline support') -----
+ interpretAddress
+ 	"This is used for asserts that check that inline cache editing results in valid addresses.
+ 	 In the C VM interpret is guaranteed to come before any primitives and so it constitutes
+ 	 the lowest address in C code that machine code should be linked.  In the simulator
+ 	we just answer something not low."
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^self cCode: [(self addressOf: #interpret) asUnsignedInteger]
+ 		inSmalltalk: [heapBase]!

Item was changed:
  ----- Method: CogIA32Compiler>>relocateCallBeforeReturnPC:by: (in category 'inline cacheing') -----
  relocateCallBeforeReturnPC: retpc by: delta
  	| distance |
  	delta ~= 0 ifTrue:
+ 		[distance :=    ((objectMemory byteAt: retpc - 1) << 24)
- 		[distance :=     ((objectMemory byteAt: retpc - 1) << 24)
  					+  ((objectMemory byteAt: retpc - 2) << 16)
  					+  ((objectMemory byteAt: retpc - 3) << 8)
  					+   (objectMemory byteAt: retpc - 4).
  		 distance := distance + delta.
  		 objectMemory
  			byteAt: retpc - 1 put: (distance >> 24 bitAnd: 16rFF);
  			byteAt: retpc - 2 put: (distance >> 16 bitAnd: 16rFF);
  			byteAt: retpc - 3 put: (distance >>   8 bitAnd: 16rFF);
+ 			byteAt: retpc - 4 put: (distance            bitAnd: 16rFF).
+ 		false
+ 			ifTrue: [self assert: (self callTargetFromReturnAddress: retpc) >= cogit minCallAddress]
+ 			ifFalse: [(self callTargetFromReturnAddress: retpc) >= cogit minCallAddress ifFalse:
+ 						[self error: 'relocating call to invalid address']]]!
- 			byteAt: retpc - 4 put: (distance            bitAnd: 16rFF)]!

Item was changed:
  ----- Method: CogIA32Compiler>>rewriteCallAt:target: (in category 'inline cacheing') -----
  rewriteCallAt: callSiteReturnAddress target: callTargetAddress
  	"Rewrite a call instruction to call a different target.  This variant is used to link PICs
  	 in ceSendMiss et al, and to rewrite cached primitive calls.   Answer the extent of
  	 the code change which is used to compute the range of the icache to flush."
+ 	<var: #callSiteReturnAddress type: #usqInt>
  	| callDistance |
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
+ 	false
+ 		ifTrue: [self assert: callTargetAddress >= cogit minCallAddress]
+ 		ifFalse: [callTargetAddress >= cogit minCallAddress ifFalse:
+ 					[self error: 'linking callsite to invalid address']].
  	callDistance := (callTargetAddress - callSiteReturnAddress) signedIntToLong.
  	objectMemory
  		byteAt: callSiteReturnAddress - 1 put: (callDistance >> 24 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 2 put: (callDistance >> 16 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 3 put: (callDistance >>   8 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 4 put: (callDistance            bitAnd: 16rFF).
+ 	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) = callTargetAddress.
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
  	^5!

Item was changed:
  ----- Method: CogIA32Compiler>>rewriteInlineCacheAt:tag:target: (in category 'inline cacheing') -----
  rewriteInlineCacheAt: callSiteReturnAddress tag: cacheTag target: callTargetAddress
  	"Rewrite an inline cache to call a different target for a new tag.  This variant is used
  	 to link unlinked sends in ceSend:to:numArgs: et al.  Answer the extent of the code
  	 change which is used to compute the range of the icache to flush."
+ 	<var: #callSiteReturnAddress type: #usqInt>
  	| callDistance |
+ 	"self cCode: ''
+ 		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
+ 	false
+ 		ifTrue: [self assert: callTargetAddress >= cogit minCallAddress]
+ 		ifFalse: [callTargetAddress >= cogit minCallAddress ifFalse:
+ 					[self error: 'linking callsite to invalid address']].
- 	self cCode: ''
- 		inSmalltalk: [false ifTrue: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]].
  	callDistance := (callTargetAddress - callSiteReturnAddress) signedIntToLong.
  	objectMemory
  		byteAt: callSiteReturnAddress - 1 put: (callDistance >> 24 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 2 put: (callDistance >> 16 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 3 put: (callDistance >>   8 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 4 put: (callDistance            bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 6 put: (cacheTag >> 24 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 7 put: (cacheTag >> 16 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 8 put: (cacheTag >>   8 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 9 put: (cacheTag            bitAnd: 16rFF).
+ 	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) = callTargetAddress.
+ 	"self cCode: ''
+ 		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
- 	self cCode: ''
- 		inSmalltalk: [false ifTrue: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]].
  	^10!

Item was changed:
  VMClass subclass: #CogMemoryManager
(excessive size, no diff calculated)

Item was changed:
  VMStructType subclass: #CogObjectHeader
+ 	instanceVariableNames: 'classIndex unused0 isPinned isImmutable format isMarked isGrey isRemembered objHash slotSize'
- 	instanceVariableNames: 'classIndex unused0 format isWeak isEphemeron isPointers isPinned isMarked isGrey isRemembered isImmutable objHash objSize'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-MemoryManager'!

Item was changed:
  ----- Method: CogObjectHeader class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a BytecodeDescriptor struct."
+ 	"self typedef"
  
  	self instVarNames do:
  		[:ivn|
  		aBinaryBlock
  			value: ivn
  			value: (ivn caseOf: {
+ 							['classIndex']	->	[#'unsigned short']. "for speed; can extend to 22 bits by absorbing unused0"
+ 							['unused0']		->	[#(unsigned ' : 6')].
+ 							['format']		->	[#(unsigned ' : 5')].
- 							['classIndex']	->	[#'unsigned short']. "for speed; can extend to 20 bits by absorbing unused0"
- 							['unused0']		->	[#(unsigned ' : 4')].
- 							['format']		->	[#(unsigned ' : 4')].
  							['objHash']		->	[#(unsigned ' : 24')].
+ 							['slotSize']		->	[#'unsigned char'] }
- 							['objSize']		->	[#'unsigned char'] }
  						otherwise: [#(#unsigned #Boolean ' : 1')])]!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>format (in category 'accessing') -----
  format
+ 	^(memory unsignedByteAt: address + 4) bitAnd: 16r1F!
- 	^((memory unsignedByteAt: address + 3) bitShift: -4) bitAnd: 16rF!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>format: (in category 'accessing') -----
  format: aValue
+ 	self assert: (aValue between: 0 and: 16r1F).
- 	self assert: (aValue between: 0 and: 16rF).
  	memory
+ 		unsignedByteAt: address + 4
+ 		put: ((memory unsignedByteAt: address + 4) bitAnd: 16rE0) + aValue.
- 		unsignedByteAt: address + 3
- 		put: ((memory unsignedByteAt: address + 3) bitAnd: 16rF) + (aValue bitShift: 4).
  	^aValue!

Item was removed:
- ----- Method: CogObjectHeaderSurrogate>>isEphemeron (in category 'accessing') -----
- isEphemeron
- 	^(((memory unsignedByteAt: address + 4) bitShift: -1) bitAnd: 16r1) ~= 0!

Item was removed:
- ----- Method: CogObjectHeaderSurrogate>>isEphemeron: (in category 'accessing') -----
- isEphemeron: aValue
- 	memory
- 		unsignedByteAt: address + 4
- 		put: (((memory unsignedByteAt: address + 4) bitAnd: 16rFD) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 1)).
- 	^aValue!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>isGrey (in category 'accessing') -----
  isGrey
+ 	^(((memory unsignedByteAt: address + 4) bitShift: -6) bitAnd: 16r1) ~= 0!
- 	^(((memory unsignedByteAt: address + 4) bitShift: -5) bitAnd: 16r1) ~= 0!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>isGrey: (in category 'accessing') -----
  isGrey: aValue
  	memory
  		unsignedByteAt: address + 4
+ 		put: (((memory unsignedByteAt: address + 4) bitAnd: 16rBF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 6)).
- 		put: (((memory unsignedByteAt: address + 4) bitAnd: 16rDF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 5)).
  	^aValue!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>isImmutable (in category 'accessing') -----
  isImmutable
+ 	^(((memory unsignedByteAt: address + 3) bitShift: -7) bitAnd: 16r1) ~= 0!
- 	^(((memory unsignedByteAt: address + 4) bitShift: -7) bitAnd: 16r1) ~= 0!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>isImmutable: (in category 'accessing') -----
  isImmutable: aValue
  	memory
+ 		unsignedByteAt: address + 3
+ 		put: (((memory unsignedByteAt: address + 3) bitAnd: 16r7F) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 7)).
- 		unsignedByteAt: address + 4
- 		put: (((memory unsignedByteAt: address + 4) bitAnd: 16r7F) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 7)).
  	^aValue!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>isMarked (in category 'accessing') -----
  isMarked
+ 	^(((memory unsignedByteAt: address + 4) bitShift: -5) bitAnd: 16r1) ~= 0!
- 	^(((memory unsignedByteAt: address + 4) bitShift: -4) bitAnd: 16r1) ~= 0!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>isMarked: (in category 'accessing') -----
  isMarked: aValue
  	memory
  		unsignedByteAt: address + 4
+ 		put: (((memory unsignedByteAt: address + 4) bitAnd: 16rDF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 5)).
- 		put: (((memory unsignedByteAt: address + 4) bitAnd: 16rEF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 4)).
  	^aValue!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>isPinned (in category 'accessing') -----
  isPinned
+ 	^(((memory unsignedByteAt: address + 3) bitShift: -6) bitAnd: 16r1) ~= 0!
- 	^(((memory unsignedByteAt: address + 4) bitShift: -3) bitAnd: 16r1) ~= 0!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>isPinned: (in category 'accessing') -----
  isPinned: aValue
  	memory
+ 		unsignedByteAt: address + 3
+ 		put: (((memory unsignedByteAt: address + 3) bitAnd: 16rBF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 6)).
- 		unsignedByteAt: address + 4
- 		put: (((memory unsignedByteAt: address + 4) bitAnd: 16rF7) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 3)).
  	^aValue!

Item was removed:
- ----- Method: CogObjectHeaderSurrogate>>isPointers (in category 'accessing') -----
- isPointers
- 	^(((memory unsignedByteAt: address + 4) bitShift: -2) bitAnd: 16r1) ~= 0!

Item was removed:
- ----- Method: CogObjectHeaderSurrogate>>isPointers: (in category 'accessing') -----
- isPointers: aValue
- 	memory
- 		unsignedByteAt: address + 4
- 		put: (((memory unsignedByteAt: address + 4) bitAnd: 16rFB) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 2)).
- 	^aValue!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>isRemembered (in category 'accessing') -----
  isRemembered
+ 	^(((memory unsignedByteAt: address + 4) bitShift: -7) bitAnd: 16r1) ~= 0!
- 	^(((memory unsignedByteAt: address + 4) bitShift: -6) bitAnd: 16r1) ~= 0!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>isRemembered: (in category 'accessing') -----
  isRemembered: aValue
  	memory
  		unsignedByteAt: address + 4
+ 		put: (((memory unsignedByteAt: address + 4) bitAnd: 16r7F) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 7)).
- 		put: (((memory unsignedByteAt: address + 4) bitAnd: 16rBF) + ((aValue ifTrue: [1] ifFalse: [0]) bitShift: 6)).
  	^aValue!

Item was removed:
- ----- Method: CogObjectHeaderSurrogate>>isWeak (in category 'accessing') -----
- isWeak
- 	^((memory unsignedByteAt: address + 4) bitAnd: 16r1) ~= 0!

Item was removed:
- ----- Method: CogObjectHeaderSurrogate>>isWeak: (in category 'accessing') -----
- isWeak: aValue
- 	memory
- 		unsignedByteAt: address + 4
- 		put: (((memory unsignedByteAt: address + 4) bitAnd: 16rFE) + (aValue ifTrue: [1] ifFalse: [0])).
- 	^aValue!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>objHash (in category 'accessing') -----
  objHash
  	^(memory unsignedLongAt: address + 5) bitAnd: 16rFFFFFF!

Item was changed:
  ----- Method: CogObjectHeaderSurrogate>>objHash: (in category 'accessing') -----
  objHash: aValue
  	self assert: (aValue between: 0 and: 16rFFFFFF).
  	memory
  		unsignedLongAt: address + 5
  		put: ((memory unsignedLongAt: address + 5) bitAnd: 16rFF000000) + aValue.
  	^aValue!

Item was removed:
- ----- Method: CogObjectHeaderSurrogate>>objSize (in category 'accessing') -----
- objSize
- 	^memory unsignedByteAt: address + 8!

Item was removed:
- ----- Method: CogObjectHeaderSurrogate>>objSize: (in category 'accessing') -----
- objSize: aValue
- 	^memory
- 		unsignedByteAt: address + 8
- 		put: aValue!

Item was added:
+ ----- Method: CogObjectHeaderSurrogate>>slotSize (in category 'accessing') -----
+ slotSize
+ 	^memory unsignedByteAt: address + 8!

Item was added:
+ ----- Method: CogObjectHeaderSurrogate>>slotSize: (in category 'accessing') -----
+ slotSize: aValue
+ 	^memory
+ 		unsignedByteAt: address + 8
+ 		put: aValue!

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 traceLinkedSends 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 bytecodePointer 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'
- 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceLinkedSends 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 bytecodePointer 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'
  	classVariableNames: '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'
  	poolDictionaries: 'CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: '<historical>' 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.
  
  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>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	#(	'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation'
  		'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass'
  		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses'
  		'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters'
  		'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep') do:
  			[:simulationVariableNotNeededForRealVM|
  			aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM].
  	NewspeakVM ifFalse:
  		[#(	'dynSuperEntry' 'dynSuperEntryAlignment' 'dynamicSuperSendTrampolines'
  			'ceImplicitReceiverTrampoline' 'ceExplicitReceiverTrampoline' 'cmDynSuperEntryOffset') do:
  				[:variableNotNeededInNormalVM|
  				aCCodeGenerator removeVariable: variableNotNeededInNormalVM]].
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"cogmethod.h"';
  		addHeaderFile:'#if COGMTVM';
  		addHeaderFile:'"cointerpmt.h"';
  		addHeaderFile:'#else';
  		addHeaderFile:'"cointerp.h"';
  		addHeaderFile:'#endif';
  		addHeaderFile:'"cogit.h"';
  		addHeaderFile:'"dispdbg.h"'.
  	aCCodeGenerator
  		var: #ceGetSP
  			declareC: 'unsigned long (*ceGetSP)(void)';
  		var: #ceCaptureCStackPointers
  			declareC: 'void (*ceCaptureCStackPointers)(void)';
  		var: #ceEnterCogCodePopReceiverReg
  			declareC: 'void (*ceEnterCogCodePopReceiverReg)(void)';
  		var: #realCEEnterCogCodePopReceiverReg
  			declareC: 'void (*realCEEnterCogCodePopReceiverReg)(void)';
  		var: #ceEnterCogCodePopReceiverAndClassRegs
  			declareC: 'void (*ceEnterCogCodePopReceiverAndClassRegs)(void)';
  		var: #realCEEnterCogCodePopReceiverAndClassRegs
  			declareC: 'void (*realCEEnterCogCodePopReceiverAndClassRegs)(void)';
  		var: #ceFlushICache
  			declareC: 'static void (*ceFlushICache)(unsigned long from, unsigned long to)';
  		var: #ceCheckFeaturesFunction
  			declareC: 'static unsigned long (*ceCheckFeaturesFunction)(void)';
  		var: #ceTryLockVMOwner
  			declareC: 'unsigned long (*ceTryLockVMOwner)(void)';
  		var: #ceUnlockVMOwner
  			declareC: 'void (*ceUnlockVMOwner)(void)';
  		var: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *, void *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *'.
  	aCCodeGenerator
  		declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel"
  		var: #backEnd declareC: 'AbstractInstruction *backEnd = &aMethodLabel';
  		var: #methodLabel declareC: 'AbstractInstruction *methodLabel = &aMethodLabel';
  		var: #primInvokeLabel type: #'AbstractInstruction *'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
  					stackOverflowCall sendMissCall entry noCheckEntry dynSuperEntry
  					mnuCall interpretCall endCPICCase0 endCPICCase1)
  			as: #'AbstractInstruction *'
  				in: aCCodeGenerator.
  	aCCodeGenerator
  		declareVar: #annotations type: #'InstructionAnnotation *';
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *'.
  	aCCodeGenerator
  		var: #sendTrampolines
  			declareC: 'sqInt sendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
  			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]';
  		var: #dynamicSuperSendTrampolines
  			declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]';
  		var: #trampolineAddresses
  			declareC: 'static char *trampolineAddresses[NumTrampolines*2]';
  		var: #objectReferencesInRuntime
  			declareC: 'static sqInt objectReferencesInRuntime[NumObjRefsInRuntime]';
  		var: #cePositive32BitIntegerTrampoline
  			declareC: 'static sqInt cePositive32BitIntegerTrampoline';
  		var: #labelCounter
  			declareC: 'static int labelCounter';
  		var: #traceLinkedSends
  			declareC: 'int traceLinkedSends = 2 /* prim trace log on by default */';
  		var: #cStackAlignment
  			declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'.
  	aCCodeGenerator
  		declareVar: #CFramePointer type: #'void *';
  		declareVar: #CStackPointer type: #'void *';
+ 		declareVar: #minValidCallAddress type: #'unsigned long';
  		declareVar: #debugPrimCallStackOffset type: #'unsigned long'.
  	aCCodeGenerator
  		var: #generatorTable
  			declareC: 'BytecodeDescriptor generatorTable[256]'
  						, (self tableInitializerFor: aCCodeGenerator vmClass generatorTable
  							in: aCCodeGenerator);
  		var: #primitiveGeneratorTable
  			declareC: 'PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]'
  						, (self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
  							in: aCCodeGenerator).
  	"In C the abstract opcode names clash with the Smalltak generator syntactic sugar.
  	 Most of the syntactic sugar is inlined, but alas some remains.  Rename the syntactic
  	 sugar to avoid the clash."
  	(self organization listAtCategoryNamed: #'abstract instructions') do:
  		[:s|
  		aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)].
  	aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'!

Item was changed:
  ----- Method: Cogit>>compilePrimitive (in category 'compile abstract instructions') -----
  compilePrimitive
  	"Compile a primitive.  If possible, performance-critical primtiives will
  	 be generated by their own routines (primitiveGenerator).  Otherwise,
  	 if there is a primitive at all, we call the C routine with the usual
  	 stack-switching dance, test the primFailCode and then either return
  	 on success or continue to the method body."
  	<inline: false>
  	| primitiveDescriptor primitiveRoutine |
  	<var: #primitiveDescriptor type: #'PrimitiveDescriptor *'>
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	primitiveIndex = 0 ifTrue: [^0].
  	((primitiveDescriptor := self primitiveGeneratorOrNil) notNil
  	 and: [primitiveDescriptor primitiveGenerator notNil]) ifTrue:
  		["If a descriptor specifies an argument count (by numArgs >= 0)
  		  then it must match for the generated code to be correct.  For
  		  example for speed many primitives use ResultReceiverReg
  		  instead of accessing the stack, so the receiver better be at
  		  numArgs down the stack.  Use the interpreter version if not."
  		 (primitiveDescriptor primNumArgs < 0 "means don't care"
  		  or: [primitiveDescriptor primNumArgs = (coInterpreter argumentCountOf: methodObj)]) ifTrue:
  			[^self perform: primitiveDescriptor primitiveGenerator]].
  	((primitiveRoutine := coInterpreter
  							functionPointerForCompiledMethod: methodObj
  							primitiveIndex: primitiveIndex) isNil "no primitive"
  	or: [primitiveRoutine = (coInterpreter functionPointerFor: 0 inClass: nil) "routine = primitiveFail"]) ifTrue:
  		[^self genFastPrimFail].
+ 	minValidCallAddress := minValidCallAddress min: primitiveRoutine asUnsignedInteger.
  	^self compileInterpreterPrimitive: primitiveRoutine!

Item was changed:
  ----- Method: Cogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
  initializeCodeZoneFrom: startAddress upTo: endAddress
  	<api>
  	self cCode: [self sqMakeMemoryExecutableFrom: startAddress To: endAddress]
  		inSmalltalk: [self initializeProcessor].
  	codeBase := methodZoneBase := (self
  											cCode: [startAddress]
  											inSmalltalk: [startAddress + guardPageSize]).
+ 	minValidCallAddress := codeBase min: coInterpreter interpretAddress.
  	self initializeBackend.
  	self maybeGenerateCheckFeatures.
  	self maybeGenerateICacheFlush.
  	self generateVMOwnerLockFunctions.
  	ceGetSP := self cCoerceSimple: self genGetLeafCallStackPointer to: #'unsigned long (*)(void)'.
  	self generateStackPointerCapture.
  	self generateTrampolines.
  	self checkPrimitiveTableEnablers.
  	methodZone manageFrom: methodZoneBase to: endAddress.
  	self computeEntryOffsets.
  	self generateClosedPICPrototype.
  	"N.B. this is assumed to be the last thing done in initialization; see Cogit>>initialized"
  	self generateOpenPICPrototype!

Item was added:
+ ----- Method: Cogit>>minCallAddress (in category 'accessing') -----
+ minCallAddress
+ 	<cmacro: '() minValidCallAddress'>
+ 	^minValidCallAddress!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveCrashVM (in category 'system control primitives') -----
  primitiveCrashVM
  	"Crash the VM by indirecting through a null pointer.  If the sole argument
+ 	 is true crash in this thread, and if it is false crash in a new thread.  If the
+ 	 argument is an integer use the method that implies.
+ 		bit 0 = thread to crash in; 1 => this thread
+ 		bit 1 = crash method; 0 => indirect through null pointer; 1 => call exit"
+ 
- 	 is true crash in this thread, and if it is false crash in a new thread."
  	| crashInThisThread |
  	<export: true>
+ 	(objectMemory isIntegerObject: self stackTop)
+ 		ifTrue: [crashInThisThread := objectMemory integerValueOf: self stackTop]
+ 		ifFalse: [crashInThisThread := self booleanValueOf: self stackTop].
- 	crashInThisThread := self booleanValueOf: self stackTop.
  	(self failed
  	 or: [argumentCount ~= 1]) ifTrue:
  		[^self primitiveFailFor: PrimErrBadNumArgs].
  	self crashInThisOrAnotherThread: crashInThisThread.
  	self pop: 1!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCodeGen
  	aCodeGen
  		var: #methodAbortTrampolines
  			declareC: 'sqInt methodAbortTrampolines[4]';
  		var: #picAbortTrampolines
  			declareC: 'sqInt picAbortTrampolines[4]';
  		var: #picMissTrampolines
  			declareC: 'sqInt picMissTrampolines[4]';
  		var: 'ceEnter0ArgsPIC'
  			declareC: 'void (*ceEnter0ArgsPIC)(void)';
  		var: 'ceEnter1ArgsPIC'
  			declareC: 'void (*ceEnter1ArgsPIC)(void)';
  		var: 'ceEnter2ArgsPIC'
  			declareC: 'void (*ceEnter2ArgsPIC)(void)';
  		var: #ceEnterCogCodePopReceiverArg0Regs
  			declareC: 'void (*ceEnterCogCodePopReceiverArg0Regs)(void)';
  		var: #realCEEnterCogCodePopReceiverArg0Regs
  			declareC: 'void (*realCEEnterCogCodePopReceiverArg0Regs)(void)';
  		var: #ceEnterCogCodePopReceiverArg1Arg0Regs
  			declareC: 'void (*ceEnterCogCodePopReceiverArg1Arg0Regs)(void)';
  		var: #realCEEnterCogCodePopReceiverArg1Arg0Regs
  			declareC: 'void (*realCEEnterCogCodePopReceiverArg1Arg0Regs)(void)';
  		var: 'simStack'
+ 			declareC: 'CogSimStackEntry simStack[', ((CoInterpreter bindingOf: #LargeContextSize) value * 5 / 4 // BytesPerWord) asString, ']';
- 			declareC: 'CogSimStackEntry simStack[256]';
  		var: 'simSelf'
  			type: #CogSimStackEntry;
  		var: #optStatus
  			type: #CogSSOptStatus.
  
  	aCodeGen
  		addSelectorTranslation: #register to: (aCodeGen cFunctionNameFor: 'registerr');
  		addSelectorTranslation: #register: to: (aCodeGen cFunctionNameFor: 'registerr:')!

Item was changed:
  ----- Method: ThreadedFFICalloutStateForARM class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a ReentrantFFICalloutState struct."
  
  	superclass instVarNamesAndTypesForTranslationDo: aBinaryBlock.
  	self instVarNames do:
  		[:ivn|
  		aBinaryBlock
  			value: ivn
  			value: (ivn caseOf: {
+ 						['integerRegisters']	-> [{#sqInt. '[', ThreadedARMFFIPlugin numRegArgs printString, ']'}] }
- 						['integerRegisters']	-> [{#sqInt. '[', ReentrantARMFFIPlugin numRegArgs printString, ']'}] }
  					otherwise:
  						[#sqInt])]!

Item was changed:
  ----- Method: ThreadedFFICalloutStateForPPC class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a ReentrantFFICalloutState struct."
  
  	superclass instVarNamesAndTypesForTranslationDo: aBinaryBlock.
  	self instVarNames do:
  		[:ivn|
  		aBinaryBlock
  			value: ivn
  			value: (ivn caseOf: {
+ 						['integerRegisters']	-> [{#sqInt. '[', ThreadedPPCBEFFIPlugin numRegArgs printString, ']'}].
+ 						['floatRegisters']		-> [{#double. '[', ThreadedPPCBEFFIPlugin numRegArgs printString, ']'}] }
- 						['integerRegisters']	-> [{#sqInt. '[', ReentrantPPCBEFFIPlugin numRegArgs printString, ']'}].
- 						['floatRegisters']		-> [{#double. '[', ReentrantPPCBEFFIPlugin numRegArgs printString, ']'}] }
  					otherwise:
  						[#sqInt])]!



More information about the Vm-dev mailing list