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

commits at source.squeak.org commits at source.squeak.org
Wed Jul 17 21:05:05 UTC 2013


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

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

Name: VMMaker.oscog-eem.305
Author: eem
Time: 17 July 2013, 2:02:59.495 pm
UUID: ca4b6f0d-e113-4cd5-b859-527f897bd29b
Ancestors: VMMaker.oscog-eem.304

Limit the ammount of space the Cogit will stack allocate when compiling.
This limits the maximum number of bytecodes in a method that the
Cogit will compile.  Currently set at 1.5Mb of stack space from empirical
tests of alloca on Mac OS X 10.6, linux 2.6 & Windows XP.

Merge initializeCompilationWithConstantsOptions: into
initializeMiscConstantsWith:.

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

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 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 YoungSelectorInPIC'
- 	classVariableNames: 'AltBlockCreationBytecodeSize AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration EncounteredUnknownBytecode FirstAnnotation HasBytecodePC InsufficientCodeSpace IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxNegativeErrorCode MaxUnitDisplacement MaxX2NDisplacement MethodTooBig NSSendIsPCAnnotated 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 removed:
- ----- Method: Cogit class>>initializeCompilationWithConstantsOptions: (in category 'class initialization') -----
- initializeCompilationWithConstantsOptions: optionsDictionary
- 	ProcessorClass := (optionsDictionary at: #ISA ifAbsent: [#IA32]) caseOf: {
- 							[#IA32] 	->	[BochsIA32Alien].
- 							[#ARMv5]	->	[GdbARMAlien]. }.
- 	NumSendTrampolines := 4!

Item was changed:
  ----- Method: Cogit class>>initializeMiscConstantsWith: (in category 'class initialization') -----
  initializeMiscConstantsWith: optionsDictionary
  	super initializeMiscConstantsWith: optionsDictionary.
  	Debug := optionsDictionary at: #Debug ifAbsent: [false].
  	(optionsDictionary includesKey: #EagerInstructionDecoration)
  		ifTrue:
  			[EagerInstructionDecoration := optionsDictionary at: #EagerInstructionDecoration]
  		ifFalse:
  			[EagerInstructionDecoration isNil ifTrue:
  				[EagerInstructionDecoration := false]]. "speeds up single stepping but could lose fidelity"
  
+ 	ProcessorClass := (optionsDictionary at: #ISA ifAbsent: [#IA32]) caseOf: {
+ 							[#IA32] 	->	[BochsIA32Alien].
+ 							[#ARMv5]	->	[GdbARMAlien]. }.
+ 	"we special-case 0, 1 & 2 argument sends, N is numArgs >= 3"
+ 	NumSendTrampolines := 4.
  	"Currently only the ceImplicitReceiverTrampoline contains object references."
+ 	NumObjRefsInRuntime := 2.
+ 	"Max size to alloca when compiling.
+ 	 Mac OS X 10.6.8 segfaults approaching 8Mb.
+ 	 Linux 2.6.9 segfaults above 11Mb.
+ 	 WIndows XP segfaults approaching 2Mb."
+ 	MaxStackAllocSize := 1024 * 1024 * 3 / 2 !
- 	NumObjRefsInRuntime := 2!

Item was changed:
  ----- Method: Cogit class>>initializeWithOptions: (in category 'class initialization') -----
  initializeWithOptions: optionsDictionary
  
  	self initializeMiscConstantsWith: optionsDictionary. "must preceed other initialization."
  	self initializeErrorCodes.
  	self initializeCogMethodConstants.
  	self initializeAnnotationConstants.
- 	self initializeCompilationWithConstantsOptions: optionsDictionary.
  	self initializeBytecodeTable.
  	self initializePrimitiveTable!

Item was added:
+ ----- Method: Cogit>>allocateOpcodes:bytecodes:ifFail: (in category 'initialization') -----
+ allocateOpcodes: numberOfAbstractOpcodes bytecodes: numberOfBytecodes ifFail: failBlock
+ 	"Allocate the various arrays needed to compile abstract instructions.
+ 	 This needs to be a macro since the arrays are alloca'ed (stack allocated)
+ 	 to ensure their being freed when compilation is done.
+ 	 Notionally we only need as many fixups as there are bytecodes.  But we
+ 	 reuse fixups to record pc-dependent instructions in generateInstructionsAt:
+ 	 and so need at least as many as there are abstract opcodes.
+ 
+ 	 N.B. We do one single alloca to save embarrassing C optimizers that
+ 	 generate incorrect code as both gcc and the intel compiler do on x86."
+ 	<cmacro: '(numberOfAbstractOpcodes,numberOfBytecodes,failBlock) do { \
+ 		int opcodeSize = sizeof(AbstractInstruction) * (numAbstractOpcodes = (numberOfAbstractOpcodes)); \
+ 		int fixupSize = sizeof(BytecodeFixup) * numAbstractOpcodes; \
+ 		int annotationSize = sizeof(InstructionAnnotation) * ((numAbstractOpcodes + 3) / 4); \
+ 		int allocSize = opcodeSize + fixupSize + annotationSize; \
+ 		if (allocSize > MaxStackAllocSize) failBlock; \
+ 		abstractOpcodes = alloca(allocSize); \
+ 		bzero(abstractOpcodes, opcodeSize + fixupSize); \
+ 		fixups = (void *)((char *)abstractOpcodes + opcodeSize); \
+ 		annotations = (void *)((char *)fixups + fixupSize); \
+ 		opcodeIndex = labelCounter = annotationIndex = 0; \
+ } while (0)'>
+ 	| opcodeSize fixupSize annotationSize allocSize |
+ 	opcodeSize := (self sizeof: #AbstractInstruction) * numberOfAbstractOpcodes.
+ 	fixupSize := (self sizeof: #BytecodeFixup) * numberOfAbstractOpcodes.
+ 	annotationSize := (self sizeof: #InstructionAnnotation) * ((numberOfAbstractOpcodes + 3) / 4).
+ 	allocSize := opcodeSize + fixupSize + annotationSize.
+ 	allocSize > MaxStackAllocSize ifTrue: [^failBlock value].
+ 	numAbstractOpcodes := numberOfAbstractOpcodes.
+ 	abstractOpcodes := CArrayAccessor on:
+ 						((1 to: numAbstractOpcodes) collect:
+ 							[:ign| processor abstractInstructionCompilerClass for: self]).
+ 	fixups := CArrayAccessor on:
+ 						((1 to: numAbstractOpcodes) collect:
+ 							[:ign| self bytecodeFixupClass new]).
+ 	annotations := CArrayAccessor on:
+ 						((1 to: numAbstractOpcodes + 3 // 4) collect:
+ 							[:ign| CogInstructionAnnotation new]).
+ 	opcodeIndex := labelCounter := annotationIndex := 0!

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
+ 		ifFail: [^coInterpreter cCoerceSimple: MethodTooBig to: #'CogMethod *'].
- 	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!



More information about the Vm-dev mailing list