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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 10 03:50:30 UTC 2022


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

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

Name: VMMaker.oscog.seperateMarking-eem.3283
Author: eem
Time: 9 December 2022, 7:50:07.446363 pm
UUID: 538b31ef-81fb-4a2d-9255-f576bc00d202
Ancestors: VMMaker.oscog.seperateMarking-eem.3282, VMMaker.oscog-eem.3281

Merge VMMaker.oscog-eem.3281

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

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveCqR (in category 'generate machine code - concretize') -----
  concretizeMoveCqR
  	"C3.3.4		Move (immediate)	C3-215
  
  	 The Move (immediate) instructions are aliases for a single MOVZ, MOVN, or ORR (immediate with zero register),
  	 instruction to load an immediate value into the destination register. An assembler must permit a signed or
  	 unsigned immediate, as long as its binary representation can be generated using one of these instructions,
  	 and an assembler error results if the immediate cannot be generated in this way. On disassembly, it is
  	 unspecified whether the immediate is output as a signed or an unsigned value.
  
  	 C6.2.191	MOVZ	C6-1102	Move wide with zero moves an optionally-shifted 16-bit immediate value to a register.
  	 C6.2.190	MOVN	C6-1100	Move wide with NOT moves the inverse of an optionally-shifted 16-bit immediate value to a register.
  	 C6.2.204	ORR (immediate)	C6-1125
  										Bitwise OR (immediate) performs a bitwise (inclusive) OR of a register value and an immediate
  										register value, and writes the result to the destination register."
  
  	| constant destReg |
  	constant := operands at: 0.
  	destReg := operands at: 1.
  	destReg ~= SP ifTrue:
  		[| lowBit lowBitMod16 mask |
  		lowBit := constant > 0
  					ifTrue: [self cCode: [self computeLowBit: constant] inSmalltalk: [constant lowBit - 1]]
  					ifFalse: [0].
  		lowBitMod16 := lowBit // 16 * 16.
  		mask := 1 << 16 - 1 << lowBitMod16.
  		(constant bitAnd: mask) = constant ifTrue:
  			["Use MOVZ"
  			 machineCode
  				at: 0
  				put: 2r110100101 << 23
  					+ (lowBitMod16 // 16 << 21)
  					+ (constant >> lowBitMod16 << 5)
  					+ destReg.
  			 ^4].
  		lowBit := constant signedIntFromLong64 < -1
  					ifTrue: [self cCode: [self computeLowBit: constant bitInvert64] inSmalltalk: [constant bitInvert64 lowBit - 1]]
  					ifFalse: [0].
  		(constant bitOr: mask) signedIntFromLong64 = -1 ifTrue:
  			["Use MOVN"
  			 self assert: (constant bitInvert64 >> lowBitMod16) = ((constant bitInvert64 >> lowBitMod16) bitAnd: mask).
  			 machineCode
  				at: 0
  				put: 2r100100101 << 23
  					+ (lowBitMod16 // 16 << 21)
  					+ (constant bitInvert64 >> lowBitMod16 << 5)
  					+ destReg.
  			 ^4]].
  	^self isImmNImmSImmREncodableBitmask: constant
  		ifTrue:
  			[:n :imms :immr| "Use ORR"
  			machineCode
  				at: 0
+ 				put: 2r1011001 << 25
+ 					+ (n << 22)
- 				put: 2r1011001001 << 22
  					+ (immr << 16)
  					+ (imms << 10)
  					+ (XZR << 5)
  					+ destReg.
  			4]
+ 		ifFalse: [self emitMoveCw: constant intoR: destReg at: 0]
+ 
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"!
- 		ifFalse: [self emitMoveCw: constant intoR: destReg at: 0]!

Item was removed:
- ----- Method: CogARMv8Compiler>>decode64Imms:immr: (in category 'generate machine code - support') -----
- decode64Imms: imms immr: immr
- 	"See aarch64/instrs/integer/bitmasks/DecodeBitMasks J1-7389.
- 	 This is a 64-bit version computing the imm mask (wmask) only."
- 	<returnTypeC: #usqInt>
- 	| mask |
- 	<var: 'mask' type: #usqInt>
- 	self assert: ((imms between: 0 and: 63) and: [immr between: 0 and: 63]).
- 	"For logical immediates an all-ones value of S is reserved since it would generate a useless all-ones result (many times)"
- 	imms = 63 ifTrue:
- 		[^self cCode: [0] inSmalltalk: [#undefined]].
- 
- 	mask := 1 << (imms + 1) - 1.
- 	^immr = 0
- 		ifTrue: [mask]
- 		ifFalse: [(mask << (64 - immr) bitAnd: 1 << 64 - 1) + (mask >> immr)]!

Item was added:
+ ----- Method: CogARMv8Compiler>>decodeN:imms:immr: (in category 'generate machine code - support') -----
+ decodeN: n imms: imms immr: immr
+ 	"See aarch64/instrs/integer/bitmasks/DecodeBitMasks J1-7389."
+ 	<returnTypeC: #usqInt>
+ 	| bits immediate mask rotation width |
+ 	<var: 'mask' type: #usqInt>
+ 	self assert: ((n between: 0 and: 1) and: [(imms between: 0 and: 63) and: [immr between: 0 and: 63]]).
+ 	"For logical immediates an all-ones value of S is reserved since it would generate a useless all-ones result (many times)"
+ 	imms = 63 ifTrue:
+ 		[^self cCode: [0] inSmalltalk: [#undefined]].
+ 
+ 	n = 1
+ 		ifTrue:
+ 			[width := 64.
+ 			 mask := 16rffffffffffffffff.
+ 			 bits := imms.
+ 			 rotation := immr]
+ 		ifFalse:
+ 			[imms < 16r20
+ 				ifTrue: [width := 32. bits := imms] ifFalse: [
+ 			 imms < 16r30
+ 				ifTrue: [width := 16. bits := imms bitAnd: 16rF] ifFalse: [
+ 			 imms < 16r38
+ 				ifTrue: [width := 8. bits := imms bitAnd: 16r7] ifFalse: [
+ 			 imms < 16r3C
+ 				ifTrue: [width := 4. bits := imms bitAnd: 16r3] ifFalse: [
+ 			 imms < 16r3E
+ 				ifTrue: [width := 2. bits := imms bitAnd: 16r1]
+ 				ifFalse: [self error: 'invalid logical immediate']]]]].
+ 			mask := 1 << width - 1.
+ 			rotation := immr bitAnd: width - 1].
+ 
+ 	width - 1 = bits ifTrue:
+ 		[^0].
+ 
+ 	immediate := (1 << (bits + 1)) - 1.
+ 
+ 	rotation > 0 ifTrue:
+ 		[immediate := immediate << (width - rotation) - 1].
+ 
+ 	(width between: 2 and: 32) ifTrue:
+ 		[immediate := (immediate bitShift: width) bitOr: immediate].
+ 
+ 	^immediate!

Item was changed:
  ----- Method: CogARMv8Compiler>>isImmNImmSImmREncodableBitmask:ifTrue:ifFalse: (in category 'generate machine code - support') -----
  isImmNImmSImmREncodableBitmask: constant ifTrue: trinaryBlock "[:n :imms :immr|...]" ifFalse: nullaryBlock
  	"See DecodeBitMasks J1-7389.
  	 See https://dinfuehr.github.io/blog/encoding-of-immediate-values-on-aarch64/
  	 This method is adapted from The LLVM Compiler Infrastructure, AArch64AddressingModes.h processLogicalImmediate"
  	<inline: #always>
  	| imm size mask numLeadingOnes numTrailingOnes immr n nImms rotateCount |
  	<var: 'mask' type: #usqInt>
  	<var: 'nImms' type: #usqInt>
  	(constant between: -1 and: 0) ifTrue:
  		[^nullaryBlock value].
  	imm := self cCode: [constant] inSmalltalk: [constant signedIntToLong64].
   
  	"First, determine the element size."
  	size := 32.
  	[mask := 1 << size - 1.
  	 (imm bitAnd: mask) ~= (imm >> size)
  			ifTrue: [size := size * 2. false]
  			ifFalse: [size > 2]]
  		whileTrue: [size := size / 2].
  
  	"Second, determine the rotation to make the element be: 0^m 1^n."
  	mask := 1 << 64 - 1 >> (64 - size).
  	imm := imm bitAnd: mask.
  
  	(self isShiftedMask: imm)
  		ifTrue:
  			[rotateCount := self countTrailingZeros: imm.
  			 numTrailingOnes := self countTrailingOnes: imm >> rotateCount]
  		ifFalse:
  			[imm := imm bitOr: mask bitInvert64.
  			 (self isShiftedMask: imm) ifFalse:
  				[^nullaryBlock value].
  			 numLeadingOnes := self countLeadingOnes: imm.
  			 rotateCount := 64 - numLeadingOnes.
  			 numTrailingOnes := numLeadingOnes + (self countTrailingOnes: imm) - (64 - size)].
  
  	"Encode in Immr the number of RORs it would take to get *from* 0^m 1^n
  	 to our target value, where I is the number of RORs to go the opposite direction."
   
  	self assert: size > rotateCount. "rotateCount should be smaller than element size"
  	immr := size - rotateCount bitAnd: size - 1.
  
  	"If size has a 1 in the n'th bit, create a value that has zeroes in bits [0, n] and ones above that."
+ 	nImms := self cCode: [(size - 1) bitInvert64 << 1] inSmalltalk: [(size - 1) bitInvert64 << 1 bitAnd: 16rFFFFFFFFFFFFFFFF].
- 	nImms := (size - 1) bitInvert64 << 1.
  
  	"Or the CTO value into the low bits, which must be below the Nth bit mentioned above."
+ 	nImms := nImms bitOr: numTrailingOnes - 1.
- 	nImms := nImms bitOr:  numTrailingOnes - 1.
  
  	"Extract the seventh bit and toggle it to create the N field."
  	n := ((nImms >> 6) bitAnd: 1) bitXor: 1.
  
  	nImms := nImms bitAnd: 16r3F.
  
+ 	self assert: (self decodeN: n imms: nImms immr: immr) = constant signedIntToLong64.
- 	self assert: (self decode64Imms: nImms immr: immr) = constant signedIntToLong64.
  
  	^trinaryBlock
  		value: n
  		value: nImms
  		value: immr
  !

Item was changed:
  ----- Method: Spur32BitMMLECoSimulator>>coInterpreter:cogit: (in category 'initialization') -----
  coInterpreter: aCoInterpreter cogit: aCogit
+ 
  	coInterpreter := aCoInterpreter.
  	cogit := aCogit.
+ 	marker coInterpreter: aCoInterpreter.
  	scavenger coInterpreter: aCoInterpreter.
+ 	compactor coInterpreter: aCoInterpreter.
+ 	gc coInterpreter: aCoInterpreter
+ 	!
- 	compactor coInterpreter: aCoInterpreter!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>coInterpreter: (in category 'initialization') -----
+ coInterpreter: aVMSimulator
+ 	<doNotGenerate>
+ 	super coInterpreter: aVMSimulator.
+ 	sweeper coInterpreter: aVMSimulator.
+ 	compactor coInterpreter: aVMSimulator!

Item was changed:
  ----- Method: StackInterpreter>>objectMemory: (in category 'initialization') -----
  objectMemory: anObjectMemory
  	<doNotGenerate>
  	objectMemory ifNotNil: [self halt].
+ 	objectMemory := anObjectMemory.
+ 	anObjectMemory coInterpreter: self!
- 	objectMemory := anObjectMemory!

Item was changed:
  ----- Method: VMClass class>>openSpurMultiWindowBrowser (in category 'utilities') -----
  openSpurMultiWindowBrowser
  	"Answer a new multi-window browser on the Spur classes, the Cog StackInterpreter classes, and the support classes"
  	"self openSpurMultiWindowBrowser"
  	| b |
  	b := Browser open.
  	#(	SpurMemoryManager Spur32BitMemoryManager Spur64BitMemoryManager
  		SpurGenerationScavenger SpurSegmentManager
  		Spur32BitMMLESimulator SpurGenerationScavengerSimulator
+ 		SpurMarker SpurAllAtOnceMarker SpurIncrementalMarker
+ 		SpurCompactor SpurPlanningCompactor SpurHybridCompactor SpurIncrementalCompactor
+ 		SpurIncrementalSweepAndCompact
  		InterpreterPrimitives StackInterpreter StackInterpreterPrimitives
  		VMStructType VMMaker CCodeGenerator TMethod)
  		do: [:className|
  			(Smalltalk classNamed: className) ifNotNil:
  				[:class| b selectCategoryForClass: class; selectClass: class]]
  		separatedBy:
  			[b multiWindowState addNewWindow].
  	b multiWindowState selectWindowIndex: 1!



More information about the Vm-dev mailing list