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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 22 23:40:34 UTC 2017


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

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

Name: Cog-eem.336
Author: eem
Time: 22 February 2017, 3:40:22.065344 pm
UUID: 57629034-08b1-4dcc-ad9a-3e69450bcdb6
Ancestors: Cog-eem.335

Add support for converting frame offsets and variable base offsets into temp and global var names.  Add support for eliding the machine code bytes.  Nuke an obsolete method.

=============== Diff against Cog-eem.335 ===============

Item was changed:
  ----- Method: BochsIA32Alien>>decorateDisassembly:for:fromAddress: (in category 'disassembly') -----
  decorateDisassembly: anInstructionString for: aSymbolManager "<Cogit>" fromAddress: address
  	| string i1 i2 v |
  	string := anInstructionString.
  	aSymbolManager relativeBaseForDisassemblyInto:
  		[:baseAddress :baseName|
  		string := baseName, '+', (address - baseAddress printStringBase: 16 length: 4 padded: true), (string copyFrom: (string indexOf: $:) + 1 to: string size)].
  	(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))].
+ 	PrintCodeBytes ifFalse:
+ 		[string := string copyFrom: 1 to: (string lastIndexOf: $:) - 2].
  	^string!

Item was removed:
- ----- Method: BochsPlugin>>primitiveDisassembleAt:InMemory: (in category 'primitives') -----
- "cpuAlien <BochsIA32|X86Alien>" primitiveDisassembleAt: address "<Integer>" InMemory: memory "<Bitmap|ByteArray|WordArray>"
- 	"Return an Array of the instruction length and its decompilation as a string for the instruction at address in memory."
- 	| cpuAlien cpu instrLenOrErr resultObj log logLen logObj logObjData |
- 	<var: #cpu type: #'void *'>
- 	<var: #log type: #'char *'>
- 	<var: #logLen type: #long>
- 	<var: #logObjData type: #'char *'>
- 	cpuAlien := self primitive: #primitiveDisassembleAtInMemory
- 					parameters: #(Unsigned WordsOrBytes)
- 					receiver: #Oop.
- 	(cpu := self cCoerceSimple: (self startOfData: cpuAlien) to: #'void *') = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	instrLenOrErr := self disassembleFor: cpu
- 						At: address
- 						In: memory
- 						Size: (interpreterProxy byteSizeOf: memory cPtrAsOop).
- 	instrLenOrErr < 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
- 	log := self getlog: (self cCode: [self addressOf: logLen] inSmalltalk: [logLen := 0]).
- 	resultObj := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: 2.
- 	resultObj = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
- 
- 	"Easier keeping the damn thing on the stack than using pushRemappableOop:/popRemappableOop.
- 	 Where is topRemappableOop when you need it?"
- 	interpreterProxy pushRemappableOop: resultObj.
- 	logObj := interpreterProxy
- 				instantiateClass: interpreterProxy classString
- 				indexableSize: logLen.
- 	interpreterProxy failed ifTrue:
- 		[interpreterProxy popRemappableOop.
- 		 ^interpreterProxy primitiveFailFor: PrimErrNoMemory].
- 	logObjData := interpreterProxy arrayValueOf: logObj.
- 	self mem: logObjData cp: log y: logLen.
- 	resultObj := interpreterProxy popRemappableOop.
- 	interpreterProxy
- 		storePointer: 0
- 		ofObject: resultObj
- 		withValue: (interpreterProxy integerObjectOf: instrLenOrErr).
- 	interpreterProxy storePointer: 1 ofObject: resultObj withValue: logObj.
- 
- 	^resultObj!

Item was changed:
  ----- Method: BochsX64Alien>>decorateDisassembly:for:fromAddress: (in category 'disassembly') -----
  decorateDisassembly: anInstructionString for: aSymbolManager "<Cogit>" fromAddress: address
  	| string i1 i2 v extra |
+ 	string := PrintCodeBytes
+ 				ifTrue: [anInstructionString]
+ 				ifFalse: [anInstructionString copyFrom: 1 to: (anInstructionString lastIndexOf: $:) - 1]. "trailing space useful for parsing numbers"
- 	string := anInstructionString.
  	aSymbolManager relativeBaseForDisassemblyInto:
  		[:baseAddress :baseName|
  		string := baseName, '+', (address - baseAddress printStringBase: 16 length: 4 padded: true), (string copyFrom: (string indexOf: $:) + 1 to: string size)].
  	((i1 := string indexOfSubCollection: '%ds:(') > 0
  	or: [(i1 := string indexOfSubCollection: '%ss:(') > 0]) ifTrue:
  		[string := string copyReplaceFrom: i1 to: i1 + 3 with: ''].
  	(i1 := string indexOfSubCollection: '%ds:0x') > 0 ifTrue:
  		[i2 := i1 + 6.
  		 ['0123456789abcdef' includes: (string at: i2)] whileTrue: [i2 := i2 + 1].
  		 (v := string copyFrom: i2 to: (i2 + 5 min: string size)) = '(%rbx)' ifTrue:
  			[v := Integer readFrom: (ReadStream on: string from: i1 + 6 to: i2 - 1) base: 16.
  		 	 (aSymbolManager lookupAddress: aSymbolManager varBaseAddress + v) ifNotNil:
  				[:varName| extra := ' = ', varName]].
  		 v = '(%rip)' ifTrue:
+ 			[v := anInstructionString size - (anInstructionString lastIndexOf: $:) - 1 / 3. "Count number of instruction bytes to find size of instruction"
- 			[v := string size - (string indexOf: $: startingAt: i2 + 5) - 1 / 3. "Count number of instruction bytes to find size of instruction"
  			 v := v + address. "Add address of instruction"
  			 v := v + (Integer readFrom: (ReadStream on: string from: i1 + 6 to: i2 - 1) base: 16) signedIntFromLong64. "Add offset to yield pc-relative address"
  		 	 (aSymbolManager lookupAddress: v) ifNotNil:
  				[:methodName| extra := ' = ', methodName]].
  		 string := string
  					copyReplaceFrom: i1
  					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:
- 		 and: [(string at: i2 + 1) = $%]) ifTrue:
  			[v := Integer readFrom: (ReadStream on: string from: i1 + 6 to: i2 - 1) base: 16.
+ 			 v := (v bitAnd: (1 bitShift: 31) - 1) - (v bitAnd: (1 bitShift: 31)).
+ 			 ((string copyFrom: i2 to: (i2 + 5 min: string size)) = '(%rbp)' and: [PrintTempNames]) ifTrue:
+ 				[(aSymbolManager lookupFrameOffset: v) ifNotNil:
+ 					[:varName| string := string copyReplaceFrom: i1 to: i2 - 1 with: varName. i2 := 0].
+ 			i2 ~= 0 ifTrue: [string := string copyReplaceFrom: i1 to: i2 - 1 with: v printString]]]].
- 			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)).
  		 i1 := string indexOfSubCollection: '+0x'. "calls & jumps"
  		 i1 > 0 ifTrue:
  			[v := Integer readFrom: (i2 := ReadStream on: string from: i1 + 3 to: string size) base: 16.
  			 v := ((v bitAnd: (1 bitShift: 63) - 1) - (v bitAnd: (1 bitShift: 63))) printStringRadix: 16.
  			 v := v first = $1
  					ifTrue: [v copyReplaceFrom: 1 to: 3 with: '+0x']
  					ifFalse: [v copyReplaceFrom: 2 to: 4 with: '0x'].
  			 string := string copyReplaceFrom: i1 to: i2 position with: v]].
  	^extra
  		ifNil: [string]
