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

commits at source.squeak.org commits at source.squeak.org
Thu Jun 26 01:48:39 UTC 2014


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

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

Name: Cog-tpr.159
Author: tpr
Time: 25 June 2014, 6:48:23.182 pm
UUID: 005cc753-401b-4701-88a0-29ecc549a0fa
Ancestors: Cog-eem.158

keep extending the ARM cog system; improve disassembly decoration to aid debugging, handel more sim aborts

=============== Diff against Cog-eem.158 ===============

Item was changed:
  CogProcessorAlien variableByteSubclass: #GdbARMAlien
  	instanceVariableNames: ''
+ 	classVariableNames: 'LongConstReg LongConstStep LongConstValue PostBuildStackDelta'
- 	classVariableNames: 'PostBuildStackDelta'
  	poolDictionaries: ''
  	category: 'Cog-Processors'!
  
  !GdbARMAlien commentStamp: 'lw 8/23/2012 19:17' prior: 0!
  I am a wrapper around the ARMulator CPU instance and emulator routines and I give access to disassembling using libopcodes. My C-part must be compiled with -DMODET, because otherwise my offesets are wrong by one field.!

Item was added:
+ ----- Method: GdbARMAlien>>callerSavedSmashRegisterAccessors (in category 'accessing-abstract') -----
+ callerSavedSmashRegisterAccessors
+ 	^#(r0: r1: r2: r3: )!

Item was added:
+ ----- Method: GdbARMAlien>>decorateDisassembly:for: (in category 'disassembly') -----
+ decorateDisassembly: anInstructionString for: aSymbolManager
+ 	| parts strm hexNum string |
+ 
+ 	"break up the string"
+ 	parts:= anInstructionString subStrings: '	 ,:'.
+ 	"part 1 is the address, part 2 is the instruction. Last part is sometimes a hex number"
+ 	
+ 	"is this a mov of a literal number?"
+ 	((parts at: 2) includesSubString: 'mov')
+ 		ifTrue:[ 
+ 			"clear the flags & running total"
+ 			LongConstReg := nil.
+ 			LongConstValue := 0.
+ 			LongConstStep := 0.
+ 			(parts at:4) first = $#
+ 				ifTrue:["looks a good candidate"
+ 					LongConstReg :=(parts at: 3). "the target register"
+ 					(parts last beginsWith: '0x') ifTrue:[
+ 						LongConstValue :=(NumberParser on: (parts last allButFirst:2)) nextUnsignedIntegerBase: 16].
+ 					LongConstStep := 1].
+ 			"not a likely candidate, just return the string"			
+ 			^anInstructionString].
+ 	
+ 	"is this a build of a literal number?"
+ 	(((parts at: 2) includesSubString: 'orr') and:[LongConstStep >0])
+ 		ifTrue:["add to running total if the register matches"
+ 			LongConstReg = (parts at: 3) 
+ 				ifTrue:[
+ 					(parts at:5) first = $#
+ 						ifTrue:["looks a good candidate"
+ 							(parts last beginsWith: '0x') ifTrue:[
+ 								LongConstValue := LongConstValue + ((NumberParser on: (parts last allButFirst:2)) nextUnsignedIntegerBase: 16) ].
+ 							LongConstStep:= LongConstStep +1].
+ 					LongConstStep = 4
+ 						ifTrue:["we've completed a pattern of mov/orr/orr/orr, so print the value it built" 
+ 							^anInstructionString, ' (', LongConstReg , ' = ', LongConstValue hex8, ((aSymbolManager lookupAddress: LongConstValue) ifNil: [''] ifNotNil:[:val| ' = ', val]), ')']]
+ 				ifFalse:[ LongConstStep := 0.
+ 						LongConstReg := nil.
+ 						LongConstValue := 0].
+ 			"either not a likely candidate orpartway through the pattern, so just return the string"			
+ 			^anInstructionString].
+ 	
+ 
+ 	strm :=anInstructionString readStream.
+ 	strm skip: 9. "the instruction address"
+ 	
+ 	strm upToAll: '0x'. "see if there is a hex number"
+ 	strm atEnd ifTrue:[^anInstructionString]. "if not, leave it be"
+ 
+ 	"extract the number"		
+ 	hexNum := (NumberParser on: strm) nextUnsignedIntegerBase: 16.
+ 	"is there an intersting address with this?"
+ 	(string := aSymbolManager lookupAddress: hexNum) ifNil: [^anInstructionString].
+ 	^ anInstructionString, ' = ', string!

