[Vm-dev] VM Maker: VMMaker.oscog-nice.2711.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Feb 16 22:35:30 UTC 2020


Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-nice.2711.mcz

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

Name: VMMaker.oscog-nice.2711
Author: nice
Time: 16 February 2020, 11:34:30.401025 pm
UUID: fe0bdc02-3e75-45d4-a2ab-c5e3dfde7c6c
Ancestors: VMMaker.oscog-eem.2710

Accelerate SmallInteger anyBitOfMagnitudeFrom:to:
Indeed, there is no need to create a large integer just for checking the bits of a small one; this can be done with a single bit mask.

Avoid some undefined behavior warnings related to integerObjectOf(-1) when compiling the VM with clang compiler option -fsanitize=undefined.

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

Item was changed:
  ----- Method: LargeIntegersPlugin>>anyBitOfLargeInt:from:to: (in category 'util') -----
  anyBitOfLargeInt: anOop from: start to: stopArg 
  	"Argument has to be a Large Integer!!"
  	"Tests for any magnitude bits in the interval from start to stopArg."
  	| magnitude stop firstDigitIx lastDigitIx firstMask lastMask |
  	<var: #digit type: #'unsigned int'>
  	<var: #firstMask type: #'unsigned int'>
  	<var: #lastMask type: #'unsigned int'>
  	<var: #firstDigitIx type: #usqInt>
  	<var: #lastDigitIx type: #usqInt>
  	<var: #ix type: #usqInt>
  	self
  		debugCode: [self msg: 'anyBitOfLargeInt: anOop from: start to: stopArg'].
- 	start < 1 | (stopArg < 1)
- 		ifTrue: [^ interpreterProxy primitiveFail].
  	magnitude := anOop.
  	stop := stopArg min: (self highBitOfLargeInt: magnitude).
  	start > stop
  		ifTrue: [^ false].
  	firstDigitIx := start - 1 // 32 + 1.
  	lastDigitIx := stop - 1 // 32 + 1.
+ 	firstMask := 16rFFFFFFFF << (start - 1 bitAnd: 31).
- 	firstMask := 16rFFFFFFFF asUnsignedLong << (start - 1 bitAnd: 31). "Note asUnsignedLong required to avoid ULLL suffix bug"
  	lastMask := 16rFFFFFFFF >> (31 - (stop - 1 bitAnd: 31)).
  	firstDigitIx = lastDigitIx
  		ifTrue: [| digit | 
  			digit := self unsafeDigitOfLargeInt: magnitude at: firstDigitIx.
  			^ (digit bitAnd: (firstMask bitAnd: lastMask))
  				~= 0].
  	((self unsafeDigitOfLargeInt: magnitude at: firstDigitIx) bitAnd: firstMask)
  			~= 0
  		ifTrue: [^ true].
  	firstDigitIx + 1
  		to: lastDigitIx - 1
  		do: [:ix | (self unsafeDigitOfLargeInt: magnitude at: ix)
  					~= 0
  				ifTrue: [^ true]].
  	((self unsafeDigitOfLargeInt: magnitude at: lastDigitIx)  bitAnd: lastMask)
  			~= 0
  		ifTrue: [^ true].
  	^ false!

Item was changed:
  ----- Method: LargeIntegersPlugin>>primAnyBitFrom:to: (in category 'Integer primitives') -----
  primAnyBitFrom: from to: to 
+ 	| integer someBitIsSet val mask |
- 	| integer large |
  	self debugCode: [self msg: 'primAnyBitFrom: from to: to'].
  	integer := self
  				primitive: 'primAnyBitFromTo'
  				parameters: #(#SmallInteger #SmallInteger )
  				receiver: #Integer.
+ 	from < 1 | (to < 1)
+ 		ifTrue: [^ interpreterProxy primitiveFail].
  	(interpreterProxy isIntegerObject: integer)
