[Vm-dev] VM Maker: Cog-tpr.154.mcz

commits at source.squeak.org commits at source.squeak.org
Thu May 29 01:33:51 UTC 2014


tim Rowledge uploaded a new version of Cog to project VM Maker:
http://source.squeak.org/VMMaker/Cog-tpr.154.mcz

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

Name: Cog-tpr.154
Author: tpr
Time: 28 May 2014, 9:40:57.428 am
UUID: 2ffcde09-dbe5-4fef-b323-817470a605c2
Ancestors: Cog-tpr.153

Add some return trapping tests in GdbARMAlianTests
Improve return failure handling in GdbARMAlien

=============== Diff against Cog-tpr.153 ===============

Item was changed:
  ----- Method: CogProcessorAlien>>disassembleNextInstructionIn:for: (in category 'disassembly') -----
  disassembleNextInstructionIn: memory for: aSymbolManager "<Cogit|nil>"
  	| string |
  	string := self pc < memory size 
  				ifTrue: [(self primitiveDisassembleAt: self pc inMemory: memory) last.]
+ 				ifFalse: [^self pc hex, ' : Invalid address'].
- 				ifFalse: [^{'Invalid address ' . self pc. ')'}].
  	^aSymbolManager
  		ifNil: [string]
  		ifNotNil: [self decorateDisassembly: string for: aSymbolManager]!

