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

commits at source.squeak.org commits at source.squeak.org
Mon Jul 26 01:41:30 UTC 2021


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

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

Name: Cog-eem.438
Author: eem
Time: 25 July 2021, 6:41:28.356061 pm
UUID: 9ba20ae6-d5e7-4ef0-be5b-cdb949b42283
Ancestors: Cog-eem.437

Fix disassembling the ARMv8's prefetch instruction.

=============== Diff against Cog-eem.437 ===============

Item was changed:
  ----- Method: GdbARMv8Alien>>decorateDisassembly:for:fromAddress:labels: (in category 'disassembly') -----
  decorateDisassembly: anInstructionString for: aSymbolManager fromAddress: address labels: labelDictionaryOrNil
  	"Decode what we can of the instruction and decorate it with useful stuff"
  	| word operand memory theInstructionString mnemonic offsetIdx nonZeroIdx size secondOperand |
  	word := (memory:= aSymbolManager objectMemory) long32At: address.
  	"See #twoWordLiteral in the (ARMv8A64Opcodes instructionIsAnyLoadStore: word) arm below.
  	 If a previous pc-relative load has been decorated it will be added to labelDictionaryOrNil,
  	 with valuer #twoWordLiteral, so just try and decode the value."
  	labelDictionaryOrNil ifNotNil:
  		[(mnemonic := labelDictionaryOrNil at: address ifAbsent: nil) == #twoWordLiteral ifTrue:
  			[^(anInstructionString copyReplaceAll: '; undefined' with: '')
  			  , ((address noMask: 7) "Is this the first word of the literal?"
  					ifTrue: [(aSymbolManager lookupAddress: (memory longAt: address)) ifNotNil: [:label| ' = ', label] ifNil: ['']]
  					ifFalse: [''])].
  		mnemonic = #oneWordLiteral ifTrue:
  			[^(anInstructionString copyReplaceAll: '; undefined' with: ''),
  			 ((aSymbolManager lookup32BitWordConstant: word) ifNotNil: [:label| ' => ', label] ifNil: [''])]].
  	mnemonic := (anInstructionString first isLetter
  					ifTrue: [anInstructionString copyUpTo: Character tab]
  					ifFalse: [anInstructionString
  								copyFrom: (anInstructionString indexOf: $:) + 2
  								to: (anInstructionString indexOf: Character tab ifAbsent: [anInstructionString size + 1]) - 1])
  						copyUpTo: Character space.
  
  	"Trim long sequences of zeros in address operands"
  	theInstructionString := 
  		(offsetIdx := (anInstructionString indexOfSubCollection: '0x' startingAt: 12)) > 0
  			ifTrue:
  				[nonZeroIdx := offsetIdx + 2.
  				size := anInstructionString size.
  				 [nonZeroIdx <= size and: [(anInstructionString at: nonZeroIdx) == $0]] whileTrue: [nonZeroIdx := nonZeroIdx + 1].
  				 nonZeroIdx < size
  					ifTrue: [anInstructionString copyReplaceFrom: offsetIdx + 2 to: nonZeroIdx - 1 with: '']
  					ifFalse: [anInstructionString]]
  			ifFalse: [anInstructionString].
  
  	mnemonic ~= '.inst' ifTrue: "All bets are off for arbitrary literals"
