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

commits at source.squeak.org commits at source.squeak.org
Mon Dec 9 00:40:39 UTC 2019


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

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

Name: VMMaker.oscog-eem.2608
Author: eem
Time: 8 December 2019, 4:40:28.547125 pm
UUID: 26282794-c203-4817-b1ac-64d70706c86a
Ancestors: VMMaker.oscog-eem.2607

A64 concretizeConditionalJump:
Fix a Slang slip in decode64Imms:immr:

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

Item was added:
+ ----- Method: CogARMv8Compiler>>computeJumpTargetOffset (in category 'generate machine code') -----
+ computeJumpTargetOffset
+ 	<inline: true>
+ 	| jumpTarget |
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 	jumpTarget := self jumpTargetAddress.
+ 	^jumpTarget signedIntFromLong - address signedIntFromLong.!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeConditionalJump: (in category 'generate machine code - concretize') -----
+ concretizeConditionalJump: conditionCode
+ 	"Will get inlined into concretizeAt: switch."
+ 	"Sizing/generating jumps.
+ 		Jump targets can be to absolute addresses or other abstract instructions.
+ 		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
+ 		Otherwise instructions must have a machineCodeSize which must be kept to."
+ 	<inline: true>
+ 	| offset |
+ 	offset := self computeJumpTargetOffset.
+  	self assert: (self isInImmediateBranchRange: offset).
+ 	self machineCodeAt: 0 put: (self cond: conditionCode br: 0 offset: offset). "B offset"
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>cond:br:offset: (in category 'generate machine code - support') -----
+ cond: cond br: link offset: offset
+ 	self assert: link = 0.
+ 	^2r010101 << 26
+ 	+ ((offset bitAnd: 1 << 19 - 1) << 5)
+ 	+ cond!

Item was changed:
  ----- 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."
  	| mask |
+ 	self assert: ((imms between: 0 and: 63) and: [immr between: 0 and: 63]).
- 	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 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 countLeadingOnes countTrailingOnes immr n nImms rotateCount |
  	(constant between: -1 and: 0) ifTrue:
  		[^nullaryBlock value].
  	imm := constant.
   
  	"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.
  			 countTrailingOnes := self countTrailingOnes: imm >> rotateCount]
  		ifFalse:
  			[imm := imm bitOr: mask bitInvert64.
  			 (self isShiftedMask: imm) ifFalse:
  				[^nullaryBlock value].
  			 countLeadingOnes := self countLeadingOnes: imm.
  			 rotateCount := 64 - countLeadingOnes.
  			 countTrailingOnes := countLeadingOnes + (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 := (size - 1) bitInvert64 << 1.
  
  	"Or the CTO value into the low bits, which must be below the Nth bit mentioned above."
  	nImms := nImms bitOr:  countTrailingOnes - 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 decode64Imms: nImms immr: immr) = constant.
  
  	^trinaryBlock
  		value: n
  		value: nImms
  		value: immr
  !

Item was added:
+ ----- Method: CogARMv8Compiler>>isInImmediateBranchRange: (in category 'testing') -----
+ isInImmediateBranchRange: offset
+ 	"ARM64 calls and jumps span +/- 1 mb."
+ 	<var: #offset type: #'usqIntptr_t'>
+ 	^offset signedIntFromLong between: -16r100000 and: 16rFFFFC!



More information about the Vm-dev mailing list