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

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

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

Name: VMMaker.oscog-eem.911
Author: eem
Time: 24 October 2014, 11:44:05.762 am
UUID: 39c7bff8-ff88-43a5-88bc-cbbdb206cbcd
Ancestors: VMMaker.oscog-eem.910

Avoid cogging methods containing unknown bytecodes
early in scanMethod.  Use a hack to avoid a test on the
common path.

Fix the return type of implicitReceiverCacheAddressAt:.

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

Item was changed:
  ----- Method: CoInterpreter>>ceInterpretMethodFromPIC:receiver: (in category 'trampolines') -----
  ceInterpretMethodFromPIC: aMethodObj receiver: rcvr
  <api>
  | pic primitiveIndex |
  <var: #pic type: #'CogMethod *'>
  self assert: (self methodHasCogMethod: aMethodObj) not.
  "pop off inner return and locate open PIC"
  pic := self cCoerceSimple: self popStack - cogit interpretOffset to: #'CogMethod *'.
  self assert: (pic cmType = CMOpenPIC or: [pic cmType = CMClosedPIC]).
  "If found from an open PIC then it must be an uncogged method and, since it's been found
  in the method cache, should be cogged if possible.  If found from a closed PIC it should
+ be interpreted (since being reached by that route implies it is uncoggable, either because
+ there was no space, it had too many literals or it contained an illegal bytecode)."
+ pic cmType = CMOpenPIC ifTrue:
+ [(self methodShouldBeCogged: aMethodObj) ifTrue:
+ [cogit cog: aMethodObj selector: pic selector.
+ (self methodHasCogMethod: aMethodObj) ifTrue:
+ [self executeCogMethod: (self cogMethodOf: aMethodObj)
+ fromUnlinkedSendWithReceiver: rcvr]]].
- be interpreted (since being reached by that route implies it is uncoggable)."
- pic cmType = CMOpenPIC
- ifTrue:
- [(self methodShouldBeCogged: aMethodObj) ifTrue:
- [cogit cog: aMethodObj selector: pic selector.
- (self methodHasCogMethod: aMethodObj) ifTrue:
- [self executeCogMethod: (self cogMethodOf: aMethodObj)
- fromUnlinkedSendWithReceiver: rcvr]]]
- ifFalse:
- [self assert: (cogCompiledCodeCompactionCalledFor
- or: [(self methodShouldBeCogged: aMethodObj) not])].
  messageSelector := pic selector.
  newMethod := aMethodObj.
  primitiveIndex := self primitiveIndexOf: aMethodObj.
  primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: objectMemory nilObject.
  argumentCount := pic cmNumArgs.
  instructionPointer := self popStack.
  ^self interpretMethodFromMachineCode
  "NOTREACHED"!

