[Vm-dev] VM Maker: Cog-lw.55.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Aug 24 18:10:53 UTC 2012


Lars Wassermann uploaded a new version of Cog to project VM Maker:
http://source.squeak.org/VMMaker/Cog-lw.55.mcz

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

Name: Cog-lw.55
Author: lw
Time: 24 August 2012, 8:10:39.178 pm
UUID: 2c9c00af-723a-ee46-9371-6386cc81ff35
Ancestors: Cog-lw.54

- added class comments to both new ProcessorAlien classes and ProcessorSimulationTrap

- pushed up decorateDisassembly:for:, for use in both, IA32Alien and ARMAlien. Also added the address as an additional parameter, to enable the ARM decoration to prepend it.

- added postCallArgumentsNumArgs:in: with an extensive comment.

=============== Diff against Cog-lw.54 ===============

Item was removed:
- ----- Method: BochsIA32Alien>>decorateDisassembly:for: (in category 'disassembly') -----
- decorateDisassembly: anInstructionString for: aSymbolManager "<Cogit>"
- 	| string i1 i2 v |
- 	string := anInstructionString.
- 	(i1 := string indexOfSubCollection: '%ds:0x') > 0 ifTrue:
- 		[i2 := i1 + 6.
- 		 ['0123456789abcdef' includes: (string at: i2)] whileTrue: [i2 := i2 + 1].
- 		 string := string
- 					copyReplaceFrom: i1 + 4
- 					to: i2 - 1
- 					with: (aSymbolManager lookupCHexString: (string copyFrom: i1 + 4 to: i2 - 1))].
- 	(i1 := string indexOfSubCollection: '%ss:0x') > 0 ifTrue:
- 		[i2 := i1 + 6.
- 		 ['0123456789abcdef' includes: (string at: i2)] whileTrue: [i2 := i2 + 1].
- 		 ((string at: i2) = $(
- 		 and: [(string at: i2 + 1) = $%]) ifTrue:
- 			[v := Integer readFrom: (ReadStream on: string from: i1 + 6 to: i2 - 1) base: 16.
- 			string := string
- 						copyReplaceFrom: i1
- 						to: i2 - 1
- 						with: ((v bitAnd: (1 bitShift: 31) - 1) - (v bitAnd: (1 bitShift: 31))) printString]].
- 	(i1 := string indexOfSubCollection: '$0x') > 0 ifTrue:
- 		[i2 := i1 + 3.
- 		 ['0123456789abcdef' includes: (string at: i2)] whileTrue: [i2 := i2 + 1].
- 		 string := string
- 					copyReplaceFrom: i1 + 1
- 					to: i2 - 1
- 					with: (aSymbolManager lookupCHexString: (string copyFrom: i1 + 1 to: i2 - 1))].
- 	((i1 := string indexOf: $() > 1
- 	 and: [(string at: i1 + 1) isDigit
- 	 and: [i1 < (i2 := string indexOf: $))]]) ifTrue:
- 		[string := string
- 					copyReplaceFrom: i1 + 1
- 					to: i2 - 1
- 					with: (aSymbolManager lookupCHexString: (string copyFrom: i1 + 1 to: i2 - 1))].
- 	^string!

Item was changed:
  Alien variableByteSubclass: #CogProcessorAlien
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Cog-Processors'!
+ 
+ !CogProcessorAlien commentStamp: 'lw 8/23/2012 19:15' prior: 0!
+ I am the superclass for the Simulation CPU instance wrappers. I ensure that methods used in both/all of them need not be copied.!

Item was added:
+ ----- Method: CogProcessorAlien>>decorateDisassembly:for: (in category 'disassembly') -----
+ decorateDisassembly: anInstructionString for: aSymbolManager "<Cogit>"
+ 	| string i1 i2 v |
+ 	string := anInstructionString.
+ 	(i1 := string indexOfSubCollection: '%ds:0x') > 0 ifTrue:
+ 		[i2 := i1 + 6.
+ 		 ['0123456789abcdef' includes: (string at: i2)] whileTrue: [i2 := i2 + 1].
+ 		 string := string
+ 					copyReplaceFrom: i1 + 4
+ 					to: i2 - 1
+ 					with: (aSymbolManager lookupCHexString: (string copyFrom: i1 + 4 to: i2 - 1))].
+ 	(i1 := string indexOfSubCollection: '%ss:0x') > 0 ifTrue:
+ 		[i2 := i1 + 6.
+ 		 ['0123456789abcdef' includes: (string at: i2)] whileTrue: [i2 := i2 + 1].
+ 		 ((string at: i2) = $(
+ 		 and: [(string at: i2 + 1) = $%]) ifTrue:
+ 			[v := Integer readFrom: (ReadStream on: string from: i1 + 6 to: i2 - 1) base: 16.
+ 			string := string
+ 						copyReplaceFrom: i1
+ 						to: i2 - 1
+ 						with: ((v bitAnd: (1 bitShift: 31) - 1) - (v bitAnd: (1 bitShift: 31))) printString]].
+ 	(i1 := string indexOfSubCollection: '$0x') > 0 ifTrue:
+ 		[i2 := i1 + 3.
+ 		 ['0123456789abcdef' includes: (string at: i2)] whileTrue: [i2 := i2 + 1].
+ 		 string := string
+ 					copyReplaceFrom: i1 + 1
+ 					to: i2 - 1
+ 					with: (aSymbolManager lookupCHexString: (string copyFrom: i1 + 1 to: i2 - 1))].
+ 	((i1 := string indexOf: $() > 1
+ 	 and: [(string at: i1 + 1) isDigit
+ 	 and: [i1 < (i2 := string indexOf: $))]]) ifTrue:
+ 		[string := string
+ 					copyReplaceFrom: i1 + 1
+ 					to: i2 - 1
+ 					with: (aSymbolManager lookupCHexString: (string copyFrom: i1 + 1 to: i2 - 1))].
+ 	^string!

Item was added:
+ ----- Method: CogProcessorAlien>>decorateDisassembly:for:fromAddress: (in category 'disassembly') -----
+ decorateDisassembly: anInstructionString for: aSymbolManager "<Cogit>" fromAddress: address
+ 	^self decorateDisassembly: anInstructionString for: aSymbolManager!

Item was changed:
  ----- Method: CogProcessorAlien>>disassembleFrom:to:in:for:labels:on: (in category 'disassembly') -----
  disassembleFrom: startAddress to: endAddress in: memory for: aSymbolManager "<Cogit>" labels: labelDictionary on: aStream
  	| address |
  	address := startAddress.
  	[address <= endAddress] whileTrue:
  		[[:size :string|
  		(aSymbolManager labelForPC: address) ifNotNil:
  			[:label| aStream nextPutAll: label; nextPut: $:; cr].
  		(labelDictionary at: address ifAbsent: []) ifNotNil:
  			[:label| aStream nextPutAll: label; nextPut: $:; cr].
+ 		aStream nextPutAll: (self decorateDisassembly: string for: aSymbolManager fromAddress: address); cr; flush.
- 		aStream nextPutAll: (self decorateDisassembly: string for: aSymbolManager); cr; flush.
  		address := address + size]
  			valueWithArguments: (self
  									primitiveDisassembleAt: address
  									inMemory: memory)]!

Item was changed:
  CogProcessorAlien variableByteSubclass: #GdbARMAlien
  	instanceVariableNames: ''
  	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 removed:
- ----- Method: GdbARMAlien>>decorateDisassembly:for: (in category 'disassembly') -----
- decorateDisassembly: anInstructionString for: aSymbolManager "<Cogit>"
- 	| string i1 i2 v |
- 	string := anInstructionString.
- 	(i1 := string indexOfSubCollection: '%ds:0x') > 0 ifTrue:
- 		[i2 := i1 + 6.
- 		 ['0123456789abcdef' includes: (string at: i2)] whileTrue: [i2 := i2 + 1].
- 		 string := string
- 					copyReplaceFrom: i1 + 4
- 					to: i2 - 1
- 					with: (aSymbolManager lookupCHexString: (string copyFrom: i1 + 4 to: i2 - 1))].
- 	(i1 := string indexOfSubCollection: '%ss:0x') > 0 ifTrue:
- 		[i2 := i1 + 6.
- 		 ['0123456789abcdef' includes: (string at: i2)] whileTrue: [i2 := i2 + 1].
- 		 ((string at: i2) = $(
- 		 and: [(string at: i2 + 1) = $%]) ifTrue:
- 			[v := Integer readFrom: (ReadStream on: string from: i1 + 6 to: i2 - 1) base: 16.
- 			string := string
- 						copyReplaceFrom: i1
- 						to: i2 - 1
- 						with: ((v bitAnd: (1 bitShift: 31) - 1) - (v bitAnd: (1 bitShift: 31))) printString]].
- 	(i1 := string indexOfSubCollection: '$0x') > 0 ifTrue:
- 		[i2 := i1 + 3.
- 		 ['0123456789abcdef' includes: (string at: i2)] whileTrue: [i2 := i2 + 1].
- 		 string := string
- 					copyReplaceFrom: i1 + 1
- 					to: i2 - 1
- 					with: (aSymbolManager lookupCHexString: (string copyFrom: i1 + 1 to: i2 - 1))].
- 	((i1 := string indexOf: $() > 1
- 	 and: [(string at: i1 + 1) isDigit
- 	 and: [i1 < (i2 := string indexOf: $))]]) ifTrue:
- 		[string := string
- 					copyReplaceFrom: i1 + 1
- 					to: i2 - 1
- 					with: (aSymbolManager lookupCHexString: (string copyFrom: i1 + 1 to: i2 - 1))].
- 	^string!

Item was added:
+ ----- Method: GdbARMAlien>>decorateDisassembly:for:fromAddress: (in category 'disassembly') -----
+ decorateDisassembly: anInstructionString for: aSymbolManager "<Cogit>" fromAddress: address
+ 	"Prepend the address to the decoration string."
+ 	| addressPrefix |
+ 	addressPrefix := ((address storeStringBase: 16 length: 9 padded: true) allButFirst: 3), ' ', String tab.
+ 	anInstructionString = 'mov	r1, r1' 
+ 		ifTrue: [^super decorateDisassembly: addressPrefix, 'nop' for: aSymbolManager].
+ 	^super decorateDisassembly: addressPrefix, anInstructionString for: aSymbolManager!

Item was added:
+ ----- Method: GdbARMAlien>>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. For ARM the Procedure Calling Specification can be found in IHI0042D_aapcs.pdf.
+ 	On ARM this typically means accessing r0 through r3 and fetching additional arguments from the stack, acording to pages 20f. aapcs.
+ 	We assume that all arguments are single word arguments, which can not be supplied on co-processor-registers.
+ 	 For compatibility with Cog/Slang we answer unsigned values."
+ 	^(1 to: numArgs) collect: [:i |
+ 		i < 5 
+ 			ifTrue: [self perform: (self registerStateNames at: i)]
+ 			"ARM uses a full descending stack. Directly after calling a procedure, nothing but the arguments are pushed."
+ 			ifFalse: [memory unsignedLongAt: self sp + (i-5)*4 bigEndian: false]].!

Item was changed:
  ----- Method: GdbARMAlien>>primitiveDisassembleAt:inMemory: (in category 'primitives') -----
  primitiveDisassembleAt: address inMemory: memoryArray "<Bitmap|ByteArray>"
  	"Answer an Array of the size and the disassembled code string for the instruction at the current instruction pointer in memory."
  	<primitive: 'primitiveDisassembleAtInMemory' module: 'GdbARMPlugin'>
+ 	^self primitiveFailed!
- 	^self reportPrimitiveFailure!

Item was changed:
  Error subclass: #ProcessorSimulationTrap
  	instanceVariableNames: 'pc nextpc address type registerAccessor'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Cog-Processors'!
+ 
+ !ProcessorSimulationTrap commentStamp: 'lw 8/23/2012 19:25' prior: 0!
+ A ProcessorSimulationTrap is an Error raised by CogProcessorAliens which allow the VMSimulator to fix the problem and resume execution.
+ I know where the problem occured (pc) and which instruction is next (nextpc), which field of the processor need be read/written and what type of memory access was the source of error.
+ 
+ I am created in #handleExecutionPrimitiveFailureIn:minimumAddress:readOnlyBelow: and associated methods. 
+ In the IA32 case, the type is managed by the OpcodeExecutionMap, using the first byte of the last instruction as index. 
+ In the ARM case, we need rely on a case statement, since no byte (sequence) is able to directly tell which type I am of.!



More information about the Vm-dev mailing list