[Vm-dev] VM Maker: VMMaker.oscog-eem.1856.mcz

commits at source.squeak.org commits at source.squeak.org
Tue May 10 02:08:18 UTC 2016


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

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

Name: VMMaker.oscog-eem.1856
Author: eem
Time: 9 May 2016, 7:06:23.09895 pm
UUID: ddc1d13f-a8de-4cb1-af85-65ca64ffbe34
Ancestors: VMMaker.oscog-eem.1855

Fix two regressions introduced into the ARM cogit in the register allocation changes made recently.  a) getSave/RestoreRegs: should do nothing on ARM, and b) Extra0Reg must be distinct from the other registers (!!).  Fix a speeling rorre.

Simulation: Fix printing of the register map (a regression from the abstract register putsch of last year).  Fix parsing invalid address traces in reporting the last N instructions.  Improve printing of ClassBindings in disassembly.

In 1856:
Gregor Mendel starts his research on genetics.
Kate Warne, the first female private detective, begins to work for the Pinkerton Detective Agency.
Pre-human remains are found in the Neandertal valley in Germany.

=============== Diff against VMMaker.oscog-eem.1855 ===============

Item was changed:
  ----- Method: CogARMCompiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  
  	"N.B. According to BSABI, R0-R3 are caller-save, R4-R12 are callee save.
  	 Note that R9 might be a special register for the implementation. In some slides
  	 it is refered to as sb. R10 can contain the stack limit (sl), R11 the fp. R12 is an
  	 intra-procedure scratch instruction pointer for link purposes. It can also be used.
  	 R10 is used as temporary inside a single abstract opcode implementation"
  	"R0-R3 are used when calling back to the interpreter. Using them would require
  	 saving and restoring their values, so they are omitted so far. R12 is the only
  	 scratch register at the moment.."
  
  	super initializeAbstractRegisters.
  
  	TempReg			:= R0.
  	ClassReg			:= R8.
  	ReceiverResultReg	:= R7.
  	SendNumArgsReg	:= R6.
+ 	SPReg				:= SP. "a.k.a. R13" self assert: SP = 13.
- 	SPReg				:= SP. "R13"
  	FPReg				:= R11.
  	Arg0Reg			:= R4.
  	Arg1Reg			:= R5.
+ 	Extra0Reg			:= R9.
+ 	VarBaseReg		:= R10.	"Must be callee saved" self assert: ConcreteVarBaseReg = R10.
+ 	RISCTempReg		:= R12.	"a.k.a. IP" self assert: ConcreteIPReg = R12.
- 	VarBaseReg		:= ConcreteVarBaseReg. "Must be callee saved"
- 	RISCTempReg		:= ConcreteIPReg. "a.k.a. IP"
- 	Extra0Reg			:= R12.
  	LinkReg				:= LR. "R14"
  	PCReg				:= PC. "R15"	
  
  	DPFPReg0			:= D0.
  	DPFPReg1			:= D1.
  	DPFPReg2			:= D2.
  	DPFPReg3			:= D3.
  	DPFPReg4			:= D4.
  	DPFPReg5			:= D5.
  	DPFPReg6			:= D6.
  	DPFPReg7			:= D7
  !

Item was changed:
  ----- Method: CogARMCompiler>>genRestoreRegs: (in category 'abi') -----
  genRestoreRegs: regMask
  	"Restore the registers in regMask as saved by genSaveRegs:.
+ 	 Restore none, because the ARM ABI only defines callee saved registers, no caller-saved regs."
- 	 Restore none, because the ARM ABI only defines callee saved registers, no caller-saved regs.
- 	 But for the future..."
- 	self assert: regMask = 0.
- 	self deny: (regMask anyMask: (cogit registerMaskFor: SP and: FPReg and: LR and: PC)).
- 	R0 to: R12 do:
- 		[:reg|
- 		 (regMask anyMask: (cogit registerMaskFor: reg)) ifTrue:
- 			[cogit PopR: reg]].
  	^0!