Item was removed:
- ----- Method: GdbARMAlien>>decorateDisassembly:for:fromAddress: (in category 'disassembly') -----
- decorateDisassembly: anInstructionString for: aSymbolManager "<Cogit>" fromAddress: address
- 	(anInstructionString endsWith: 'mov	r0, r0')
- 		ifTrue: [^super decorateDisassembly: 'nop' for: aSymbolManager].
- 	^super decorateDisassembly: anInstructionString for: aSymbolManager!

Item was changed:
  ----- Method: GdbARMAlien>>handleLongJmpFailureAt:in: (in category 'error handling') -----
  handleLongJmpFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
  	"Convert an execution primitive failure for a long jump into a ProcessorSimulationTrap signal."
  	|  callAddress failedInstruction|
  	"grab the instruction at issue"
  	failedInstruction := memoryArray unsignedLongAt: pc + 1 bigEndian: false.
  	"Hmm. Perhaps we ought to test for an actual BX here rather than assuming?"
  	(self instructionIsBX: failedInstruction)
  				ifFalse:[ self halt: 'failed call type test'].
  	"The memoryArray starts indexing from 1, whereas the pc is based on 0-indexing, therefore all access-offsets are one greater than expected" 
  	"address, combined from prior four MOV/ORR instructions. See CogARMCompiler>concretizeLongCall"
  	callAddress := (memoryArray byteAt: pc -3) 
  						+ ((memoryArray byteAt: pc - 7) << 8) 
  						+ ((memoryArray byteAt: pc - 11) << 16) 
+ 						+ ((memoryArray byteAt: pc - 15) << 24).
- 						+ ((memoryArray byteAt: pc - 15) << 248).
  	^(ProcessorSimulationTrap
  			pc: pc
  			nextpc: pc + 4
  			address: callAddress signedIntToLong
  			type: #jump)
  		signal!

Item was changed:
  ----- Method: GdbARMAlien>>handleMoveMbrRFailureAt:in: (in category 'error handling') -----
+ handleMoveMbrRFailureAt: pc in: memoryArray 
- handleMoveMbrRFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
  	"Convert an execution primitive failure for a byte register load into a ProcessorSimulationTrap signal."
+ 	"generated by MoveMbrR"
+ 	"might be ldrb destReg, [srcReg, #immediate] or ldrb destReg, [srcReg, RISCTempReg] "
+ 
+ 	"first test for ldrb destReg, [srcReg, RISCTempReg]
+ 	-test for 0xE7DX as the most significant three nibbles"
+ 	((memoryArray byteAt: pc + 4) = 16rE7 and: [(memoryArray byteAt: pc + 3) >> 4 = 13])
+ 		ifTrue: [(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4
+ 				address: (memoryArray byteAt: pc - 3)
+ 						+ ((memoryArray byteAt: pc - 7)
+ 								<< 8) + ((memoryArray byteAt: pc - 11)
+ 							<< 16) + ((memoryArray byteAt: pc - 15)
+ 							<< 24)
+ 				type: #read
+ 				accessor: ("work out the dest register name"self registerStateSetters at: (memoryArray byteAt: pc + 2) >> 4 + 1)) signal
+ 			]
+ 		ifFalse: [self reportPrimitiveFailure]!
- 	"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 changed:
  ----- 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."
+ 	"LEA RISCTempReg
+ 	str srcReg, [RISCTempReg]"
+ 	"first we check this is a str r?, [sl]"
  	^((memoryArray byteAt: pc + 4) = 16rE5 
  		and: [(memoryArray byteAt: pc + 3) = (16r80 + CogARMCompiler ARMTempReg)])
  		ifTrue:
  			[(ProcessorSimulationTrap
  					pc: pc
  					nextpc: pc + 4
  					address: (memoryArray byteAt: pc -3) 
  								+ ((memoryArray byteAt: pc - 7) << 8) 
  								+ ((memoryArray byteAt: pc - 11) << 16) 
  								+ ((memoryArray byteAt: pc - 15) <<24)
  					type: #write
+ 					accessor: ("work out the dest register name" self registerStateNames at: ((memoryArray byteAt: pc + 2) >> 4) + 1))
- 					accessor: (self registerStateNames at: ((memoryArray byteAt: pc + 2) >> 4) + 1))
  				signal]
  		ifFalse:
  			[self reportPrimitiveFailure]!