+ 		ifNotNil:
+ 			[PrintCodeBytes
+ 				ifTrue: [i1 := string lastIndexOf: $:.
+ 						string copyReplaceFrom: i1 - 1 to: i1 - 2 with: extra]
+ 				ifFalse: [string, ';', extra]]!
- 		ifNotNil: [i1 := string lastIndexOf: $:. string copyReplaceFrom: i1 - 1 to: i1 - 2 with: extra]!

Item was changed:
  Alien variableByteSubclass: #CogProcessorAlien
  	instanceVariableNames: ''
+ 	classVariableNames: 'PrintCodeBytes PrintTempNames SavedState'
- 	classVariableNames: 'SavedState'
  	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 changed:
  ----- Method: CogProcessorAlien class>>initialize (in category 'class initialization') -----
  initialize
+ 	PrintCodeBytes ifNil: [PrintCodeBytes := true].  "Does disassembly include code bytes?"
+ 	PrintTempNames ifNil: [PrintTempNames := false].  "Does disassembly include temp names?"
  	SavedState := WeakIdentityKeyDictionary new.
  	Smalltalk
  		addToStartUpList: self;
  		addToShutDownList: self!

Item was added:
+ ----- Method: CogProcessorAlien class>>printCodeBytes (in category 'accessing') -----
+ printCodeBytes
+ 	<preference: 'Does disassembly include code bytes'
+ 	  category: 'Cogit'
+ 	  description: 'If true, assembly will include machine code bytes..'
+ 	  type: #Boolean>
+ 	^PrintCodeBytes ifNil: [true]!

