VM Maker: VMMaker.oscog-eem.754.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-eem.754.mcz

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

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

Name: VMMaker.oscog-eem.754
Author: eem
Time: 3 June 2014, 3:24:19.178 pm
UUID: d9c78dfc-173f-43b0-8568-52f5cfd95c05
Ancestors: VMMaker.oscog-eem.753

Fix the abort sequence for RISCs.  The assert check on the
sendMissCall requires that sendMissCall means the
sendMissCall. But on RISCs we must push the link reg before
calling it.  Hence we need a sendMiss label.

Fix the offset of numCounters in the method surrogates to
fix Sista Spur.

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

Item was changed:
  ----- Method: CogSistaMethodSurrogate32>>numCounters (in category 'accessing') -----
  numCounters
+ ^memory unsignedLongAt: address + 21 + baseHeaderSize!
- ^memory unsignedLongAt: address + 25!

Item was changed:
  ----- Method: CogSistaMethodSurrogate32>>numCounters: (in category 'accessing') -----
  numCounters: aValue
  ^memory
+ unsignedLongAt: address + 21 + baseHeaderSize
- unsignedLongAt: address + 25
  put: aValue!

Item was changed:
  ----- Method: CogSistaMethodSurrogate64>>numCounters (in category 'accessing') -----
  numCounters
+ ^memory unsignedLongLongAt: address + 33 + baseHeaderSize!
- ^memory unsignedLongLongAt: address + 41!

Item was changed:
  ----- Method: CogSistaMethodSurrogate64>>numCounters: (in category 'accessing') -----
  numCounters: aValue
  ^memory
+ unsignedLongLongAt: address + 33 + baseHeaderSize
- unsignedLongLongAt: address + 41
  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 traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent usesMethodClass primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss 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 ceEnterCogCodePopReceiverReg ceEnterCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline 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 ceEnterCogCodePopReceiverReg ceEnterCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline 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 sendMiss sendMissCall entry noCheckEntry dynSuperEntry
- 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: #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:
  [:bytecodeGenTable|
  aCCodeGenerator
  var: #generatorTable
  declareC: 'BytecodeDescriptor generatorTable[', bytecodeGenTable size, ']',
  (self tableInitializerFor: bytecodeGenTable
  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>>compileAbort (in category 'compile abstract instructions') -----
  compileAbort
  "The start of a CogMethod has a call to a run-time abort routine that either
  handles an in-line cache failure or a stack overflow.  The routine selects the
  path depending on ReceiverResultReg; if zero it takes the stack overflow
  path; if nonzero the in-line cache miss path.  Neither of these paths returns.
  The abort routine must be called;  In the callee the method is located by
  adding the relevant offset to the return address of the call."
  stackOverflowCall := self MoveCq: 0 R: ReceiverResultReg.
+ backEnd hasLinkRegister
+ ifTrue:
+ [sendMiss := self PushR: LinkReg.
+ sendMissCall := self Call: (self methodAbortTrampolineFor: methodOrBlockNumArgs)]
+ ifFalse:
+ [sendMiss :=
+ sendMissCall := self Call: (self methodAbortTrampolineFor: methodOrBlockNumArgs)]!
- backEnd hasLinkRegister ifTrue:
- [self PushR: LinkReg].
- sendMissCall := self Call: (self methodAbortTrampolineFor: methodOrBlockNumArgs)!

Item was changed:
  ----- Method: Cogit>>compileEntry (in category 'compile abstract instructions') -----
  compileEntry
  "The entry code to a method checks that the class of the current receiver matches
  that in the inline cache.  Other non-obvious elements are that its alignment must be
  different from the alignment of the noCheckEntry so that the method map machinery
  can distinguish normal and super sends (super sends bind to the noCheckEntry).
  In Newspeak we also need to distinguish dynSuperSends from normal and super
  and so bind a the preceeding nop (on x86 there happens to be one anyway)."
 
  self cppIf: NewspeakVM ifTrue:
  [self Nop. "1st nop differentiates dynSuperEntry from no-check entry if using nextMethod"
  dynSuperEntry := self Nop].
  entry := objectRepresentation getInlineCacheClassTagFrom: ReceiverResultReg into: TempReg.
  self CmpR: ClassReg R: TempReg.
+ self JumpNonZero: sendMiss.
- self JumpNonZero: sendMissCall.
  noCheckEntry := self Label.
  self recordSendTrace ifTrue:
  [self CallRT: ceTraceLinkedSendTrampoline]!