VM Maker Inbox: VMMaker.oscog-akg.2487.mcz

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

VM Maker Inbox: VMMaker.oscog-akg.2487.mcz

commits-2
 
Alistair Grant uploaded a new version of VMMaker to project VM Maker Inbox:
http://source.squeak.org/VMMakerInbox/VMMaker.oscog-akg.2487.mcz

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

Name: VMMaker.oscog-akg.2487
Author: akg
Time: 29 November 2018, 6:40:57.726983 pm
UUID: 81e92544-31de-4944-a742-11a331113606
Ancestors: VMMaker.oscog-cb.2486

#isContext: is sent to self instead of objectMemory

Fix a couple of typo's in:

- CoInterpreter>>ceNonLocalReturn:
- StackInterpreter>>commonReturn

where #isContext: is sent to self instead of objectMemory.

=============== Diff against VMMaker.oscog-cb.2486 ===============

Item was changed:
  ----- Method: CoInterpreter>>ceNonLocalReturn: (in category 'trampolines') -----
  ceNonLocalReturn: returnValue
  <api>
  | closure home unwindContextOrNilOrZero ourContext frameToReturnTo contextToReturnTo theFP callerFP newPage |
  <var: #frameToReturnTo type: #'char *'>
  <var: #theFP type: #'char *'>
  <var: #callerFP type: #'char *'>
  <var: #newPage type: #'StackPage *'>
  <var: #thePage type: #'StackPage *'>
 
  "self shortPrintFrameAndCallers: framePointer.
  self printOop: returnValue.
  self halt."
 
  self assert: (self isMachineCodeFrame: framePointer).
  self assert: (self frameIsBlockActivation: framePointer).
 
  "Update the current page's headFrame pointers to enable the search for unwind protects below
  to identify widowed contexts correctly."
  self externalWriteBackHeadFramePointers.
 
  "Since this is a block activation the closure is on the stack above any args and the frame."
  closure := self pushedReceiverOrClosureOfFrame: framePointer.
  home := nil. "avoid compiler warning"
  "Walk the closure's lexical chain to find the context or frame to return from (home)."
  [closure ~= objectMemory nilObject] whileTrue:
  [home := objectMemory followField: ClosureOuterContextIndex ofObject: closure.
+ (objectMemory isContext: home) ifFalse:
- (self isContext: home) ifFalse:
  ["error: can't find home on chain; cannot return"
  ourContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  ^self externalCannotReturn: returnValue from: ourContext].
  closure := objectMemory followField: ClosureIndex ofObject: home].
  "home is to be returned from provided there is no unwind-protect activation between
  this frame and home's sender.  Search for an unwind.  findUnwindThroughContext:
  will answer either the context for an unwind-protect activation or nilObj if the sender
  cannot be found or 0 if no unwind is found but the sender is."
  unwindContextOrNilOrZero := self findUnwindThroughContext: home.
  unwindContextOrNilOrZero = objectMemory nilObject ifTrue:
  ["error: can't find home on chain; cannot return"
  ourContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  ^self externalCannotReturn: returnValue from: ourContext].
  unwindContextOrNilOrZero ~= 0 ifTrue:
  [^self externalAboutToReturn: returnValue through: unwindContextOrNilOrZero].
 
  "Now we know home is on the sender chain.
  We could be returning to either a context or a frame.  Find out which."
  contextToReturnTo := nil.
  (self isMarriedOrWidowedContext: home)
  ifTrue:
  [self assert: (self checkIsStillMarriedContext: home currentFP: framePointer).
  theFP := self frameOfMarriedContext: home.
  (self isBaseFrame: theFP)
  ifTrue:
  [contextToReturnTo := self frameCallerContext: theFP]
  ifFalse:
  [frameToReturnTo := self frameCallerFP: theFP]]
  ifFalse:
  [contextToReturnTo := objectMemory fetchPointer: SenderIndex ofObject: home.
  ((objectMemory isContext: contextToReturnTo)
   and: [self isMarriedOrWidowedContext: contextToReturnTo]) ifTrue:
  [self assert: (self checkIsStillMarriedContext: contextToReturnTo currentFP: framePointer).
  frameToReturnTo := self frameOfMarriedContext: contextToReturnTo.
  contextToReturnTo := nil]].
 
  "If returning to a context we must make a frame for it unless it is dead."
  contextToReturnTo ~= nil ifTrue:
  [frameToReturnTo := self establishFrameForContextToReturnTo: contextToReturnTo.
  frameToReturnTo = 0 ifTrue:
  ["error: home's sender is dead; cannot return"
  ourContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  ^self externalCannotReturn: returnValue from: ourContext]].
 
  "Now we have a frame to return to.  If it is on a different page we must
  free intervening pages and nil out intervening contexts.  We must free
  intervening stack pages because if we leave the pages to be divorced
  then their contexts will be divorced with intact senders and instruction
  pointers.  This code is similar to primitiveTerminateTo."
  self assert: stackPages pageListIsWellFormed.
  newPage := stackPages stackPageFor: frameToReturnTo.
  newPage ~~ stackPage ifTrue:
  [| currentCtx thePage nextCntx |
  currentCtx := self frameCallerContext: stackPage baseFP.
  self assert: (objectMemory isContext: currentCtx).
  stackPages freeStackPage: stackPage.
  [self assert: (objectMemory isContext: currentCtx).
   (self isMarriedOrWidowedContext: currentCtx)
    and: [(stackPages stackPageFor: (theFP := self frameOfMarriedContext: currentCtx)) = newPage]] whileFalse:
  [(self isMarriedOrWidowedContext: currentCtx)
  ifTrue:
  [thePage := stackPages stackPageFor: theFP.
  currentCtx := self frameCallerContext: thePage baseFP.
  stackPages freeStackPage: thePage]
  ifFalse:
  [nextCntx := objectMemory fetchPointer: SenderIndex ofObject: currentCtx.
  self markContextAsDead: currentCtx.
  currentCtx := nextCntx]].
  self setStackPageAndLimit: newPage.
  self setStackPointersFromPage: newPage].
 
  "Two cases.  Returning to the top frame or an interior frame.  The
  top frame has its instruction pointer on top of stack.  An interior
  frame has its instruction pointer in the caller frame. We need to
  peel back any frames on the page until we get to the correct frame."
  framePointer = frameToReturnTo
  ifTrue:
  [instructionPointer := self popStack]
  ifFalse:
  [[callerFP := framePointer.
   framePointer := self frameCallerFP: framePointer.
   framePointer ~~ frameToReturnTo] whileTrue.
  instructionPointer := (self frameCallerSavedIP: callerFP) asUnsignedInteger.
  stackPointer := (self frameCallerSP: callerFP)].
  ^self return: returnValue toExecutive: false!