Item was added:
+ ----- Method: CogProcessorAlien class>>printCodeBytes: (in category 'accessing') -----
+ printCodeBytes: aBoolean
+ 	PrintCodeBytes := aBoolean!

Item was added:
+ ----- Method: CogProcessorAlien class>>printTempNames (in category 'accessing') -----
+ printTempNames
+ 	<preference: 'Does disassembly include temp names?'
+ 	  category: 'Cogit'
+ 	  description: 'If true, assembly will try and associate frame-relative offsets as temp names.'
+ 	  type: #Boolean>
+ 	^PrintTempNames ifNil: [false]!

Item was added:
+ ----- Method: CogProcessorAlien class>>printTempNames: (in category 'accessing') -----
+ printTempNames: aBoolean
+ 	PrintTempNames := aBoolean!

Item was removed:
- ----- Method: GdbARMPlugin>>primitiveDisassembleAt:InMemory: (in category 'primitives') -----
- "cpuAlien <GdbARMAlien>" primitiveDisassembleAt: address "<Integer>" InMemory: memory "<Bitmap|ByteArray|WordArray>"
- 	"Return an Array of the instruction length and its decompilation as a string for the instruction at address in memory."
- 	| cpuAlien cpu instrLenOrErr resultObj log logLen logObj logObjData |
- 	<var: #cpu type: #'void *'>
- 	cpuAlien := self primitive: #primitiveDisassembleAtInMemory
- 					parameters: #(Unsigned WordsOrBytes)
- 					receiver: #Oop.
- 	(cpu := self startOfData: cpuAlien) = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
- 	instrLenOrErr := self disassembleFor: cpu
- 						At: address
- 						In: memory
- 						Size: (interpreterProxy byteSizeOf: memory cPtrAsOop).
- 	instrLenOrErr < 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
- 	log := self getlog: (self cCode: [self addressOf: logLen] inSmalltalk: [logLen := 0]).
- 	resultObj := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: 2.
- 	resultObj = 0 ifTrue:
- 		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
- 
- 	"Easier keeping the damn thing on the stack than using pushRemappableOop:/popRemappableOop.
- 	 Where is topRemappableOop when you need it?"
- 	interpreterProxy pushRemappableOop: resultObj.
- 	logObj := interpreterProxy
- 				instantiateClass: interpreterProxy classString
- 				indexableSize: logLen.
- 	interpreterProxy failed ifTrue:
- 		[interpreterProxy popRemappableOop.
- 		 ^interpreterProxy primitiveFailFor: PrimErrNoMemory].
- 	logObjData := interpreterProxy arrayValueOf: logObj.
- 	self mem: logObjData cp: log y: logLen.
- 	resultObj := interpreterProxy popRemappableOop.
- 	interpreterProxy
- 		storePointer: 0
- 		ofObject: resultObj
- 		withValue: (interpreterProxy integerObjectOf: instrLenOrErr).
- 	interpreterProxy storePointer: 1 ofObject: resultObj withValue: logObj.
- 
- 	^resultObj!



More information about the Vm-dev mailing list