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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 5 06:55:33 UTC 2015


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

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

Name: VMMaker.oscog-eem.1552
Author: eem
Time: 4 December 2015, 10:53:48.8 pm
UUID: f86a39c0-4b4e-459d-aa15-15cadd793672
Ancestors: VMMaker.oscog-eem.1551

x64 Cogit:
Fix double adding of numSLots to header in ByteString>>basicNew:

Fix the simulator's defaulting of ISA so that x64 is the default if 64-bit spur is selected.

Include the new scratch regs in the register map printing.

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

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genInnerPrimitiveNewWithArg: (in category 'primitive generators') -----
  genInnerPrimitiveNewWithArg: retNoffset
  	"Implement primitiveNewWithArg for convenient cases:
  	- the receiver has a hash
  	- the receiver is variable and not compiled method
  	- single word header/num slots < numSlotsMask
  	- the result fits in eden
  	See superclass method for dynamic frequencies of formats.
  	For the moment we implement only arrayFormat, firstByteFormat & firstLongFormat"
  
  	| headerReg fillReg instSpecReg byteSizeReg maxSlots
  	  jumpArrayTooBig jumpByteTooBig jumpLongTooBig
  	  jumpArrayFormat jumpByteFormat jumpBytePrepDone jumpLongPrepDone
  	  jumpUnhashed jumpNElementsNonInt jumpFailCuzFixed jumpNoSpace jumpHasSlots fillLoop skip |
  	<var: 'skip' type: #'AbstractInstruction *'>
  	<var: 'fillLoop' type: #'AbstractInstruction *'>	
  	<var: 'jumpHasSlots' type: #'AbstractInstruction *'>
  	<var: 'jumpNoSpace' type: #'AbstractInstruction *'>
  	<var: 'jumpUnhashed' type: #'AbstractInstruction *'>
  	<var: 'jumpByteFormat' type: #'AbstractInstruction *'>
  	<var: 'jumpByteTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpLongTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpArrayFormat' type: #'AbstractInstruction *'>
  	<var: 'jumpArrayTooBig' type: #'AbstractInstruction *'>
  	<var: 'jumpFailCuzFixed' type: #'AbstractInstruction *'>
  	<var: 'jumpBytePrepDone' type: #'AbstractInstruction *'>
  	<var: 'jumpLongPrepDone' type: #'AbstractInstruction *'>
  	<var: 'jumpNElementsNonInt' type: #'AbstractInstruction *'>
  
  	"header will contain classIndex/class's hash & format & numSlots/fixed size"
  	headerReg := SendNumArgsReg.
  	"Assume there's an available scratch register on 64-bit machines"
  	fillReg := Scratch0Reg.
  	self assert: (cogit backEnd concreteRegister: fillReg) > 0.
  	"inst spec will hold class's instance specification and then byte size"
  	instSpecReg := byteSizeReg := ClassReg.
  	"The max slots we'll allocate here are those for a single header"
  	maxSlots := objectMemory numSlotsMask - 1.
  
  	"get freeStart as early as possible so as not to wait later..."
  	cogit MoveAw: objectMemory freeStartAddress R: Arg1Reg.
  	"get class's hash & fail if 0"
  	self genGetHashFieldNonImmOf: ReceiverResultReg into: headerReg.
  	jumpUnhashed := cogit JumpZero: 0.
  	"get index and fail if not a +ve integer"
  	jumpNElementsNonInt := self genJumpNotSmallInteger: Arg0Reg scratch: TempReg.
  	"get class's format inst var for inst spec (format field)"
  	self genLoadSlot: InstanceSpecificationIndex sourceReg: ReceiverResultReg destReg: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory fixedFieldsFieldWidth + self numSmallIntegerTagBits R: instSpecReg.
  	cogit AndCq: objectMemory formatMask R: instSpecReg.
  	"Add format to classIndex/format header now"
  	cogit MoveR: instSpecReg R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"get integer value of num fields in TempReg now"
  	cogit MoveR: Arg0Reg R: TempReg.
  	self genConvertSmallIntegerToIntegerInReg: TempReg.
  	"dispatch on format, failing if not variable or if compiled method"
  	cogit CmpCq: objectMemory arrayFormat R: instSpecReg.
  	jumpArrayFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstByteFormat R: instSpecReg.
  	jumpByteFormat := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory firstLongFormat R: instSpecReg.
  	jumpFailCuzFixed := cogit JumpNonZero: 0.
  
  	cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg.
  	jumpLongTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: TempReg R: instSpecReg.
  	cogit MoveCq: 0 R: fillReg.
  	jumpLongPrepDone := cogit Jump: 0. "go allocate"
  
  	jumpByteFormat jmpTarget:
  	(cogit CmpCq: (objectMemory integerObjectOf: maxSlots * objectMemory wordSize) R: Arg0Reg).
  	jumpByteTooBig := cogit JumpAbove: 0.
  	"save num elements to instSpecReg"
  	cogit MoveR: TempReg R: instSpecReg.
  	"compute odd bits and add into headerReg; oddBits := 4 - nElements bitAnd: 3"
  	cogit MoveCq: objectMemory wordSize R: TempReg.
  	cogit SubR: instSpecReg R: TempReg.
  	cogit AndCq: objectMemory wordSize - 1 R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory formatShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"round up num elements to numSlots in instSpecReg"
  	cogit AddCq: objectMemory wordSize - 1 R: instSpecReg.
  	cogit LogicalShiftRightCq: objectMemory shiftForWord R: instSpecReg.
