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

commits at source.squeak.org commits at source.squeak.org
Sat May 31 17:20:40 UTC 2014


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

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

Name: VMMaker.oscog-eem.739
Author: eem
Time: 31 May 2014, 10:17:47.951 am
UUID: 122f7bd7-99a3-48e6-856a-bd4a90cda75a
Ancestors: VMMaker.oscog-dtl.738

Refactor ceCreateNewArray & cePositive32BitInteger
trampolines, moving them into the object representations as
required (cePositive32BitInteger is only used in the Squeak
obj rep).  In the Spur obj rep inline allocation in pushNewArray
bytecodes.  This as a test case for allocating closures and
contexts in machine-code.

Fix simulated call of checkSegments.

=============== Diff against VMMaker.oscog-dtl.738 ===============

Item was added:
+ ----- Method: CogObjectRepresentation>>genNewArrayOfSize:initialized: (in category 'bytecode generator support') -----
+ genNewArrayOfSize: size initialized: initialized
+ 	"Generate a call to code that allocates a new Array of size.
+ 	 The Array should be initialized with nils iff initialized is true.
+ 	 The size arg is passed in SendNumArgsReg, the result
+ 	 must come back in ReceiverResultReg."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genNewArrayOfSize:initialized: (in category 'bytecode generator support') -----
+ genNewArrayOfSize: size initialized: initialized
+ 	"Generate a call to code that allocates a new Array of size.
+ 	 The Array should be initialized with nils iff initialized is true.
+ 	 The size arg is passed in SendNumArgsReg, the result
+ 	 must come back in ReceiverResultReg."
+ 	| header headerLow headerHigh byteSize skip |
+ 	<var: #skip type: #'AbstractInstruction *'>
+ 	self assert: size < objectMemory numSlotsMask.
+ 	header := objectMemory
+ 					headerForSlots: size
+ 					format: objectMemory arrayFormat
+ 					classIndex: ClassArrayCompactIndex.
+ 	headerLow := self cCoerceSimple: header to: #usqInt.
+ 	headerHigh := header >> 32.
+ 	byteSize := (size max: 1) + 3 >> 1 * 8. "round up to 8 bytes and add 8 bytes of header"
+ 	self flag: #endianness.
+ 	cogit
+ 		MoveAw: objectMemory freeStartAddress R: ReceiverResultReg;
+ 		MoveCq: headerLow R: TempReg;
+ 		MoveR: TempReg Mw: 0 r: ReceiverResultReg;
+ 		MoveCq: headerHigh R: TempReg;
+ 		MoveR: TempReg Mw: 4 r: ReceiverResultReg.
+ 	(initialized and: size > 0) ifTrue:
+ 		[cogit MoveCw: objectMemory nilObject R: TempReg.
+ 		 1 to: size do:
+ 			[:i| cogit MoveR: TempReg Mw: i * 4 + 4 r: ReceiverResultReg]].
+ 	cogit
+ 		MoveR: ReceiverResultReg R: TempReg;
+ 		AddCq: byteSize R: TempReg;
+ 		MoveR: TempReg Aw: objectMemory freeStartAddress;
+ 		CmpCq: objectMemory getScavengeThreshold R: TempReg.
+ 	skip := cogit JumpLess: 0.
+ 	cogit CallRT: ceSheduleScavengeTrampoline.
+ 	skip jmpTarget: cogit Label.
+ 	^0!

Item was changed:
  CogObjectRepresentation subclass: #CogObjectRepresentationForSpur
+ 	instanceVariableNames: 'ceSheduleScavengeTrampoline'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: 'CogCompilationConstants VMSqueakClassIndices'
  	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>generateObjectRepresentationTrampolines (in category 'initialization') -----
+ generateObjectRepresentationTrampolines
+ 	super generateObjectRepresentationTrampolines.
+ 	ceSheduleScavengeTrampoline := cogit
+ 											genSafeTrampolineFor: #ceSheduleScavenge
+ 											called: 'ceSheduleScavengeTrampoline'!