Item was changed:
  ----- Method: Cogit class>>generatorTableFrom: (in category 'class initialization') -----
  generatorTableFrom: anArray
  | blockCreationBytecodeSize |
  generatorTable := CArrayAccessor on: (Array new: 256).
  anArray do:
  [:tuple| | descriptor |
  (descriptor := CogBytecodeDescriptor new)
  numBytes: tuple first;
  generator: tuple fourth;
  isReturn: (tuple includes: #return);
  isMapped: (tuple includes: #isMapped);
  isMappedInBlock: (tuple includes: #isMappedInBlock);
  isBlockCreation: (tuple includes: #block);
  spanFunction: (((tuple includes: #block) or: [(tuple includes: #branch)]) ifTrue:
  [tuple detect: [:thing| thing isSymbol and: [thing numArgs = 4]]]);
  isBranchTrue: (tuple includes: #isBranchTrue);
  isBranchFalse: (tuple includes: #isBranchFalse);
  isExtension: (tuple includes: #extension);
  hasIRC: (tuple includes: #hasIRC);
  yourself.
+ "As a hack to cut down on descriptor flags, use opcode to tag unusedBytecode for
+ scanning. Currently descriptors are exactly 16 bytes with all 8 flag bits used.  As
+ another hack to eliminate a test in scanMethod mark unknows as extensions."
+ descriptor generator == #unknownBytecode ifTrue:
+ [descriptor opcode: Nop; isExtension: true].
  descriptor isBlockCreation ifTrue:
  [blockCreationBytecodeSize
  ifNil: [blockCreationBytecodeSize := descriptor numBytes]
  ifNotNil: [self assert: blockCreationBytecodeSize = descriptor numBytes]].
  tuple do:
  [:thing|
  thing isSymbol ifTrue:
  [(thing beginsWith: #needsFrame) ifTrue:
  [descriptor needsFrameFunction: thing].
  (CogRTLOpcodes classPool at: thing ifAbsent: []) ifNotNil:
  [:opcode| descriptor opcode: opcode]]].
  tuple last isInteger
  ifTrue: [descriptor stackDelta: tuple last]
  ifFalse:
  [descriptor needsFrameFunction ifNotNil:
  [self error: 'frameless block bytecodes must specify a stack delta']].
  tuple second to: tuple third do:
  [:index|
  generatorTable at: index put: descriptor]].
  BlockCreationBytecodeSize := blockCreationBytecodeSize.
  ^generatorTable!

Item was changed:
  ----- Method: Cogit>>implicitReceiverCacheAddressAt: (in category 'newspeak support') -----
  implicitReceiverCacheAddressAt: mcpc
  "Cached push implicit receiver implementation.  If objectRepresentation doesn't support
  pinning then caller looks like
  mov selector, SendNumArgsReg
  call ceImplicitReceiver
  br continue
  Lclass: .word
  Lmixin:: .word
  continue:
  If objectRepresentation supports pinning then caller looks like
  mov Lclass, Arg1Reg
  mov selector, SendNumArgsReg
  call ceImplicitReceiver
  and Lclass: .word; Lmixin: .word is somewhere on the heap."
  <option: #NewspeakVM>
  <inline: true>
+ <returnTypeC: #usqInt>
  ^objectRepresentation canPinObjects
  ifTrue:
+ [(backEnd implicitReceiveCacheAt: mcpc) asUnsignedInteger]
- [backEnd implicitReceiveCacheAt: mcpc]
  ifFalse:
  [mcpc asUnsignedInteger + backEnd jumpShortByteSize]!

Item was changed:
  ----- Method: Cogit>>scanMethod (in category 'compile abstract instructions') -----
  scanMethod
  "Scan the method (and all embedded blocks) to determine
  - what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
  - if the method needs a frame or not
  - what are the targets of any backward branches.
  - how many blocks it creates
+ - if it contans an unknown bytecode
  Answer the block count or on error a negative error code"
  | latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
  <var: #descriptor type: #'BytecodeDescriptor *'>
  needsFrame := false.
  inBlock := false.
  self cppIf: #NewspeakVM ifTrue:
  [numIRCs := 0].
  (primitiveIndex > 0
  and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
  [^0].
  pc := latestContinuation := initialPC.
  numBlocks := framelessStackDelta := nExts := extA := extB := 0.
  [pc <= endPC] whileTrue:
  [byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  descriptor := self generatorAt: byte0.
  descriptor isExtension ifTrue:
+ [descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
+ [^EncounteredUnknownBytecode].
+ self loadSubsequentBytesForDescriptor: descriptor at: pc.
- [self loadSubsequentBytesForDescriptor: descriptor at: pc.
  self perform: descriptor generator].
  (descriptor isReturn
   and: [pc >= latestContinuation]) ifTrue:
  [endPC := pc].
  needsFrame ifFalse:
  [(descriptor needsFrameFunction isNil
   or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  ifTrue: [needsFrame := true]
  ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  descriptor isBranch ifTrue:
  [distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  targetPC := pc + descriptor numBytes + distance.
  (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
  ifTrue: [self initializeFixupAt: targetPC - initialPC]
  ifFalse: [latestContinuation := latestContinuation max: targetPC]].
  descriptor isBlockCreation ifTrue:
  [numBlocks := numBlocks + 1.
  distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  targetPC := pc + descriptor numBytes + distance.
  latestContinuation := latestContinuation max: targetPC].
  self cppIf: #NewspeakVM ifTrue:
  [descriptor hasIRC ifTrue:
  [numIRCs := numIRCs + 1]].
  pc := pc + descriptor numBytes.
  descriptor isExtension
  ifTrue: [nExts := nExts + 1]
  ifFalse: [nExts := extA := extB := 0]].
  ^numBlocks!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>scanMethod (in category 'compile abstract instructions') -----
  scanMethod
  "Scan the method (and all embedded blocks) to determine
  - what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
  - if the method needs a frame or not
  - what are the targets of any backward branches.
  - how many blocks it creates
  - how many counters it needs/conditional branches it contains
  Answer the block count or on error a negative error code"
  | latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
  <var: #descriptor type: #'BytecodeDescriptor *'>
  needsFrame := false.
  inBlock := false.
  prevBCDescriptor := nil.
  numCounters := 0.
  self cppIf: #NewspeakVM ifTrue:
  [numIRCs := 0].
  (primitiveIndex > 0
  and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
  [^0].
  pc := latestContinuation := initialPC.
  numBlocks := framelessStackDelta := nExts := extA := extB := 0.
  [pc <= endPC] whileTrue:
  [byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  descriptor := self generatorAt: byte0.
  descriptor isExtension ifTrue:
+ [descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
+ [^EncounteredUnknownBytecode].
+ self loadSubsequentBytesForDescriptor: descriptor at: pc.
- [self loadSubsequentBytesForDescriptor: descriptor at: pc.
  self perform: descriptor generator].
  (descriptor isReturn
   and: [pc >= latestContinuation]) ifTrue:
  [endPC := pc].
  needsFrame ifFalse:
  [(descriptor needsFrameFunction isNil
   or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  ifTrue: [needsFrame := true]
  ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  descriptor isBranch ifTrue:
  [distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  targetPC := pc + descriptor numBytes + distance.
  (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
  ifTrue: [self initializeFixupAt: targetPC - initialPC]
  ifFalse:
  [latestContinuation := latestContinuation max: targetPC.
  (descriptor isBranchTrue or: [descriptor isBranchFalse]) ifTrue:
  [numCounters := numCounters + 1]]].
  descriptor isBlockCreation ifTrue:
  [numBlocks := numBlocks + 1.
  distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  targetPC := pc + descriptor numBytes + distance.
  latestContinuation := latestContinuation max: targetPC].
  self cppIf: #NewspeakVM ifTrue:
  [descriptor hasIRC ifTrue:
  [numIRCs := numIRCs + 1]].
  pc := pc + descriptor numBytes.
  descriptor isExtension
  ifTrue: [nExts := nExts + 1]
  ifFalse: [nExts := extA := extB := 0].
  prevBCDescriptor := descriptor].
  ^numBlocks!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>scanMethod (in category 'compile abstract instructions') -----
  scanMethod
  "Scan the method (and all embedded blocks) to determine
  - what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
  - if the method needs a frame or not
  - what are the targets of any backward branches.
  - how many blocks it creates
  Answer the block count or on error a negative error code"
  | latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
  <var: #descriptor type: #'BytecodeDescriptor *'>
  needsFrame := false.
  inBlock := false.
  prevBCDescriptor := nil.
  self cppIf: #NewspeakVM ifTrue:
  [numIRCs := 0].
  (primitiveIndex > 0
  and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
  [^0].
  pc := latestContinuation := initialPC.
  numBlocks := framelessStackDelta := nExts := extA := extB := 0.
  [pc <= endPC] whileTrue:
  [byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  descriptor := self generatorAt: byte0.
  descriptor isExtension ifTrue:
+ [descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
+ [^EncounteredUnknownBytecode].
+ self loadSubsequentBytesForDescriptor: descriptor at: pc.
- [self loadSubsequentBytesForDescriptor: descriptor at: pc.
  self perform: descriptor generator].
  (descriptor isReturn
   and: [pc >= latestContinuation]) ifTrue:
  [endPC := pc].
  needsFrame ifFalse:
  [(descriptor needsFrameFunction isNil
   or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  ifTrue: [needsFrame := true]
  ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  descriptor isBranch ifTrue:
  [distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  targetPC := pc + descriptor numBytes + distance.
  (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
  ifTrue: [self initializeFixupAt: targetPC - initialPC]
  ifFalse: [latestContinuation := latestContinuation max: targetPC]].
  descriptor isBlockCreation ifTrue:
  [numBlocks := numBlocks + 1.
  distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  targetPC := pc + descriptor numBytes + distance.
  latestContinuation := latestContinuation max: targetPC].
  self cppIf: #NewspeakVM ifTrue:
  [descriptor hasIRC ifTrue:
  [numIRCs := numIRCs + 1]].
  pc := pc + descriptor numBytes.
  descriptor isExtension
  ifTrue: [nExts := nExts + 1]
  ifFalse: [nExts := extA := extB := 0].
  prevBCDescriptor := descriptor].
  ^numBlocks!