Item was changed:
  ----- Method: CogARMCompiler>>genSaveRegs: (in category 'abi') -----
  genSaveRegs: regMask
  	"Save the registers in regMask for a call into the C run-time from a trampoline.
+ 	 Save none, because the ARM ABI only defines callee saved registers, no caller-saved regs."
- 	 Save none, because the ARM ABI only defines callee saved registers, no caller-saved regs.
- 	 But for the future..."
- 	self assert: regMask = 0.
- 	self deny: (regMask anyMask: (cogit registerMaskFor: SP and: FPReg and: LR and: PC)).
- 	R12 to: R0 by: -1 do:
- 		[:reg|
- 		 (regMask anyMask: (cogit registerMaskFor: reg)) ifTrue:
- 			[cogit PushR: reg]].
  	^0!

Item was changed:
  ----- Method: CogX64Compiler>>genMarshallNArgs:arg:arg:arg:arg: (in category 'abi') -----
  genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
  	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is
  	 either a negative number, which encodes a constant, or a non-negative number, that of a register.
  
  	 Run-time calls have no more than four arguments, so chosen so that on ARM, where in its C ABI the
  	 first four integer arguments are passed in registers, all arguments can be passed in registers.  We
  	 defer to the back end to generate this code not so much that the back end knows whether it uses
  	 the stack or registers to pass arguments (it does, but...). In fact we defer for an extremely evil reason.
  	 Doing so allows the x64 (where up to 6 args are passed) to assign the register arguments in an order
  	 that allows some of the argument registers to be used for specific abstract  registers, specifically
  	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also it's really nice to keep using the old
  	 register assignments the original author has grown accustomed to.
  
  	 How can this possibly work?  Look at Cogit class>>runtime for a list of the run-time calls and their
  	 arguments, including which arguments are passed in which registers.  Look at CogX64Compiler's
+ 	 subclass implementations of initializeAbstractRegisters.  There are no calls in which ReceiverResultReg
- 	 subclass implementations of initializeAbstractregisters.  There are no calls in which ReceiverResultReg
  	 (RDX) and/or ClassReg (RCX) are passed along with Arg0Reg and Arg1Reg, and none in which the use of
  	 either ReceiverResultReg or ClassReg conflict for args 3 & 4.  So if args are assigned in order, the
+ 	 registers do not get overwritten.  Yes, this is evil, but it's so nice to continue to use RCX & RDX.
+ 
+ 	 Argument registers for args 0 to 3 in SysV are RDI RSI RDX RCX, and in Win64 are RDI RSI R8 R9"
- 	 registers do not get overwritten.  Yes, this is evil, but it's so nice to continue to use RCX & RDX."
  	<inline: true>
  	numArgs = 0 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst0)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst0) R: RDI]
  		ifFalse:
  			[regOrConst0 ~= RDI ifTrue:
  				[cogit MoveR: regOrConst0 R: RDI]].
  	numArgs = 1 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst1)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst1) R: RSI]
  		ifFalse:
  			[regOrConst1 ~= RSI ifTrue:
  				[cogit MoveR: regOrConst1 R: RSI]].
  	numArgs = 2 ifTrue: [^self].
  	self cppIf: ABI == #SysV ifTrue:
  		[(cogit isTrampolineArgConstant: regOrConst2)
  			ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: RDX]
  			ifFalse:
  				[regOrConst2 ~= RDX ifTrue:
  					[cogit MoveR: regOrConst2 R: RDX]].
  		 numArgs = 3 ifTrue: [^self].
  		 (cogit isTrampolineArgConstant: regOrConst3)
  				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: RCX]
  				ifFalse:
  					[regOrConst3 ~= RCX ifTrue:
  						[cogit MoveR: regOrConst3 R: RCX]]].
  	self cppIf: ABI == #MSVC ifTrue:
  		[(cogit isTrampolineArgConstant: regOrConst2)
  			ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: R8]
  			ifFalse:
  				[regOrConst2 ~= R8 ifTrue:
  					[cogit MoveR: regOrConst2 R: R8]].
  		 numArgs = 3 ifTrue: [^self].
  		 (cogit isTrampolineArgConstant: regOrConst3)
  				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: R9]
  				ifFalse:
  					[regOrConst3 ~= R9 ifTrue:
  						[cogit MoveR: regOrConst3 R: R9]]].
  	self assert: numArgs <= 4!