Item was changed:
  ----- Method: StackInterpreter>>commonReturn (in category 'return bytecodes') -----
  commonReturn
  "Do an ^-return (return from method), checking for unwinds if this is a block activation.
  Note: Assumed to be inlined into the dispatch loop."
 
  <sharedCodeInCase: #returnReceiver>
  | closure home unwindContextOrNilOrZero frameToReturnTo contextToReturnTo theFP callerFP newPage |
  <var: #frameToReturnTo type: #'char *'>
  <var: #theFP type: #'char *'>
  <var: #callerFP type: #'char *'>
  <var: #newPage type: #'StackPage *'>
  <var: #thePage type: #'StackPage *'>
 
  "If this is a method simply return to the  sender/caller."
  (self iframeIsBlockActivation: localFP) ifFalse:
  [^self commonCallerReturn].
 
  "Update the current page's headFrame pointers to enable the search for unwind protects below
  to identify widowed contexts correctly."
  self writeBackHeadFramePointers.
  self externalizeIPandSP.
 
  "Since this is a block activation the closure is on the stack above any args and the frame."
  closure := self pushedReceiverOrClosureOfFrame: localFP.
  home := nil. "avoid compiler warning"
  "Walk the closure's lexical chain to find the context or frame to return from (home).
  If home is missing (Sista closures) then throw cannotReturn rather than crash."
  [closure ~= objectMemory nilObject] whileTrue:
  [home := objectMemory followField: ClosureOuterContextIndex ofObject: closure.
+ (objectMemory isContext: home) ifFalse:
- (self isContext: home) ifFalse:
  [^self internalCannotReturn: localReturnValue].
  closure := objectMemory followField: ClosureIndex ofObject: home].
  "home is to be returned from provided there is no unwind-protect activation between
  this frame and home's sender.  Search for an unwind.  findUnwindThroughContext:
  will answer either the context for an unwind-protect activation or nilObj if the sender
  cannot be found or 0 if no unwind is found but the sender is."
  unwindContextOrNilOrZero := self findUnwindThroughContext: home.
  unwindContextOrNilOrZero = objectMemory nilObject ifTrue:
  ["error: can't find home on chain; cannot return"
  ^self internalCannotReturn: localReturnValue].
  unwindContextOrNilOrZero ~= 0 ifTrue:
  [^self internalAboutToReturn: localReturnValue through: unwindContextOrNilOrZero].
 
  "Now we know home is on the sender chain.
  We could be returning to either a context or a frame.  Find out which."
  contextToReturnTo := nil.
  (self isMarriedOrWidowedContext: home)
  ifTrue:
  [self assert: (self checkIsStillMarriedContext: home currentFP: localFP).
  theFP := self frameOfMarriedContext: home.
  (self isBaseFrame: theFP)
  ifTrue:
  [contextToReturnTo := self frameCallerContext: theFP]
  ifFalse:
  [frameToReturnTo := self frameCallerFP: theFP]]
  ifFalse:
  [contextToReturnTo := objectMemory fetchPointer: SenderIndex ofObject: home.
  ((objectMemory isContext: contextToReturnTo)
   and: [self isMarriedOrWidowedContext: contextToReturnTo]) ifTrue:
  [self assert: (self checkIsStillMarriedContext: contextToReturnTo currentFP: localFP).
  frameToReturnTo := self frameOfMarriedContext: contextToReturnTo.
  contextToReturnTo := nil]].
 
  "If returning to a context we must make a frame for it unless it is dead."
  contextToReturnTo ~= nil ifTrue:
  [frameToReturnTo := self establishFrameForContextToReturnTo: contextToReturnTo.
  frameToReturnTo = 0 ifTrue: "error: home's sender is dead; cannot return"
  [^self internalCannotReturn: localReturnValue]].
 
  "Now we have a frame to return to.  If it is on a different page we must free intervening pages and
  nil out intervening contexts.  We must free intervening stack pages because if we leave the pages
  to be divorced then their contexts will be divorced with intact senders and instruction pointers.  This
  code is similar to primitiveTerminateTo.  We must move any frames on intervening pages above the
  frame linked to because these may be in use, e.g. via co-routining (see baseFrameReturn)."
  self assert: stackPages pageListIsWellFormed.
  newPage := stackPages stackPageFor: frameToReturnTo.
  newPage ~~ stackPage ifTrue:
  [| currentCtx thePage nextCntx |
  currentCtx := self frameCallerContext: stackPage baseFP.
  stackPages freeStackPage: stackPage.
  [self assert: (objectMemory isContext: currentCtx).
   (self isMarriedOrWidowedContext: currentCtx)
    and: [(stackPages stackPageFor: (theFP := self frameOfMarriedContext: currentCtx)) = newPage]] whileFalse:
  [(self isMarriedOrWidowedContext: currentCtx)
  ifTrue:
  [thePage := stackPages stackPageFor: theFP.
  theFP ~= thePage headFP ifTrue:
  ["Since we've just deallocated a page we know that newStackPage won't deallocate an existing one."
  self moveFramesIn: thePage through: (self findFrameAbove: theFP inPage: thePage) toPage: stackPages newStackPage].
  currentCtx := self frameCallerContext: thePage baseFP.
  stackPages freeStackPage: thePage]
  ifFalse:
  [nextCntx := objectMemory fetchPointer: SenderIndex ofObject: currentCtx.
  self markContextAsDead: currentCtx.
  currentCtx := nextCntx]].
  self setStackPageAndLimit: newPage.
  localSP := stackPage headSP.
  localFP := stackPage headFP].
 
  "Two cases.  Returning to the top frame on a new page or an interior frame on the current page.
  The top frame has its instruction pointer on top of stack. An interior frame has its instruction pointer
  in the caller frame. We need to peel back any frames on the page until we get to the correct frame."
 
  localFP = frameToReturnTo
  ifTrue: "pop the saved IP, push the return value and continue."
  [localIP := self pointerForOop: self internalStackTop]
  ifFalse:
  [[callerFP := localFP.
   localFP := self frameCallerFP: localFP.
   localFP ~~ frameToReturnTo] whileTrue.
  localIP := self frameCallerSavedIP: callerFP.
  localSP := (self frameCallerSP: callerFP) - objectMemory wordSize].
  self maybeReturnToMachineCodeFrame.
  self setMethod: (self frameMethod: localFP).
  self fetchNextBytecode.
  self internalStackTopPut: localReturnValue!