VM Maker: VMMaker.oscog-eem.2153.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.2153.mcz

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

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

Name: VMMaker.oscog-eem.2153
Author: eem
Time: 14 March 2017, 12:10:25.609187 pm
UUID: fd47d333-75f0-46ea-a3a7-fab3a6ddebdd
Ancestors: VMMaker.oscog-eem.2152

Sista:
Fix mapping back from inline cache tags to classes on 32-bit Spur where, because SmallIntegers are 31 bits (tag = 1, not 01), Character (tag = 10) gets mapped to 0.

Cogit PC Mapping:
Fix testBcToMcPcMappingForCogMethod: now that dead codee removal can eliminate blocks that are unreachable.

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

Item was added:
+ ----- Method: BlockClosure>>value:value:value:value:value: (in category '*VMMaker-conveniences') -----
+ value: firstArg value: secondArg value: thirdArg value: fourthArg value: fifthArg
+ "Activate the receiver, creating a closure activation (MethodContext)
+ whose closure is the receiver and whose caller is the sender of this
+ message. Supply the arguments and copied values to the activation
+ as its arguments and copied temps. Primitive. Essential."
+ <primitive: 205>
+ | newContext |
+ numArgs ~= 5 ifTrue:
+ [self numArgsError: 5].
+ false
+ ifTrue: "Old code to simulate the closure value primitive on VMs that lack it."
+ [newContext := self asContextWithSender: thisContext sender.
+ newContext at: 1 put: firstArg.
+ newContext at: 2 put: secondArg.
+ newContext at: 3 put: thirdArg.
+ newContext at: 4 put: fourthArg.
+ newContext at: 5 put: fifthArg.
+ thisContext privSender: newContext]
+ ifFalse: [self primitiveFailed]!

Item was added:
+ ----- Method: CogObjectRepresentation>>classForInlineCacheTag: (in category 'in-line cacheing') -----
+ classForInlineCacheTag: classIndex
+ ^self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>classForInlineCacheTag: (in category 'in-line cacheing') -----
+ classForInlineCacheTag: inlineCacheTag
+ "Character gets mapped to zero.  See inlineCacheTagForInstance:."
+ ^objectMemory classOrNilAtIndex: (inlineCacheTag = 0
+ ifTrue: [objectMemory characterTag]
+ ifFalse: [inlineCacheTag])!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>classForInlineCacheTag: (in category 'in-line cacheing') -----
+ classForInlineCacheTag: classIndex
+ ^objectMemory classOrNilAtIndex: classIndex!

Item was removed:
- ----- Method: CogObjectRepresentationForSpur>>classForInlineCacheTag: (in category 'in-line cacheing') -----
- classForInlineCacheTag: classIndex
- ^objectMemory classOrNilAtIndex: classIndex!

Item was added:
+ ----- Method: Cogit>>bcpcsDescriptorsAndStartpcsFor:bsOffset:do: (in category 'tests-method map') -----
+ bcpcsDescriptorsAndStartpcsFor: aMethod bsOffset: bsOffset do: quinternaryBlock
+ "Evaluate quinternaryBlock with the pc, byte, descriptor and numExtensions for
+ all the bytecodes in aMethod.  Evaluate with byte, descriptor and numExtensions
+ nil for the initialPC of the mehtod and any blocks within it."
+ <doNotGenerate>
+ | nExts byte descriptor endpc latestContinuation pc primIdx blockEndPCs startpcs |
+ ((primIdx := coInterpreter primitiveIndexOf: aMethod) > 0
+ and: [coInterpreter isQuickPrimitiveIndex: primIdx]) ifTrue:
+ [^self].
+ latestContinuation := pc := coInterpreter startPCOfMethod: aMethod.
+ startpcs := OrderedCollection with: pc.
+ blockEndPCs := OrderedCollection with: (coInterpreter numBytesOf: aMethod).
+ quinternaryBlock value: pc value: nil value: nil value: 0 value: pc. "stackCheck/entry pc"
+ primIdx > 0 ifTrue:
+ [pc := pc + (self deltaToSkipPrimAndErrorStoreIn: aMethod
+ header: (coInterpreter methodHeaderOf: aMethod))].
+ nExts := 0.
+ endpc := objectMemory numBytesOf: aMethod.
+ [pc <= endpc] whileTrue:
+ [byte := objectMemory fetchByte: pc ofObject: aMethod.
+ descriptor := self generatorAt: byte + bsOffset.
+ descriptor isExtension ifFalse:
+ [quinternaryBlock value: pc value: byte value: descriptor value: nExts value: startpcs last].
+ descriptor isReturn ifTrue:
+ [pc >= latestContinuation ifTrue:
+ [endpc := pc]].
+ (descriptor isBranch
+ or: [descriptor isBlockCreation]) ifTrue:
+ [| targetPC |
+ targetPC := self latestContinuationPCFor: descriptor at: pc exts: nExts in: aMethod.
+ descriptor isBlockCreation ifTrue:
+ [quinternaryBlock value: (startpcs addLast: pc + descriptor numBytes) value: nil value: nil value: 0 value: startpcs last.
+ blockEndPCs addLast: targetPC]. "stackCheck/entry pc"
+ self assert: targetPC < endpc.
+ latestContinuation := latestContinuation max: targetPC].
+ descriptor isReturn ifTrue:
+ [pc + descriptor numBytes >= blockEndPCs last ifTrue:
+ [blockEndPCs removeLast.
+ startpcs removeLast]].
+ pc := pc + descriptor numBytes.
+ nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]]!