Item was changed:
  ----- Method: Cogit>>printRegisterMapOn: (in category 'disassembly') -----
  printRegisterMapOn: aStream
  	<doNotGenerate>
  	| map n |
  	map := backEnd generalPurposeRegisterMap.
  	n := 0.
  	map keys sort
  		do:	[:regName| | abstractName |
+ 			abstractName := CogAbstractRegisters nameForRegister: (map at: regName).
- 			abstractName := CogRTLOpcodes nameForRegister: (map at: regName).
  			aStream nextPutAll: abstractName; nextPutAll: ' => '; nextPutAll: regName]
  		separatedBy: [(n := n + 1) \\ 4 = 0 ifTrue: [aStream cr] ifFalse: [aStream tab]].
  	aStream cr; flush!

Item was changed:
  ----- Method: Cogit>>reportLastNInstructions (in category 'debugging') -----
  reportLastNInstructions
  	<doNotGenerate>
  	| skipNext printInst |
  	skipNext := false.
  	printInst := [:inst|
  				coInterpreter transcript nextPutAll:
  					(EagerInstructionDecoration
  						ifTrue: [inst]
  						ifFalse: [processor
  									decorateDisassembly: inst
  									for: self
+ 									fromAddress: ((inst at: 3) = $r
+ 													ifTrue: [Integer readFrom: inst readStream]
+ 													ifFalse: [Integer readFrom: inst readStream base: 16])]); cr].
- 									fromAddress: (Integer readFrom: inst readStream base: 16)]); cr].
  	lastNInstructions withIndexDo:
  		[:thing :idx| | next pc label |
  		skipNext
  			ifTrue: [skipNext := false]
  			ifFalse:
  				[thing isArray
  					ifTrue:
  						[thing first isString "i.e. { '(simulated return to '. processor retpcIn: coInterpreter memory. ')'}"
  							ifTrue:
  								[thing do:
  									[:stringOrNumber|
  									coInterpreter transcript nextPutAll: (stringOrNumber isString
  															ifTrue: [stringOrNumber]
  															ifFalse: [stringOrNumber hex])].
  									coInterpreter transcript cr]
  							ifFalse: "if possible, add the label to the instruction line to condense the output"
  								[coInterpreter transcript cr.
  								 pc := thing at: processor registerStatePCIndex.
  								 label := self relativeLabelForPC: pc.
  								 ((next := lastNInstructions at: idx + 1 ifAbsent: []) notNil
  								  and: [next isString
  								  and: [(Integer readFrom: next readStream radix: 16) = pc]])
  									ifTrue: "Decorate instruction and eliminate pc line"
  										[skipNext := true.
  										 processor printRegisterStateExceptPC: thing on: coInterpreter transcript.
  										 label ifNotNil: [coInterpreter transcript nextPutAll: label; space].
  										 printInst value: next]
  									ifFalse:
  										[label ifNotNil: [coInterpreter transcript nextPutAll: label; nextPut: $:; cr].
  										 processor printRegisterState: thing on: coInterpreter transcript]]]
  					ifFalse:
  						[printInst value: thing]]].
  	coInterpreter transcript flush!

