[squeak-dev] The Trunk: Kernel-eem.857.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jun 23 17:27:09 UTC 2014


Eliot Miranda uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-eem.857.mcz

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

Name: Kernel-eem.857
Author: eem
Time: 23 June 2014, 10:26:23.836 am
UUID: 9ff469b7-fc26-4f39-9212-144316319dbb
Ancestors: Kernel-dtl.856

Make the debuggber process faithful.

"Process>>effectiveProcess is a mechanism to allow process-
faithful debugging. The debugger executes code on behalf of
processes, so unless some effort is made the identity of
Processor activeProcess is not correctly maintained when
debugging code. The debugger uses evaluate:onBehalfOf: to
assign the debugged process as the effectiveProcess of the
process executing the code, preserving process identity."

=============== Diff against Kernel-dtl.856 ===============

Item was changed:
  Link subclass: #Process
+ 	instanceVariableNames: 'suspendedContext priority myList threadId effectiveProcess name island env'
- 	instanceVariableNames: 'suspendedContext priority myList threadId name island env'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Kernel-Processes'!
  
  !Process commentStamp: 'ul 3/22/2011 05:18' prior: 0!
  I represent an independent path of control in the system. This path of control may be stopped (by sending the message suspend) in such a way that it can later be restarted (by sending the message resume). When any one of several paths of control can be advanced, the single instance of ProcessorScheduler named Processor determines which one will actually be advanced partly using the value of priority.
  
  (If anyone ever makes a subclass of Process, be sure to use allSubInstances in anyProcessesAbove:.)
  
  The threadId variable is used by multi-threaded CogVMs to control process-to-thread binding. It's required to be the fourth instance variable. See SmalltalkImage >> #processHasThreadIdInstVar: for further information.
  
  The island and env instance variables are not used by core squeak, but are used by external packages and included here because Monticello cannot handle external instance variables:
  island: used by Tweak and Croquet to partition the image into multiple address spaces
  env: used by ProcessSpecific to implement per-process variables!

Item was changed:
  ----- Method: Process>>activateReturn:value: (in category 'changing suspended state') -----
  activateReturn: aContext value: value
  	"Activate 'aContext return: value', so execution will return to aContext's sender"
  
+ 	^Processor activeProcess
+ 		evaluate: [suspendedContext := suspendedContext activateReturn: aContext value: value]
+ 		onBehalfOf: self!
- 	^ suspendedContext := suspendedContext activateReturn: aContext value: value!

Item was changed:
  ----- Method: Process>>complete: (in category 'changing suspended state') -----
  complete: aContext 
  	"Run self until aContext is popped or an unhandled error is raised.  Return self's new top context, unless an unhandled error was raised then return the signaler context (rather than open a debugger)."
  	
  	| ctxt pair error |
  	ctxt := suspendedContext.
  	suspendedContext := nil.  "disable this process while running its stack in active process below"
+ 	pair := Processor activeProcess
+ 				evaluate: [ctxt runUntilErrorOrReturnFrom: aContext]
+ 				onBehalfOf: self.
- 	pair := ctxt runUntilErrorOrReturnFrom: aContext.
  	suspendedContext := pair first.
  	error := pair second.
  	error ifNotNil: [^ error signalerContext].
  	^ suspendedContext!

Item was added:
+ ----- Method: Process>>effectiveProcess (in category 'accessing') -----
+ effectiveProcess
+ 	"effectiveProcess is a mechanism to allow process-faithful debugging.  The debugger executes code
+ 	 on behalf of processes, so unless some effort is made the identity of Processor activeProcess is not
+ 	 correctly maintained when debugging code.  The debugger uses evaluate:onBehalfOf: to assign the
+ 	 debugged process as the effectiveProcess of the process executing the code, preserving process
+ 	 identity."
+ 	^effectiveProcess ifNil: [self]!

Item was added:
+ ----- Method: Process>>evaluate:onBehalfOf: (in category 'private') -----
+ evaluate: aBlock onBehalfOf: aProcess
+ 	"Evaluate aBlock setting effectiveProcess to aProcess.  Used
+ 	 in the execution simulation machinery to ensure that
+ 	 Processor activeProcess evaluates correctly when debugging."
+ 	| oldEffectiveProcess |
+ 	oldEffectiveProcess := effectiveProcess.
+ 	effectiveProcess := aProcess.
+ 	^aBlock ensure: [effectiveProcess := oldEffectiveProcess]!

Item was changed:
  ----- Method: Process>>popTo: (in category 'changing suspended state') -----
  popTo: aContext 
  	"Pop self down to aContext by remote returning from aContext's callee.  Unwind blocks will be executed on the way.
  	This is done by pushing a new context on top which executes 'aContext callee return' then resuming self until aContext is reached.  This way any errors raised in an unwind block will get handled by senders in self and not by senders in the activeProcess.
  	If an unwind block raises an error that is not handled then the popping stops at the error and the signalling context is returned, othewise aContext is returned."
  
