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

Clément Bera bera.clement at gmail.com
Mon Jun 2 14:40:49 UTC 2014


Eliot,

Recent commits are very exciting. Context and closure creations are now
inlined in machine code :-)

Have you already done at:put: and stringAt:put: or is it your next step ?

Please tell us about the new bench results with these features.

Clément


2014-06-02 16:14 GMT+02:00 <commits at source.squeak.org>:

>
> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.746.mcz
>
> ==================== Summary ====================
>
> Name: VMMaker.oscog-eem.746
> Author: eem
> Time: 1 June 2014, 6:05:30.694 pm
> UUID: cc4961d3-e629-4e28-b308-88eab314a8c9
> Ancestors: VMMaker.oscog-eem.745
>
> Implement a peephole in the Spur Cogit for an indirection
> vector initialized with a single value  Avoid initializing the
> slot in the array to nil and instead initialize it with the value.
>
> Refactor setting byte1, byte2 & byte3 into
> loadSubsequentBytesForDescriptor:at: for the peephole
> tryCollapseTempVectorInitializationOfSize:.
>
> No loner inline CoInterpreter>>pre/postGCAction: for VM profiling.
>
> Increase the number of trampoline table slots.
>
> Simulator:
> Fix CurrentImageCoInterpreterFacade for the new Spur
> inline instantiation code.
>
> =============== Diff against VMMaker.oscog-eem.745 ===============
>
> Item was changed:
>   ----- Method: CoInterpreter>>postGCAction: (in category 'object memory
> support') -----
>   postGCAction: gcModeArg
>         "Attempt to shrink free memory, signal the gc semaphore and let
> the Cogit do its post GC thang"
> +       <inline: false>
>         self assert: gcModeArg = gcMode.
>         super postGCAction: gcModeArg.
>         cogit cogitPostGCAction: gcModeArg.
>         lastCoggableInterpretedBlockMethod :=
> lastUncoggableInterpretedBlockMethod := nil.
>         gcMode := 0!
>
> Item was changed:
>   ----- Method: CoInterpreter>>preGCAction: (in category 'object memory
> support') -----
>   preGCAction: gcModeArg
> +       <inline: false>
> -       <inline: true>
>         "Need to write back the frame pointers unless all pages are free
> (as in snapshot).
>          Need to set gcMode var (to avoid passing the flag through a lot
> of the updating code)"
>         super preGCAction: gcModeArg.
>
>         gcMode := gcModeArg.
>
>         cogit recordEventTrace ifTrue:
>                 [| traceType |
>                 traceType := gcModeArg == GCModeFull ifTrue: [TraceFullGC]
> ifFalse: [TraceIncrementalGC].
>                 self recordTrace: traceType thing: traceType source: 0].
>
>         cogit recordPrimTrace ifTrue:
>                 [| traceType |
>                 traceType := gcModeArg == GCModeFull ifTrue: [TraceFullGC]
> ifFalse: [TraceIncrementalGC].
>                 self fastLogPrim: traceType]!
>
> Item was added:
> + ----- Method: CogObjectRepresentation>>createsArraysInline (in category
> 'bytecode generator support') -----
> + createsArraysInline
> +       "Answer if the object representation allocates arrays inline.  By
> +        default answer false. Better code can be generated when creating
> +        arrays inline if values are /not/ flushed to the stack."
> +       ^false!
>
> Item was removed:
> - ----- Method: CogObjectRepresentationFor32BitSpur>>createsClosuresInline
> (in category 'bytecode generator support') -----
> - createsClosuresInline
> -       "Answer if the object representation allocates closures inline.  By
> -        default answer false. Better code can be generated when creating
> -        closures inline if copied values are /not/ flushed to the stack."
> -       ^true!
>
> Item was added:
> + ----- Method: CogObjectRepresentationForSpur>>createsArraysInline (in
> category 'bytecode generator support') -----
> + createsArraysInline
> +       "Answer if the object representation allocates arrays inline.  By
> +        default answer false. Better code can be generated when creating
> +        arrays inline if values are /not/ flushed to the stack."
> +       ^true!
>
> Item was added:
> + ----- Method: CogObjectRepresentationForSpur>>createsClosuresInline (in
> category 'bytecode generator support') -----
> + createsClosuresInline
> +       "Answer if the object representation allocates closures inline.  By
> +        default answer false. Better code can be generated when creating
> +        closures inline if copied values are /not/ flushed to the stack."
> +       ^true!
>
> Item was changed:
>   ----- Method: Cogit>>compileAbstractInstructionsFrom:through: (in
> category 'compile abstract instructions') -----
>   compileAbstractInstructionsFrom: start through: end
>         "Loop over bytecodes, dispatching to the generator for each
> bytecode, handling fixups in due course."
>         | nextOpcodeIndex descriptor fixup result nExts |
>         <var: #descriptor type: #'BytecodeDescriptor *'>
>         <var: #fixup type: #'BytecodeFixup *'>
>         bytecodePC := start.
>         nExts := 0.
>         [byte0 := (objectMemory fetchByte: bytecodePC ofObject: methodObj)
>  + bytecodeSetOffset.
>          descriptor := self generatorAt: byte0.
> +        self loadSubsequentBytesForDescriptor: descriptor at: bytecodePC.
> -        descriptor numBytes > 1 ifTrue:
> -               [byte1 := objectMemory fetchByte: bytecodePC + 1 ofObject:
> methodObj.
> -                descriptor numBytes > 2 ifTrue:
> -                       [byte2 := objectMemory fetchByte: bytecodePC + 2
> ofObject: methodObj.
> -                        descriptor numBytes > 3 ifTrue:
> -                               [byte3 := objectMemory fetchByte:
> bytecodePC + 3 ofObject: methodObj.
> -                                descriptor numBytes > 4 ifTrue:
> -                                       [self notYetImplemented]]]].
>          nextOpcodeIndex := opcodeIndex.
>          result := self perform: descriptor generator.
>          descriptor isExtension ifFalse: "extended bytecodes must consume
> their extensions"
>                 [self assert: (extA = 0 and: [extB = 0])].
>          fixup := self fixupAt: bytecodePC - initialPC.
>          fixup targetInstruction ~= 0 ifTrue:
>                 ["There is a fixup for this bytecode.  It must point to
> the first generated
>                    instruction for this bytecode.  If there isn't one we
> need to add a label."
>                  opcodeIndex = nextOpcodeIndex ifTrue:
>                         [self Label].
>                  fixup targetInstruction: (self abstractInstructionAt:
> nextOpcodeIndex)].
>          bytecodePC := self nextBytecodePCFor: descriptor at: bytecodePC
> exts: nExts in: methodObj.
>          result = 0 and: [bytecodePC <= end]]
>                 whileTrue:
>                         [nExts := descriptor isExtension ifTrue: [nExts +
> 1] ifFalse: [0]].
>         self checkEnoughOpcodes.
>         ^result!
>
> Item was added:
> + ----- Method: Cogit>>loadSubsequentBytesForDescriptor:at: (in category
> 'compile abstract instructions') -----
> + loadSubsequentBytesForDescriptor: descriptor at: pc
> +       <var: #descriptor type: #'BytecodeDescriptor *'>
> +       descriptor numBytes > 1 ifTrue:
> +               [byte1 := objectMemory fetchByte: pc + 1 ofObject:
> methodObj.
> +                descriptor numBytes > 2 ifTrue:
> +                       [byte2 := objectMemory fetchByte: pc + 2 ofObject:
> methodObj.
> +                        descriptor numBytes > 3 ifTrue:
> +                               [byte3 := objectMemory fetchByte: pc + 3
> ofObject: methodObj.
> +                                descriptor numBytes > 4 ifTrue:
> +                                       [self notYetImplemented]]]]!
>
> Item was added:
> + ----- Method: CurrentImageCoInterpreterFacade class>>objectMemoryClass
> (in category 'accessing') -----
> + objectMemoryClass
> +       ^self subclassResponsibility!
>
> Item was changed:
>   ----- Method: CurrentImageCoInterpreterFacade>>cogit: (in category
> 'initialize-release') -----
>   cogit: aCogit
>         cogit := aCogit.
>         coInterpreter cogit: aCogit.
> +       (objectMemory respondsTo: #cogit:) ifTrue:
> +               [objectMemory cogit: aCogit]!
> -       objectMemory cogit: aCogit!
>
> Item was added:
> + ----- Method: CurrentImageCoInterpreterFacade>>indexablePointersFormat
> (in category 'accessing') -----
> + indexablePointersFormat
> +       ^objectMemory indexablePointersFormat!
>
> Item was changed:
>   ----- Method: CurrentImageCoInterpreterFacade>>initialize (in category
> 'initialize-release') -----
>   initialize
>         memory := ByteArray new: 262144.
> +       objectMemory := self class objectMemoryClass new.
> -       objectMemory := NewCoObjectMemory new.
>         coInterpreter := CoInterpreter new.
>         coInterpreter
>                 instVarNamed: 'objectMemory'
>                         put: objectMemory;
>                 instVarNamed: 'primitiveTable'
>                         put: (CArrayAccessor on: CoInterpreter
> primitiveTable copy).
>         variables := Dictionary new.
>         #('stackLimit') do:
>                 [:l| self addressForLabel: l].
>         self initializeObjectMap!
>
> Item was added:
> + ----- Method: CurrentImageCoInterpreterFacade>>methodNeedsLargeContext:
> (in category 'accessing') -----
> + methodNeedsLargeContext: aMethodOop
> +       ^(self objectForOop: aMethodOop) frameSize > CompiledMethod
> smallFrameSize!
>
> Item was added:
> + ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation
> class>>objectMemoryClass (in category 'accessing') -----
> + objectMemoryClass
> +       ^Spur32BitCoMemoryManager!
>
> Item was added:
> + ----- Method:
> CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>arrayFormat (in
> category 'accessing') -----
> + arrayFormat
> +       ^objectMemory arrayFormat!
>
> Item was added:
> + ----- Method:
> CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>getScavengeThreshold
> (in category 'accessing') -----
> + getScavengeThreshold
> +       ^objectMemory getScavengeThreshold ifNil: [16r24680]!
>
> Item was added:
> + ----- Method:
> CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>headerForSlots:format:classIndex:
> (in category 'accessing') -----
> + headerForSlots: numSlots format: formatField classIndex: classIndex
> +       ^objectMemory headerForSlots: numSlots format: formatField
> classIndex: classIndex!
>
> Item was added:
> + ----- Method:
> CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>numSlotsMask
> (in category 'accessing') -----
> + numSlotsMask
> +       ^objectMemory numSlotsMask!
>
> Item was added:
> + ----- Method:
> CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>rememberedBitShift
> (in category 'accessing') -----
> + rememberedBitShift
> +       ^objectMemory rememberedBitShift!
>
> Item was added:
> + ----- Method:
> CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>smallObjectBytesForSlots:
> (in category 'accessing') -----
> + smallObjectBytesForSlots: numSlots
> +       ^objectMemory smallObjectBytesForSlots: numSlots!
>
> Item was added:
> + ----- Method:
> CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>storeCheckBoundary
> (in category 'accessing') -----
> + storeCheckBoundary
> +       ^objectMemory storeCheckBoundary ifNil: [16r12345678]!
>
> Item was added:
> + ----- Method:
> CurrentImageCoInterpreterFacadeForSqueakV3ObjectRepresentation
> class>>objectMemoryClass (in category 'accessing') -----
> + objectMemoryClass
> +       ^NewObjectMemory!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit class>>initializeMiscConstants (in
> category 'class initialization') -----
>   initializeMiscConstants
>         super initializeMiscConstants.
>         MaxLiteralCountForCompile := initializationOptions at:
> #MaxLiteralCountForCompile ifAbsent: [60].
>         NumTrampolines := NewspeakVM
> +                                                       ifTrue: [50]
> +                                                       ifFalse: [42]!
> -                                                       ifTrue: [46]
> -                                                       ifFalse: [38]!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit class>>initializeMiscConstants
> (in category 'class initialization') -----
>   initializeMiscConstants
>         super initializeMiscConstants.
>         NumTrampolines := NewspeakVM
> +                                                       ifTrue: [60]
> +                                                       ifFalse: [52]!
> -                                                       ifTrue: [58]
> -                                                       ifFalse: [50]!
>
> Item was changed:
>   ----- Method:
> StackToRegisterMappingCogit>>compileAbstractInstructionsFrom:through: (in
> category 'compile abstract instructions') -----
>   compileAbstractInstructionsFrom: start through: end
>         "Loop over bytecodes, dispatching to the generator for each
> bytecode, handling fixups in due course."
>         | nextOpcodeIndex descriptor nExts fixup result |
>         <var: #descriptor type: #'BytecodeDescriptor *'>
>         <var: #fixup type: #'BytecodeFixup *'>
>         self traceSimStack.
>         bytecodePC := start.
>         nExts := 0.
>         descriptor := nil.
>         deadCode := false.
>         [self cCode: '' inSmalltalk:
>                 [(debugBytecodePointers includes: bytecodePC) ifTrue:
> [self halt]].
>         fixup := self fixupAt: bytecodePC - initialPC.
>         fixup targetInstruction asUnsignedInteger > 0
>                 ifTrue:
>                         [deadCode := false.
>                          fixup targetInstruction asUnsignedInteger >= 2
> ifTrue:
>                                 [self merge: fixup
>                                         afterContinuation: (descriptor
> notNil
>
>       and: [descriptor isUnconditionalBranch
>
>               or: [descriptor isReturn]]) not]]
>                 ifFalse: "If there's no fixup following a return there's
> no jump to that code and it is dead."
>                         [(descriptor notNil and: [descriptor isReturn])
> ifTrue:
>                                 [deadCode := true]].
>          self cCode: '' inSmalltalk:
>                 [deadCode ifFalse:
>                         [self assert: simStackPtr + (needsFrame ifTrue:
> [0] ifFalse: [1])
>                                                 = (self
> debugStackPointerFor: bytecodePC)]].
>          byte0 := (objectMemory fetchByte: bytecodePC ofObject: methodObj)
> + bytecodeSetOffset.
>          descriptor := self generatorAt: byte0.
> +        self loadSubsequentBytesForDescriptor: descriptor at: bytecodePC.
> -        descriptor numBytes > 1 ifTrue:
> -               [byte1 := objectMemory fetchByte: bytecodePC + 1 ofObject:
> methodObj.
> -                descriptor numBytes > 2 ifTrue:
> -                       [byte2 := objectMemory fetchByte: bytecodePC + 2
> ofObject: methodObj.
> -                        descriptor numBytes > 3 ifTrue:
> -                               [byte3 := objectMemory fetchByte:
> bytecodePC + 3 ofObject: methodObj.
> -                                descriptor numBytes > 4 ifTrue:
> -                                       [self notYetImplemented]]]].
>          nextOpcodeIndex := opcodeIndex.
>          result := deadCode
>                                 ifTrue: "insert nops for dead code that is
> mapped so that bc to mc mapping is not many to one"
>                                         [(descriptor isMapped
>                                           or: [inBlock and: [descriptor
> isMappedInBlock]]) ifTrue:
>                                                 [self annotateBytecode:
> self Nop].
>                                                 0]
>                                 ifFalse:
>                                         [self perform: descriptor
> generator].
>          descriptor isExtension ifFalse: "extended bytecodes must consume
> their extensions"
>                 [self assert: (extA = 0 and: [extB = 0])].
>          self traceDescriptor: descriptor; traceSimStack.
>          (fixup targetInstruction asUnsignedInteger between: 1 and: 2)
> ifTrue:
>                 ["There is a fixup for this bytecode.  It must point to
> the first generated
>                    instruction for this bytecode.  If there isn't one we
> need to add a label."
>                  opcodeIndex = nextOpcodeIndex ifTrue:
>                         [self Label].
>                  fixup targetInstruction: (self abstractInstructionAt:
> nextOpcodeIndex)].
>          bytecodePC := self nextBytecodePCFor: descriptor at: bytecodePC
> exts: nExts in: methodObj.
>          result = 0 and: [bytecodePC <= end]] whileTrue:
>                 [nExts := descriptor isExtension ifTrue: [nExts + 1]
> ifFalse: [0]].
>         self checkEnoughOpcodes.
>         ^result!
>
> Item was added:
> + ----- Method: StackToRegisterMappingCogit>>evaluate:at: (in category
> 'peephole optimizations') -----
> + evaluate: descriptor at: pc
> +       <var: #descriptor type: #'BytecodeDescriptor *'>
> +       byte0 := objectMemory fetchByte: pc ofObject: methodObj.
> +       self assert: descriptor = (self generatorAt: bytecodeSetOffset +
> byte0).
> +       self loadSubsequentBytesForDescriptor: descriptor at: pc.
> +       self perform: descriptor generator!
>
> 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.
> +       popValues ifFalse:
> +               [(self tryCollapseTempVectorInitializationOfSize: size)
> ifTrue:
> +                       [^0]].
>         objectRepresentation genNewArrayOfSize: size initialized:
> popValues not.
>         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!
>
> Item was added:
> + ----- Method:
> StackToRegisterMappingCogit>>tryCollapseTempVectorInitializationOfSize: (in
> category 'peephole optimizations') -----
> + tryCollapseTempVectorInitializationOfSize: slots
> +       "Try and collapse
> +               push: (Array new: 1)
> +               popIntoTemp: tempIndex
> +               pushConstant: const or pushTemp: n
> +               popIntoTemp: 0 inVectorAt: tempIndex
> +        into
> +               tempAt: tempIndex put: {const}.
> +        One might think that we should look for a sequence of more than
> +        one pushes and pops but this is extremely rare."
> +       | pushArrayDesc storeArrayDesc pushValueDesc storeValueDesc reg |
> +       <var: #pushArrayDesc type: #'BytecodeDescriptor *'>
> +       <var: #pushValueDesc type: #'BytecodeDescriptor *'>
> +       <var: #storeArrayDesc type: #'BytecodeDescriptor *'>
> +       <var: #storeValueDesc type: #'BytecodeDescriptor *'>
> +       slots ~= 1 ifTrue:
> +               [^false].
> +       pushArrayDesc := self generatorAt: bytecodeSetOffset
> +
>       + (objectMemory
> +
>                       fetchByte: bytecodePC
> +
>                       ofObject: methodObj).
> +       self assert: pushArrayDesc generator == #genPushNewArrayBytecode.
> +       storeArrayDesc := self generatorAt: bytecodeSetOffset
> +
>       + (objectMemory
> +
>                       fetchByte: bytecodePC
> +
>                                       + pushArrayDesc numBytes
> +
>                       ofObject: methodObj).
> +       storeArrayDesc generator ~~
> #genStoreAndPopTemporaryVariableBytecode ifTrue:
> +               [^false].
> +       pushValueDesc := self generatorAt: bytecodeSetOffset
> +
>       + (objectMemory
> +
>                       fetchByte: bytecodePC
> +
>                                       + pushArrayDesc numBytes
> +
>                                       + storeArrayDesc numBytes
> +
>                       ofObject: methodObj).
> +       (pushValueDesc generator ~~ #genPushLiteralConstantBytecode
> +        and: [pushValueDesc generator ~~
> #genPushQuickIntegerConstantBytecode
> +        and: [pushValueDesc generator ~~
> #genPushTemporaryVariableBytecode]]) ifTrue:
> +               [^false].
> +       storeValueDesc := self generatorAt: bytecodeSetOffset
> +
>       + (objectMemory
> +
>                       fetchByte: bytecodePC
> +
>                                       + pushArrayDesc numBytes
> +
>                                       + storeArrayDesc numBytes
> +
>                                       + pushValueDesc numBytes
> +
>                       ofObject: methodObj).
> +       storeValueDesc generator ~~ #genStoreAndPopRemoteTempLongBytecode
> ifTrue:
> +               [^false].
> +
> +       objectRepresentation genNewArrayOfSize: 1 initialized: false.
> +       self evaluate: pushValueDesc at: bytecodePC + pushArrayDesc
> numBytes + storeArrayDesc numBytes.
> +       reg := self ssStorePop: true toPreferredReg: TempReg.
> +       objectRepresentation
> +               genStoreSourceReg: reg
> +               slotIndex: 0
> +               intoNewObjectInDestReg: ReceiverResultReg.
> +       self ssPushRegister: ReceiverResultReg.
> +       self evaluate: storeArrayDesc at: bytecodePC + pushArrayDesc
> numBytes.
> +       bytecodePC := bytecodePC
> +                                       "+ pushArrayDesc numBytes this
> gets added by nextBytecodePCFor:at:exts:in:"
> +                                       + storeArrayDesc numBytes
> +                                       + pushValueDesc numBytes
> +                                       + storeValueDesc numBytes.
> +       ^true!
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://lists.squeakfoundation.org/pipermail/vm-dev/attachments/20140602/fa8d59eb/attachment.html


More information about the Vm-dev mailing list