The Trunk: Kernel-mt.1272.mcz

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

The Trunk: Kernel-mt.1272.mcz

commits-2
Marcel Taeumel uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-mt.1272.mcz

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

Name: Kernel-mt.1272
Author: mt
Time: 7 October 2019, 10:09:56.205231 am
UUID: 8fe3f896-0806-fe46-8e86-68f3c0f98d4d
Ancestors: Kernel-ul.1271

Complements System-mt.1112, which fixes and clean-up in the debugger infrastructure.

=============== Diff against Kernel-ul.1271 ===============

Item was changed:
  ----- Method: Context>>cannotReturn: (in category 'private-exceptions') -----
  cannotReturn: result
 
  closureOrNil notNil ifTrue:
  [^self cannotReturn: result to: self home sender].
+ Processor activeProcess
+ debug: thisContext
+ title: 'computation has been terminated'
+ full: false.!
- ToolSet
- debugActiveProcessContext: thisContext
- label: 'computation has been terminated'
- contents: nil!

Item was changed:
  ----- Method: Context>>doPrimitive:method:receiver:args: (in category 'private') -----
  doPrimitive: primitiveIndex method: meth receiver: receiver args: arguments
  "Simulate a primitive method whose index is primitiveIndex.  The simulated receiver and
  arguments are given as arguments to this message. If successful, push result and return
  resuming context, else ^ {errCode, PrimitiveFailToken}. Any primitive which provokes
  execution needs to be intercepted and simulated to avoid execution running away."
 
  | value |
  "Judicious use of primitive 19 (a null primitive that doesn't do anything) prevents
  the debugger from entering various run-away activities such as spawning a new
  process, etc.  Injudicious use results in the debugger not being able to debug
  interesting code, such as the debugger itself.  Hence use primitive 19 with care :-)"
  "SystemNavigation new browseAllSelect: [:m| m primitive = 19]"