Item was changed:
  ----- Method: SpurMemoryManager>>lookupAddress: (in category 'simulation only') -----
  lookupAddress: address
  	"If address appears to be that of a Symbol or a few well-known objects (such as classes) answer it, otherwise answer nil.
  	 For code disassembly"
  	<doNotGenerate>
  	| fmt size string class classSize maybeThisClass classNameIndex thisClassIndex |
  	((self addressCouldBeObj: address)
  	 and: [(thisClassIndex := self classIndexOf: address) > 0]) ifFalse:
  		[^address = scavengeThreshold ifTrue:
  			['scavengeThreshold']].
  	address - self baseHeaderSize = hiddenRootsObj ifTrue:
  		[^'(hiddenRootsObj+baseHeaderSize)'].
  	fmt := self formatOf: address.
  	size := self lengthOf: address baseHeader: (self baseHeader: address) format: fmt.
  	size = 0 ifTrue:
  		[^address caseOf: { [nilObj] -> ['nil']. [trueObj] -> ['true']. [falseObj] -> ['false'] } otherwise: []].
  	((fmt between: self firstByteFormat and: self firstCompiledMethodFormat - 1) "indexable byte fields"
  	and: [(size between: 1 and: 64)
  	and: [(Scanner isLiteralSymbol: (string := (0 to: size - 1) collect: [:i| Character value: (self fetchByte: i ofObject: address)]))
  		or: [NewspeakVM and: [string noneSatisfy: [:c| c isSeparator or: [c asInteger > 126]]]]]]) ifTrue:
  		[^'#', (ByteString withAll: string)].
  	class := self noCheckClassAtIndex: thisClassIndex.
  	(class isNil or: [class = nilObj]) ifTrue:
  		[^nil].
  	"address is either a class or a metaclass, or an instance of a class or invalid.  determine which."
  	classNameIndex := coInterpreter classNameIndex.
  	thisClassIndex := coInterpreter thisClassIndex.
  	((classSize := self numSlotsOf: class) <= (classNameIndex max: thisClassIndex)
  	 or: [classSize > 255]) ifTrue:
  		[^nil].
  	"Address could be a class or a metaclass"
  	(fmt = 1 and: [size > classNameIndex]) ifTrue:
  		["Is address a class? If so class's thisClass is address."
  		 (self lookupAddress: (self fetchPointer: classNameIndex ofObject: address)) ifNotNil:
  			[:maybeClassName|
  			(self fetchPointer: thisClassIndex ofObject: class) = address ifTrue:
  				[^maybeClassName allButFirst]].
  		"Is address a Metaclass?  If so class's name is Metaclass and address's thisClass holds the class name"
  		((self isBytes: (self fetchPointer: classNameIndex ofObject: class))
  		 and: [(self lookupAddress: (self fetchPointer: classNameIndex ofObject: class)) = '#Metaclass'
  		 and: [size >= thisClassIndex]]) ifTrue:
  			[maybeThisClass := self fetchPointer: thisClassIndex ofObject: address.
  			(self lookupAddress: (self fetchPointer: classNameIndex ofObject: maybeThisClass)) ifNotNil:
  				[:maybeThisClassName| ^maybeThisClassName allButFirst, ' class']]].
  	^(self lookupAddress: (self fetchPointer: classNameIndex ofObject: class)) ifNotNil:
+ 		[:maybeClassName|
+ 		(size = 2
+ 		 and: [fmt = self nonIndexablePointerFormat
+ 		 and: ['#ClassBinding' = maybeClassName]]) ifTrue:
+ 			[^'a ClassBinding '
+ 				, ((self lookupAddress: (self fetchPointer: KeyIndex ofObject: address)) ifNil: [''])
+ 				, ((self lookupAddress: (self fetchPointer: ValueIndex ofObject: address)) ifNil: [''] ifNotNil: [:val| ' -> ', val])].
+ 		'a(n) ', maybeClassName allButFirst]!
- 		[:maybeClassName| 'a(n) ', maybeClassName allButFirst]!



More information about the Vm-dev mailing list