Item was changed:
  ----- 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."
+ 	"generated by MoveRMbr"
+ 
+ 	"might be strb destReg, [srcReg, #immediate] or strb destReg, [srcReg, RISCTempReg] "
+ 
+ 	"first test for ldrb destReg, [srcReg, RISCTempReg]
+ 	-test for 0xE7CX as the most significant three nibbles"
+ 	((memoryArray byteAt: pc + 4) = 16rE7 and: [(memoryArray byteAt: pc + 3) >> 4 = 16rC])
+ 		ifTrue: [(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4
+ 				address: (memoryArray byteAt: pc - 3)
+ 						+ ((memoryArray byteAt: pc - 7)
+ 								<< 8) + ((memoryArray byteAt: pc - 11)
+ 							<< 16) + ((memoryArray byteAt: pc - 15)
+ 							<< 24)
+ 				type: #write
+ 				accessor: ("work out the dest register name"self registerStateNames at: (memoryArray byteAt: pc + 2) >> 4 + 1)) signal
+ ]
- 		"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>>retpcIn: (in category 'accessing-abstract') -----
+ retpcIn: aMemory
+ "the return address is on the stack, apparently"
+ 	^aMemory unsignedLongAt: self fp + 5 bigEndian: false!

Item was added:
+ ----- Method: GdbARMAlien>>simulateJumpCallOf:memory: (in category 'execution simulation') -----
+ simulateJumpCallOf: address memory: aMemory
+ 	"Simulate a frame-building jump of address.  Build a frame since
+ 	a) this is used for calls into the run-time which are unlikely to be leaf-calls"
+ 	"This method builds a stack frame as expected by the simulator, not as defined by ARM aapcs-abi.
+ 	In ARM aapcs, every method can define for itself, wether it wants to push lr (nextpc), and wether it 
+ 	uses a frame pointer. The standard never mentions a fp. It merely defines r4-r11 to be callee-saved."
+ 
+ 	self assert: self sp \\ 8 = 0. "This check ensures, that we conform with ARM abi. Before doing anything to the stack, we ensure 2-word alignment."
+ 	self pushWord: self fp in: aMemory.
+ 	self fp: self sp.
+ 	PostBuildStackDelta ~= 0 ifTrue:
+ 		[self sp: self sp - PostBuildStackDelta]. "In order to satisfy the CStackAlignment check by cogit, which is only valid on IA32 platforms."
+ 	self pc: address!

Item was added:
+ ----- Method: GdbARMAlien>>smashCallerSavedRegistersWithValuesFrom:by: (in category 'accessing-abstract') -----
+ smashCallerSavedRegistersWithValuesFrom: base by: step
+ 	self callerSavedSmashRegisterAccessors
+ 	   withIndexDo:
+ 		[:accessor :index|
+ 		self perform: accessor with: index - 1 * step + base]!



More information about the Vm-dev mailing list