Item was changed:
  CogObjectRepresentation subclass: #CogObjectRepresentationForSqueakV3
+ 	instanceVariableNames: 'ceCreateNewArrayTrampoline cePositive32BitIntegerTrampoline'
- 	instanceVariableNames: ''
  	classVariableNames: 'RootBitDigitLength'
  	poolDictionaries: 'VMSqueakClassIndices VMSqueakV3ObjectRepresentationConstants'
  	category: 'VMMaker-JIT'!
  
  !CogObjectRepresentationForSqueakV3 commentStamp: '<historical>' prior: 0!
  Read my superclass' class comment.  I am a CogObjectRepresentation for the Squeak V3 object representation.!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>genInnerPrimitiveAt: (in category 'primitive generators') -----
  genInnerPrimitiveAt: retNoffset
  	| jumpSI jumpNotSI jumpNotIndexable jumpIsContext jumpBounds jumpFmtGt4 jumpFmtEq2 jumpFmtLt8 jumpFmtGt11 jumpLarge |
  	"c.f. StackInterpreter>>stSizeOf: lengthOf:baseHeader:format: fixedFieldsOf:format:length:"
  	<var: #jumpSI type: #'AbstractInstruction *'>
  	<var: #jumpNotSI type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
  	<var: #jumpIsContext type: #'AbstractInstruction *'>
  	<var: #jumpBounds type: #'AbstractInstruction *'>
  	<var: #jumpFmtGt4 type: #'AbstractInstruction *'>
  	<var: #jumpFmtEq2 type: #'AbstractInstruction *'>
  	<var: #jumpFmtLt8 type: #'AbstractInstruction *'>
  	<var: #jumpFmtGt11 type: #'AbstractInstruction *'>
  	<var: #jumpLarge type: #'AbstractInstruction *'>
  	cogit MoveR: ReceiverResultReg R: TempReg.
  	jumpSI := self genJumpSmallIntegerInScratchReg: TempReg.
  	cogit MoveR: Arg0Reg R: TempReg.
  	cogit MoveR: Arg0Reg R: Arg1Reg.
  	jumpNotSI := self genJumpNotSmallIntegerInScratchReg: TempReg.
  	self
  		genGetSizeOf: ReceiverResultReg
  		into: ClassReg
  		formatReg: SendNumArgsReg
  		scratchReg: TempReg
  		abortJumpsInto: [:jnx :jic| jumpNotIndexable := jnx. jumpIsContext := jic].
  	self genConvertSmallIntegerToIntegerInReg: Arg1Reg.
  	cogit SubCq: 1 R: Arg1Reg.
  	cogit CmpR: ClassReg R: Arg1Reg.
  	jumpBounds := cogit JumpAboveOrEqual: 0.
  	"This is tedious.  Because of register pressure on x86 (and the baroque
  	 complexity of the size computation) we have to recompute the format
  	 because it may have been smashed computing the fixed fields.  But at
  	 least we have the fixed fields, if any, in formatReg and recomputing
  	 these is more expensive than recomputing format.  In any case this
  	 should still be faster than the interpreter and we hope this object
  	 representation's days are numbered."
  	cogit
  		MoveMw: 0 r: ReceiverResultReg R: ClassReg;	"self baseHeader: receiver"
  		LogicalShiftRightCq: objectMemory instFormatFieldLSB R: ClassReg;
  		AndCq: self instFormatFieldMask R: ClassReg;	"self formatOfHeader: ClassReg"
  		CmpCq: 4 R: ClassReg.
  	jumpFmtGt4 := cogit JumpGreater: 0.
  	cogit CmpCq: 2 R: ClassReg.	"Common case, e.g. Array, has format = 2"
  	jumpFmtEq2 := cogit JumpZero: 0.
  	cogit AddR: SendNumArgsReg R: Arg1Reg. "Add fixed fields to index"
  	jumpFmtEq2 jmpTarget: cogit Label.
  	cogit "Too lazy [knackered, more like. ed.] to define index with displacement addressing right now"
  		AddCq: BaseHeaderSize / BytesPerWord R: Arg1Reg;
  		MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg;
  		RetN: retNoffset.
  	jumpFmtGt4 jmpTarget: cogit Label.
  	"Byte objects have formats 8 through 15, Compiled methods being 12 through 15;
  	 fail for CompiledMethod allowing the CoInterpeter to impose stricter bounds checks."
  	cogit CmpCq: 8 R: ClassReg.
  	jumpFmtLt8 := cogit JumpLess: 0.
  	cogit CmpCq: 11 R: ClassReg.
  	jumpFmtGt11 := cogit JumpGreater: 0.
  	cogit
  		AddCq: BaseHeaderSize R: Arg1Reg;
  		MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
  	self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
  	cogit RetN: retNoffset.
  	jumpFmtLt8 jmpTarget: cogit Label.
  	self assert: BytesPerWord = 4. "documenting my laziness"
  	cogit "Too lazy [knackered, more like. ed.] to define index with displacement addressing right now"
  		AddCq: BaseHeaderSize / BytesPerWord R: Arg1Reg;
  		MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg;
  		CmpCq: 16r3FFFFFFF R: ReceiverResultReg.
  	jumpLarge := cogit JumpAbove: 0.
  	self genConvertIntegerToSmallIntegerInScratchReg: ReceiverResultReg.
  	cogit RetN: retNoffset.
