[Vm-dev] VM Maker: VMMaker.oscog-cb.2219.mcz

Eliot Miranda eliot.miranda at gmail.com
Mon May 22 18:43:10 UTC 2017


Woot!

_,,,^..^,,,_ (phone)

> On May 22, 2017, at 7:07 AM, commits at source.squeak.org wrote:
> 
> 
> ClementBera uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-cb.2219.mcz
> 
> ==================== Summary ====================
> 
> Name: VMMaker.oscog-cb.2219
> Author: cb
> Time: 22 May 2017, 5:06:35.456414 pm
> UUID: c5c5f727-9862-4164-9721-104ccd73f9bc
> Ancestors: VMMaker.oscog-eem.2218
> 
> Modified with Sophie K the collectCogConstituents primitive to take a boolean parameter "withDetails". If false or no parameter, the primitive does the same thing as before. If true, the primitive maps each CogMethod that is frameful to an array starting with the cogMethod address followed by a mapping between the mcpc and the bcpc instead of just the cogMethod address.
> 
> Minor fix in register in branchIfInstanceOf: in SistaCogit for Characters.
> 
> =============== Diff against VMMaker.oscog-eem.2218 ===============
> 
> Item was changed:
>  ----- Method: CoInterpreterPrimitives>>primitiveCollectCogCodeConstituents (in category 'process primitives') -----
>  primitiveCollectCogCodeConstituents
>      "Answer the contents of the code zone as an array of pair-wise element, address in ascending address order.
>       Answer a string for a runtime routine or abstract label (beginning, end, etc), a CompiledMethod for a CMMethod,
> +     or a selector (presumably a Symbol) for a PIC.
> +     If the last argument (or the receiver if no arguments) is true, then collect inner information about the CogMethod."
> +    | constituents withDetails |
> +    withDetails := self stackTop.
> +    constituents := cogit cogCodeConstituents: (withDetails = objectMemory trueObject).
> -     or a selector (presumably a Symbol) for a PIC."
> -    | constituents |
> -    constituents := cogit cogCodeConstituents.
>      constituents ifNil:
>          [^self primitiveFailFor: PrimErrNoMemory].
>      self pop: 1 thenPush: constituents!
> 
> Item was changed:
>  ----- Method: CogObjectRepresentationFor32BitSpur>>branchIf:hasNotImmediateTag:target: (in category 'sista support') -----
>  branchIf: reg hasNotImmediateTag: classIndex target: targetFixUp
>      <var: #targetFixUp type: #'AbstractInstruction *'>
>      | jmpImmediate |
>      <inline: true>
>      classIndex = objectMemory smallIntegerTag ifTrue:
>          [jmpImmediate := self genJumpNotSmallInteger: reg].
>      classIndex = objectMemory characterTag ifTrue:
> +        ["Character test destroy register value in Spur"
> +         cogit MoveR: reg R: TempReg.
> +         jmpImmediate := self genJumpNotCharacterInScratchReg: TempReg].
> -        [cogit MoveR: reg R: TempReg.
> -         jmpImmediate := self genJumpNotCharacterInScratchReg: reg].
>      jmpImmediate jmpTarget: targetFixUp!
> 
> 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 enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cP
> ICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointers ordinarySendTrampolines superSen
> dTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline debugBytecodePointers debugOpcodeIndices disassemblingMethod cogConstituentIndex'
> -    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 enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cP
> ICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointers ordinarySendTrampolines superSen
> dTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline debugBytecodePointers debugOpcodeIndices disassemblingMethod'
>      classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCPICCases MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass RRRName'
>      poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants VMObjectIndices VMStackFrameOffsets'
>      category: 'VMMaker-JIT'!
>  Cogit class
>      instanceVariableNames: 'generatorTable primitiveTable'!
> 
>  !Cogit commentStamp: 'eem 2/25/2017 17:53' 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.
> 
>      SistaCogit is an experimental code generator with support for counting
>      conditional branches, intended to support adaptive optimization.
> 
>      RegisterAllocatingCogit is an experimental code generator with support for allocating temporary variables
>      to registers. It is inended to serve as the superclass to SistaCogit once it is working.
> 
>      SistaRegisterAllocatingCogit and SistaCogitClone are temporary classes that allow testing a clone of
>      SistaCogit that inherits from RegisterAllocatingCogit.  Once things work these will be merged and
>      will replace SistaCogit.
> 
>  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.  fixups has one element per byte in methodObj's bytecode; initialPC maps to fixups[0].
>  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 eventually the 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>>cogCodeConstituents (in category 'profiling primitives') -----
> - cogCodeConstituents
> -    "Answer the contents of the code zone as an array of pair-wise element, address in ascending address order.
> -     Answer a string for a runtime routine or abstract label (beginning, end, etc), a CompiledMethod for a CMMethod,
> -     or a selector (presumably a Symbol) for a PIC."
> -    <api>
> -    | count cogMethod constituents label value |
> -    <var: #cogMethod type: #'CogMethod *'>
> -    count := trampolineTableIndex / 2 + 3. "+ 3 for start, freeStart and end"
> -    cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
> -    [cogMethod < methodZone limitZony] whileTrue:
> -        [cogMethod cmType ~= CMFree ifTrue:
> -            [count := count + 1].
> -        cogMethod := methodZone methodAfter: cogMethod].
> -    constituents := coInterpreter instantiateClass: coInterpreter classArray indexableSize: count * 2.
> -    constituents ifNil:
> -        [^constituents].
> -    coInterpreter pushRemappableOop: constituents.
> -    ((label := objectMemory stringForCString: 'CogCode') isNil
> -     or: [(value := self positiveMachineIntegerFor: codeBase) isNil]) ifTrue:
> -        [^nil].
> -    coInterpreter
> -        storePointerUnchecked: 0 ofObject: coInterpreter topRemappableOop withValue: label;
> -        storePointerUnchecked: 1 ofObject: coInterpreter topRemappableOop withValue: value.
> -    0 to: trampolineTableIndex - 1 by: 2 do:
> -        [:i|
> -        ((label := objectMemory stringForCString: (trampolineAddresses at: i)) isNil
> -         or: [(value := self positiveMachineIntegerFor: (trampolineAddresses at: i + 1) asUnsignedInteger) isNil]) ifTrue:
> -            [coInterpreter popRemappableOop.
> -             ^nil].
> -        coInterpreter
> -            storePointerUnchecked: 2 + i ofObject: coInterpreter topRemappableOop withValue: label;
> -            storePointerUnchecked: 3 + i ofObject: coInterpreter topRemappableOop withValue: value].
> -    count := trampolineTableIndex + 2.
> -    cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
> -    [cogMethod < methodZone limitZony] whileTrue:
> -        [cogMethod cmType ~= CMFree ifTrue:
> -            [coInterpreter
> -                storePointerUnchecked: count
> -                ofObject: coInterpreter topRemappableOop
> -                withValue: (cogMethod cmType = CMMethod
> -                                ifTrue: [cogMethod methodObject]
> -                                ifFalse: [cogMethod selector]).
> -             (value := self positiveMachineIntegerFor: cogMethod asUnsignedInteger) ifNil:
> -                [coInterpreter popRemappableOop.
> -                 ^nil].
> -             coInterpreter
> -                storePointerUnchecked: count + 1
> -                ofObject: coInterpreter topRemappableOop
> -                withValue: value.
> -             count := count + 2].
> -        cogMethod := methodZone methodAfter: cogMethod].
> -    ((label := objectMemory stringForCString: 'CCFree') isNil
> -     or: [(value := self positiveMachineIntegerFor: methodZone zoneFree) isNil]) ifTrue:
> -        [coInterpreter popRemappableOop.
> -         ^nil].
> -    coInterpreter
> -        storePointerUnchecked: count ofObject: coInterpreter topRemappableOop withValue: label;
> -        storePointerUnchecked: count + 1 ofObject: coInterpreter topRemappableOop withValue: value.
> -    ((label := objectMemory stringForCString: 'CCEnd') isNil
> -     or: [(value := self positiveMachineIntegerFor: methodZone zoneEnd) isNil]) ifTrue:
> -        [coInterpreter popRemappableOop.
> -         ^nil].
> -    coInterpreter
> -        storePointerUnchecked: count + 2 ofObject: coInterpreter topRemappableOop withValue: label;
> -        storePointerUnchecked: count + 3 ofObject: coInterpreter topRemappableOop withValue: value.
> -    constituents := coInterpreter popRemappableOop.
> -    coInterpreter beRootIfOld: constituents.
> -    ^constituents!
> 
> Item was added:
> + ----- Method: Cogit>>cogCodeConstituents: (in category 'profiling primitives') -----
> + cogCodeConstituents: withDetails
> +    "Answer the contents of the code zone as an array of pair-wise element, address in ascending address order.
> +     Answer a string for a runtime routine or abstract label (beginning, end, etc), a CompiledMethod for a CMMethod,
> +     or a selector (presumably a Symbol) for a PIC."
> +    <api>
> +    | count cogMethod constituents label value |
> +    <var: #cogMethod type: #'CogMethod *'>
> +    count := trampolineTableIndex / 2 + 3. "+ 3 for start, freeStart and end"
> +    cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
> +    [cogMethod < methodZone limitZony] whileTrue:
> +        [cogMethod cmType ~= CMFree ifTrue:
> +            [count := count + 1].
> +        cogMethod := methodZone methodAfter: cogMethod].
> +    constituents := coInterpreter instantiateClass: coInterpreter classArray indexableSize: count * 2.
> +    constituents ifNil:
> +        [^constituents].
> +    coInterpreter pushRemappableOop: constituents.
> +    ((label := objectMemory stringForCString: 'CogCode') isNil
> +     or: [(value := self positiveMachineIntegerFor: codeBase) isNil]) ifTrue:
> +        [^nil].
> +    coInterpreter
> +        storePointerUnchecked: 0 ofObject: coInterpreter topRemappableOop withValue: label;
> +        storePointerUnchecked: 1 ofObject: coInterpreter topRemappableOop withValue: value.
> +    0 to: trampolineTableIndex - 1 by: 2 do:
> +        [:i|
> +        ((label := objectMemory stringForCString: (trampolineAddresses at: i)) isNil
> +         or: [(value := self positiveMachineIntegerFor: (trampolineAddresses at: i + 1) asUnsignedInteger) isNil]) ifTrue:
> +            [coInterpreter popRemappableOop.
> +             ^nil].
> +        coInterpreter
> +            storePointerUnchecked: 2 + i ofObject: coInterpreter topRemappableOop withValue: label;
> +            storePointerUnchecked: 3 + i ofObject: coInterpreter topRemappableOop withValue: value].
> +    count := trampolineTableIndex + 2.
> +    cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
> +    [cogMethod < methodZone limitZony] whileTrue:
> +        [cogMethod cmType ~= CMFree ifTrue:
> +            [coInterpreter
> +                storePointerUnchecked: count
> +                ofObject: coInterpreter topRemappableOop
> +                withValue: (cogMethod cmType = CMMethod
> +                                ifTrue: [cogMethod methodObject]
> +                                ifFalse: [cogMethod selector]).
> +            value := withDetails
> +                ifFalse: [self positiveMachineIntegerFor: cogMethod asUnsignedInteger]
> +                ifTrue: [self collectCogMethodConstituent: cogMethod].
> +            value ifNil: [coInterpreter popRemappableOop. ^nil].
> +            coInterpreter
> +                        storePointerUnchecked: count + 1
> +                        ofObject: coInterpreter topRemappableOop
> +                        withValue: value.
> +             count := count + 2].
> +        cogMethod := methodZone methodAfter: cogMethod].
> +    ((label := objectMemory stringForCString: 'CCFree') isNil
> +     or: [(value := self positiveMachineIntegerFor: methodZone zoneFree) isNil]) ifTrue:
> +        [coInterpreter popRemappableOop.
> +         ^nil].
> +    coInterpreter
> +        storePointerUnchecked: count ofObject: coInterpreter topRemappableOop withValue: label;
> +        storePointerUnchecked: count + 1 ofObject: coInterpreter topRemappableOop withValue: value.
> +    ((label := objectMemory stringForCString: 'CCEnd') isNil
> +     or: [(value := self positiveMachineIntegerFor: methodZone zoneEnd) isNil]) ifTrue:
> +        [coInterpreter popRemappableOop.
> +         ^nil].
> +    coInterpreter
> +        storePointerUnchecked: count + 2 ofObject: coInterpreter topRemappableOop withValue: label;
> +        storePointerUnchecked: count + 3 ofObject: coInterpreter topRemappableOop withValue: value.
> +    constituents := coInterpreter popRemappableOop.
> +    coInterpreter beRootIfOld: constituents.
> +    ^constituents!
> 
> Item was added:
> + ----- Method: Cogit>>collectCogConstituentFor:Annotation:Mcpc:Bcpc:Method: (in category 'profiling primitives') -----
> + collectCogConstituentFor: descriptor Annotation: isBackwardBranchAndAnnotation Mcpc: mcpc Bcpc: bcpc Method: cogMethodArg
> +    <var: #descriptor type: #'BytecodeDescriptor *'>
> +    <var: #mcpc type: #'char *'>
> +    <var: #cogMethodArg type: #'void *'>
> +    | address |
> +    descriptor ifNil: [^0].
> +    descriptor isMapped ifFalse: [^0].
> +    address := self positiveMachineIntegerFor: mcpc.
> +    address ifNil: [^InsufficientCodeSpace]. "We should have a dedicated error code... This cannot trigger a GC but fails if not enough space in Eden,"
> +    "Assumes we write the values into topRemappableOop"
> +    coInterpreter
> +        storePointerUnchecked: cogConstituentIndex
> +        ofObject: coInterpreter topRemappableOop
> +        withValue: address.
> +    coInterpreter
> +        storePointerUnchecked: cogConstituentIndex + 1
> +        ofObject: coInterpreter topRemappableOop
> +        withValue: (objectMemory integerObjectOf: bcpc)..
> +    cogConstituentIndex := cogConstituentIndex + 2.
> +    ^ 0!
> 
> Item was added:
> + ----- Method: Cogit>>collectCogMethodConstituent: (in category 'profiling primitives') -----
> + collectCogMethodConstituent: cogMethod
> +    "Answer a description of the mapping between machine code pointers and bytecode pointers for the Cog Method.
> +     First value is the address of the cog method.
> +     Following values are pairs of machine code pc and bytecode pc"
> +    <var: #cogMethod type: #'CogMethod *'>
> +    <var: #cogBlockMethod type: #'CogBlockMethod *'>
> +    | cm nSlots errCode cogBlockMethod address data |
> +    (cogMethod cmType = CMMethod) 
> +        ifFalse: [^self positiveMachineIntegerFor: cogMethod asUnsignedInteger ].
> +    cogBlockMethod := self cCoerceSimple: cogMethod to: #'CogBlockMethod *'.
> +    cogBlockMethod stackCheckOffset = 0 "isFrameless ?"
> +        ifTrue: [^self positiveMachineIntegerFor: cogMethod asUnsignedInteger].
> +    cm := cogMethod methodObject.
> +    nSlots := ((objectMemory byteSizeOf: cm) - (coInterpreter startPCOfMethod: cm)) * 2 + objectMemory minSlotsForShortening + 1."+1 for first address"
> +    data := objectMemory instantiateClass: (objectMemory splObj: ClassArray) indexableSize: nSlots.
> +    data ifNil: [^nil].
> +    coInterpreter pushRemappableOop: data.
> +    "The iteration assumes the object is the top remappable oop"
> +    address := (self positiveMachineIntegerFor: cogMethod asUnsignedInteger).
> +    address ifNil: [coInterpreter popRemappableOop. ^nil].
> +    coInterpreter
> +        storePointerUnchecked: 0
> +        ofObject: coInterpreter topRemappableOop
> +        withValue: address.
> +    cogConstituentIndex := 1.
> +    errCode := self
> +        mapFor: cogBlockMethod
> +        bcpc: (coInterpreter startPCOfMethod: cogMethod methodObject)
> +        performUntil: #collectCogConstituentFor:Annotation:Mcpc:Bcpc:Method:
> +        arg: cogMethod asVoidPointer.
> +    errCode ~= 0 ifTrue: [coInterpreter popRemappableOop. ^nil].
> +    cogConstituentIndex < nSlots ifTrue:
> +        [objectMemory shorten: coInterpreter topRemappableOop toIndexableSize: cogConstituentIndex].
> +    ^coInterpreter popRemappableOop.!
> 
> Item was changed:
>  ----- Method: NewObjectMemory>>shorten:toIndexableSize: (in category 'allocation') -----
>  shorten: obj toIndexableSize: nSlots
>      "Reduce the number of indexable fields in obj, a pointer object, to nSlots. Convert the
>      unused residual to a free chunk. Word and byte indexable objects are not changed.
>      Answer the number of bytes returned to free memory, which may be zero if no change
>      was possible."
>      | deltaBytes desiredLength fixedFields fmt hdr totalLength
>       indexableFields |
> +    <api>
>      (self isPointersNonImm: obj) ifFalse: [^0].
>      nSlots >  0
>          ifFalse: [^0]. "no change if nSlots is zero, error if nSlots is negative"
>      hdr := self baseHeader: obj.
>      fmt := self formatOfHeader: hdr.
>      totalLength := self lengthOf: obj baseHeader: hdr format: fmt.
>      fixedFields := self fixedFieldsOf: obj format: fmt length: totalLength.
>      indexableFields := totalLength - fixedFields.
>      nSlots >= indexableFields
>          ifTrue: [^0]. "no change, or error if attempting to increase size into next chunk"
>      desiredLength := fixedFields + nSlots.        
>      deltaBytes := (totalLength - desiredLength) * self wordSize.
>      obj + self baseHeaderSize + (totalLength * self wordSize) = freeStart
>          ifTrue: "Shortening the last object.  Need to reduce freeStart."
>              [self maybeFillWithAllocationCheckFillerFrom: obj + self baseHeaderSize + (desiredLength * self wordSize) to: freeStart.
>              freeStart := obj + self baseHeaderSize + (desiredLength * self wordSize)]
>          ifFalse: "Shortening some interior object.  Need to create a free block."
>              [self setSizeOfFree: obj + self baseHeaderSize + (desiredLength * self wordSize)
>                  to: deltaBytes].
>      (self headerType: obj) caseOf:    {
>          [HeaderTypeSizeAndClass] ->
>              [self longAt: (obj - (self baseHeaderSize * 2)) put: (self sizeHeader: obj) - deltaBytes].
>          [HeaderTypeClass] ->
>              [self longAt: obj put: ((hdr bitClear: SizeMask) bitOr: (hdr bitAnd: SizeMask) - deltaBytes)].
>          [HeaderTypeShort] ->
>              [self longAt: obj put: ((hdr bitClear: SizeMask) bitOr: (hdr bitAnd: SizeMask) - deltaBytes)] }.
>      ^deltaBytes!
> 
> Item was changed:
>  ----- Method: ObjectMemory>>minSlotsForShortening (in category 'allocation') -----
>  minSlotsForShortening
>      "HeaderTypeFree free chunks require 1 word of header"
> +    <api>
>      ^1!
> 
> Item was changed:
>  ----- Method: ObjectMemory>>shorten:toIndexableSize: (in category 'allocation') -----
>  shorten: obj toIndexableSize: nSlots
>      "Reduce the number of indexable fields in obj, a pointer object, to nSlots. Convert the
>      unused residual to a free chunk. Word and byte indexable objects are not changed.
>      Answer the number of bytes returned to free memory, which may be zero if no change
>      was possible."
>      | deltaBytes desiredLength fixedFields fmt hdr totalLength
>       indexableFields |
> +    <api>
>      (self isPointersNonImm: obj) ifFalse: [^0].
>      nSlots >  0
>          ifFalse: [^0]. "no change if nSlots is zero, error if nSlots is negative"
>      hdr := self baseHeader: obj.
>      fmt := self formatOfHeader: hdr.
>      totalLength := self lengthOf: obj baseHeader: hdr format: fmt.
>      fixedFields := self fixedFieldsOf: obj format: fmt length: totalLength.
>      indexableFields := totalLength - fixedFields.
>      nSlots >= indexableFields
>          ifTrue: [^0]. "no change, or error if attempting to increase size into next chunk"
>      desiredLength := fixedFields + nSlots.        
>      deltaBytes := (totalLength - desiredLength) * self wordSize.
>      self setSizeOfFree: obj + self baseHeaderSize + (desiredLength * self wordSize)
>          to: deltaBytes.
>      (self headerType: obj) caseOf:    {
>          [HeaderTypeSizeAndClass] ->
>              [self longAt: (obj - (self baseHeaderSize * 2)) put: (self sizeHeader: obj) - deltaBytes].
>          [HeaderTypeClass] ->
>              [self longAt: obj put: ((hdr bitClear: SizeMask) bitOr: (hdr bitAnd: SizeMask) - deltaBytes)].
>          [HeaderTypeShort] ->
>              [self longAt: obj put: ((hdr bitClear: SizeMask) bitOr: (hdr bitAnd: SizeMask) - deltaBytes)] }.
>      ^deltaBytes!
> 
> Item was changed:
>  ----- Method: Spur32BitMemoryManager>>shorten:toIndexableSize: (in category 'allocation') -----
>  shorten: objOop toIndexableSize: indexableSize
>      "Reduce the number of indexable fields in objOop, a pointer object, to nSlots. Convert the
>       unused residual to a free chunk. Without changes to numSlotsForShortening:toIndexableSize:
>       this only works for arrayFormat and longFormat objects.
>       Answer the number of bytes returned to free memory, which may be zero if no change
>       was possible."
>      <inline: false>
> +    <api>
>      | numSlots bytesBefore delta copy freeChunk |
>      self assert: (self oop: (self addressAfter: objOop) isLessThanOrEqualTo: endOfMemory).
>      numSlots := self numSlotsForShortening: objOop toIndexableSize: indexableSize.
>      numSlots = (self numSlotsOf: objOop) ifTrue:
>          [^0].
>      bytesBefore := self bytesInObject: objOop.
>      delta := bytesBefore - (self objectBytesForSlots: numSlots).
> 
>      (delta > 0
>       and: [delta <= self allocationUnit]) ifTrue:
>          [copy := self allocateSlots: numSlots
>                      format: (self formatOf: objOop)
>                      classIndex: (self classIndexOf: objOop).
>           copy ifNil: [self error: 'shorten:toIndexableSize: attempted to shorten to allocationUnit!!'].
>           0 to: numSlots - 1 do:
>              [:i|
>              self storePointerUnchecked: i
>                  ofObject: copy
>                  withValue: (self fetchPointer: i ofObject: objOop)].
>           (self isRemembered: objOop) ifTrue:
>              [scavenger remember: copy].
>           self forward: objOop to: copy.
>           ^0].
> 
>      (self hasOverflowHeader: objOop)
>          ifTrue:
>              [self rawOverflowSlotsOf: objOop put: numSlots.
>               numSlots < self numSlotsMask ifTrue:
>                  [delta := delta - self allocationUnit]]
>          ifFalse:
>              [self assert: numSlots < self numSlotsMask.
>               self rawNumSlotsOf: objOop put: numSlots].
> 
>      self assert: (self oop: (self addressAfter: objOop) + delta isLessThanOrEqualTo: endOfMemory).
>      "Since the 32-bit system rounds objects up to 64-bits, loosing
>       a slot may not actually change the bytes occupied by the object."
>      delta = 0 ifTrue:
>          [^0].
> 
>      freeChunk := self initFreeChunkWithBytes: delta at: (self addressAfter: objOop).
>      self assert: (self addressAfter: freeChunk) <= endOfMemory.
>      (self isInOldSpace: objOop)
>          ifTrue:
>              [totalFreeOldSpace := totalFreeOldSpace + delta.
>               self addToFreeList: freeChunk bytes: delta]
>          ifFalse:
>              [self
>                  setClassIndexOf: freeChunk to: self wordSizeClassIndexPun;
>                  setFormatOf: freeChunk to: self firstLongFormat].
>      ^delta!
> 
> Item was changed:
>  ----- Method: Spur64BitMemoryManager>>shorten:toIndexableSize: (in category 'allocation') -----
>  shorten: objOop toIndexableSize: indexableSize
>      "Reduce the number of indexable fields in objOop, a pointer object, to nSlots. Convert the
>       unused residual to a free chunk. Without changes to numSlotsForShortening:toIndexableSize:
>       this only works for arrayFormat and longFormat objects.
>       Answer the number of bytes returned to free memory, which may be zero if no change
>       was possible."
>      <inline: false>
> +    <api>
>      | numSlots bytesBefore delta copy freeChunk |
>      numSlots := self numSlotsForShortening: objOop toIndexableSize: indexableSize.
>      numSlots = (self numSlotsOf: objOop) ifTrue:
>          [^0].
>      bytesBefore := self bytesInObject: objOop.
>      delta := bytesBefore - (self objectBytesForSlots: numSlots).
> 
>      self flag: 'this should update format for 32-bit indexable words; too lazy today.'.
> 
>      delta = 0 ifTrue:
>          [^0].
> 
>      delta <= self allocationUnit ifTrue:
>          [copy := self allocateSlots: numSlots
>                      format: (self formatOf: objOop)
>                      classIndex: (self classIndexOf: objOop).
>           copy ifNil: [self error: 'shorten:toIndexableSize: attempted to shorten to allocationUnit!!'].
>           0 to: numSlots - 1 do:
>              [:i|
>              self storePointerUnchecked: i
>                  ofObject: copy
>                  withValue: (self fetchPointer: i ofObject: objOop)].
>           (self isRemembered: objOop) ifTrue:
>              [scavenger remember: copy].
>           self forward: objOop to: copy.
>           ^0].
> 
>      (self hasOverflowHeader: objOop)
>          ifTrue:
>              [self rawOverflowSlotsOf: objOop put: numSlots.
>               numSlots < self numSlotsMask ifTrue:
>                  [delta := delta - self allocationUnit]]
>          ifFalse:
>              [self assert: numSlots < self numSlotsMask.
>               self rawNumSlotsOf: objOop put: numSlots].
> 
>      freeChunk := self initFreeChunkWithBytes: delta at: (self addressAfter: objOop).
>      self assert: (self addressAfter: freeChunk) <= endOfMemory.
>      (self isInOldSpace: objOop)
>          ifTrue:
>              [totalFreeOldSpace := totalFreeOldSpace + delta.
>               self addToFreeList: freeChunk bytes: delta]
>          ifFalse:
>              [self
>                  setClassIndexOf: freeChunk to: self wordSizeClassIndexPun;
>                  setFormatOf: freeChunk to: self firstLongFormat].
>      ^delta!
> 
> Item was changed:
>  ----- Method: SpurMemoryManager>>minSlotsForShortening (in category 'allocation') -----
>  minSlotsForShortening
>      "Answer the minimum number of additional slots to allocate in an object to always be able to shorten it.
>       This is enough slots to allocate a minimum-sized object."
> +    <api>
>      ^self allocationUnit * 2 / self bytesPerOop!
> 



More information about the Vm-dev mailing list