+ primitiveIndex = 19 ifTrue: [
+ Processor activeProcess
+ debug: self
+ title:'Code simulation error'
+ full: false].
- primitiveIndex = 19 ifTrue:
- [ToolSet
- debugActiveProcessContext: self
- label:'Code simulation error'
- contents: nil].
 
  ((primitiveIndex between: 201 and: 222)
  and: [(self objectClass: receiver) includesBehavior: BlockClosure]) ifTrue:
  [(primitiveIndex = 206
   or: [primitiveIndex = 208]) ifTrue: "[Full]BlockClosure>>valueWithArguments:"
  [^receiver simulateValueWithArguments: arguments first caller: self].
  ((primitiveIndex between: 201 and: 209) "[Full]BlockClosure>>value[:value:...]"
   or: [primitiveIndex between: 221 and: 222]) ifTrue: "[Full]BlockClosure>>valueNoContextSwitch[:]"
  [^receiver simulateValueWithArguments: arguments caller: self]].
 
  primitiveIndex = 83 ifTrue: "afr 9/11/1998 19:50" "Object>>perform:[with:...]"
  [^self send: arguments first to: receiver with: arguments allButFirst].
  primitiveIndex = 84 ifTrue: "afr 9/11/1998 19:50 & eem 8/18/2009 17:04" "Object>>perform:withArguments:"
  [^self send: arguments first to: receiver with: (arguments at: 2) lookupIn: (self objectClass: receiver)].
  primitiveIndex = 100 ifTrue: "eem 8/18/2009 16:57" "Object>>perform:withArguments:inSuperclass:"
  [^self send: arguments first to: receiver with: (arguments at: 2) lookupIn: (arguments at: 3)].
 
  "Mutex>>primitiveEnterCriticalSection
  Mutex>>primitiveTestAndSetOwnershipOfCriticalSection"
  (primitiveIndex = 186 or: [primitiveIndex = 187]) ifTrue:
  [| effective |
  effective := Processor activeProcess effectiveProcess.
  "active == effective"
  value := primitiveIndex = 186
  ifTrue: [receiver primitiveEnterCriticalSectionOnBehalfOf: effective]
  ifFalse: [receiver primitiveTestAndSetOwnershipOfCriticalSectionOnBehalfOf: effective].
  ^(self isPrimFailToken: value)
  ifTrue: [value]
  ifFalse: [self push: value]].
 
  primitiveIndex = 188 ifTrue: "Object>>withArgs:executeMethod:
  CompiledMethod class>>receiver:withArguments:executeMethod:
  VMMirror>>ifFail:object:with:executeMethod: et al"
  [| n args methodArg thisReceiver |
  ((n := arguments size) between: 2 and: 4) ifFalse:
  [^self class primitiveFailTokenFor: #'unsupported operation'].
  ((self objectClass: (args := arguments at: n - 1)) == Array
   and: [(self objectClass: (methodArg := arguments at: n)) includesBehavior: CompiledMethod]) ifFalse:
  [^self class primitiveFailTokenFor: #'bad argument'].
  methodArg numArgs = args size ifFalse:
  [^self class primitiveFailTokenFor: #'bad number of arguments'].
  thisReceiver := arguments at: n - 2 ifAbsent: [receiver].
  methodArg primitive > 0 ifTrue:
  [methodArg isQuick ifTrue:
  [^self push: (methodArg valueWithReceiver: thisReceiver arguments: args)].
  ^self doPrimitive: methodArg primitive method: meth receiver: thisReceiver args: args].
  ^Context
  sender: self
  receiver: thisReceiver
  method: methodArg
  arguments: args].
 
  primitiveIndex = 118 ifTrue: "[receiver:]tryPrimitive:withArgs:; avoid recursing in the VM"
  [(arguments size = 3
   and: [(self objectClass: arguments second) == SmallInteger
   and: [(self objectClass: arguments last) == Array]]) ifTrue:
  [^self doPrimitive: arguments second method: meth receiver: arguments first args: arguments last].
  (arguments size = 2
  and: [(self objectClass: arguments first) == SmallInteger
  and: [(self objectClass: arguments last) == Array]]) ifFalse:
  [^self class primitiveFailTokenFor: nil].
  ^self doPrimitive: arguments first method: meth receiver: receiver args: arguments last].
 
  value := primitiveIndex = 120 "FFI method"
  ifTrue: [(meth literalAt: 1) tryInvokeWithArguments: arguments]
  ifFalse:
  [primitiveIndex = 117 "named primitives"
  ifTrue: [self tryNamedPrimitiveIn: meth for: receiver withArgs: arguments]
  ifFalse: "should use self receiver: receiver tryPrimitive: primitiveIndex withArgs: arguments but this is only in later VMs (and appears to be broken)"
  [receiver tryPrimitive: primitiveIndex withArgs: arguments]].
 
  ^(self isPrimFailToken: value)
  ifTrue: [value]
  ifFalse: [self push: value]!

Item was changed:
  ----- Method: Process>>debug (in category 'debugging') -----
  debug
+
+ ^ self debugWithTitle: 'Debug'!
- self debugWithTitle: 'Debug'.!

Item was added:
+ ----- Method: Process>>debug: (in category 'debugging') -----
+ debug: context
+
+ ^ self debug: context title: 'Debug'!

Item was changed:
  ----- Method: Process>>debug:title: (in category 'debugging') -----
  debug: context title: title
  "Open debugger on self with context shown on top"
 
+ ^ self debug: context title: title full: false
- self debug: context title: title full: false.
  !

Item was changed:
  ----- Method: Process>>debug:title:full: (in category 'debugging') -----
  debug: context title: title full: bool
 
+ ^ self
- self
  debug: context
  title: title
  full: bool
  contents: nil!

Item was changed:
  ----- Method: Process>>debug:title:full:contents: (in category 'debugging') -----
  debug: context title: title full: bool contents: contents
  "Open debugger on self with context shown on top"
 
  | topCtxt |
  topCtxt := self isActiveProcess ifTrue: [thisContext] ifFalse: [self suspendedContext].
  (topCtxt hasContext: context) ifFalse: [^ self error: 'context not in process'].
+ ^ ToolSet debugProcess: self context: context label: title contents: contents fullView: bool!
- ToolSet debugProcess: self context: context label: title contents: contents fullView: bool.!

Item was changed:
  ----- Method: Process>>debugWithTitle: (in category 'debugging') -----
  debugWithTitle: title
- "Open debugger on self"
 
+ ^ self debugWithTitle: title full: true!
- | context |
- context := self isActiveProcess ifTrue: [thisContext] ifFalse: [self suspendedContext].
- self debug: context title: title full: true.
- !

Item was added:
+ ----- Method: Process>>debugWithTitle:full: (in category 'debugging') -----
+ debugWithTitle: title full: aBoolean
+
+ ^ self debugWithTitle: title full: aBoolean contents: nil!

Item was added:
+ ----- Method: Process>>debugWithTitle:full:contents: (in category 'debugging') -----
+ debugWithTitle: title full: bool contents: contents
+ "Automatically choose the top context."
+
+ ^ self
+ debug: (self isActiveProcess ifTrue: [thisContext] ifFalse: [self suspendedContext])
+ title: title
+ full: bool
+ contents: contents!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Kernel-mt.1272.mcz

Levente Uzonyi
I think these methods should all be extension methods in Kernel, and be
methods of System, since that's where ToolSet is.

Levente

On Mon, 7 Oct 2019, [hidden email] wrote:

> Marcel Taeumel uploaded a new version of Kernel to project The Trunk:
> http://source.squeak.org/trunk/Kernel-mt.1272.mcz
>
> ==================== Summary ====================
>
> Name: Kernel-mt.1272
> Author: mt
> Time: 7 October 2019, 10:09:56.205231 am
> UUID: 8fe3f896-0806-fe46-8e86-68f3c0f98d4d
> Ancestors: Kernel-ul.1271
>
> Complements System-mt.1112, which fixes and clean-up in the debugger infrastructure.
>
> =============== Diff against Kernel-ul.1271 ===============
>
> Item was changed:
>  ----- Method: Context>>cannotReturn: (in category 'private-exceptions') -----
>  cannotReturn: result
>
>   closureOrNil notNil ifTrue:
>   [^self cannotReturn: result to: self home sender].
> + Processor activeProcess
> + debug: thisContext
> + title: 'computation has been terminated'
> + full: false.!
> - ToolSet
> - debugActiveProcessContext: thisContext
> - label: 'computation has been terminated'
> - contents: nil!
>
> Item was changed:
>  ----- Method: Context>>doPrimitive:method:receiver:args: (in category 'private') -----
>  doPrimitive: primitiveIndex method: meth receiver: receiver args: arguments
>   "Simulate a primitive method whose index is primitiveIndex.  The simulated receiver and
>   arguments are given as arguments to this message. If successful, push result and return
>   resuming context, else ^ {errCode, PrimitiveFailToken}. Any primitive which provokes
>   execution needs to be intercepted and simulated to avoid execution running away."
>
>   | value |
>   "Judicious use of primitive 19 (a null primitive that doesn't do anything) prevents
>   the debugger from entering various run-away activities such as spawning a new
>   process, etc.  Injudicious use results in the debugger not being able to debug
>   interesting code, such as the debugger itself.  Hence use primitive 19 with care :-)"
>   "SystemNavigation new browseAllSelect: [:m| m primitive = 19]"
> + primitiveIndex = 19 ifTrue: [
> + Processor activeProcess
> + debug: self
> + title:'Code simulation error'
> + full: false].
> - primitiveIndex = 19 ifTrue:
> - [ToolSet
> - debugActiveProcessContext: self
> - label:'Code simulation error'
> - contents: nil].
>
>   ((primitiveIndex between: 201 and: 222)
>   and: [(self objectClass: receiver) includesBehavior: BlockClosure]) ifTrue:
>   [(primitiveIndex = 206
>    or: [primitiveIndex = 208]) ifTrue: "[Full]BlockClosure>>valueWithArguments:"
>   [^receiver simulateValueWithArguments: arguments first caller: self].
>   ((primitiveIndex between: 201 and: 209) "[Full]BlockClosure>>value[:value:...]"
>    or: [primitiveIndex between: 221 and: 222]) ifTrue: "[Full]BlockClosure>>valueNoContextSwitch[:]"
>   [^receiver simulateValueWithArguments: arguments caller: self]].
>
>   primitiveIndex = 83 ifTrue: "afr 9/11/1998 19:50" "Object>>perform:[with:...]"
>   [^self send: arguments first to: receiver with: arguments allButFirst].
>   primitiveIndex = 84 ifTrue: "afr 9/11/1998 19:50 & eem 8/18/2009 17:04" "Object>>perform:withArguments:"
>   [^self send: arguments first to: receiver with: (arguments at: 2) lookupIn: (self objectClass: receiver)].
>   primitiveIndex = 100 ifTrue: "eem 8/18/2009 16:57" "Object>>perform:withArguments:inSuperclass:"
>   [^self send: arguments first to: receiver with: (arguments at: 2) lookupIn: (arguments at: 3)].
>
>   "Mutex>>primitiveEnterCriticalSection
>   Mutex>>primitiveTestAndSetOwnershipOfCriticalSection"
>   (primitiveIndex = 186 or: [primitiveIndex = 187]) ifTrue:
>   [| effective |
>   effective := Processor activeProcess effectiveProcess.
>   "active == effective"
>   value := primitiveIndex = 186
>   ifTrue: [receiver primitiveEnterCriticalSectionOnBehalfOf: effective]
>   ifFalse: [receiver primitiveTestAndSetOwnershipOfCriticalSectionOnBehalfOf: effective].
>   ^(self isPrimFailToken: value)
>   ifTrue: [value]
>   ifFalse: [self push: value]].
>
>   primitiveIndex = 188 ifTrue: "Object>>withArgs:executeMethod:
>   CompiledMethod class>>receiver:withArguments:executeMethod:
>   VMMirror>>ifFail:object:with:executeMethod: et al"
>   [| n args methodArg thisReceiver |
>   ((n := arguments size) between: 2 and: 4) ifFalse:
>   [^self class primitiveFailTokenFor: #'unsupported operation'].
>   ((self objectClass: (args := arguments at: n - 1)) == Array
>    and: [(self objectClass: (methodArg := arguments at: n)) includesBehavior: CompiledMethod]) ifFalse:
>   [^self class primitiveFailTokenFor: #'bad argument'].
>   methodArg numArgs = args size ifFalse:
>   [^self class primitiveFailTokenFor: #'bad number of arguments'].
>   thisReceiver := arguments at: n - 2 ifAbsent: [receiver].
>   methodArg primitive > 0 ifTrue:
>   [methodArg isQuick ifTrue:
>   [^self push: (methodArg valueWithReceiver: thisReceiver arguments: args)].
>   ^self doPrimitive: methodArg primitive method: meth receiver: thisReceiver args: args].
>   ^Context
>   sender: self
>   receiver: thisReceiver
>   method: methodArg
>   arguments: args].
>
>   primitiveIndex = 118 ifTrue: "[receiver:]tryPrimitive:withArgs:; avoid recursing in the VM"
>   [(arguments size = 3
>    and: [(self objectClass: arguments second) == SmallInteger
>    and: [(self objectClass: arguments last) == Array]]) ifTrue:
>   [^self doPrimitive: arguments second method: meth receiver: arguments first args: arguments last].
>   (arguments size = 2
>   and: [(self objectClass: arguments first) == SmallInteger
>   and: [(self objectClass: arguments last) == Array]]) ifFalse:
>   [^self class primitiveFailTokenFor: nil].
>   ^self doPrimitive: arguments first method: meth receiver: receiver args: arguments last].
>
>   value := primitiveIndex = 120 "FFI method"
>   ifTrue: [(meth literalAt: 1) tryInvokeWithArguments: arguments]
>   ifFalse:
>   [primitiveIndex = 117 "named primitives"
>   ifTrue: [self tryNamedPrimitiveIn: meth for: receiver withArgs: arguments]
>   ifFalse: "should use self receiver: receiver tryPrimitive: primitiveIndex withArgs: arguments but this is only in later VMs (and appears to be broken)"
>   [receiver tryPrimitive: primitiveIndex withArgs: arguments]].
>
>   ^(self isPrimFailToken: value)
>   ifTrue: [value]
>   ifFalse: [self push: value]!
>
> Item was changed:
>  ----- Method: Process>>debug (in category 'debugging') -----
>  debug
> +
> + ^ self debugWithTitle: 'Debug'!
> - self debugWithTitle: 'Debug'.!
>
> Item was added:
> + ----- Method: Process>>debug: (in category 'debugging') -----
> + debug: context
> +
> + ^ self debug: context title: 'Debug'!
>
> Item was changed:
>  ----- Method: Process>>debug:title: (in category 'debugging') -----
>  debug: context title: title
>   "Open debugger on self with context shown on top"
>
> + ^ self debug: context title: title full: false
> - self debug: context title: title full: false.
>  !
>
> Item was changed:
>  ----- Method: Process>>debug:title:full: (in category 'debugging') -----
>  debug: context title: title full: bool
>
> + ^ self
> - self
>   debug: context
>   title: title
>   full: bool
>   contents: nil!
>
> Item was changed:
>  ----- Method: Process>>debug:title:full:contents: (in category 'debugging') -----
>  debug: context title: title full: bool contents: contents
>   "Open debugger on self with context shown on top"
>
>   | topCtxt |
>   topCtxt := self isActiveProcess ifTrue: [thisContext] ifFalse: [self suspendedContext].
>   (topCtxt hasContext: context) ifFalse: [^ self error: 'context not in process'].
> + ^ ToolSet debugProcess: self context: context label: title contents: contents fullView: bool!
> - ToolSet debugProcess: self context: context label: title contents: contents fullView: bool.!
>
> Item was changed:
>  ----- Method: Process>>debugWithTitle: (in category 'debugging') -----
>  debugWithTitle: title
> - "Open debugger on self"
>
> + ^ self debugWithTitle: title full: true!
> - | context |
> - context := self isActiveProcess ifTrue: [thisContext] ifFalse: [self suspendedContext].
> - self debug: context title: title full: true.
> - !
>
> Item was added:
> + ----- Method: Process>>debugWithTitle:full: (in category 'debugging') -----
> + debugWithTitle: title full: aBoolean
> +
> + ^ self debugWithTitle: title full: aBoolean contents: nil!
>
> Item was added:
> + ----- Method: Process>>debugWithTitle:full:contents: (in category 'debugging') -----
> + debugWithTitle: title full: bool contents: contents
> + "Automatically choose the top context."
> +
> + ^ self
> + debug: (self isActiveProcess ifTrue: [thisContext] ifFalse: [self suspendedContext])
> + title: title
> + full: bool
> + contents: contents!

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Kernel-mt.1272.mcz

marcel.taeumel
Hi Levente,

good idea. Except for

Context>>cannotReturn:
Context>>doPrimitive:method:receiver:args:

Correct? Since code simulation is part of the Process interface itself.

Best,
Marcel

Am 07.10.2019 23:58:05 schrieb Levente Uzonyi <[hidden email]>:

I think these methods should all be extension methods in Kernel, and be
methods of System, since that's where ToolSet is.

Levente

On Mon, 7 Oct 2019, [hidden email] wrote:

> Marcel Taeumel uploaded a new version of Kernel to project The Trunk:
> http://source.squeak.org/trunk/Kernel-mt.1272.mcz
>
> ==================== Summary ====================
>
> Name: Kernel-mt.1272
> Author: mt
> Time: 7 October 2019, 10:09:56.205231 am
> UUID: 8fe3f896-0806-fe46-8e86-68f3c0f98d4d
> Ancestors: Kernel-ul.1271
>
> Complements System-mt.1112, which fixes and clean-up in the debugger infrastructure.
>
> =============== Diff against Kernel-ul.1271 ===============
>
> Item was changed:
> ----- Method: Context>>cannotReturn: (in category 'private-exceptions') -----
> cannotReturn: result
>
> closureOrNil notNil ifTrue:
> [^self cannotReturn: result to: self home sender].
> + Processor activeProcess
> + debug: thisContext
> + title: 'computation has been terminated'
> + full: false.!
> - ToolSet
> - debugActiveProcessContext: thisContext
> - label: 'computation has been terminated'
> - contents: nil!
>
> Item was changed:
> ----- Method: Context>>doPrimitive:method:receiver:args: (in category 'private') -----
> doPrimitive: primitiveIndex method: meth receiver: receiver args: arguments
> "Simulate a primitive method whose index is primitiveIndex. The simulated receiver and
> arguments are given as arguments to this message. If successful, push result and return
> resuming context, else ^ {errCode, PrimitiveFailToken}. Any primitive which provokes
> execution needs to be intercepted and simulated to avoid execution running away."
>
> | value |
> "Judicious use of primitive 19 (a null primitive that doesn't do anything) prevents
> the debugger from entering various run-away activities such as spawning a new
> process, etc. Injudicious use results in the debugger not being able to debug
> interesting code, such as the debugger itself. Hence use primitive 19 with care :-)"
> "SystemNavigation new browseAllSelect: [:m| m primitive = 19]"
> + primitiveIndex = 19 ifTrue: [
> + Processor activeProcess
> + debug: self
> + title:'Code simulation error'
> + full: false].
> - primitiveIndex = 19 ifTrue:
> - [ToolSet
> - debugActiveProcessContext: self
> - label:'Code simulation error'
> - contents: nil].
>
> ((primitiveIndex between: 201 and: 222)
> and: [(self objectClass: receiver) includesBehavior: BlockClosure]) ifTrue:
> [(primitiveIndex = 206
> or: [primitiveIndex = 208]) ifTrue: "[Full]BlockClosure>>valueWithArguments:"
> [^receiver simulateValueWithArguments: arguments first caller: self].
> ((primitiveIndex between: 201 and: 209) "[Full]BlockClosure>>value[:value:...]"
> or: [primitiveIndex between: 221 and: 222]) ifTrue: "[Full]BlockClosure>>valueNoContextSwitch[:]"
> [^receiver simulateValueWithArguments: arguments caller: self]].
>
> primitiveIndex = 83 ifTrue: "afr 9/11/1998 19:50" "Object>>perform:[with:...]"
> [^self send: arguments first to: receiver with: arguments allButFirst].
> primitiveIndex = 84 ifTrue: "afr 9/11/1998 19:50 & eem 8/18/2009 17:04" "Object>>perform:withArguments:"
> [^self send: arguments first to: receiver with: (arguments at: 2) lookupIn: (self objectClass: receiver)].
> primitiveIndex = 100 ifTrue: "eem 8/18/2009 16:57" "Object>>perform:withArguments:inSuperclass:"
> [^self send: arguments first to: receiver with: (arguments at: 2) lookupIn: (arguments at: 3)].
>
> "Mutex>>primitiveEnterCriticalSection
> Mutex>>primitiveTestAndSetOwnershipOfCriticalSection"
> (primitiveIndex = 186 or: [primitiveIndex = 187]) ifTrue:
> [| effective |
> effective := Processor activeProcess effectiveProcess.
> "active == effective"
> value := primitiveIndex = 186
> ifTrue: [receiver primitiveEnterCriticalSectionOnBehalfOf: effective]
> ifFalse: [receiver primitiveTestAndSetOwnershipOfCriticalSectionOnBehalfOf: effective].
> ^(self isPrimFailToken: value)
> ifTrue: [value]
> ifFalse: [self push: value]].
>
> primitiveIndex = 188 ifTrue: "Object>>withArgs:executeMethod:
> CompiledMethod class>>receiver:withArguments:executeMethod:
> VMMirror>>ifFail:object:with:executeMethod: et al"
> [| n args methodArg thisReceiver |
> ((n := arguments size) between: 2 and: 4) ifFalse:
> [^self class primitiveFailTokenFor: #'unsupported operation'].
> ((self objectClass: (args := arguments at: n - 1)) == Array
> and: [(self objectClass: (methodArg := arguments at: n)) includesBehavior: CompiledMethod]) ifFalse:
> [^self class primitiveFailTokenFor: #'bad argument'].
> methodArg numArgs = args size ifFalse:
> [^self class primitiveFailTokenFor: #'bad number of arguments'].
> thisReceiver := arguments at: n - 2 ifAbsent: [receiver].
> methodArg primitive > 0 ifTrue:
> [methodArg isQuick ifTrue:
> [^self push: (methodArg valueWithReceiver: thisReceiver arguments: args)].
> ^self doPrimitive: methodArg primitive method: meth receiver: thisReceiver args: args].
> ^Context
> sender: self
> receiver: thisReceiver
> method: methodArg
> arguments: args].
>
> primitiveIndex = 118 ifTrue: "[receiver:]tryPrimitive:withArgs:; avoid recursing in the VM"
> [(arguments size = 3
> and: [(self objectClass: arguments second) == SmallInteger
> and: [(self objectClass: arguments last) == Array]]) ifTrue:
> [^self doPrimitive: arguments second method: meth receiver: arguments first args: arguments last].
> (arguments size = 2
> and: [(self objectClass: arguments first) == SmallInteger
> and: [(self objectClass: arguments last) == Array]]) ifFalse:
> [^self class primitiveFailTokenFor: nil].
> ^self doPrimitive: arguments first method: meth receiver: receiver args: arguments last].
>
> value := primitiveIndex = 120 "FFI method"
> ifTrue: [(meth literalAt: 1) tryInvokeWithArguments: arguments]
> ifFalse:
> [primitiveIndex = 117 "named primitives"
> ifTrue: [self tryNamedPrimitiveIn: meth for: receiver withArgs: arguments]
> ifFalse: "should use self receiver: receiver tryPrimitive: primitiveIndex withArgs: arguments but this is only in later VMs (and appears to be broken)"
> [receiver tryPrimitive: primitiveIndex withArgs: arguments]].
>
> ^(self isPrimFailToken: value)
> ifTrue: [value]
> ifFalse: [self push: value]!
>
> Item was changed:
> ----- Method: Process>>debug (in category 'debugging') -----
> debug
> +
> + ^ self debugWithTitle: 'Debug'!
> - self debugWithTitle: 'Debug'.!
>
> Item was added:
> + ----- Method: Process>>debug: (in category 'debugging') -----
> + debug: context
> +
> + ^ self debug: context title: 'Debug'!
>
> Item was changed:
> ----- Method: Process>>debug:title: (in category 'debugging') -----
> debug: context title: title
> "Open debugger on self with context shown on top"
>
> + ^ self debug: context title: title full: false
> - self debug: context title: title full: false.
> !
>
> Item was changed:
> ----- Method: Process>>debug:title:full: (in category 'debugging') -----
> debug: context title: title full: bool
>
> + ^ self
> - self
> debug: context
> title: title
> full: bool
> contents: nil!
>
> Item was changed:
> ----- Method: Process>>debug:title:full:contents: (in category 'debugging') -----
> debug: context title: title full: bool contents: contents
> "Open debugger on self with context shown on top"
>
> | topCtxt |
> topCtxt := self isActiveProcess ifTrue: [thisContext] ifFalse: [self suspendedContext].
> (topCtxt hasContext: context) ifFalse: [^ self error: 'context not in process'].
> + ^ ToolSet debugProcess: self context: context label: title contents: contents fullView: bool!
> - ToolSet debugProcess: self context: context label: title contents: contents fullView: bool.!
>
> Item was changed:
> ----- Method: Process>>debugWithTitle: (in category 'debugging') -----
> debugWithTitle: title
> - "Open debugger on self"
>
> + ^ self debugWithTitle: title full: true!
> - | context |
> - context := self isActiveProcess ifTrue: [thisContext] ifFalse: [self suspendedContext].
> - self debug: context title: title full: true.
> - !
>
> Item was added:
> + ----- Method: Process>>debugWithTitle:full: (in category 'debugging') -----
> + debugWithTitle: title full: aBoolean
> +
> + ^ self debugWithTitle: title full: aBoolean contents: nil!
>
> Item was added:
> + ----- Method: Process>>debugWithTitle:full:contents: (in category 'debugging') -----
> + debugWithTitle: title full: bool contents: contents
> + "Automatically choose the top context."
> +
> + ^ self
> + debug: (self isActiveProcess ifTrue: [thisContext] ifFalse: [self suspendedContext])
> + title: title
> + full: bool
> + contents: contents!