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

commits at source.squeak.org commits at source.squeak.org
Wed Oct 21 22:46:55 UTC 2015


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

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

Name: Cog-eem.287
Author: eem
Time: 21 October 2015, 3:46:40.857 pm
UUID: f06b8b38-4ad3-4112-8aa2-6cccf6a75afe
Ancestors: Cog-eem.286

Flesh out a good portion of the executuion error failure handling for x64.  Pass the REX byte to the failure handlers.  Leave unexamined error handlers using self shouldBeImplemented to catch my eye.

Fix the order of ebx, ecx & edx in the IA32 alien's getters and setters.

Refactor the methods answering the default debugger integer printing base.

=============== Diff against Cog-eem.286 ===============

Item was removed:
- ----- Method: BochsIA32Alien class>>defaultIntegerBaseInDebugger (in category 'debugger') -----
- defaultIntegerBaseInDebugger
- 	^16!

Item was changed:
  ----- Method: BochsIA32Alien>>registerStateGetters (in category 'accessing-abstract') -----
  registerStateGetters
+ 	^#(	eax ecx edx ebx esp ebp esi edi eip eflags
- 	^#(	eax ebx ecx edx esp ebp esi edi eip eflags
  		xmm0low xmm1low xmm2low xmm3low
  		xmm4low xmm5low xmm6low xmm7low )!

Item was changed:
  ----- Method: BochsIA32Alien>>registerStateSetters (in category 'accessing-abstract') -----
  registerStateSetters
+ 	^#(	eax: ecx: edx: ebx: esp: ebp: esi: edi: eip: eflags:
- 	^#(	eax: ebx: ecx: edx: esp: ebp: esi: edi: eip: eflags:
  		xmm0low: xmm1low: xmm2low: xmm3low:
  		xmm4low: xmm5low: xmm6low: xmm7low: )!

Item was changed:
  ----- Method: BochsX64Alien class>>initialize (in category 'class initialization') -----
  initialize
  	"BochsX64Alien initialize"
  	| it |
  	it := self basicNew.
  	PostBuildStackDelta := 0.
+ 	OpcodeExceptionMap := Array new: 256 withAll: #handleExecutionPrimitiveFailureAt:in:rex:.
- 	OpcodeExceptionMap := Array new: 256 withAll: #handleExecutionPrimitiveFailureAt:in:.
  	OpcodeExceptionMap
+ 		at: 1 + it callOpcode			put: #handleCallFailureAt:in:rex:;
+ 		at: 1 + it jmpOpcode			put: #handleJmpFailureAt:in:rex:;
+ 		at: 1 + it retOpcode			put: #handleRetFailureAt:in:rex:;
+ 		at: 1 + it movALObOpcode	put: #handleMovALObFailureAt:in:rex:;
+ 		at: 1 + it movObALOpcode	put: #handleMovObALFailureAt:in:rex:;
+ 		at: 1 + it movGvEvOpcode	put: #handleMovGvEvFailureAt:in:rex:;
+ 		at: 1 + it movEvGvOpcode	put: #handleMovEvGvFailureAt:in:rex:;
+ 		at: 1 + it movGbEbOpcode	put: #handleMovGbEbFailureAt:in:rex:;
+ 		at: 1 + it movEbGbOpcode	put: #handleMovEbGbFailureAt:in:rex:;
+ 		at: 1 + 16rFF				put: #handleGroup5FailureAt:in:rex:. "Table A6 One-Byte and Two-Byte Opcode ModRM Extensions"
+ 	ExtendedOpcodeExceptionMap := Array new: 256 withAll: #handleExecutionPrimitiveFailureAt:in:rex:.
- 		at: 1 + it callOpcode			put: #handleCallFailureAt:in:;
- 		at: 1 + it jmpOpcode			put: #handleJmpFailureAt:in:;
- 		at: 1 + it retOpcode			put: #handleRetFailureAt:in:;
- 		at: 1 + it movALObOpcode	put: #handleMovALObFailureAt:in:;
- 		at: 1 + it movObALOpcode	put: #handleMovObALFailureAt:in:;
- 		at: 1 + it movGvEvOpcode	put: #handleMovGvEvFailureAt:in:;
- 		at: 1 + it movEvGvOpcode	put: #handleMovEvGvFailureAt:in:;
- 		at: 1 + it movGbEbOpcode	put: #handleMovGbEbFailureAt:in:;
- 		at: 1 + it movEbGbOpcode	put: #handleMovEbGbFailureAt:in:.
- 	ExtendedOpcodeExceptionMap := Array new: 256 withAll: #handleExecutionPrimitiveFailureAt:in:.
  	ExtendedOpcodeExceptionMap