+ 	self == Processor activeProcess ifTrue:
+ 		[^self error: 'The active process cannot pop contexts'].
+ 	^(self calleeOf: aContext)
+ 		ifNil: [aContext]  "aContext is on top"
+ 		ifNotNil:
+ 			[:callee|
+ 			 Processor activeProcess
+ 				evaluate: [self return: callee value: callee receiver]
+ 				onBehalfOf: self]!
- 	| callee |
- 	self == Processor activeProcess
- 		ifTrue: [^ self error: 'The active process cannot pop contexts'].
- 	callee := (self calleeOf: aContext) ifNil: [^ aContext].  "aContext is on top"
- 	^ self return: callee value: callee receiver!

Item was changed:
  ----- Method: Process>>popTo:value: (in category 'changing suspended state') -----
  popTo: aContext value: aValue
  	"Replace the suspendedContext with aContext, releasing all contexts 
+ 	 between the currently suspendedContext and it."
- 	between the currently suspendedContext and it."
  
+ 	self == Processor activeProcess ifTrue:
+ 		[^self error: 'The active process cannot pop contexts'].
+ 	^(self calleeOf: aContext)
+ 		ifNil: [aContext]  "aContext is on top"
+ 		ifNotNil:
+ 			[:callee|
+ 			 Processor activeProcess
+ 				evaluate: [self return: callee value: aValue]
+ 				onBehalfOf: self]!
- 	| callee |
- 	self == Processor activeProcess
- 		ifTrue: [^ self error: 'The active process cannot pop contexts'].
- 	callee := (self calleeOf: aContext) ifNil: [^ self].  "aContext is on top"
- 	self return: callee value: aValue!

Item was changed:
  ----- Method: Process>>return:value: (in category 'changing suspended state') -----
  return: aContext value: value
  	"Pop thread down to aContext's sender.  Execute any unwind blocks on the way.  See #popTo: comment and #runUntilErrorOrReturnFrom: for more details."
  
+ 	suspendedContext == aContext ifTrue:
+ 		[^Processor activeProcess
+ 			evaluate: [suspendedContext := aContext return: value from: aContext]
+ 			onBehalfOf: self].
- 	suspendedContext == aContext ifTrue: [
- 		^ suspendedContext := aContext return: value from: aContext].
  	self activateReturn: aContext value: value.
+ 	^self complete: aContext!
- 	^ self complete: aContext.
- !

Item was changed:
  ----- Method: Process>>step (in category 'changing suspended state') -----
  step
  
+ 	^Processor activeProcess
+ 		evaluate: [suspendedContext := suspendedContext step]
+ 		onBehalfOf: self!
- 	^ suspendedContext := suspendedContext step!

Item was changed:
  ----- Method: Process>>step: (in category 'changing suspended state') -----
  step: aContext 
  	"Resume self until aContext is on top, or if already on top, do next step"
  
+ 	^Processor activeProcess
+ 		evaluate:
+ 			[self suspendedContext == aContext
+ 				ifTrue: [suspendedContext := suspendedContext step]
+ 				ifFalse: [self complete: (self calleeOf: aContext)]]
+ 		onBehalfOf: self!
- 	^ self suspendedContext == aContext
- 		ifTrue: [self step]
- 		ifFalse: [self complete: (self calleeOf: aContext)]!

Item was changed:
  ----- Method: Process>>stepToCallee (in category 'changing suspended state') -----
  stepToCallee
  	"Step until top context changes"
  
+ 	Processor activeProcess
+ 		evaluate:
+ 			[| ctxt |
+ 			ctxt := suspendedContext.
+ 			[ctxt == suspendedContext] whileTrue: [
+ 				suspendedContext := suspendedContext step]]
+ 		onBehalfOf: self.
+ 	^suspendedContext!
- 	| ctxt |
- 	ctxt := suspendedContext.
- 	[ctxt == suspendedContext] whileTrue: [
- 		suspendedContext := suspendedContext step].
- 	^ suspendedContext!

Item was changed:
  ----- Method: Process>>stepToSendOrReturn (in category 'changing suspended state') -----
  stepToSendOrReturn
  
+ 	^Processor activeProcess
+ 		evaluate: [suspendedContext := suspendedContext stepToSendOrReturn]
+ 		onBehalfOf: self!
- 	^ suspendedContext := suspendedContext stepToSendOrReturn!

Item was changed:
  ----- Method: ProcessorScheduler>>activePriority (in category 'accessing') -----
  activePriority
  	"Answer the priority level of the currently running Process."
  
+ 	^activeProcess effectiveProcess priority!
- 	^activeProcess priority!

Item was changed:
  ----- Method: ProcessorScheduler>>activeProcess (in category 'accessing') -----
  activeProcess
  	"Answer the currently running Process."
  
+ 	^activeProcess effectiveProcess!
- 	^activeProcess!

Item was changed:
  ----- Method: ProcessorScheduler>>terminateActive (in category 'process state change') -----
  terminateActive
  	"Terminate the process that is currently running."
  
+ 	activeProcess effectiveProcess terminate!
- 	activeProcess terminate!



More information about the Squeak-dev mailing list