[Vm-dev] VM Maker: Cog-eem.122.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Nov 22 23:00:18 UTC 2013


Eliot Miranda uploaded a new version of Cog to project VM Maker:
http://source.squeak.org/VMMaker/Cog-eem.122.mcz

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

Name: Cog-eem.122
Author: eem
Time: 22 November 2013, 2:59:51.351 pm
UUID: 1ca89f5f-0258-44b3-b7c0-acb52206aaf2
Ancestors: Cog-eem.121

Add new run/single-step primitives to the processor aliens that
allow for the read-only/executable range to be origined above
zero, so that Spur can place the code zone between newSpace and
oldSpace and hence avoid two range checks when scavenging.
(If the codeZone is below newSpace then copyAndForward: must
check for both <= newSpaceLimit and >= newSpaceStart).

Simplify the error-handling routines; they don't use
minimumWritableAddress so it can be nuked.

Add some hex output to ProcessorSimulationTrap printing.

=============== Diff against Cog-eem.121 ===============

Item was changed:
  ----- Method: BochsIA32Alien class>>initialize (in category 'class initialization') -----
  initialize
  	"BochsIA32Alien initialize"
  	PostBuildStackDelta := 0.
+ 	OpcodeExceptionMap := Array new: 256 withAll: #handleExecutionPrimitiveFailureAt:in:.
- 	OpcodeExceptionMap := Array new: 256 withAll: #handleExecutionPrimitiveFailureAt:in:readOnlyBelow:.
  	OpcodeExceptionMap
+ 		at: 1 + self basicNew callOpcode			put: #handleCallFailureAt:in:;
+ 		at: 1 + self basicNew jmpOpcode			put: #handleJmpFailureAt:in:;
+ 		at: 1 + self basicNew retOpcode			put: #handleRetFailureAt:in:;
+ 		at: 1 + self basicNew movALObOpcode	put: #handleMovALObFailureAt:in:;
+ 		at: 1 + self basicNew movObALOpcode	put: #handleMovObALFailureAt:in:;
+ 		at: 1 + self basicNew movGvEvOpcode	put: #handleMovGvEvFailureAt:in:;
+ 		at: 1 + self basicNew movEvGvOpcode	put: #handleMovEvGvFailureAt:in:;
+ 		at: 1 + self basicNew movGbEbOpcode	put: #handleMovGbEbFailureAt:in:;
+ 		at: 1 + self basicNew movEbGbOpcode	put: #handleMovEbGbFailureAt:in:!
- 		at: 1 + self basicNew callOpcode			put: #handleCallFailureAt:in:readOnlyBelow:;
- 		at: 1 + self basicNew jmpOpcode			put: #handleJmpFailureAt:in:readOnlyBelow:;
- 		at: 1 + self basicNew retOpcode			put: #handleRetFailureAt:in:readOnlyBelow:;
- 		at: 1 + self basicNew movALObOpcode	put: #handleMovALObFailureAt:in:readOnlyBelow:;
- 		at: 1 + self basicNew movObALOpcode	put: #handleMovObALFailureAt:in:readOnlyBelow:;
- 		at: 1 + self basicNew movGvEvOpcode	put: #handleMovGvEvFailureAt:in:readOnlyBelow:;
- 		at: 1 + self basicNew movEvGvOpcode	put: #handleMovEvGvFailureAt:in:readOnlyBelow:;
- 		at: 1 + self basicNew movGbEbOpcode	put: #handleMovGbEbFailureAt:in:readOnlyBelow:;
- 		at: 1 + self basicNew movEbGbOpcode	put: #handleMovEbGbFailureAt:in:readOnlyBelow:!