+ 		at: 1 + it movGvEbOpcode put: #handleMovGvEbFailureAt:in:rex:!
- 		at: 1 + it movGvEbOpcode put: #handleMovGvEbFailureAt:in:!

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

Item was removed:
- ----- Method: BochsX64Alien>>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 added:
+ ----- Method: BochsX64Alien>>handleExecutionPrimitiveFailureAt:in:rex: (in category 'error handling') -----
+ handleExecutionPrimitiveFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" rex: rexByteOrNil "<Integer|nil>"
+ 	"Handle an execution primitive failure for an unhandled opcode."
+ 	^self reportPrimitiveFailure!

Item was changed:
  ----- Method: BochsX64Alien>>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 rexByte offset |
- 	| pc opcode offset |
  	((pc := self rip) between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
  		[opcode := memoryArray byteAt: pc + (offset := 1).
  		 (opcode bitAnd: 16rF8) = self rexPrefix ifTrue: "skip rex prefix if present"
+ 			[rexByte := opcode.
+ 			 opcode := memoryArray byteAt: pc + (offset := 2)].
- 			[opcode := memoryArray byteAt: pc + (offset := 2)].
  		 opcode ~= 16r0f ifTrue:
  			[^self
  				perform: (OpcodeExceptionMap at: opcode + 1)
  				with: pc
+ 				with: memoryArray
+ 				with: rexByte].
- 				with: memoryArray].
  		 opcode := memoryArray byteAt: pc + offset + 1.
  		 ^self
  				perform: (ExtendedOpcodeExceptionMap at: opcode + 1)
  				with: pc
+ 				with: memoryArray
+ 				with: rexByte].
- 				with: memoryArray].
  	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: BochsX64Alien>>handleGroup5FailureAt:in:rex: (in category 'as yet unclassified') -----