- 	"store numSlots to headerReg"
- 	cogit MoveR: instSpecReg R: TempReg.
- 	cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R: TempReg.
- 	cogit AddR: TempReg R: headerReg.
  	cogit MoveCq: 0 R: fillReg.
  	jumpBytePrepDone := cogit Jump: 0. "go allocate"
  
  	jumpArrayFormat jmpTarget:
  		(cogit CmpCq: (objectMemory integerObjectOf: maxSlots) R: Arg0Reg).
  	jumpArrayTooBig := cogit JumpAbove: 0.
  	"save num elements/slot size to instSpecReg"
  	cogit MoveR: TempReg R: instSpecReg.
  	cogit MoveCq: objectMemory nilObject R: fillReg.
  	"fall through to allocate"
  
  	jumpBytePrepDone jmpTarget:
  	(jumpLongPrepDone jmpTarget: cogit Label).
  
  	"store numSlots to headerReg"
  	cogit MoveR: instSpecReg R: TempReg.
  	cogit LogicalShiftLeftCq: objectMemory numSlotsFullShift R: TempReg.
  	cogit AddR: TempReg R: headerReg.
  	"compute byte size; remember 0-sized objects still need 1 slot."
  	cogit CmpCq: 0 R: byteSizeReg. "a.k.a. instSpecReg"
  	jumpHasSlots := cogit JumpNonZero: 0.
  	cogit MoveCq: objectMemory baseHeaderSize * 2 R: byteSizeReg.
  	skip := cogit Jump: 0.
  	"round up to allocationUnit"
  	jumpHasSlots jmpTarget:
  	(cogit MoveR: byteSizeReg R: TempReg).
  	cogit AddR: TempReg R: byteSizeReg.
  	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize R: byteSizeReg.
  	cogit LogicalShiftLeftCq: objectMemory shiftForWord R: byteSizeReg.
  	skip jmpTarget:
  	"check if allocation fits"
  	(cogit AddR: Arg1Reg R: byteSizeReg).
  	cogit CmpCq: objectMemory getScavengeThreshold R: byteSizeReg.
  	jumpNoSpace := cogit JumpAboveOrEqual: 0.
  	"get result, increment freeStart and write it back. Arg1Reg holds new freeStart, the limit of the object"
  	cogit MoveR: Arg1Reg R: ReceiverResultReg.
  	cogit MoveR: byteSizeReg Aw: objectMemory freeStartAddress.
  	"write other half of header (numSlots/0 identityHash)"
  	cogit MoveR: headerReg Mw: 0 r: ReceiverResultReg.
  	"now fill"
  	cogit LoadEffectiveAddressMw: objectMemory baseHeaderSize r: ReceiverResultReg R: Arg1Reg.
  	fillLoop := 
  	cogit MoveR: fillReg Mw: 0 r: Arg1Reg.
  	cogit AddCq: 8 R: Arg1Reg.
  	cogit CmpR: Arg1Reg R: byteSizeReg.
  	cogit JumpAbove: fillLoop.
  	cogit RetN: retNoffset.
  	
  	jumpNoSpace jmpTarget:
  	(jumpUnhashed jmpTarget:
  	(jumpFailCuzFixed jmpTarget:
  	(jumpArrayTooBig jmpTarget:
  	(jumpByteTooBig jmpTarget:
  	(jumpLongTooBig jmpTarget:
  	(jumpNElementsNonInt jmpTarget: cogit Label)))))).
  
  	^0!

Item was changed:
  ----- Method: CogRTLOpcodes class>>nameForRegister: (in category 'debug printing') -----
  nameForRegister: reg "<Integer>"
  	^#(Arg0Reg Arg1Reg ClassReg FPReg ReceiverResultReg SPReg SendNumArgsReg TempReg
  		DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7
+ 		LinkReg RISCTempReg VarBaseReg PCReg
+ 		Scratch0Reg Scratch1Reg Scratch2Reg Scratch3Reg Scratch4Reg Scratch5Reg)
- 		LinkReg RISCTempReg VarBaseReg PCReg)
  			detect: [:sym| (classPool at: sym) = reg]
  			ifNone: ['REG', reg printString, '?']!