Item was added:
+ ----- Method: BochsIA32Alien>>handleCallFailureAt:in: (in category 'error handling') -----
+ handleCallFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a call into a ProcessorSimulationTrap signal."
+ 	|  relativeJump |
+ 	relativeJump := memoryArray longAt: pc + 2 bigEndian: false.
+ 	^(ProcessorSimulationTrap
+ 			pc: pc
+ 			nextpc: pc + 5
+ 			address: (pc + 5 + relativeJump) signedIntToLong
+ 			type: #call)
+ 		signal!

Item was removed:
- ----- Method: BochsIA32Alien>>handleCallFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleCallFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a call into a ProcessorSimulationTrap signal."
- 	|  relativeJump |
- 	relativeJump := memoryArray longAt: pc + 2 bigEndian: false.
- 	^(ProcessorSimulationTrap
- 			pc: pc
- 			nextpc: pc + 5
- 			address: (pc + 5 + relativeJump) signedIntToLong
- 			type: #call)
- 		signal!

Item was added:
+ ----- Method: BochsIA32Alien>>handleExecutionPrimitiveFailureAt:in: (in category 'error handling') -----
+ handleExecutionPrimitiveFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Handle an execution primitive failure for an unhandled opcode."
+ 	^self reportPrimitiveFailure!

Item was removed:
- ----- Method: BochsIA32Alien>>handleExecutionPrimitiveFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleExecutionPrimitiveFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Handle an execution primitive failure for an unhandled opcode."
- 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: BochsIA32Alien>>handleExecutionPrimitiveFailureIn:minimumAddress: (in category 'error handling') -----
+ handleExecutionPrimitiveFailureIn: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress
+ 	"Handle an execution primitive failure.  Convert out-of-range call and absolute
+ 	 memory read into register instructions into ProcessorSimulationTrap signals."
+ 	"self printIntegerRegistersOn: Transcript"
+ 	"self printRegistersOn: Transcript"
+ 	| pc opcode |
+ 	((pc := self eip) between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
+ 		[opcode := memoryArray byteAt: pc + 1.
+ 		^self
+ 			perform: (OpcodeExceptionMap at: opcode + 1)
+ 			with: pc
+ 			with: memoryArray].
+ 	^self reportPrimitiveFailure!

Item was removed:
- ----- Method: BochsIA32Alien>>handleExecutionPrimitiveFailureIn:minimumAddress:readOnlyBelow: (in category 'error handling') -----
- handleExecutionPrimitiveFailureIn: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Handle an execution primitive failure.  Convert out-of-range call and absolute
- 	 memory read into register instructions into ProcessorSimulationTrap signals."
- 	"self printIntegerRegistersOn: Transcript"
- 	"self printRegistersOn: Transcript"
- 	| pc opcode |
- 	((pc := self eip) between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
- 		[opcode := memoryArray byteAt: pc + 1.
- 		^self
- 			perform: (OpcodeExceptionMap at: opcode + 1)
- 			with: pc
- 			with: memoryArray
- 			with: minimumWritableAddress].
- 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: BochsIA32Alien>>handleJmpFailureAt:in: (in category 'error handling') -----
+ handleJmpFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a jmp into a ProcessorSimulationTrap signal."
+ 	|  relativeJump |
+ 	relativeJump := memoryArray longAt: pc + 2 bigEndian: false.
+ 	^(ProcessorSimulationTrap
+ 			pc: pc
+ 			nextpc: pc + 5
+ 			address: (pc + 5 + relativeJump) signedIntToLong
+ 			type: #jump)
+ 		signal!

Item was removed:
- ----- Method: BochsIA32Alien>>handleJmpFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleJmpFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a jmp into a ProcessorSimulationTrap signal."
- 	|  relativeJump |
- 	relativeJump := memoryArray longAt: pc + 2 bigEndian: false.
- 	^(ProcessorSimulationTrap
- 			pc: pc
- 			nextpc: pc + 5
- 			address: (pc + 5 + relativeJump) signedIntToLong
- 			type: #jump)
- 		signal!

Item was added:
+ ----- Method: BochsIA32Alien>>handleMovALObFailureAt:in: (in category 'error handling') -----
+ handleMovALObFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a read into eax into a ProcessorSimulationTrap signal."
+ 	^(ProcessorSimulationTrap
+ 			pc: pc
+ 			nextpc: pc + 5
+ 			address: (memoryArray unsignedLongAt: pc + 2 bigEndian: false)
+ 			type: #read
+ 			accessor: #eax:)
+ 		signal!

Item was removed:
- ----- Method: BochsIA32Alien>>handleMovALObFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleMovALObFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a read into eax into a ProcessorSimulationTrap signal."
- 	^(ProcessorSimulationTrap
- 			pc: pc
- 			nextpc: pc + 5
- 			address: (memoryArray unsignedLongAt: pc + 2 bigEndian: false)
- 			type: #read
- 			accessor: #eax:)
- 		signal!

Item was added:
+ ----- Method: BochsIA32Alien>>handleMovEbGbFailureAt:in: (in category 'error handling') -----
+ handleMovEbGbFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a byte register write into a ProcessorSimulationTrap signal."
+ 	| modrmByte |
+ 	^(((modrmByte := memoryArray byteAt: pc + 2) bitAnd: 16rC0) = 16r80) "ModRegRegDisp32"
+ 		ifTrue:
+ 			[(ProcessorSimulationTrap
+ 					pc: pc
+ 					nextpc: pc + 6
+ 					address: ((self perform: (#(eax ecx edx ebx esp ebp esi edi) at: (modrmByte bitAnd: 7) + 1))
+ 							+ (memoryArray unsignedLongAt: pc + 3 bigEndian: false)
+ 								bitAnd: 16rFFFFFFFF)
+ 					type: #write
+ 					accessor: (#(al cl dl bl ah ch dh bh) at: ((modrmByte >> 3 bitAnd: 7) + 1)))
+ 				signal]
+ 		ifFalse:
+ 			[self reportPrimitiveFailure]!

Item was removed:
- ----- Method: BochsIA32Alien>>handleMovEbGbFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleMovEbGbFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a byte register write into a ProcessorSimulationTrap signal."
- 	| modrmByte |
- 	^(((modrmByte := memoryArray byteAt: pc + 2) bitAnd: 16rC0) = 16r80) "ModRegRegDisp32"
- 		ifTrue:
- 			[(ProcessorSimulationTrap
- 					pc: pc
- 					nextpc: pc + 6
- 					address: ((self perform: (#(eax ecx edx ebx esp ebp esi edi) at: (modrmByte bitAnd: 7) + 1))
- 							+ (memoryArray unsignedLongAt: pc + 3 bigEndian: false)
- 								bitAnd: 16rFFFFFFFF)
- 					type: #write
- 					accessor: (#(al cl dl bl ah ch dh bh) at: ((modrmByte >> 3 bitAnd: 7) + 1)))
- 				signal]
- 		ifFalse:
- 			[self reportPrimitiveFailure]!

Item was added:
+ ----- Method: BochsIA32Alien>>handleMovEvGvFailureAt:in: (in category 'error handling') -----
+ handleMovEvGvFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a register write into a ProcessorSimulationTrap signal."
+ 	| modrmByte |
+ 	^((modrmByte := memoryArray byteAt: pc + 2) bitAnd: 16rC7) = 16r5 "ModRegInd & disp32"
+ 		ifTrue:
+ 			[(ProcessorSimulationTrap
+ 					pc: pc
+ 					nextpc: pc + 6
+ 					address: (memoryArray unsignedLongAt: pc + 3 bigEndian: false)
+ 					type: #write
+ 					accessor: (#(eax ecx edx ebx esp ebp esi edi) at: ((modrmByte >> 3 bitAnd: 7) + 1)))
+ 				signal]
+ 		ifFalse:
+ 			[self reportPrimitiveFailure]!

Item was removed:
- ----- Method: BochsIA32Alien>>handleMovEvGvFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleMovEvGvFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a register write into a ProcessorSimulationTrap signal."
- 	| modrmByte |
- 	^((modrmByte := memoryArray byteAt: pc + 2) bitAnd: 16rC7) = 16r5 "ModRegInd & disp32"
- 		ifTrue:
- 			[(ProcessorSimulationTrap
- 					pc: pc
- 					nextpc: pc + 6
- 					address: (memoryArray unsignedLongAt: pc + 3 bigEndian: false)
- 					type: #write
- 					accessor: (#(eax ecx edx ebx esp ebp esi edi) at: ((modrmByte >> 3 bitAnd: 7) + 1)))
- 				signal]
- 		ifFalse:
- 			[self reportPrimitiveFailure]!

Item was added:
+ ----- Method: BochsIA32Alien>>handleMovGbEbFailureAt:in: (in category 'error handling') -----
+ handleMovGbEbFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a byte register load into a ProcessorSimulationTrap signal."
+ 	| modrmByte |
+ 	^(((modrmByte := memoryArray byteAt: pc + 2) bitAnd: 16rC0) = 16r80) "ModRegRegDisp32"
+ 		ifTrue:
+ 			[(ProcessorSimulationTrap
+ 					pc: pc
+ 					nextpc: pc + 6
+ 					address: ((self perform: (#(eax ecx edx ebx esp ebp esi edi) at: (modrmByte bitAnd: 7) + 1))
+ 							+ (memoryArray unsignedLongAt: pc + 3 bigEndian: false)
+ 								bitAnd: 16rFFFFFFFF)
+ 					type: #read
+ 					accessor: (#(al: cl: dl: bl: ah: ch: dh: bh:) at: ((modrmByte >> 3 bitAnd: 7) + 1)))
+ 				signal]
+ 		ifFalse:
+ 			[self reportPrimitiveFailure]!

Item was removed:
- ----- Method: BochsIA32Alien>>handleMovGbEbFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleMovGbEbFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a byte register load into a ProcessorSimulationTrap signal."
- 	| modrmByte |
- 	^(((modrmByte := memoryArray byteAt: pc + 2) bitAnd: 16rC0) = 16r80) "ModRegRegDisp32"
- 		ifTrue:
- 			[(ProcessorSimulationTrap
- 					pc: pc
- 					nextpc: pc + 6
- 					address: ((self perform: (#(eax ecx edx ebx esp ebp esi edi) at: (modrmByte bitAnd: 7) + 1))
- 							+ (memoryArray unsignedLongAt: pc + 3 bigEndian: false)
- 								bitAnd: 16rFFFFFFFF)
- 					type: #read
- 					accessor: (#(al: cl: dl: bl: ah: ch: dh: bh:) at: ((modrmByte >> 3 bitAnd: 7) + 1)))
- 				signal]
- 		ifFalse:
- 			[self reportPrimitiveFailure]!

Item was added:
+ ----- Method: BochsIA32Alien>>handleMovGvEvFailureAt:in: (in category 'error handling') -----
+ handleMovGvEvFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a register load into a ProcessorSimulationTrap signal."
+ 	| modrmByte |
+ 	^(((modrmByte := memoryArray byteAt: pc + 2) bitAnd: 16rC7) = 16r5) "ModRegInd & disp32"
+ 		ifTrue:
+ 			[(ProcessorSimulationTrap
+ 					pc: pc
+ 					nextpc: pc + 6
+ 					address: (memoryArray unsignedLongAt: pc + 3 bigEndian: false)
+ 					type: #read
+ 					accessor: (#(eax: ecx: edx: ebx: esp: ebp: esi: edi:) at: ((modrmByte >> 3 bitAnd: 7) + 1)))
+ 				signal]
+ 		ifFalse:
+ 			[self reportPrimitiveFailure]!

Item was removed:
- ----- Method: BochsIA32Alien>>handleMovGvEvFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleMovGvEvFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a register load into a ProcessorSimulationTrap signal."
- 	| modrmByte |
- 	^(((modrmByte := memoryArray byteAt: pc + 2) bitAnd: 16rC7) = 16r5) "ModRegInd & disp32"
- 		ifTrue:
- 			[(ProcessorSimulationTrap
- 					pc: pc
- 					nextpc: pc + 6
- 					address: (memoryArray unsignedLongAt: pc + 3 bigEndian: false)
- 					type: #read
- 					accessor: (#(eax: ecx: edx: ebx: esp: ebp: esi: edi:) at: ((modrmByte >> 3 bitAnd: 7) + 1)))
- 				signal]
- 		ifFalse:
- 			[self reportPrimitiveFailure]!

Item was added:
+ ----- Method: BochsIA32Alien>>handleMovObALFailureAt:in: (in category 'error handling') -----
+ handleMovObALFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a write of eax into a ProcessorSimulationTrap signal."
+ 	^(ProcessorSimulationTrap
+ 			pc: pc
+ 			nextpc: pc + 5
+ 			address: (memoryArray unsignedLongAt: pc + 2 bigEndian: false)
+ 			type: #write
+ 			accessor: #eax)
+ 		signal!

Item was removed:
- ----- Method: BochsIA32Alien>>handleMovObALFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleMovObALFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a write of eax into a ProcessorSimulationTrap signal."
- 	^(ProcessorSimulationTrap
- 			pc: pc
- 			nextpc: pc + 5
- 			address: (memoryArray unsignedLongAt: pc + 2 bigEndian: false)
- 			type: #write
- 			accessor: #eax)
- 		signal!

Item was added:
+ ----- Method: BochsIA32Alien>>handleRetFailureAt:in: (in category 'error handling') -----
+ handleRetFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a ret into a ProcessorSimulationTrap signal."
+ 	^(ProcessorSimulationTrap
+ 			pc: pc
+ 			nextpc: pc + 1
+ 			address: (memoryArray unsignedLongAt: self esp + 1)
+ 			type: #return
+ 			accessor: #eip:)
+ 		signal!

Item was removed:
- ----- Method: BochsIA32Alien>>handleRetFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleRetFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a ret into a ProcessorSimulationTrap signal."
- 	^(ProcessorSimulationTrap
- 			pc: pc
- 			nextpc: pc + 1
- 			address: (memoryArray unsignedLongAt: self esp + 1)
- 			type: #return
- 			accessor: #eip:)
- 		signal!

Item was added:
+ ----- Method: BochsIA32Alien>>primitiveRunInMemory:minimumAddress:executableAndReadOnlyFrom:to: (in category 'primitives') -----
+ primitiveRunInMemory: memoryArray "<Bitmap|ByteArray>"
+ 	minimumAddress: minimumAddress "<Integer>"
+ 		executableAndReadOnlyFrom: minExecAndReadOnlyAddress "<Integer>"
+ 			to: maxExecAndReadOnlyAddress "<Integer>"
+ 	"Run the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
+ 	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
+ 	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
+ 	<primitive: 'primitiveRunInMemoryMinimumAddressERFromTo' module: 'BochsIA32Plugin' error: ec>
+ 	^ec == #'inappropriate operation'
+ 		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 					minimumAddress: minimumAddress]
+ 		ifFalse: [self reportPrimitiveFailure]
+ 
+ 	"self printRegistersOn: Transcript"!

Item was changed:
  ----- Method: BochsIA32Alien>>primitiveRunInMemory:minimumAddress:maximumAddress:readOnlyBelow: (in category 'primitives') -----
  primitiveRunInMemory: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" maximumAddress: maximimAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
  	"Run the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
  	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
  	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
  	<primitive: 'primitiveRunInMemoryMinAddressMaxAddressReadWrite' module: 'BochsIA32Plugin' error: ec>
  	^ec == #'inappropriate operation'
  		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 					minimumAddress: minimumAddress]
- 					minimumAddress: minimumAddress
- 					readOnlyBelow: minimumWritableAddress]
  		ifFalse: [self reportPrimitiveFailure]
  
  	"self printRegistersOn: Transcript"!

Item was changed:
  ----- Method: BochsIA32Alien>>primitiveRunInMemory:minimumAddress:readOnlyBelow: (in category 'primitives') -----
  primitiveRunInMemory: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
  	"Run the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
  	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
  	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
  	<primitive: 'primitiveRunInMemoryMinimumAddressReadWrite' module: 'BochsIA32Plugin' error: ec>
  	^ec == #'inappropriate operation'
  		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 					minimumAddress: minimumAddress]
- 					minimumAddress: minimumAddress
- 					readOnlyBelow: minimumWritableAddress]
  		ifFalse: [self reportPrimitiveFailure]
  
  	"self printRegistersOn: Transcript"!

Item was added:
+ ----- Method: BochsIA32Alien>>primitiveSingleStepInMemory:minimumAddress:executableAndReadOnlyFrom:to: (in category 'primitives') -----
+ primitiveSingleStepInMemory: memoryArray "<Bitmap|ByteArray>"
+ 	minimumAddress: minimumAddress "<Integer>"
+ 		executableAndReadOnlyFrom: minExecAndReadOnlyAddress "<Integer>"
+ 			to: maxExecAndReadOnlyAddress "<Integer>"
+ 	"Single-step the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
+ 	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
+ 	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
+ 	<primitive: 'primitiveSingleStepInMemoryMinimumAddressERFromTo' module: 'BochsIA32Plugin' error: ec>
+ 	^ec == #'inappropriate operation'
+ 		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 					minimumAddress: minimumAddress]
+ 		ifFalse: [self reportPrimitiveFailure]
+ 
+ 	"self printRegistersOn: Transcript"!

Item was changed:
  ----- Method: BochsIA32Alien>>primitiveSingleStepInMemory:minimumAddress:maximumAddress:readOnlyBelow: (in category 'primitives') -----
  primitiveSingleStepInMemory: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" maximumAddress: maximimAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
  	"Single-step the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
  	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
  	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
  	<primitive: 'primitiveSingleStepInMemoryMinAddressMaxAddressReadWrite' module: 'BochsIA32Plugin' error: ec>
  	^ec == #'inappropriate operation'
  		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 					minimumAddress: minimumAddress]
- 					minimumAddress: minimumAddress
- 					readOnlyBelow: minimumWritableAddress]
  		ifFalse: [self reportPrimitiveFailure]!

Item was changed:
  ----- Method: BochsIA32Alien>>primitiveSingleStepInMemory:minimumAddress:readOnlyBelow: (in category 'primitives') -----
  primitiveSingleStepInMemory: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
  	"Single-step the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
  	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
  	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
  	<primitive: 'primitiveSingleStepInMemoryMinimumAddressReadWrite' module: 'BochsIA32Plugin' error: ec>
  	^ec == #'inappropriate operation'
  		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 					minimumAddress: minimumAddress]
- 					minimumAddress: minimumAddress
- 					readOnlyBelow: minimumWritableAddress]
  		ifFalse: [self reportPrimitiveFailure]!

Item was added:
+ ----- Method: BochsIA32Plugin>>primitiveRunInMemory:minimumAddress:executableAndReadOnlyFrom:to: (in category 'primitives') -----
+ "cpuAlien <BochsIA32Alien>" primitiveRunInMemory: memory "<Bitmap|ByteArray|WordArray>" minimumAddress: minAddress "<Integer>" executableAndReadOnlyFrom: minExecAndReadOnlyAddress "<Integer>" to: maxExecAndReadOnlyAddress "<Integer>"
+ 	"Run the cpu using the first argument as the memory and the following arguments defining valid addresses, running until it halts or hits an exception."
+ 	| cpuAlien cpu maybeErr |
+ 	<var: #cpu type: #'void *'>
+ 	cpuAlien := self primitive: #primitiveRunInMemoryMinimumAddressERFromTo
+ 					parameters: #(WordsOrBytes Unsigned Unsigned Unsigned)
+ 					receiver: #Oop.
+ 	(cpu := self startOfData: cpuAlien) = 0 ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 	prevInterruptCheckChain := interpreterProxy setInterruptCheckChain: #forceStopOnInterrupt asSymbol.
+ 	prevInterruptCheckChain = #forceStopOnInterrupt asSymbol ifTrue:
+ 		[prevInterruptCheckChain = 0].
+ 	maybeErr := self runCPU: cpu
+ 					In: memory
+ 					Size: (interpreterProxy byteSizeOf: memory cPtrAsOop)
+ 					MinAddress: minAddress
+ 					EROFrom: minExecAndReadOnlyAddress
+ 					To: maxExecAndReadOnlyAddress.
+ 	interpreterProxy setInterruptCheckChain: prevInterruptCheckChain.
+ 	maybeErr ~= 0 ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
+ 	^cpuAlien!

Item was added:
+ ----- Method: BochsIA32Plugin>>primitiveSingleStepInMemory:minimumAddress:executableAndReadOnlyFrom:to: (in category 'primitives') -----
+ "cpuAlien <BochsIA32Alien>" primitiveSingleStepInMemory: memory "<Bitmap|ByteArray|WordArray>" minimumAddress: minAddress "<Integer>" executableAndReadOnlyFrom: minExecAndReadOnlyAddress "<Integer>" to: maxExecAndReadOnlyAddress "<Integer>"
+ 	"Single-step the cpu using the first argument as the memory and the following arguments defining valid addresses, running until it halts or hits an exception."
+ 	| cpuAlien cpu maybeErr |
+ 	<var: #cpu type: #'void *'>
+ 	cpuAlien := self primitive: #primitiveSingleStepInMemoryMinimumAddressERFromTo
+ 					parameters: #(WordsOrBytes Unsigned Unsigned Unsigned)
+ 					receiver: #Oop.
+ 	(cpu := self startOfData: cpuAlien) = 0 ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 	maybeErr := self singleStepCPU: cpu
+ 					In: memory
+ 					Size: (interpreterProxy byteSizeOf: memory cPtrAsOop)
+ 					MinAddress: minAddress
+ 					EROFrom: minExecAndReadOnlyAddress
+ 					To: maxExecAndReadOnlyAddress.
+ 	interpreterProxy setInterruptCheckChain: prevInterruptCheckChain.
+ 	maybeErr ~= 0 ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
+ 	^cpuAlien!

Item was added:
+ ----- Method: CogProcessorAlien>>runInMemory:minimumAddress:executableAndReadOnlyFrom:to: (in category 'execution') -----
+ runInMemory: aMemory minimumAddress: minimumAddress executableAndReadOnlyFrom: minExecAndReadOnlyAddress to: maxExecAndReadOnlyAddress
+ 	| result |
+ 	result := self primitiveRunInMemory: aMemory
+ 				minimumAddress: minimumAddress
+ 				executableAndReadOnlyFrom: minExecAndReadOnlyAddress
+ 				to: maxExecAndReadOnlyAddress.
+ 	result ~~ self ifTrue:
+ 		[self error: 'eek!!']!

Item was added:
+ ----- Method: CogProcessorAlien>>singleStepInMemory:minimumAddress:executableAndReadOnlyFrom:to: (in category 'execution') -----
+ singleStepInMemory: aMemory minimumAddress: minimumAddress executableAndReadOnlyFrom: minExecAndReadOnlyAddress to: maxExecAndReadOnlyAddress
+ 	| result |
+ 	result := self primitiveSingleStepInMemory: aMemory
+ 				minimumAddress: minimumAddress
+ 				executableAndReadOnlyFrom: minExecAndReadOnlyAddress
+ 				to: maxExecAndReadOnlyAddress.
+ 	result ~~ self ifTrue:
+ 		[self error: 'eek!!']!

Item was added:
+ ----- Method: GdbARMAlien>>handleCallFailureAt:in: (in category 'error handling') -----
+ handleCallFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a call into a ProcessorSimulationTrap signal."
+ 	|  relativeJump callAddress |
+ 	((memoryArray byteAt: pc + 4) bitAnd: 16rF) = 16rB "BL opcode"
+ 		ifTrue: ["short jump via BL, therefore we have a 24bit signed integer offset"
+ 			relativeJump := (memoryArray unsignedLongAt: pc + 1 bigEndian: false) bitAnd: 16r00FFFFFF.
+ 			relativeJump := (relativeJump bitAt: 24) = 1 
+ 									ifTrue: [((relativeJump bitOr: 16r3F000000) << 2) signedIntFromLong]
+ 									ifFalse: [relativeJump << 2].
+ 			callAddress := (pc + 8 + relativeJump)]
+ 		
+ 		ifFalse: ["long jump using RISCTempReg"
+ 			"The memoryArray starts indexing from 1, whereas the pc is based on 0-indexing, therefore all access-offsets are one greater than expected"
+ 			callAddress := (memoryArray byteAt: pc + 4) 
+ 								+ ((memoryArray byteAt: pc - 4) << 24) 
+ 								+ ((memoryArray byteAt: pc - 8) << 16) 
+ 								+ ((memoryArray byteAt: pc - 12) << 8)].
+ 	^(ProcessorSimulationTrap
+ 			pc: pc
+ 			nextpc: pc + 4
+ 			address: callAddress signedIntToLong
+ 			type: #call)
+ 		signal!

Item was removed:
- ----- Method: GdbARMAlien>>handleCallFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleCallFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a call into a ProcessorSimulationTrap signal."
- 	|  relativeJump callAddress |
- 	((memoryArray byteAt: pc + 4) bitAnd: 16rF) = 16rB "BL opcode"
- 		ifTrue: ["short jump via BL, therefore we have a 24bit signed integer offset"
- 			relativeJump := (memoryArray unsignedLongAt: pc + 1 bigEndian: false) bitAnd: 16r00FFFFFF.
- 			relativeJump := (relativeJump bitAt: 24) = 1 
- 									ifTrue: [((relativeJump bitOr: 16r3F000000) << 2) signedIntFromLong]
- 									ifFalse: [relativeJump << 2].
- 			callAddress := (pc + 8 + relativeJump)]
- 		
- 		ifFalse: ["long jump using RISCTempReg"
- 			"The memoryArray starts indexing from 1, whereas the pc is based on 0-indexing, therefore all access-offsets are one greater than expected"
- 			callAddress := (memoryArray byteAt: pc + 4) 
- 								+ ((memoryArray byteAt: pc - 4) << 24) 
- 								+ ((memoryArray byteAt: pc - 8) << 16) 
- 								+ ((memoryArray byteAt: pc - 12) << 8)].
- 	^(ProcessorSimulationTrap
- 			pc: pc
- 			nextpc: pc + 4
- 			address: callAddress signedIntToLong
- 			type: #call)
- 		signal!

Item was added:
+ ----- Method: GdbARMAlien>>handleExecutionPrimitiveFailureAt:in: (in category 'error handling') -----
+ handleExecutionPrimitiveFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Handle an execution primitive failure for an unhandled opcode."
+ 	^self reportPrimitiveFailure!

Item was removed:
- ----- Method: GdbARMAlien>>handleExecutionPrimitiveFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleExecutionPrimitiveFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Handle an execution primitive failure for an unhandled opcode."
- 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: GdbARMAlien>>handleExecutionPrimitiveFailureIn:minimumAddress: (in category 'error handling') -----
+ handleExecutionPrimitiveFailureIn: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>"
+ 	"Handle an execution primitive failure.  Convert out-of-range call and absolute
+ 	 memory read into register instructions into ProcessorSimulationTrap signals."
+ 	"self printRegistersOn: Transcript"
+ 	| pc |
+ 	((pc := self pc) between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
+ 		[(self instructionTypeAt: pc in: memoryArray)
+ 			caseOf: {
+ 				[#Call] 			-> [^self handleCallFailureAt: pc in: memoryArray].
+ 				[#Jump] 		-> [^self handleJmpFailureAt: pc in: memoryArray].
+ 				[#MoveAwR]	-> [^self handleMoveAwRFailureAt: pc in: memoryArray].
+ 				[#MoveMbrR]	-> [^self handleMoveMbrRFailureAt: pc in: memoryArray].
+ 				[#MoveRAw]	-> [^self handleMoveRAwFailureAt: pc in: memoryArray].
+ 				[#MoveRMbr]	-> [^self handleMoveRMbrFailureAt: pc in: memoryArray].
+ 				[#Ret]			-> [^self handleRetFailureAt: pc in: memoryArray].} 
+ 			otherwise: [^self handleExecutionPrimitiveFailureAt: pc in: memoryArray]].
+ 	((pc := self lr - 4) between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
+ 		[(self instructionTypeAt: pc in: memoryArray)
+ 			caseOf: {
+ 				[#Call] 		-> [^self handleCallFailureAt: pc in: memoryArray].
+ 				[#Jump] 	-> [^self handleJmpFailureAt: pc in: memoryArray].
+ 				[#Ret]		-> [^self handleRetFailureAt: pc in: memoryArray].} 
+ 			otherwise: [^self handleExecutionPrimitiveFailureAt: pc in: memoryArray]].
+ 	^self reportPrimitiveFailure!

Item was removed:
- ----- Method: GdbARMAlien>>handleExecutionPrimitiveFailureIn:minimumAddress:readOnlyBelow: (in category 'error handling') -----
- handleExecutionPrimitiveFailureIn: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Handle an execution primitive failure.  Convert out-of-range call and absolute
- 	 memory read into register instructions into ProcessorSimulationTrap signals."
- 	"self printRegistersOn: Transcript"
- 	| pc |
- 	((pc := self pc) between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
- 		[(self instructionTypeAt: pc in: memoryArray)
- 			caseOf: {
- 				[#Call] 			-> [^self handleCallFailureAt: pc in: memoryArray readOnlyBelow: minimumWritableAddress].
- 				[#Jump] 		-> [^self handleJmpFailureAt: pc in: memoryArray readOnlyBelow: minimumWritableAddress].
- 				[#MoveAwR]	-> [^self handleMoveAwRFailureAt: pc in: memoryArray readOnlyBelow: minimumWritableAddress].
- 				[#MoveMbrR]	-> [^self handleMoveMbrRFailureAt: pc in: memoryArray readOnlyBelow: minimumWritableAddress].
- 				[#MoveRAw]	-> [^self handleMoveRAwFailureAt: pc in: memoryArray readOnlyBelow: minimumWritableAddress].
- 				[#MoveRMbr]	-> [^self handleMoveRMbrFailureAt: pc in: memoryArray readOnlyBelow: minimumWritableAddress].
- 				[#Ret]			-> [^self handleRetFailureAt: pc in: memoryArray readOnlyBelow: minimumWritableAddress].} 
- 			otherwise: [^self handleExecutionPrimitiveFailureAt: pc in: memoryArray readOnlyBelow: minimumWritableAddress]].
- 	((pc := self lr - 4) between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
- 		[(self instructionTypeAt: pc in: memoryArray)
- 			caseOf: {
- 				[#Call] 		-> [^self handleCallFailureAt: pc in: memoryArray readOnlyBelow: minimumWritableAddress].
- 				[#Jump] 	-> [^self handleJmpFailureAt: pc in: memoryArray readOnlyBelow: minimumWritableAddress].
- 				[#Ret]		-> [^self handleRetFailureAt: pc in: memoryArray readOnlyBelow: minimumWritableAddress].} 
- 			otherwise: [^self handleExecutionPrimitiveFailureAt: pc in: memoryArray readOnlyBelow: minimumWritableAddress]].
- 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: GdbARMAlien>>handleJmpFailureAt:in: (in category 'error handling') -----
+ handleJmpFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a jmp into a ProcessorSimulationTrap signal."
+ 	|  relativeJump |
+ 	self halt.
+ 	relativeJump := memoryArray longAt: pc + 2 bigEndian: false.
+ 	^(ProcessorSimulationTrap
+ 			pc: pc
+ 			nextpc: pc + 5
+ 			address: (pc + 5 + relativeJump) signedIntToLong
+ 			type: #jump)
+ 		signal!

Item was removed:
- ----- Method: GdbARMAlien>>handleJmpFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleJmpFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a jmp into a ProcessorSimulationTrap signal."
- 	|  relativeJump |
- 	self halt.
- 	relativeJump := memoryArray longAt: pc + 2 bigEndian: false.
- 	^(ProcessorSimulationTrap
- 			pc: pc
- 			nextpc: pc + 5
- 			address: (pc + 5 + relativeJump) signedIntToLong
- 			type: #jump)
- 		signal!

Item was added:
+ ----- Method: GdbARMAlien>>handleMoveAwRFailureAt:in: (in category 'error handling') -----
+ handleMoveAwRFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a register load from an Address into a ProcessorSimulationTrap signal."
+ 	((memoryArray byteAt: pc + 4) = 16rE5  "test for E593 as the most significant two bytes"
+ 		and: [(memoryArray byteAt: pc + 3) = (16r90 + (CogARMCompiler classPool at: #RISCTempReg))])
+ 		ifTrue:
+ 			[(ProcessorSimulationTrap
+ 					pc: pc
+ 					nextpc: pc + 4 
+ 					address: (memoryArray byteAt: pc + 1) "address, combined from four instructions"
+ 								+ ((memoryArray byteAt: pc - 3) << 24) 
+ 								+ ((memoryArray byteAt: pc - 7) << 16) 
+ 								+ ((memoryArray byteAt: pc - 11) << 8)
+ 					type: #read
+ 					accessor: (self registerStateSetters at: ((memoryArray byteAt: pc + 2) >> 4) + 1))
+ 				signal]
+ 		ifFalse:
+ 			[self reportPrimitiveFailure]!

Item was removed:
- ----- Method: GdbARMAlien>>handleMoveAwRFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleMoveAwRFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a register load from an Address into a ProcessorSimulationTrap signal."
- 	((memoryArray byteAt: pc + 4) = 16rE5  "test for E593 as the most significant two bytes"
- 		and: [(memoryArray byteAt: pc + 3) = (16r90 + (CogARMCompiler classPool at: #RISCTempReg))])
- 		ifTrue:
- 			[(ProcessorSimulationTrap
- 					pc: pc
- 					nextpc: pc + 4 
- 					address: (memoryArray byteAt: pc + 1) "address, combined from four instructions"
- 								+ ((memoryArray byteAt: pc - 3) << 24) 
- 								+ ((memoryArray byteAt: pc - 7) << 16) 
- 								+ ((memoryArray byteAt: pc - 11) << 8)
- 					type: #read
- 					accessor: (self registerStateSetters at: ((memoryArray byteAt: pc + 2) >> 4) + 1))
- 				signal]
- 		ifFalse:
- 			[self reportPrimitiveFailure]!

Item was added:
+ ----- Method: GdbARMAlien>>handleMoveMbrRFailureAt:in: (in category 'error handling') -----
+ handleMoveMbrRFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a byte register load into a ProcessorSimulationTrap signal."
+ 	"MoveMbrR"
+ 	| modrmByte |
+ 	self halt.
+ 	^(((modrmByte := memoryArray byteAt: pc + 2) bitAnd: 16rC0) = 16r80) "ModRegRegDisp32"
+ 		ifTrue:
+ 			[(ProcessorSimulationTrap
+ 					pc: pc
+ 					nextpc: pc + 6
+ 					address: ((self perform: (#(eax ecx edx ebx esp ebp esi edi) at: (modrmByte bitAnd: 7) + 1))
+ 							+ (memoryArray unsignedLongAt: pc + 3 bigEndian: false)
+ 								bitAnd: 16rFFFFFFFF)
+ 					type: #read
+ 					accessor: (#(al: cl: dl: bl: ah: ch: dh: bh:) at: ((modrmByte >> 3 bitAnd: 7) + 1)))
+ 				signal]
+ 		ifFalse:
+ 			[self reportPrimitiveFailure]!

Item was removed:
- ----- Method: GdbARMAlien>>handleMoveMbrRFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleMoveMbrRFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a byte register load into a ProcessorSimulationTrap signal."
- 	"MoveMbrR"
- 	| modrmByte |
- 	self halt.
- 	^(((modrmByte := memoryArray byteAt: pc + 2) bitAnd: 16rC0) = 16r80) "ModRegRegDisp32"
- 		ifTrue:
- 			[(ProcessorSimulationTrap
- 					pc: pc
- 					nextpc: pc + 6
- 					address: ((self perform: (#(eax ecx edx ebx esp ebp esi edi) at: (modrmByte bitAnd: 7) + 1))
- 							+ (memoryArray unsignedLongAt: pc + 3 bigEndian: false)
- 								bitAnd: 16rFFFFFFFF)
- 					type: #read
- 					accessor: (#(al: cl: dl: bl: ah: ch: dh: bh:) at: ((modrmByte >> 3 bitAnd: 7) + 1)))
- 				signal]
- 		ifFalse:
- 			[self reportPrimitiveFailure]!

Item was added:
+ ----- Method: GdbARMAlien>>handleMoveRAwFailureAt:in: (in category 'error handling') -----
+ handleMoveRAwFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a register write into Memory at a predefined address into a ProcessorSimulationTrap signal."
+ 	^((memoryArray byteAt: pc + 4) = 16rE5 
+ 		and: [(memoryArray byteAt: pc + 3) = (16r80 + (CogARMCompiler classPool at: #RISCTempReg))])
+ 		ifTrue:
+ 			[(ProcessorSimulationTrap
+ 					pc: pc
+ 					nextpc: pc + 4
+ 					address: (memoryArray byteAt: pc + 1) 
+ 								+ ((memoryArray byteAt: pc - 3) << 24) 
+ 								+ ((memoryArray byteAt: pc - 7) << 16) 
+ 								+ ((memoryArray byteAt: pc - 11) << 8)
+ 					type: #write
+ 					accessor: (self registerStateNames at: ((memoryArray byteAt: pc + 2) >> 4) + 1))
+ 				signal]
+ 		ifFalse:
+ 			[self reportPrimitiveFailure]!

Item was removed:
- ----- Method: GdbARMAlien>>handleMoveRAwFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleMoveRAwFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a register write into Memory at a predefined address into a ProcessorSimulationTrap signal."
- 	^((memoryArray byteAt: pc + 4) = 16rE5 
- 		and: [(memoryArray byteAt: pc + 3) = (16r80 + (CogARMCompiler classPool at: #RISCTempReg))])
- 		ifTrue:
- 			[(ProcessorSimulationTrap
- 					pc: pc
- 					nextpc: pc + 4
- 					address: (memoryArray byteAt: pc + 1) 
- 								+ ((memoryArray byteAt: pc - 3) << 24) 
- 								+ ((memoryArray byteAt: pc - 7) << 16) 
- 								+ ((memoryArray byteAt: pc - 11) << 8)
- 					type: #write
- 					accessor: (self registerStateNames at: ((memoryArray byteAt: pc + 2) >> 4) + 1))
- 				signal]
- 		ifFalse:
- 			[self reportPrimitiveFailure]!

Item was added:
+ ----- Method: GdbARMAlien>>handleMoveRMbrFailureAt:in: (in category 'error handling') -----
+ handleMoveRMbrFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 		"Convert an execution primitive failure for a byte register write into a ProcessorSimulationTrap signal."
+ 	"MoveRMbr"
+ 	| modrmByte |
+ 	self halt.
+ 	^(((modrmByte := memoryArray byteAt: pc + 2) bitAnd: 16rC0) = 16r80) "ModRegRegDisp32"
+ 		ifTrue:
+ 			[(ProcessorSimulationTrap
+ 					pc: pc
+ 					nextpc: pc + 6
+ 					address: ((self perform: (#(eax ecx edx ebx esp ebp esi edi) at: (modrmByte bitAnd: 7) + 1))
+ 							+ (memoryArray unsignedLongAt: pc + 3 bigEndian: false)
+ 								bitAnd: 16rFFFFFFFF)
+ 					type: #write
+ 					accessor: (#(al cl dl bl ah ch dh bh) at: ((modrmByte >> 3 bitAnd: 7) + 1)))
+ 				signal]
+ 		ifFalse:
+ 			[self reportPrimitiveFailure]!

Item was removed:
- ----- Method: GdbARMAlien>>handleMoveRMbrFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleMoveRMbrFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 		"Convert an execution primitive failure for a byte register write into a ProcessorSimulationTrap signal."
- 	"MoveRMbr"
- 	| modrmByte |
- 	self halt.
- 	^(((modrmByte := memoryArray byteAt: pc + 2) bitAnd: 16rC0) = 16r80) "ModRegRegDisp32"
- 		ifTrue:
- 			[(ProcessorSimulationTrap
- 					pc: pc
- 					nextpc: pc + 6
- 					address: ((self perform: (#(eax ecx edx ebx esp ebp esi edi) at: (modrmByte bitAnd: 7) + 1))
- 							+ (memoryArray unsignedLongAt: pc + 3 bigEndian: false)
- 								bitAnd: 16rFFFFFFFF)
- 					type: #write
- 					accessor: (#(al cl dl bl ah ch dh bh) at: ((modrmByte >> 3 bitAnd: 7) + 1)))
- 				signal]
- 		ifFalse:
- 			[self reportPrimitiveFailure]!

Item was added:
+ ----- Method: GdbARMAlien>>handleRetFailureAt:in: (in category 'error handling') -----
+ handleRetFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a ret into a ProcessorSimulationTrap signal."
+ 	self halt.
+ 	^(ProcessorSimulationTrap
+ 			pc: pc
+ 			nextpc: pc + 4
+ 			address: (memoryArray unsignedLongAt: self sp + 1)
+ 			type: #return
+ 			accessor: #pc:)
+ 		signal!

Item was removed:
- ----- Method: GdbARMAlien>>handleRetFailureAt:in:readOnlyBelow: (in category 'error handling') -----
- handleRetFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" readOnlyBelow: minimumWritableAddress "<Integer>"
- 	"Convert an execution primitive failure for a ret into a ProcessorSimulationTrap signal."
- 	self halt.
- 	^(ProcessorSimulationTrap
- 			pc: pc
- 			nextpc: pc + 4
- 			address: (memoryArray unsignedLongAt: self sp + 1)
- 			type: #return
- 			accessor: #pc:)
- 		signal!

Item was added:
+ ----- Method: GdbARMAlien>>primitiveRunInMemory:minimumAddress:executableAndReadOnlyFrom:to: (in category 'primitives') -----
+ primitiveRunInMemory: memoryArray "<Bitmap|ByteArray>"
+ 	minimumAddress: minimumAddress "<Integer>"
+ 		executableAndReadOnlyFrom: minExecAndReadOnlyAddress "<Integer>"
+ 			to: maxExecAndReadOnlyAddress "<Integer>"
+ 	"Run the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
+ 	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
+ 	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
+ 	<primitive: 'primitiveRunInMemoryMinimumAddressERFromTo' module: 'GdbARMPlugin' error: ec>
+ 	^ec == #'inappropriate operation'
+ 		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 					minimumAddress: minimumAddress]
+ 		ifFalse: [self reportPrimitiveFailure]
+ 
+ 	"self printRegistersOn: Transcript"!

Item was changed:
  ----- Method: GdbARMAlien>>primitiveRunInMemory:minimumAddress:maximumAddress:readOnlyBelow: (in category 'primitives') -----
  primitiveRunInMemory: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" maximumAddress: maximimAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
  	"Run the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
  	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
  	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
  	<primitive: 'primitiveRunInMemoryMinAddressMaxAddressReadWrite' module: 'GdbARMPlugin' error: ec>
  	^ec == #'inappropriate operation'
  		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 					minimumAddress: minimumAddress]
- 					minimumAddress: minimumAddress
- 					readOnlyBelow: minimumWritableAddress]
  		ifFalse: [self reportPrimitiveFailure]
  
  	"self printRegistersOn: Transcript"!

Item was changed:
  ----- Method: GdbARMAlien>>primitiveRunInMemory:minimumAddress:readOnlyBelow: (in category 'primitives') -----
  primitiveRunInMemory: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
  	"Run the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
  	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
  	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
  	<primitive: 'primitiveRunInMemoryMinimumAddressReadWrite' module: 'GdbARMPlugin' error: ec>
  	^ec == #'inappropriate operation'
  		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 					minimumAddress: minimumAddress]
- 					minimumAddress: minimumAddress
- 					readOnlyBelow: minimumWritableAddress]
  		ifFalse: [self reportPrimitiveFailure]
  
  	"self printRegistersOn: Transcript"!

Item was added:
+ ----- Method: GdbARMAlien>>primitiveSingleStepInMemory:minimumAddress:executableAndReadOnlyFrom:to: (in category 'primitives') -----
+ primitiveSingleStepInMemory: memoryArray "<Bitmap|ByteArray>"
+ 	minimumAddress: minimumAddress "<Integer>"
+ 		executableAndReadOnlyFrom: minExecAndReadOnlyAddress "<Integer>"
+ 			to: maxExecAndReadOnlyAddress "<Integer>"
+ 	"Single-step the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
+ 	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
+ 	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
+ 	<primitive: 'primitiveSingleStepInMemoryMinimumAddressERFromTo' module: 'GdbARMPlugin' error: ec>
+ 	^ec == #'inappropriate operation'
+ 		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 					minimumAddress: minimumAddress]
+ 		ifFalse: [self reportPrimitiveFailure]
+ 
+ 	"self printRegistersOn: Transcript"!

Item was changed:
  ----- Method: GdbARMAlien>>primitiveSingleStepInMemory:minimumAddress:maximumAddress:readOnlyBelow: (in category 'primitives') -----
  primitiveSingleStepInMemory: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" maximumAddress: maximimAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
  	"Single-step the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
  	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
  	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
  	<primitive: 'primitiveSingleStepInMemoryMinAddressMaxAddressReadWrite' module: 'GdbARMPlugin' error: ec>
  	^ec == #'inappropriate operation'
  		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 					minimumAddress: minimumAddress]
- 					minimumAddress: minimumAddress
- 					readOnlyBelow: minimumWritableAddress]
  		ifFalse: [self reportPrimitiveFailure]!

Item was changed:
  ----- Method: GdbARMAlien>>primitiveSingleStepInMemory:minimumAddress:readOnlyBelow: (in category 'primitives') -----
  primitiveSingleStepInMemory: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
  	"Single-step the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
  	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
  	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
  	<primitive: 'primitiveSingleStepInMemoryMinimumAddressReadWrite' module: 'GdbARMPlugin' error: ec>
  	^ec == #'inappropriate operation'
  		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 					minimumAddress: minimumAddress]
- 					minimumAddress: minimumAddress
- 					readOnlyBelow: minimumWritableAddress]
  		ifFalse: [self reportPrimitiveFailure]!

Item was added:
+ ----- Method: GdbARMPlugin>>primitiveRunInMemory:minimumAddress:executableAndReadOnlyFrom:to: (in category 'primitives') -----
+ "cpuAlien <GdbARMAlien>" primitiveRunInMemory: memory "<Bitmap|ByteArray|WordArray>" minimumAddress: minAddress "<Integer>" executableAndReadOnlyFrom: minExecAndReadOnlyAddress "<Integer>" to: maxExecAndReadOnlyAddress "<Integer>"
+ 	"Run the cpu using the first argument as the memory and the following arguments defining valid addresses, running until it halts or hits an exception."
+ 	| cpuAlien cpu maybeErr |
+ 	<var: #cpu type: #'void *'>
+ 	cpuAlien := self primitive: #primitiveRunInMemoryMinimumAddressERFromTo
+ 					parameters: #(WordsOrBytes Unsigned Unsigned Unsigned)
+ 					receiver: #Oop.
+ 	(cpu := self startOfData: cpuAlien) = 0 ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 	prevInterruptCheckChain := interpreterProxy setInterruptCheckChain: #forceStopOnInterrupt asSymbol.
+ 	prevInterruptCheckChain = #forceStopOnInterrupt asSymbol ifTrue:
+ 		[prevInterruptCheckChain = 0].
+ 	maybeErr := self runCPU: cpu
+ 					In: memory
+ 					Size: (interpreterProxy byteSizeOf: memory cPtrAsOop)
+ 					MinAddress: minAddress
+ 					EROFrom: minExecAndReadOnlyAddress
+ 					To: maxExecAndReadOnlyAddress.
+ 	interpreterProxy setInterruptCheckChain: prevInterruptCheckChain.
+ 	maybeErr ~= 0 ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
+ 	^cpuAlien!

Item was changed:
  ----- Method: GdbARMPlugin>>primitiveRunInMemory:minimumAddress:maximumAddress:readOnlyBelow: (in category 'primitives') -----
  "cpuAlien <GdbARMAlien>" primitiveRunInMemory: memory "<Bitmap|ByteArray|WordArray>" minimumAddress: minAddress "<Integer>" maximumAddress: maxAddress "<Integer>" readOnlyBelow: minWriteMaxExecAddress "<Integer>"
  	"Run the cpu using the first argument as the memory and the following arguments defining valid addresses, running until it halts or hits an exception."
  	| cpuAlien cpu memorySize maybeErr |
  	<var: #cpu type: #'void *'>
  	cpuAlien := self primitive: #primitiveRunInMemoryMinAddressMaxAddressReadWrite
  					parameters: #(WordsOrBytes Unsigned Unsigned Unsigned)
  					receiver: #Oop.
  	(cpu := self startOfData: cpuAlien) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	prevInterruptCheckChain := interpreterProxy setInterruptCheckChain: #forceStopOnInterrupt asSymbol.
  	prevInterruptCheckChain = #forceStopOnInterrupt asSymbol ifTrue:
  		[prevInterruptCheckChain = 0].
  	memorySize := interpreterProxy byteSizeOf: memory cPtrAsOop.
  	maybeErr := self runCPU: cpu
  					In: memory
  					Size: (memorySize min: maxAddress)
  					MinAddressRead: minAddress
  					Write: minWriteMaxExecAddress.
  	interpreterProxy setInterruptCheckChain: prevInterruptCheckChain.
  	maybeErr ~= 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
  	^cpuAlien!

Item was added:
+ ----- Method: GdbARMPlugin>>primitiveSingleStepInMemory:minimumAddress:executableAndReadOnlyFrom:to: (in category 'primitives') -----
+ "cpuAlien <GdbARMAlien>" primitiveSingleStepInMemory: memory "<Bitmap|ByteArray|WordArray>" minimumAddress: minAddress "<Integer>" executableAndReadOnlyFrom: minExecAndReadOnlyAddress "<Integer>" to: maxExecAndReadOnlyAddress "<Integer>"
+ 	"Single-step the cpu using the first argument as the memory and the following arguments defining valid addresses, running until it halts or hits an exception."
+ 	| cpuAlien cpu maybeErr |
+ 	<var: #cpu type: #'void *'>
+ 	cpuAlien := self primitive: #primitiveSingleStepInMemoryMinimumAddressERFromTo
+ 					parameters: #(WordsOrBytes Unsigned Unsigned Unsigned)
+ 					receiver: #Oop.
+ 	(cpu := self startOfData: cpuAlien) = 0 ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 	maybeErr := self singleStepCPU: cpu
+ 					In: memory
+ 					Size: (interpreterProxy byteSizeOf: memory cPtrAsOop)
+ 					MinAddress: minAddress
+ 					EROFrom: minExecAndReadOnlyAddress
+ 					To: maxExecAndReadOnlyAddress.
+ 	interpreterProxy setInterruptCheckChain: prevInterruptCheckChain.
+ 	maybeErr ~= 0 ifTrue:
+ 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
+ 	^cpuAlien!

Item was changed:
  ----- Method: GdbARMPlugin>>primitiveSingleStepInMemory:minimumAddress:maximumAddress:readOnlyBelow: (in category 'primitives') -----
  "cpuAlien <GdbARMAlien>" primitiveSingleStepInMemory: memory "<Bitmap|ByteArray|WordArray>" minimumAddress: minAddress "<Integer>" maximumAddress: maxAddress "<Integer>" readOnlyBelow: minWriteMaxExecAddress "<Integer>"
+ 	"Single-step the cpu using the first argument as the memory and the following arguments defining valid addresses, running until it halts or hits an exception."
- 	"Single-step the cpu using the first argument as the memory and the following arguments defining valid addresses."
  	| cpuAlien cpu memorySize maybeErr |
  	<var: #cpu type: #'void *'>
  	cpuAlien := self primitive: #primitiveSingleStepInMemoryMinAddressMaxAddressReadWrite
  					parameters: #(WordsOrBytes Unsigned Unsigned Unsigned)
  					receiver: #Oop.
  	(cpu := self startOfData: cpuAlien) = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 	prevInterruptCheckChain := interpreterProxy setInterruptCheckChain: #forceStopOnInterrupt asSymbol.
+ 	prevInterruptCheckChain = #forceStopOnInterrupt asSymbol ifTrue:
+ 		[prevInterruptCheckChain = 0].
  	memorySize := interpreterProxy byteSizeOf: memory cPtrAsOop.
  	maybeErr := self singleStepCPU: cpu
  					In: memory
  					Size: (memorySize min: maxAddress)
  					MinAddressRead: minAddress
  					Write: minWriteMaxExecAddress.
+ 	interpreterProxy setInterruptCheckChain: prevInterruptCheckChain.
  	maybeErr ~= 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
  	^cpuAlien!

Item was changed:
  ----- Method: ProcessorSimulationTrap>>printOn: (in category 'printing') -----
  printOn: aStream
  	super printOn: aStream.
+ 	aStream nextPutAll: ' (pc: '; print: pc; nextPut: $/. pc printOn: aStream base: 16.
+ 	aStream nextPutAll: ' nextpc: '; print: nextpc; nextPut: $/. nextpc printOn: aStream base: 16.
+ 	aStream nextPutAll: ' address: '; print: address; nextPut: $/. address printOn: aStream base: 16.
- 	aStream nextPutAll: ' (pc: '; print: pc.
- 	aStream nextPutAll: ' nextpc: '; print: nextpc.
- 	aStream nextPutAll: ' address: '; print: address.
  	aStream nextPutAll: ' type: '; print: type.
  	aStream nextPutAll: ' accessor: '; print: registerAccessor; nextPut: $)!



More information about the Vm-dev mailing list