+ handleGroup5FailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" rex: rexByteOrNil "<Integer|nil>"
+ 	"Convert an execution primitive failure for a group 5 instruction into the relevant ProcessorSimulationTrap signal."
+ 	| modrmByte getter |
+ 	self assert: rexByteOrNil isNil.
+ 	modrmByte := memoryArray byteAt: pc + 2.
+ 	(modrmByte >> 3 bitAnd: 7)
+ 		caseOf: {
+ 			[2 "Call Ev"]	->	[getter := self registerStateGetters at: (modrmByte bitAnd: 7) + 1.
+ 							^(ProcessorSimulationTrap
+ 									pc: pc
+ 									nextpc: pc + 2
+ 									address: (self perform: getter)
+ 									type: #call)
+ 								signal] }!

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

Item was added:
+ ----- Method: BochsX64Alien>>handleMovALObFailureAt:in:rex: (in category 'error handling') -----
+ handleMovALObFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" rex: rexByteOrNil "<Integer|nil>"
+ 	"Convert an execution primitive failure for a read into rax/eax into a ProcessorSimulationTrap signal."
+ 	rexByteOrNil ifNotNil:
+ 		[^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 10
+ 				address: (memoryArray unsignedLong64At: pc + 3)
+ 				type: #read
+ 				accessor: #rax:)
+ 			signal].
+ 	^(ProcessorSimulationTrap
+ 			pc: pc
+ 			nextpc: pc + 5
+ 			address: (memoryArray unsignedLongAt: pc + 2)
+ 			type: #read
+ 			accessor: #eax:)
+ 		signal!

Item was added:
+ ----- Method: BochsX64Alien>>handleMovEbGbFailureAt:in:rex: (in category 'error handling') -----
+ handleMovEbGbFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" rex: rexByteOrNil "<Integer|nil>"
+ 	"Convert an execution primitive failure for a byte register write into a ProcessorSimulationTrap signal."
+ 	| modrmByte |
+ 	self shouldBeImplemented.
+ 	^(((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: BochsX64Alien>>handleMovEvGvFailureAt:in:rex: (in category 'error handling') -----
+ handleMovEvGvFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" rex: rexByteOrNil "<Integer|nil>"
+ 	"Convert an execution primitive failure for a register write into a ProcessorSimulationTrap signal."
+ 	| modrmByte getter base offset |
+ 	self assert: rexByteOrNil notNil.
+ 	modrmByte := memoryArray byteAt: pc + 3.
+ 	getter := self registerStateGetters at: ((modrmByte >> 3 bitAnd: 7) + ((rexByteOrNil bitAnd: 4) << 1) + 1).
+ 	(modrmByte bitAnd: 16rC7) = 16r5 ifTrue: "ModRegInd & disp32"
+ 		[^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 7
+ 				address: (memoryArray unsignedLongAt: pc + 4 bigEndian: false)
+ 				type: #write
+ 				accessor: getter)
+ 			signal].
+ 	(modrmByte bitAnd: 16rC0) = 16r80 ifTrue: "ModRegRegDisp8"
+ 		[offset := memoryArray longAt: pc + 4 bigEndian: false.
+ 		 base := self registerStateGetters at: ((modrmByte bitAnd: 7) + ((rexByteOrNil bitAnd: 1) << 3) + 1).
+ 		 ^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 7
+ 				address: (self perform: base) + offset
+ 				type: #write
+ 				accessor: getter)
+ 			signal].
+ 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: BochsX64Alien>>handleMovGbEbFailureAt:in:rex: (in category 'error handling') -----
+ handleMovGbEbFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" rex: rexByteOrNil "<Integer|nil>"
+ 	"Convert an execution primitive failure for a byte register load into a ProcessorSimulationTrap signal."
+ 	| modrmByte |
+ 	self shouldBeImplemented.
+ 	^(((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: BochsX64Alien>>handleMovGvEbFailureAt:in:rex: (in category 'error handling') -----
+ handleMovGvEbFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" rex: rexByteOrNil "<Integer|nil>"
+ 	"Convert an execution primitive failure for a register load into a ProcessorSimulationTrap signal."
+ 	| modrmByte mode srcIsSP srcVal dst offset |
+ 	self shouldBeImplemented.
+ 	modrmByte := memoryArray byteAt: pc + 3.
+ 	mode := modrmByte >> 6 bitAnd: 3.
+ 	srcIsSP := (modrmByte bitAnd: 7) = 4.
+ 	srcVal := self perform: (#(eax ecx edx ebx esp ebp esi edi) at: (modrmByte bitAnd: 7) + 1).
+ 	dst := #(eax: ecx: edx: ebx: esp: ebp: esi: edi:) at: ((modrmByte >> 3 bitAnd: 7) + 1).
+ 	mode = 1 ifTrue: "ModRegRegDisp8"
+ 		[offset := memoryArray byteAt: pc + (srcIsSP ifTrue: [5] ifFalse: [4]). "1-relative"
+ 		 offset > 127 ifTrue: [offset := offset - 256].
+ 		 ^(ProcessorSimulationTrap
+ 					pc: pc
+ 					nextpc: pc + (srcIsSP ifTrue: [5] ifFalse: [4])
+ 					address: ((srcVal + offset) bitAnd: 16rFFFFFFFF)
+ 					type: #read
+ 					accessor: dst)
+ 				signal].
+ 	mode = 2 ifTrue: "ModRegRegDisp32"
+ 		[offset := memoryArray unsignedLongAt: pc + (srcIsSP ifTrue: [5] ifFalse: [4]). "1-relative"
+ 		 ^(ProcessorSimulationTrap
+ 					pc: pc
+ 					nextpc: pc + (srcIsSP ifTrue: [8] ifFalse: [7])
+ 					address: ((srcVal + offset) bitAnd: 16rFFFFFFFF)
+ 					type: #read
+ 					accessor: dst)
+ 				signal].
+ 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: BochsX64Alien>>handleMovGvEvFailureAt:in:rex: (in category 'error handling') -----
+ handleMovGvEvFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>" rex: rexByteOrNil "<Integer|nil>"
+ 	"Convert an execution primitive failure for a register load into a ProcessorSimulationTrap signal."
+ 	| modrmByte getter setter offset |
+ 	self assert: rexByteOrNil notNil.
+ 	modrmByte := memoryArray byteAt: pc + 3.
+ 	setter := self registerStateSetters at: ((modrmByte >> 3 bitAnd: 7) + ((rexByteOrNil bitAnd: 4) << 1) + 1).
+ 	(modrmByte bitAnd: 16rC7) = 16r5 ifTrue: "ModRegInd & disp32"
+ 		[^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 7
+ 				address: (memoryArray unsignedLongAt: pc + 4 bigEndian: false)
+ 				type: #read
+ 				accessor: setter)
+ 			signal].
+ 	(modrmByte bitAnd: 16rC0) = 16r80 ifTrue: "ModRegRegDisp8"
+ 		[offset := memoryArray longAt: pc + 4 bigEndian: false.
+ 		 getter := self registerStateGetters at: ((modrmByte bitAnd: 7) + ((rexByteOrNil bitAnd: 1) << 3) + 1).
+ 		 ^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 7
+ 				address: (self perform: getter) + offset
+ 				type: #read
+ 				accessor: setter)
+ 			signal].
+ 	^self reportPrimitiveFailure!

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

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

Item was added:
+ ----- Method: BochsX64Alien>>postCallArgumentsNumArgs:in: (in category 'execution') -----
+ postCallArgumentsNumArgs: numArgs "<Integer>" in: memory "<ByteArray|Bitmap>"
+ 	"Answer an argument vector of the requested size after a vanilla
+ 	 ABI call.  On X86 this simply means accessing register arguments.
+ 	 For compatibility with Cog/Slang we answer unsigned values."
+ 	self assert: numArgs <= 4. "Microsoft & System V agree for the first 4 reg args oinly"
+ 	^((CogX64Compiler ABI == #SysV
+ 				ifTrue: [#(rdi rsi rdx rcx r8 r9)]
+ 				ifFalse: [#(rdi rsi r8 r9)]) copyFrom: 1 to: numArgs) collect:
+ 		[:getter|
+ 		self perform: getter]!

Item was added:
+ ----- Method: BochsX64Alien>>printRegisterStateExceptPC:on: (in category 'printing') -----
+ printRegisterStateExceptPC: registerStateVector on: aStream
+ 	self printFields:
+ 			((registerStateVector size < 34
+ 			  or: [(19 to: 34) allSatisfy: [:i| (registerStateVector at: i) isZero]])
+ 				ifTrue:
+ 					[#(	rax rbx rcx rdx cr
+ 						rsp rbp rsi rdi cr
+ 						r8 r9 r10 r11 cr
+ 						r12 r13 r14 r15 cr)]
+ 				ifFalse:
+ 					[#(	rax rbx rcx rdx cr
+ 						rsp rbp rsi rdi cr
+ 						r8 r9 r10 r11 cr
+ 						r12 r13 r14 r15 cr
+ 						xmm0low xmm1low cr
+ 						xmm2low xmm3low cr
+ 						xmm4low xmm5low cr
+ 						xmm6low xmm7low cr )])
+ 		inRegisterState: registerStateVector
+ 		on: aStream!

Item was added:
+ ----- Method: BochsX64Alien>>registerStateGetters (in category 'accessing-abstract') -----
+ registerStateGetters
+ 	^#(rax rcx rdx rbx rsp rbp rsi rdi r8 r9 r10 r11 r12 r13 r14 r15
+ 		rip rflags
+ 		xmm0low xmm1low xmm2low xmm3low
+ 		xmm4low xmm5low xmm6low xmm7low )!

Item was added:
+ ----- Method: BochsX64Alien>>registerStatePCIndex (in category 'accessing-abstract') -----
+ registerStatePCIndex
+ 	^17!

Item was changed:
  ----- Method: BochsX64Alien>>registerStateSetters (in category 'accessing-abstract') -----
  registerStateSetters
+ 	^#(rax: rcx: rdx: rbx: rsp: rbp: rsi: rdi: r8: r9: r10: r11: r12: r13: r14: r15:
- 	^#(rax: rbx: rcx: rdx: rsp: rbp: rsi: rdi: r8: r9: r10: r11: r12: r13: r14: r15:
  		rip: rflags:
  		xmm0low: xmm1low: xmm2low: xmm3low:
  		xmm4low: xmm5low: xmm6low: xmm7low: )!

Item was added:
+ ----- Method: BochsX64Alien>>simulateCallOf:nextpc:memory: (in category 'execution') -----
+ simulateCallOf: address nextpc: nextpc memory: aMemory
+ 	"Simulate a frame-building call of address.  Build a frame since
+ 	a) this is used for calls into the run-time which are unlikely to be leaf-calls, and
+ 	b) stack alignment needs to be realistic for assert checking for platforms such as Mac OS X"
+ 	self pushWord: nextpc in: aMemory.
+ 	self pushWord: self rbp in: aMemory.
+ 	self rbp: self rsp.
+ 	PostBuildStackDelta ~= 0 ifTrue:
+ 		[self rsp: self rsp - PostBuildStackDelta].
+ 	self rip: address!

Item was added:
+ ----- Method: CogProcessorAlien class>>defaultIntegerBaseInDebugger (in category 'debugger') -----
+ defaultIntegerBaseInDebugger
+ 	^16!

Item was removed:
- ----- Method: GdbARMAlien class>>defaultIntegerBaseInDebugger (in category 'debugger') -----
- defaultIntegerBaseInDebugger
- 	^16!

Item was added:
+ ----- Method: ProcessorSimulationTrap class>>defaultIntegerBaseInDebugger (in category 'debugger') -----
+ defaultIntegerBaseInDebugger
+ 	^16!



More information about the Vm-dev mailing list