+ 	jumpLarge jmpTarget: (cogit CallRT: cePositive32BitIntegerTrampoline).
- 	jumpLarge jmpTarget: (cogit CallRT: cogit cePositive32BitIntegerTrampoline).
  	cogit
  		MoveR: TempReg R: ReceiverResultReg;
  		RetN: retNoffset.
  	jumpSI jmpTarget:
  	(jumpNotSI jmpTarget:
  	(jumpNotIndexable jmpTarget:
  	(jumpIsContext jmpTarget:
  	(jumpBounds jmpTarget:
  	(jumpFmtGt11 jmpTarget:
  		cogit Label))))).
  	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genNewArrayOfSize:initialized: (in category 'bytecode generator support') -----
+ genNewArrayOfSize: size initialized: initialized
+ 	"Generate a call to code that allocates a new Array of size.
+ 	 The Array should be initialized with nils iff initialized is true.
+ 	 The size arg is passed in SendNumArgsReg, the result
+ 	 must come back in ReceiverResultReg."
+ 	cogit
+ 		MoveCq: size R: SendNumArgsReg;
+ 		CallRT: ceCreateNewArrayTrampoline!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>generateObjectRepresentationTrampolines (in category 'in-line cacheing') -----
+ generateObjectRepresentationTrampolines
+ 	super generateObjectRepresentationTrampolines.
+ 	ceCreateNewArrayTrampoline := cogit genTrampolineFor: #ceNewArraySlotSize:
+ 											called: 'ceCreateNewArrayTrampoline'
+ 											arg: SendNumArgsReg
+ 											result: ReceiverResultReg.
+ 	cePositive32BitIntegerTrampoline := cogit genTrampolineFor: #cePositive32BitIntegerFor:
+ 											called: 'cePositive32BitIntegerTrampoline'
+ 											arg: ReceiverResultReg
+ 											result: TempReg!

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 usesMethodClass primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment 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 ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceClosureCopyTrampoline 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'
- 	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 usesMethodClass primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment 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 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 AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration EncounteredUnknownBytecode FirstAnnotation HasBytecodePC InsufficientCodeSpace IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxNegativeErrorCode MaxStackAllocSize MaxUnitDisplacement MaxX2NDisplacement MethodTooBig NSSendIsPCAnnotated NotFullyInitialized NumObjRefsInRuntime NumSendTrampolines NumTrampolines ProcessorClass UnimplementedPrimitive YoungSelectorInPIC'
  	poolDictionaries: 'CogCompilationConstants 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>>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 removeConstant: #COGMTVM. "this should be defined at compile time"
  	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 * const backEnd = &aMethodLabel';
  		var: #methodLabel declareC: 'AbstractInstruction * const 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
  			type: #int;
  		var: #traceFlags
  			declareC: 'int traceFlags = 8 /* 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 vmClass generatorTable ifNotNil:
  		[:generatorTable|
  		aCCodeGenerator
  			var: #generatorTable
  				declareC: 'BytecodeDescriptor generatorTable[', aCCodeGenerator vmClass generatorTable size, ']'
  							, (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 removed:
- ----- Method: Cogit>>cePositive32BitIntegerTrampoline (in category 'accessing') -----
- cePositive32BitIntegerTrampoline
- 	<cmacro: '() cePositive32BitIntegerTrampoline'>
- 	^cePositive32BitIntegerTrampoline!

Item was added:
+ ----- Method: Cogit>>genSafeTrampolineFor:called: (in category 'initialization') -----
+ genSafeTrampolineFor: aRoutine called: aString
+ 	"Generate a trampoline with no arguments that will
+ 	 save and restore all registers around the call"
+ 	<var: #aRoutine type: #'void *'>
+ 	<var: #aString type: #'char *'>
+ 	^self
+ 		genTrampolineFor: aRoutine
+ 		called: aString
+ 		callJumpBar: true
+ 		numArgs: 0
+ 		arg: nil
+ 		arg: nil
+ 		arg: nil
+ 		arg: nil
+ 		saveRegs: true
+ 		resultReg: nil
+ 		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>generateRunTimeTrampolines (in category 'initialization') -----
  generateRunTimeTrampolines
  	"Generate the run-time entries at the base of the native code zone and update the base."
  	
  	ceSendMustBeBooleanAddFalseTrampoline := self genMustBeBooleanTrampolineFor: objectMemory falseObject
  														called: 'ceSendMustBeBooleanAddFalseTrampoline'.
  	ceSendMustBeBooleanAddTrueTrampoline := self genMustBeBooleanTrampolineFor: objectMemory trueObject
  														called: 'ceSendMustBeBooleanAddTrueTrampoline'.
  	ceClosureCopyTrampoline := self genTrampolineFor: #ceClosureCopyDescriptor:
  									called: 'ceClosureCopyTrampoline'
  									arg: SendNumArgsReg
  									result: ReceiverResultReg.
  	ceActiveContextTrampoline := self genActiveContextTrampoline.
  	ceNonLocalReturnTrampoline := self genNonLocalReturnTrampoline.
  	ceBaseFrameReturnTrampoline := self genTrampolineFor: #ceBaseFrameReturn:
  										called: 'ceBaseFrameReturnTrampoline'
  										arg: ReceiverResultReg.
- 	ceCreateNewArrayTrampoline := self genTrampolineFor: #ceNewArraySlotSize:
- 										called: 'ceCreateNewArrayTrampoline'
- 										arg: SendNumArgsReg
- 										result: ReceiverResultReg.
  	ceCheckForInterruptTrampoline := self genCheckForInterruptsTrampoline.
  	ceFetchContextInstVarTrampoline := self genTrampolineFor: #ceContext:instVar:
  											called: 'ceFetchContextInstVarTrampoline'
  											arg: ReceiverResultReg
  											arg: SendNumArgsReg
  											result: SendNumArgsReg.
  	ceStoreContextInstVarTrampoline := self genTrampolineFor: #ceContext:instVar:value:
  											called: 'ceStoreContextInstVarTrampoline'
  											arg: ReceiverResultReg
  											arg: SendNumArgsReg
  											arg: ClassReg
  											result: ReceiverResultReg. "to keep ReceiverResultReg live."
- 	cePositive32BitIntegerTrampoline := self genTrampolineFor: #cePositive32BitIntegerFor:
- 											called: 'cePositive32BitIntegerTrampoline'
- 											arg: ReceiverResultReg
- 											result: TempReg.
  	ceReturnToInterpreterTrampoline := self genTrampolineFor: #ceReturnToInterpreter:
  											called: 'ceReturnToInterpreterTrampoline'
  											arg: ReceiverResultReg.
  	ceCannotResumeTrampoline := self genTrampolineFor: #ceCannotResume
  											called: 'ceCannotResumeTrampoline'!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPushNewArrayBytecode (in category 'bytecode generators') -----
  genPushNewArrayBytecode
  	| size popValues |
  	self assert: needsFrame.
  	popValues := byte1 > 127.
  	size := byte1 bitAnd: 127.
+ 	objectRepresentation genNewArrayOfSize: size initialized: popValues not.
- 	self MoveCq: size R: SendNumArgsReg.
- 	self CallRT: ceCreateNewArrayTrampoline.
  	popValues ifTrue:
  		[size - 1 to: 0 by: -1 do:
  			[:i|
  			self PopR: TempReg.
  			objectRepresentation
  				genStoreSourceReg: TempReg
  				slotIndex: i
  				intoNewObjectInDestReg: ReceiverResultReg]].
  	self PushR: ReceiverResultReg.
  	^0!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>ceSheduleScavenge (in category 'trampolines') -----
+ ceSheduleScavenge
+ 	<api>
+ 	self assert: freeStart >= scavengeThreshold.
+ 	self scheduleScavenge!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>scavengeThresholdAddress (in category 'trampoline support') -----
+ scavengeThresholdAddress
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^self cCode: [(self addressOf: scavengeThreshold) asUnsignedInteger]
+ 		inSmalltalk: [cogit simulatedReadWriteVariableAddress: #getScavengeThreshold in: self]!

Item was changed:
  ----- Method: SpurMemoryManager>>growOldSpaceByAtLeast: (in category 'growing/shrinking memory') -----
  growOldSpaceByAtLeast: minAmmount
  	"Attempt to grow memory by at least minAmmount.
  	 Answer the size of the new segment, or nil if the attempt failed."
  	| ammount |
  	<var: #segInfo type: #'SpurSegmentInfo *'>
  	"statGrowMemory counts attempts, not successes."
  	statGrowMemory := statGrowMemory + 1.
  	"we need to include overhead for a new object header plus the segment bridge."
  	ammount := minAmmount + (self baseHeaderSize * 2 + self bridgeSize).
  	"round up to the nearest power of two."
  	ammount := 1 << (ammount - 1) highBit.
  	"and grow by at least growHeadroom."
  	ammount := ammount max: growHeadroom.
  	^(segmentManager addSegmentOfSize: ammount) ifNotNil:
  		[:segInfo|
  		 self assimilateNewSegment: segInfo.
  		 "and add the new free chunk to the free list; done here
  		  instead of in assimilateNewSegment: for the assert"
  		 self addFreeChunkWithBytes: segInfo segSize - self bridgeSize at: segInfo segStart.
  		 self assert: (self addressAfter: (self objectStartingAt: segInfo segStart))
  					= (segInfo segLimit - self bridgeSize).
  		 self checkFreeSpace.
+ 		 segmentManager checkSegments.
- 		 self checkSegments.
  		 segInfo segSize]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPushNewArrayBytecode (in category 'bytecode generators') -----
  genPushNewArrayBytecode
  	| size popValues |
  	self assert: needsFrame.
  	optStatus isReceiverResultRegLive: false.
  	(popValues := byte1 > 127)
  		ifTrue: [self ssFlushTo: simStackPtr]
  		ifFalse: [self ssAllocateCallReg: SendNumArgsReg and: ReceiverResultReg].
  	size := byte1 bitAnd: 127.
+ 	objectRepresentation genNewArrayOfSize: size initialized: popValues not.
- 	self MoveCq: size R: SendNumArgsReg.
- 	self CallRT: ceCreateNewArrayTrampoline.
  	popValues ifTrue:
  		[size - 1 to: 0 by: -1 do:
  			[:i|
  			self PopR: TempReg.
  			objectRepresentation
  				genStoreSourceReg: TempReg
  				slotIndex: i
  				intoNewObjectInDestReg: ReceiverResultReg].
  		 self ssPop: size].
  	^self ssPushRegister: ReceiverResultReg!



More information about the Vm-dev mailing list