+ 		[((mnemonic beginsWith: 'ld') or: [(mnemonic beginsWith: 'st') or: [mnemonic = 'prfm' or: [mnemonic beginsWith: 'cas']]])
- 		[((mnemonic beginsWith: 'ld') or: [(mnemonic beginsWith: 'st') or: [mnemonic beginsWith: 'cas']])
  			ifTrue: [self assert: (ARMv8A64Opcodes instructionIsAnyLoadStore: word)]
  			ifFalse: [self deny: (ARMv8A64Opcodes instructionIsAnyLoadStore: word)].
  		((mnemonic beginsWith: 'br') or: [(mnemonic beginsWith: 'bl') or: [(mnemonic beginsWith: 'b.')
  		 or: [mnemonic = 'b' or: [mnemonic = 'ret']]]])
  			ifTrue: [self assert: (ARMv8A64Opcodes instructionIsAnyB: word)]
  			ifFalse: [self deny: (ARMv8A64Opcodes instructionIsAnyB: word)].
  		"add register names..."
  		offsetIdx := theInstructionString size + 2.
  		[(offsetIdx := theInstructionString lastIndexOf: $x startingAt: offsetIdx - 2) > 1] whileTrue:
  			[| regNum regName stream |
  			((theInstructionString at: offsetIdx - 1) isAlphaNumeric not
  			 and: [(theInstructionString at: offsetIdx + 1) isDigit
  			 and: [stream := ReadStream on: theInstructionString from: offsetIdx + 1 to: offsetIdx + 2.
  				   (regName := aSymbolManager lookupRegisterNumber: (regNum := Integer readFrom:stream)) notNil]])
  				ifTrue:
  					[((theInstructionString at: offsetIdx - 1) == $[
  					  and: [stream position + 4 < theInstructionString size
  					  and: [(theInstructionString at: stream position + 3) == $#]]) ifTrue: "excludes e.g. ldr	x29, [x16], #8'"
  						[| offsetStream |
  						 offsetStream := ReadStream on: theInstructionString from: stream position + 4 to: theInstructionString size.
  						(regNum = FPReg and: [PrintTempNames]) ifTrue:
  							 [(aSymbolManager lookupFrameOffset: (Integer readFrom: offsetStream)) ifNotNil:
  								[:varName|
  								 theInstructionString := theInstructionString
  															copyReplaceFrom: offsetStream position + 1
  															to: offsetStream position
  															with: ':', varName]].
  						regNum = ReceiverResultReg ifTrue:
  							[(aSymbolManager lookupInstVarOffset: (Integer readFrom: offsetStream)) ifNotNil:
  								[:varName|
  								 theInstructionString := theInstructionString
  															copyReplaceFrom: offsetStream position + 1
  															to: offsetStream position
  															with: ':', varName]]].
  					theInstructionString := theInstructionString
  												copyReplaceFrom: stream position + 1
  												to: stream position
  												with: '/', regName]]].
  
  	(ARMv8A64Opcodes instructionIsAnyB: word)
  		ifTrue:
  			[(ARMv8A64Opcodes instructionIsBImm26: word) ifTrue:
  				[operand := ARMv8A64Opcodes extractOffsetFromBImm26: word].
  			(ARMv8A64Opcodes instructionIsBImm19: word) ifTrue:
  				[operand := ARMv8A64Opcodes extractOffsetFromBImm19: word].
  			operand ifNotNil:
  				[operand := (operand bitShift: 2) + address bitAnd: aSymbolManager addressSpaceMask].
  			"We can't extract the offset from a BX/BLX instructions register, unless we're at the current pc,
  			 because otherwise its current value has nothing to do with the value when this instruction is executed."
  			(self pc = address
  			 and: [ARMv8A64Opcodes instructionIsAnyBX: word]) ifTrue:
  				[operand := (self perform: (self registerStateGetters at: (word >> 5 bitAnd: 31) + 1))]]
  		ifFalse:
  			[(ARMv8A64Opcodes instructionIsAnyLoadStore: word)
  				ifTrue:
  					[| baseR twoWords addr lit signExtend |
  					"first see if this is a load via the varBase register" 
  					operand := (baseR := (word >> 5 bitAnd: 31)) = CogARMv8Compiler VarBaseReg ifTrue:
  									[aSymbolManager varBaseAddress + (ARMv8A64Opcodes extractOffsetFromLoadStore: word)].
  					(operand ~~ nil and: [mnemonic = 'ldp' or: [mnemonic = 'stp']]) ifTrue:
  						[secondOperand := operand + 8].
  					"See if this is a pc-relative literal load"
  					(ARMv8A64Opcodes instructionIsPCRelativeLoad: word) ifTrue:
  						[twoWords := word >> 30 anyMask: 1.
  						 addr := aSymbolManager backEnd pcRelativeAddressAt: address.
  						 lit := twoWords
  								ifTrue: [self assert: (addr noMask: 7).
  										labelDictionaryOrNil ifNotNil:
  											[labelDictionaryOrNil at: addr put: #twoWordLiteral; at: addr + 4 put: #twoWordLiteral].
  										memory longAt: addr]
  								ifFalse:
  									["If the next instruction is a linked send then mark the literal and it'll get mapped to a class index"
  									 labelDictionaryOrNil ifNotNil:
  										[| nextInst |
  										nextInst := memory long32At: address + 4.
  										(ARMv8A64Opcodes instructionIsBImm26: nextInst) ifTrue:
  											[operand := ARMv8A64Opcodes extractOffsetFromBImm26: word.
  											 operand := (operand bitShift: 2) + address bitAnd: aSymbolManager addressSpaceMask.
  											 operand := aSymbolManager lookupAddress: operand.
  											 (operand isNil "Closed PICs"
  											  or: [operand includes: $@]) "likely linked send" ifTrue:
  												[labelDictionaryOrNil at: addr put: #oneWordLiteral]]].
  									 lit := memory long32At: addr.
  									 (signExtend := word >> 31 anyMask: 1)
  										ifTrue: [lit - (lit >> 31 << 32)]
  										ifFalse: [lit]].
  						 ^(aSymbolManager lookupAddress: lit)
  							ifNotNil: [:label| theInstructionString, ' = ', label]
  							ifNil: [theInstructionString, ' = ', (lit hex allButFirst: 3)]]]
  				ifFalse:
  					[operand := word]].
  
  	"is there an interesting address for the operand, for this instruction?"
  	operand ifNotNil:
  		[labelDictionaryOrNil ifNotNil:
  			[(labelDictionaryOrNil at: operand ifAbsent: nil) ifNotNil:
  				[:string| ^theInstructionString, ' = ', string]].
  		 (aSymbolManager lookupAddress: operand) ifNotNil:
  				[:string| ^theInstructionString, ' = ', string, (secondOperand ifNil: [''] ifNotNil: [',', (aSymbolManager lookupAddress: secondOperand)])]].
  
  	^theInstructionString!



More information about the Vm-dev mailing list