+ 		ifTrue: ["For small integers, use a single bit mask operation"
+ 			from <= to
+ 				ifTrue: 
+ 					[val := interpreterProxy integerValueOf: integer.
+ 					val < 0 ifTrue: ["Get the bits of magnitude" val := 0 - val].
+ 					mask := (1 asUnsignedInteger << (to min: (self sizeof: #usqInt)*8-1))
+ 						- (1 asUnsignedInteger << (from - 1 min: (self sizeof: #usqInt)*8-1)).
+ 					someBitIsSet := val anyMask: mask]
+ 				ifFalse: [someBitIsSet := 0]]
+ 		ifFalse: [someBitIsSet := self
+ 			anyBitOfLargeInt: integer
+ 			from: from
+ 			to: to].
+ 	^someBitIsSet asOop: Boolean!
- 		ifTrue: ["convert it to a not normalized LargeInteger"
- 			large := self createLargeFromSmallInteger: integer]
- 		ifFalse: [large := integer].
- 	^ (self
- 		anyBitOfLargeInt: large
- 		from: from
- 		to: to)
- 		asOop: Boolean!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>integerObjectOf: (in category 'immediates') -----
  integerObjectOf: value
  	"Convert the integer value, assumed to be in SmallInteger range, into a tagged SmallInteger object.
  	 In C, use a shift and an add to set the tag bit.
  	 In Smalltalk we have to work harder because the simulator works with strictly positive bit patterns."
  	<returnTypeC: #sqInt>
  	^self
+ 		cCode: [value asUnsignedInteger << 1 + 1]
- 		cCode: [value << 1 + 1]
  		inSmalltalk: [value >= 0
  						ifTrue: [value << 1 + 1]
  						ifFalse: [16r80000000 + value << 1 + 1]]!

Item was changed:
  ----- Method: VMPluginCodeGenerator>>preDeclareMacrosForFastClassCheckingOn:guardWith: (in category 'C code generator') -----
  preDeclareMacrosForFastClassCheckingOn: aStream guardWith: guardMacroOrNil
  	"These macros can be used to check for various cases of Integer types.
  	 Since they can be defined based on existing API, this is a good trade off:
  	 - avoid extending the interpreterProxy API unnecessarily
  	 - provide fast type checking"
  	
  	"Speed-up generated code for internal plugins by using macros and fixed class indices to define this well known functionality."
  	(guardMacroOrNil ifNotNil: [{'#if defined(', guardMacroOrNil, ')'. #cr}] ifNil: [#()]),
  	#(	'# define isIntegerObject(oop) ((oop) & 1)'
+ 		'# define integerObjectOf(value) ((((usqInt) value) << NumSmallIntegerTagBits) | 1)'
- 		'# define integerObjectOf(oop) (((oop) << NumSmallIntegerTagBits) | 1)'
  		'# define integerValueOf(oop) ((oop) >> NumSmallIntegerTagBits)' cr
  
  		'# if SPURVM'
  		'extern sqInt classIndexOf(sqInt);'
  	"Compact class indices are hardcoded here because there is no guarantee that the pool values at generation time
  	 are that of SPUR.. Make sure they are in sync with SpurMemoryManager class>>initializeCompactClassIndices"
  		'#	define LargeNegativeIntegerClassIndex 32'
  		'#	define LargePositiveIntegerClassIndex 33'
  		'#	if BytesPerOop == 4'
  		'#	  define isImmediate(oop) ((oop) & 3)'
  		'#	else'
  		'#	  define isImmediate(oop) ((oop) & 7)'
  		'#	endif'
  		'#	define isKindOfInteger(oop) (isImmediate(oop) ? isIntegerObject(oop) : (unsigned)(classIndexOf(oop) - LargeNegativeIntegerClassIndex) <= 1)'
  		'#	define isLargeIntegerObject(oop) (!!isImmediate(oop) && (unsigned)(classIndexOf(oop) - LargeNegativeIntegerClassIndex) <= 1)'
  		'#	define isLargeNegativeIntegerObject(oop) (!!isImmediate(oop) && classIndexOf(oop) == LargeNegativeIntegerClassIndex)'
  		'#	define isLargePositiveIntegerObject(oop) (!!isImmediate(oop) && classIndexOf(oop) == LargePositiveIntegerClassIndex)'
  		'# endif /* SPURVM */'),
  	(guardMacroOrNil ifNotNil: [{'#endif /* defined(', guardMacroOrNil, ') */'}] ifNil: [#()]),
  
  	"If the functionality has not been defined via macros, define default versions using existing plugin API"
  	#(	cr
  		'#if !!defined(isKindOfInteger)'
  		'# define isLargeNegativeIntegerObject(oop) (fetchClassOf(oop) == classLargeNegativeInteger())'
  		'# define isLargePositiveIntegerObject(oop) (fetchClassOf(oop) == classLargePositiveInteger())'
  		'# define isLargeIntegerObject(oop) (isLargeNegativeIntegerObject(oop) || isLargePositiveIntegerObject(oop))'
  		'# define isKindOfInteger(oop) (isIntegerObject(oop) || isLargeNegativeIntegerObject(oop) || isLargePositiveIntegerObject(oop))'
  		'#endif' cr) do:
  		[:element|
  		aStream cr.
  		element ~~ #cr ifTrue: [aStream nextPutAll: element]]!



More information about the Vm-dev mailing list