Item was changed:
  ----- Method: Cogit>>testBcToMcPcMappingForCogMethod: (in category 'testing') -----
  testBcToMcPcMappingForCogMethod: cogMethod
  <doNotGenerate>
  "self disassembleMethod: cogMethod"
  "self printPCMapPairsFor: cogMethod on: Transcript"
  | aMethodObj subMethods bsOffset |
  aMethodObj := cogMethod methodObject.
  subMethods := self subMethodsAsRangesFor: cogMethod.
  subMethods first endPC: (self endPCOf: aMethodObj).
  bsOffset := self bytecodeSetOffsetFor: aMethodObj.
+ self bcpcsDescriptorsAndStartpcsFor: aMethodObj bsOffset: bsOffset do:
+ [:bcpc :byte :desc :nExts :startpc|
- self bcpcsAndDescriptorsFor: aMethodObj bsOffset: bsOffset do:
- [:bcpc :byte :desc :nExts| | subMethod |
  (desc notNil and: [desc isBlockCreation]) ifTrue:
+ ["dead code removal may result in blocks not being generated ;-)"
+ (subMethods detect: [:sm| sm startpc = (bcpc + desc numBytes)] ifNone: [nil]) ifNotNil:
+ [:subMethod|
+ subMethod endPC: bcpc + desc numBytes + (self spanFor: desc at: bcpc exts: -1 in: aMethodObj) - 1]]].
- [subMethod := subMethods detect: [:sm| sm startpc = (bcpc + desc numBytes)].
- subMethod endPC: bcpc + desc numBytes + (self spanFor: desc at: bcpc exts: -1 in: aMethodObj) - 1]].
  subMethods allButFirst do:
  [:blockSubMethod| | cogBlockMethod |
  cogBlockMethod := self
  findMethodForStartBcpc: blockSubMethod startpc
  inHomeMethod: cogMethod.
  self assert: cogBlockMethod address = (blockSubMethod first - (self sizeof: CogBlockMethod))].
+ self bcpcsDescriptorsAndStartpcsFor: aMethodObj bsOffset: bsOffset do:
+ [:bcpc :byte :desc :nExts :startpc| | startBcpc currentSubMethod subCogMethod absMcpc mappedBcpc |
- self bcpcsAndDescriptorsFor: aMethodObj bsOffset: bsOffset do:
- [:bcpc :byte :desc :nExts| | startBcpc currentSubMethod subCogMethod absMcpc mappedBcpc |
  currentSubMethod := self innermostSubMethodFor: bcpc in: subMethods startingAt: 1.
+ startpc = currentSubMethod startpc ifTrue:
+ [subCogMethod := currentSubMethod cogMethod.
+ (subCogMethod stackCheckOffset > 0
+ and: [desc isNil or: [desc isMapped
+ or: [inBlock = InFullBlock and: [desc isMappedInBlock]]]]) ifTrue:
+ [startBcpc := subCogMethod = cogMethod
+ ifTrue: [coInterpreter startPCOfMethod: aMethodObj]
+ ifFalse: [currentSubMethod startpc].
+ "The first bytecode and backward branch bytecodes are mapped to their pc.
+  Other bytecodes map to their following pc."
+ absMcpc := (desc notNil
+   and: [desc isBranch
+   and: [self isBackwardBranch: desc at: bcpc exts: nExts in: aMethodObj]])
+ ifTrue: "Backward branches have a special mapper"
+ [mappedBcpc := bcpc.
+ self
+ mcPCForBackwardBranch: mappedBcpc
+ startBcpc: startBcpc
+ in: subCogMethod]
+ ifFalse: "All others use the generic mapper"
+ [mappedBcpc := desc ifNil: [bcpc] ifNotNil: [bcpc + desc numBytes].
+ self
+ mcPCFor: mappedBcpc
+ startBcpc: startBcpc
+ in: subCogMethod].
+ self assert: absMcpc >= (subCogMethod asInteger + subCogMethod stackCheckOffset).
+ self assert: (self bytecodePCFor: absMcpc startBcpc: startBcpc in: subCogMethod) = mappedBcpc]]]!
- subCogMethod := currentSubMethod cogMethod.
- (subCogMethod stackCheckOffset > 0
- and: [desc isNil or: [desc isMapped
- or: [ inBlock = InFullBlock and: [desc isMappedInBlock]]]]) ifTrue:
- [startBcpc := subCogMethod = cogMethod
- ifTrue: [coInterpreter startPCOfMethod: aMethodObj]
- ifFalse: [currentSubMethod startpc].
- "The first bytecode and backward branch bytecodes are mapped to their pc.
-  Other bytecodes map to their following pc."
- absMcpc := (desc notNil
-   and: [desc isBranch
-   and: [self isBackwardBranch: desc at: bcpc exts: nExts in: aMethodObj]])
- ifTrue: "Backward branches have a special mapper"
- [mappedBcpc := bcpc.
- self
- mcPCForBackwardBranch: mappedBcpc
- startBcpc: startBcpc
- in: subCogMethod]
- ifFalse: "All others use the generic mapper"
- [mappedBcpc := desc ifNil: [bcpc] ifNotNil: [bcpc + desc numBytes].
- self
- mcPCFor: mappedBcpc
- startBcpc: startBcpc
- in: subCogMethod].
- self assert: absMcpc >= (subCogMethod asInteger + subCogMethod stackCheckOffset).
- self assert: (self bytecodePCFor: absMcpc startBcpc: startBcpc in: subCogMethod) = mappedBcpc]]!