Item was added:
+ ----- Method: CogX64Compiler class>>defaultCompilerClass (in category 'translation') -----
+ defaultCompilerClass
+ 	^CogInLineLiteralsX64Compiler!

Item was added:
+ ----- Method: CogX64Compiler>>generalPurposeRegisterMap (in category 'disassembly') -----
+ generalPurposeRegisterMap
+ 	<doNotGenerate>
+ 	"Answer a Dictionary from register getter to register index."
+ 	^Dictionary newFromPairs:
+ 		{	#rax. RAX.
+ 			#rcx. RCX.
+ 			#rdx. RDX.
+ 			#rbx. RBX.
+ 			#rsi.  RSI.
+ 			#rdi.  RDI.
+ 			#r8. R8.
+ 			#r9. R9.
+ 			#r10. R10.
+ 			#r11. R11.
+ 			#r12. R12.
+ 			#r13. R13.
+ 			#r14. R14.
+ 			#r15. R15	}!

Item was changed:
  ----- Method: Cogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
  	Debug := initializationOptions at: #Debug ifAbsent: [false].
  	(initializationOptions includesKey: #EagerInstructionDecoration)
  		ifTrue:
  			[EagerInstructionDecoration := initializationOptions at: #EagerInstructionDecoration]
  		ifFalse:
  			[EagerInstructionDecoration ifNil:
  				[EagerInstructionDecoration := false]]. "speeds up single stepping but could lose fidelity"
  
+ 	ProcessorClass := (initializationOptions at: #ISA ifAbsentPut: [self objectMemoryClass defaultISA]) caseOf: {
- 	ProcessorClass := (initializationOptions at: #ISA ifAbsentPut: [#IA32]) caseOf: {
  							[#X64] 		->	[BochsX64Alien].
  							[#IA32] 	->	[BochsIA32Alien].
  							[#ARMv5]	->	[GdbARMAlien].
  							[#MIPSEL]	->	[MIPSELSimulator] }.
  	CogCompilerClass := self activeCompilerClass.
  	(CogCompilerClass withAllSuperclasses copyUpTo: CogAbstractInstruction) do:
  		[:compilerClass| compilerClass initialize].
  	"Our criterion for which methods to JIT is literal count.  The default value is 60 literals or less."
  	MaxLiteralCountForCompile := initializationOptions at: #MaxLiteralCountForCompile ifAbsent: [60].
  	"we special-case 0, 1 & 2 argument sends, N is numArgs >= 3"
  	NumSendTrampolines := 4.
  	"Currently not even the ceImplicitReceiverTrampoline contains object references."
  	NumObjRefsInRuntime := 0.
  
  	NSCSelectorIndex := (NSSendCache instVarNames indexOf: #selector) - 1.
  	NSCNumArgsIndex := (NSSendCache instVarNames indexOf: #numArgs) - 1.
  	NSCClassTagIndex := (NSSendCache instVarNames indexOf: #classTag) - 1.
  	NSCEnclosingObjectIndex := (NSSendCache instVarNames indexOf: #enclosingObject) - 1.
  	NSCTargetIndex := (NSSendCache instVarNames indexOf: #target) - 1.
  	NumOopsPerNSC := NSSendCache instVarNames size.
  
  	"Max size to alloca when compiling.
  	 Mac OS X 10.6.8 segfaults approaching 8Mb.
  	 Linux 2.6.9 segfaults above 11Mb.
  	 WIndows XP segfaults approaching 2Mb."
  	MaxStackAllocSize := 1024 * 1024 * 3 / 2 !

Item was added:
+ ----- Method: NewCoObjectMemory class>>defaultISA (in category 'simulation') -----
+ defaultISA
+ 	"Answer the default instruction set architecture to use for simulation."
+ 	^#IA32!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager class>>defaultISA (in category 'simulation') -----
+ defaultISA
+ 	"Answer the default instruction set architecture to use for simulation."
+ 	^#IA32!

Item was changed:
+ ----- Method: Spur32BitCoMemoryManager class>>simulatorClass (in category 'simulation') -----
- ----- Method: Spur32BitCoMemoryManager class>>simulatorClass (in category 'simulation only') -----
  simulatorClass
  	^Spur32BitMMLECoSimulator!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager class>>defaultISA (in category 'simulation') -----
+ defaultISA
+ 	"Answer the default instruction set architecture to use for simulation."
+ 	^#X64!

Item was changed:
+ ----- Method: Spur64BitCoMemoryManager class>>simulatorClass (in category 'simulation') -----
- ----- Method: Spur64BitCoMemoryManager class>>simulatorClass (in category 'simulation only') -----
  simulatorClass
  	^Spur64BitMMLECoSimulator!



More information about the Vm-dev mailing list