Item was changed:
  ----- 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 |
  	self endCondition = 5 ifTrue:[self pc: self priorPc].
  	((pc := self pc) between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
  		[(self instructionTypeAt: pc in: memoryArray)
  			caseOf: {
  				[#Call] 			-> [^self handleCallFailureAt: pc in: memoryArray].
  				[#LongCall] 	-> [^self handleLongCallFailureAt: pc in: memoryArray].
  				[#Jump] 		-> [^self handleJmpFailureAt: pc in: memoryArray].
  				[#LongJump] 	-> [^self handleLongJmpFailureAt: 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 = 0 ifTrue:[self halt: 'pc should not be 0 at this point; simulator failure'].
+ 
  	((pc := self lr - 4) between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
  		[(self instructionTypeAt: pc in: memoryArray)
  			caseOf: {
  				[#Call] 		-> [^self handleCallFailureAt: pc in: memoryArray].
  				[#LongCall] -> [^self handleLongCallFailureAt: pc in: memoryArray].
  				[#Jump] 	-> [^self handleJmpFailureAt: pc in: memoryArray].
  				[#LongJump] 	-> [^self handleLongJmpFailureAt: pc in: memoryArray].
  				[#Ret]		-> [^self handleRetFailureAt: pc in: memoryArray].} 
  			otherwise: [^self handleExecutionPrimitiveFailureAt: pc in: memoryArray]].
  	^self reportPrimitiveFailure!

Item was changed:
  ----- 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 -3) 
- 			address: (memoryArray unsignedLongAt: self sp + 1)
  			type: #return
  			accessor: #pc:)
  		signal!

Item was added:
+ ----- Method: GdbARMAlien>>instructionIsReturnViaLR: (in category 'testing') -----
+ instructionIsReturnViaLR: instr
+ "is this a MOV pc, lr instruction?"
+ 	^instr =  16rE1A0F00E!

Item was changed:
  ----- Method: GdbARMAlien>>instructionTypeAt:in: (in category 'error handling') -----
  instructionTypeAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
  	"Identify which type of instruction is at pc in memoryArray. For the time being, only those instructions needed for PrimitiveFailure are identified."
  	| RISCTempReg lastInstruction typeOperandStatus |
  	RISCTempReg := CogARMCompiler ARMTempReg.
  	lastInstruction := memoryArray unsignedLongAt:  pc + 1 bigEndian: false .
  	"self disassembleFrom: pc - 16 to: pc + 11 in: memoryArray on: Transcript cr"
  	
  	"Ret"
+ 	(self instructionIsReturnViaLR: lastInstruction ) ifTrue: [^#Ret].
- 	lastInstruction = self popPcOpcode ifTrue: [#Ret].
  
  	"Call"
  	(self instructionIsBL: lastInstruction) ifTrue: [^#Call].
  	"long call"
  	(self instructionIsBLX: lastInstruction) ifTrue: [^#LongCall].
  	
  	
  	"Jump"
  	(self instructionIsB: lastInstruction) ifTrue: [^#Jump].
  	"long Jump"
  	(self instructionIsBX: lastInstruction) ifTrue: [^#LongJump].
  		
  	typeOperandStatus := lastInstruction >> 20 bitAnd: 16rFF.
  	"MoveRMbr"
  	(self instructionIsSTRB: lastInstruction) ifTrue: [^#MoveRMbr].
  		
  	"MoveRAw"
  	(self instructionIsSTR: lastInstruction byReg: RISCTempReg) ifTrue: [^#MoveRAw].
  		
  	"MoveMbrR"
  	(self instructionIsLDRB: lastInstruction) ifTrue: [^#MoveMbrR].
  		
  	"MoveAwR"
  	(self instructionIsLDR: lastInstruction byReg: RISCTempReg) ifTrue: [^#MoveAwR].
  	
  	
  	^#UnidentifiedInstruction!

Item was added:
+ ----- Method: GdbARMAlienTests>>testReturnTrap (in category 'tests') -----
+ testReturnTrap
+ 	"return above-range."
+ 	
+ 	"self new testReturnTrap"
+ 	| memory |
+ 	memory := self memory.
+ 	self processor reset.
+ 
+ 	"assemble a nasty number in r10"
+ 	memory unsignedLongAt: 5 put: (CogARMCompiler new mov: 10 imm: 16r1E ror: 8)  bigEndian: false. 
+ 	memory unsignedLongAt: 9 put: (CogARMCompiler new orr: 10 imm: 0 ror: 0) bigEndian: false.
+ 	memory unsignedLongAt: 13 put: (CogARMCompiler new orr: 10 imm: 0 ror: 0) bigEndian: false. 
+ 	memory unsignedLongAt: 17 put: (CogARMCompiler new orr: 10 imm: 1 ror: 0) bigEndian: false. 
+ 	"push this on the stack"
+ 	memory unsignedLongAt: 21 put: (CogARMCompiler new pushR: 10) bigEndian: false.
+ 	"pop the stack into pc to emulate a return via stack as generated in  various trampoline code"	
+ 	memory unsignedLongAt: 25 put: (CogARMCompiler new popR: 15) bigEndian: false.
+ 
+ 	
+ 	"processor disassembleFrom: 0 to: 60 in: memory on: Transcript cr"
+ 	self processor
+ 			pc: 4;
+ 			sp: (memory size - 4); "Room for return address"
+ 			singleStepIn: memory readExecuteOnlyBelow: memory size /2 .
+ 			"We have to step several times, because the first step only changes the pc, but does not fetch anything from the address it points to."
+ 	self should: [self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2.
+ 				self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2.
+ 				self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2.
+ 				self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2.
+ 				self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2.
+ 				self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2.
+ 				self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2]
+ 		raise: ProcessorSimulationTrap
+ 		withExceptionDo:
+ 			[:pst|
+ 			self assert: self processor pc = 16r18.
+ 			self assert: pst pc = 16r18.
+ 			self assert: pst nextpc = 16r1C.
+ 			self assert: pst address = 16r1E000000.
+ 			self assert: pst type = #return].!

Item was added:
+ ----- Method: GdbARMAlienTests>>testReturnTrap2 (in category 'tests') -----
+ testReturnTrap2
+ 	"return above-range."
+ 	
+ 	"self new testReturnTrap2"
+ 	| memory |
+ 	memory := self memory.
+ 	self processor reset.
+ 
+ 	"assemble a nasty number in r10"
+ 	memory unsignedLongAt: 5 put: (CogARMCompiler new mov: 10 imm: 16r1E ror: 8)  bigEndian: false. 
+ 	memory unsignedLongAt: 9 put: (CogARMCompiler new orr: 10 imm: 0 ror: 0) bigEndian: false.
+ 	memory unsignedLongAt: 13 put: (CogARMCompiler new orr: 10 imm: 0 ror: 0) bigEndian: false. 
+ 	memory unsignedLongAt: 17 put: (CogARMCompiler new orr: 10 imm: 0 ror: 0) bigEndian: false. 
+ 	"push this on the stack"
+ 	memory unsignedLongAt: 21 put: (CogARMCompiler new pushR: 10) bigEndian: false.
+ 	"pop the stack into pc to emulate a return via stack as generated in  various trampoline code"	
+ 	memory unsignedLongAt: 25 put: (CogARMCompiler new popR: 15) bigEndian: false.
+ 
+ 	
+ 	"processor disassembleFrom: 0 to: 60 in: memory on: Transcript cr"
+ 	self processor
+ 			pc: 4;
+ 			sp: (memory size - 4); "Room for return address"
+ 			singleStepIn: memory readExecuteOnlyBelow: memory size /2 .
+ 			"We have to step several times, because the first step only changes the pc, but does not fetch anything from the address it points to."
+ 	self should: [self processor runInMemory: memory readExecuteOnlyBelow: memory size /2.]
+ 		raise: ProcessorSimulationTrap
+ 		withExceptionDo:
+ 			[:pst|
+ 			self assert: self processor pc = 16r18.
+ 			self assert: pst pc = 16r18.
+ 			self assert: pst nextpc = 16r1C.
+ 			self assert: pst address = 16r1E000000.
+ 			self assert: pst type = #return].!

Item was added:
+ ----- Method: GdbARMAlienTests>>testReturnTrapWithThumbBug (in category 'tests') -----
+ testReturnTrapWithThumbBug
+ 	"return above-range with a bad address that ends in 1 - which triggers an ARM sim bug"
+ 	
+ 	"self new testReturnTrapWithThumbBug"
+ 	| memory |
+ 	memory := self memory.
+ 	self processor reset.
+ 
+ 	"pop the stack into pc to emulate a return via stack as generated in  various trampoline code"	
+ 	memory unsignedLongAt: 1 put: (CogARMCompiler new mov: 15 rn: 14) bigEndian: false.
+ 
+ 	
+ 	"processor disassembleFrom: 0 to: 60 in: memory on: Transcript cr"
+ 	self processor
+ 			pc: 0;
+ 			sp: (memory size - 4); "Room for return address"
+ 			pushWord:16r1E000001 in: memory;
+ 			singleStepIn: memory readExecuteOnlyBelow: memory size /2 .
+ 			"We have to step several times, because the first step only changes the pc, but does not fetch anything from the address it points to."
+ 	self should: [self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2.
+ 				self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2.
+ 				self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2.
+ 				self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2.
+ 				self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2.
+ 				self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2.
+ 				self processor singleStepIn: memory readExecuteOnlyBelow: memory size /2]
+ 		raise: ProcessorSimulationTrap
+ 		withExceptionDo:
+ 			[:pst|
+ 			self assert: self processor pc = 16r18.
+ 			self assert: pst pc = 16r18.
+ 			self assert: pst nextpc = 16r1C.
+ 			self assert: pst address = 16r1E000000.
+ 			self assert: pst type = #return].!



More information about the Vm-dev mailing list