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

commits at source.squeak.org commits at source.squeak.org
Tue Apr 5 18:14:47 UTC 2016


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

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

Name: VMMaker.oscog-nice.1759
Author: nice
Time: 3 April 2016, 9:26:39.76 pm
UUID: 19e95bf2-b480-4986-8d9a-8345e44f3099
Ancestors: VMMaker.oscog-nice.1758

Use the new macro SQ_SWAP_4/8_BYTES_IF_BIGENDIAN to factor out proliferation of cppIf: VMBIGENDIAN.

Memory is 8 bytes aligned on Spur. When storing 32/64 bits large integers values, allways fill the eight bytes whatever the effectivily used size, rather than bothering with dissertion of size.

Prepare the same change for fetching 32/64 LargeIntegers values on SpurVM, but comment it out for now as it's unclear whether those oversize bytes are effectively zero for already created LargeIntegers.

=============== Diff against VMMaker.oscog-nice.1758 ===============

Item was added:
+ ----- Method: CCodeGenerator>>generateByteSwap32IfBigEndian:on:indent: (in category 'C translation') -----
+ generateByteSwap32IfBigEndian: msgNode on: aStream indent: level
+ 	"Generate the C code for this message onto the given stream."
+ 
+ 	aStream nextPutAll: #'SQ_SWAP_4_BYTES_IF_BIGENDIAN'.
+ 	aStream nextPut: $(.
+ 	self emitCExpression: msgNode args first on: aStream.
+ 	aStream nextPut: $)!

Item was added:
+ ----- Method: CCodeGenerator>>generateByteSwap64IfBigEndian:on:indent: (in category 'C translation') -----
+ generateByteSwap64IfBigEndian: msgNode on: aStream indent: level
+ 	"Generate the C code for this message onto the given stream."
+ 
+ 	aStream nextPutAll: #'SQ_SWAP_8_BYTES_IF_BIGENDIAN'.
+ 	aStream nextPut: $(.
+ 	self emitCExpression: msgNode args first on: aStream.
+ 	aStream nextPut: $)!

Item was changed:
  ----- Method: CCodeGenerator>>initializeCTranslationDictionary (in category 'C translation support') -----
  initializeCTranslationDictionary 
  	"Initialize the dictionary mapping message names to actions for C code generation."
  
  	| pairs |
  	
  	translationDict := Dictionary new: 200.
  	pairs := #(
  	#&				#generateAnd:on:indent:
  	#|				#generateOr:on:indent:
  	#abs			#generateAbs:on:indent:
  	#and:			#generateSequentialAnd:on:indent:
  	#or:			#generateSequentialOr:on:indent:
  	#not			#generateNot:on:indent:
  
  	#+				#generatePlus:on:indent:
  	#-				#generateMinus:on:indent:
  	#negated		#generateNegated:on:indent:
  	#*				#generateTimes:on:indent:
  	#/				#generateDivide:on:indent:
  	#//				#generateDivide:on:indent:
  	#\\				#generateModulo:on:indent:
  	#<<			#generateShiftLeft:on:indent:
  	#>>			#generateShiftRight:on:indent:
  	#>>>			#generateSignedShiftRight:on:indent:
  	#min:			#generateMin:on:indent:
  	#max:			#generateMax:on:indent:
  	#between:and:	#generateBetweenAnd:on:indent:
  
  	#bitAnd:			#generateBitAnd:on:indent:
  	#bitOr:				#generateBitOr:on:indent:
  	#bitXor:			#generateBitXor:on:indent:
  	#bitShift:			#generateBitShift:on:indent:
  	#signedBitShift:	#generateSignedBitShift:on:indent:
  	#bitInvert32		#generateBitInvert:on:indent:
  	#bitInvert64		#generateBitInvert:on:indent:
  	#bitClear:			#generateBitClear:on:indent:
  	#truncateTo:		#generateTruncateTo:on:indent:
  	#rounded			#generateRounded:on:indent:
  
  	#byteSwap32		#generateByteSwap32:on:indent:
  	#byteSwap64		#generateByteSwap64:on:indent:
+ 	#byteSwapped32IfBigEndian:	generateByteSwap32IfBigEndian:on:indent:
+ 	#byteSwapped64IfBigEndian:	generateByteSwap64IfBigEndian:on:indent:
  	
  	#<				#generateLessThan:on:indent:
  	#<=			#generateLessThanOrEqual:on:indent:
  	#=				#generateEqual:on:indent:
  	#>				#generateGreaterThan:on:indent:
  	#>=			#generateGreaterThanOrEqual:on:indent:
  	#~=			#generateNotEqual:on:indent:
  	#==			#generateEqual:on:indent:
  	#~~			#generateNotEqual:on:indent:
  	#isNil			#generateIsNil:on:indent:
  	#notNil			#generateNotNil:on:indent:
  
  	#whileTrue: 	#generateWhileTrue:on:indent:
  	#whileFalse:	#generateWhileFalse:on:indent:
  	#whileTrue 	#generateDoWhileTrue:on:indent:
  	#whileFalse		#generateDoWhileFalse:on:indent:
  	#to:do:			#generateToDo:on:indent:
  	#to:by:do:		#generateToByDo:on:indent:
  	#repeat 		#generateRepeat:on:indent:
  	#timesRepeat:	#generateTimesRepeat:on:indent:
  
  	#ifTrue:			#generateIfTrue:on:indent:
  	#ifFalse:		#generateIfFalse:on:indent:
  	#ifTrue:ifFalse:	#generateIfTrueIfFalse:on:indent:
  	#ifFalse:ifTrue:	#generateIfFalseIfTrue:on:indent:
  
  	#ifNotNil:		#generateIfNotNil:on:indent:
  	#ifNil:			#generateIfNil:on:indent:
  	#ifNotNil:ifNil:	#generateIfNotNilIfNil:on:indent:
  	#ifNil:ifNotNil:	#generateIfNilIfNotNil:on:indent:
  
  	#at:				#generateAt:on:indent:
  	#at:put:			#generateAtPut:on:indent:
  	#basicAt:		#generateAt:on:indent:
  	#basicAt:put:	#generateAtPut:on:indent:
  
  	#integerValueOf:			#generateIntegerValueOf:on:indent:
  	#integerObjectOf:			#generateIntegerObjectOf:on:indent:
  	#isIntegerObject: 			#generateIsIntegerObject:on:indent:
  	#cCode:					#generateInlineCCode:on:indent:
  	#cCode:inSmalltalk:			#generateInlineCCode:on:indent:
  	#cPreprocessorDirective:	#generateInlineCPreprocessorDirective:on:indent:
  	#cppIf:ifTrue:ifFalse:		#generateInlineCppIfElse:on:indent:
  	#cppIf:ifTrue:				#generateInlineCppIfElse:on:indent:
  	#cCoerce:to:				#generateCCoercion:on:indent:
  	#cCoerceSimple:to:			#generateCCoercion:on:indent:
  	#addressOf:				#generateAddressOf:on:indent:
  	#addressOf:put:			#generateAddressOf:on:indent:
  	#asAddress:put:			#generateAsAddress:on:indent:
  	#signedIntFromLong64		#generateSignedIntFromLong64:on:indent:
  	#signedIntFromLong		#generateSignedIntFromLong:on:indent:
  	#signedIntFromShort		#generateSignedIntFromShort:on:indent:
  	#signedIntToLong64		#generateSignedIntToLong64:on:indent:
  	#signedIntToLong			#generateSignedIntToLong:on:indent:
  	#signedIntToShort			#generateSignedIntToShort:on:indent:
  	#preIncrement				#generatePreIncrement:on:indent:
  	#preDecrement			#generatePreDecrement:on:indent:
  	#inline:						#generateInlineDirective:on:indent:
  	#asFloat					#generateAsFloat:on:indent:
  	#asInteger					#generateAsInteger:on:indent:
  	#asUnsignedInteger		#generateAsUnsignedInteger:on:indent:
  	#asLong					#generateAsLong:on:indent:
  	#asUnsignedLong			#generateAsUnsignedLong:on:indent:
  	#asUnsignedLongLong		#generateAsUnsignedLongLong:on:indent:
  	#asVoidPointer				#generateAsVoidPointer:on:indent:
  	#asSymbol					#generateAsSymbol:on:indent:
  	#flag:						#generateFlag:on:indent:
  	#anyMask:					#generateBitAnd:on:indent:
  	#allMask:					#generateAllMask:on:indent:
  	#noMask:					#generateNoMask:on:indent:
  	#raisedTo:					#generateRaisedTo:on:indent:
  	#touch:						#generateTouch:on:indent:
  
  	#bytesPerOop 				#generateBytesPerOop:on:indent:
  	#bytesPerWord 			#generateBytesPerWord:on:indent:
  	#wordSize		 			#generateBytesPerWord:on:indent:
  	#baseHeaderSize			#generateBaseHeaderSize:on:indent:
  	#minSmallInteger			#generateSmallIntegerConstant:on:indent:
  	#maxSmallInteger			#generateSmallIntegerConstant:on:indent:
  	
  	#sharedCodeNamed:inCase:		#generateSharedCodeDirective:on:indent:
  
  	#perform:							#generatePerform:on:indent:
  	#perform:with:						#generatePerform:on:indent:
  	#perform:with:with:					#generatePerform:on:indent:
  	#perform:with:with:with:				#generatePerform:on:indent:
  	#perform:with:with:with:with:		#generatePerform:on:indent:
  	#perform:with:with:with:with:with:	#generatePerform:on:indent:
  
  	#value								#generateValue:on:indent:
  	#value:								#generateValue:on:indent:
  	#value:value:						#generateValue:on:indent:
  	#value:value:value:					#generateValue:on:indent:
  	#value:value:value:value:			#generateValue:on:indent:
  
  	#deny:								#generateDeny:on:indent:
  
  	#shouldNotImplement				#generateSmalltalkMetaError:on:indent:
  	#shouldBeImplemented			#generateSmalltalkMetaError:on:indent:
  	#subclassResponsibility			#generateSmalltalkMetaError:on:indent:
  	).
  
  	1 to: pairs size by: 2 do: [:i |
  		translationDict at: (pairs at: i) put: (pairs at: i + 1)].
  
  	pairs := #(
  	#ifTrue:					#generateIfTrueAsArgument:on:indent:	
  	#ifFalse:				#generateIfFalseAsArgument:on:indent:
  	#ifTrue:ifFalse:			#generateIfTrueIfFalseAsArgument:on:indent:
  	#ifFalse:ifTrue:			#generateIfFalseIfTrueAsArgument:on:indent:
  	#ifNotNil:				#generateIfNotNilAsArgument:on:indent:	
  	#ifNil:					#generateIfNilAsArgument:on:indent:
  	#ifNotNil:ifNil:			#generateIfNotNilIfNilAsArgument:on:indent:
  	#ifNil:ifNotNil:			#generateIfNilIfNotNilAsArgument:on:indent:
  	#cCode:				#generateInlineCCodeAsArgument:on:indent:
  	#cCode:inSmalltalk:		#generateInlineCCodeAsArgument:on:indent:
  	#cppIf:ifTrue:ifFalse:	#generateInlineCppIfElseAsArgument:on:indent:
  	#cppIf:ifTrue:			#generateInlineCppIfElseAsArgument:on:indent:
  
  	#value					#generateValueAsArgument:on:indent:
  	#value:					#generateValueAsArgument:on:indent:
  	#value:value:			#generateValueAsArgument:on:indent:
  	).
  
  	asArgumentTranslationDict := Dictionary new: 8.
  	1 to: pairs size by: 2 do: [:i |
  		asArgumentTranslationDict at: (pairs at: i) put: (pairs at: i + 1)].
  !

Item was changed:
  ----- Method: InterpreterPrimitives>>magnitude64BitIntegerFor:neg: (in category 'primitive support') -----
  magnitude64BitIntegerFor: magnitude neg: isNegative
  	"Return a Large Integer object for the given integer magnitude and sign"
  	| newLargeInteger largeClass highWord sz isSmall smallVal |
  	<var: 'magnitude' type: #usqLong>
  	<var: 'highWord' type: #usqInt>
  
  	isSmall := isNegative
  				ifTrue: [magnitude <= (objectMemory maxSmallInteger + 1)]
  				ifFalse: [magnitude <= objectMemory maxSmallInteger].
  	isSmall ifTrue:
  		[smallVal := self cCoerceSimple: magnitude to: #sqInt.
  		 isNegative ifTrue: [smallVal := 0 - smallVal].
  		 ^objectMemory integerObjectOf: smallVal].
  
  	largeClass := isNegative
  					ifTrue: [objectMemory classLargeNegativeInteger]
  					ifFalse: [objectMemory classLargePositiveInteger].
  	objectMemory wordSize = 8
  		ifTrue: [sz := 8]
  		ifFalse:
  			[(highWord := magnitude >> 32) = 0
  				ifTrue: [sz := 4] 
  				ifFalse:
  					[sz := 5.
  					 (highWord := highWord >> 8) = 0 ifFalse:
  						[sz := sz + 1.
  						 (highWord := highWord >> 8) = 0 ifFalse:
  							[sz := sz + 1.
  							 (highWord := highWord >> 8) = 0 ifFalse: [sz := sz + 1]]]]].
  	newLargeInteger := objectMemory instantiateClass: largeClass indexableSize:  sz.
+ 	self cppIf: SPURVM
- 	self cppIf: VMBIGENDIAN
  		ifTrue:
+ 			["Memory is eight byte aligned in SPUR, so we are sure to have room for 64bits word whatever allocated sz"
+ 			objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped64IfBigEndian: magnitude)]
- 			[sz > 4
- 				ifTrue: [objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: magnitude byteSwap64]
- 				ifFalse: [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (magnitude byteSwap32)]]
  		ifFalse:
  			[sz > 4
+ 				ifTrue: [objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped64IfBigEndian: magnitude)]
+ 				ifFalse: [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: magnitude)]].
- 				ifTrue: [objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: magnitude]
- 				ifFalse: [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (self cCode: [magnitude] inSmalltalk: [magnitude bitAnd: 16rFFFFFFFF])]].
  
  	^newLargeInteger!

Item was changed:
  ----- Method: InterpreterPrimitives>>magnitude64BitValueOf: (in category 'primitive support') -----
  magnitude64BitValueOf: oop
  	"Convert the given object into an integer value.
  	The object may be either a positive SmallInteger or an eight-byte LargeInteger."
  	| sz value ok smallIntValue |
  	<returnTypeC: #usqLong>
  	<var: #value type: #usqLong>
  
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[smallIntValue := (objectMemory integerValueOf: oop).
  		smallIntValue < 0 ifTrue: [smallIntValue := 0 - smallIntValue].
  		^self cCoerce: smallIntValue to: #usqLong].
  
  	(objectMemory isNonIntegerImmediate: oop) ifTrue:
  		[self primitiveFail.
  		 ^0].
  
  	ok := objectMemory isClassOfNonImm: oop
  					equalTo: (objectMemory splObj: ClassLargePositiveInteger)
  					compactClassIndex: ClassLargePositiveIntegerCompactIndex.
  	ok
  		ifFalse:
  			[ok := objectMemory isClassOfNonImm: oop
  							equalTo: (objectMemory splObj: ClassLargeNegativeInteger)
  							compactClassIndex: ClassLargeNegativeIntegerCompactIndex.
  			ok ifFalse:
  				[self primitiveFail.
  				 ^0]].
  	sz := objectMemory numBytesOfBytes: oop.
  	sz > (self sizeof: #sqLong) ifTrue:
  		[self primitiveFail.
  		 ^0].
  
+ 	"self cppIf: SPURVM
- 	self cppIf: VMBIGENDIAN
  		ifTrue:
+ 			[""Memory is 8 byte aligned in Spur and oversized bytes are set to zero, so we can safely fetch 8 bytes""
+ 			value := objectMemory byteSwapped64IfBigEndian: (objectMemory fetchLong64: 0 ofObject: oop)]
- 			[sz > 4
- 				ifTrue: [value := (self cCoerceSimple: (objectMemory fetchLong64: 0 ofObject: oop) to: #usqLong) byteSwap64]
- 				ifFalse: [value := (self cCoerceSimple: (objectMemory fetchLong32: 0 ofObject: oop) to: #'unsigned int') byteSwap32].]
  		ifFalse:
+ 			["sz > 4
+ 				ifTrue: [value := objectMemory byteSwapped64IfBigEndian: (objectMemory fetchLong64: 0 ofObject: oop)]
+ 				ifFalse: [value := self cCoerceSimple: (objectMemory byteSwapped32IfBigEndian: (objectMemory fetchLong32: 0 ofObject: oop)) to: #'unsigned int']"]".
- 			[sz > 4
- 				ifTrue: [value := self cCoerceSimple: (objectMemory fetchLong64: 0 ofObject: oop) to: #usqLong]
- 				ifFalse: [value := self cCoerceSimple: (objectMemory fetchLong32: 0 ofObject: oop) to: #'unsigned int'].].
  	^value!

Item was changed:
  ----- Method: InterpreterPrimitives>>positive32BitValueOf: (in category 'primitive support') -----
  positive32BitValueOf: oop
  	"Convert the given object into an integer value.
  	The object may be either a positive SmallInteger or a four-byte LargePositiveInteger."
  	<returnTypeC: #usqInt>
  	| value ok sz |
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[value := objectMemory integerValueOf: oop.
  		 (value < 0
  		  or: [objectMemory wordSize > 4
  		  and: [self cCode: [(self cCoerceSimple: value to: #'unsigned int') ~= value]
  					inSmalltalk: [value >> 32 ~= 0]]]) ifTrue:
  			[self primitiveFail. value := 0].
  		 ^value].
  
  	(objectMemory hasSixtyFourBitImmediates
  	 or: [objectMemory isNonIntegerImmediate: oop])
  		ifTrue:
  			[self primitiveFail.
  			 ^0]
  		ifFalse:
  			[ok := objectMemory
  					isClassOfNonImm: oop
  					equalTo: (objectMemory splObj: ClassLargePositiveInteger)
  					compactClassIndex: ClassLargePositiveIntegerCompactIndex.
  			ok ifFalse:
  				[self primitiveFail.
  				 ^0].
  			sz := objectMemory numBytesOfBytes: oop.
  			sz > 4 ifTrue:
  				[self primitiveFail.
  				 ^0].
+ 			^self cCoerceSimple: (objectMemory byteSwapped32IfBigEndian: (objectMemory fetchLong32: 0 ofObject: oop)) to: #'unsigned int']!
- 			^self cppIf: VMBIGENDIAN
- 				ifTrue:
- 					[(objectMemory fetchLong32: 0 ofObject: oop) byteSwap32]
- 				ifFalse:
- 					[objectMemory fetchLong32: 0 ofObject: oop]]!

Item was changed:
  ----- Method: InterpreterPrimitives>>positive64BitValueOf: (in category 'primitive support') -----
  positive64BitValueOf: oop
  	"Convert the given object into an integer value.
  	The object may be either a positive SmallInteger or an eight-byte LargePositiveInteger."
  
  	<returnTypeC: #usqLong>
  	| sz value ok |
  	<var: #value type: #usqLong>
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[(objectMemory integerValueOf: oop) < 0 ifTrue:
  			[^self primitiveFail].
  		 ^objectMemory integerValueOf: oop].
  
  	(objectMemory isNonIntegerImmediate: oop) ifTrue:
  		[self primitiveFail.
  		 ^0].
  
  	ok := objectMemory
  			isClassOfNonImm: oop
  			equalTo: (objectMemory splObj: ClassLargePositiveInteger)
  			compactClassIndex: ClassLargePositiveIntegerCompactIndex.
  	ok ifFalse:
  		[self primitiveFail.
  		 ^0].
  	sz := objectMemory numBytesOfBytes: oop.
  	sz > (self sizeof: #sqLong) ifTrue:
  		[self primitiveFail.
  		 ^0].
  
+ 	"self cppIf: SPURVM
- 	self cppIf: VMBIGENDIAN
  		ifTrue:
+ 			[""Memory is 8 byte aligned in Spur and oversized bytes are set to zero, so we can safely fetch 8 bytes""
+ 			value := objectMemory byteSwapped64IfBigEndian: (objectMemory fetchLong64: 0 ofObject: oop)]
- 			[sz > 4
- 				ifTrue: [value := (self cCoerceSimple: (objectMemory fetchLong64: 0 ofObject: oop) to: #usqLong) byteSwap64]
- 				ifFalse: [value := (self cCoerceSimple: (objectMemory fetchLong32: 0 ofObject: oop) to: #'unsigned int') byteSwap32].]
  		ifFalse:
+ 			["sz > 4
+ 				ifTrue: [value := objectMemory byteSwapped64IfBigEndian: (objectMemory fetchLong64: 0 ofObject: oop)]
+ 				ifFalse: [value := self cCoerceSimple: (objectMemory byteSwapped32IfBigEndian: (objectMemory fetchLong32: 0 ofObject: oop)) to: #'unsigned int']"]".
- 			[sz > 4
- 				ifTrue: [value := self cCoerceSimple: (objectMemory fetchLong64: 0 ofObject: oop) to: #usqLong]
- 				ifFalse: [value := self cCoerceSimple: (objectMemory fetchLong32: 0 ofObject: oop) to: #'unsigned int'].].
  	^value!

Item was changed:
  ----- Method: InterpreterPrimitives>>positiveMachineIntegerValueOf: (in category 'primitive support') -----
  positiveMachineIntegerValueOf: oop
  	"Answer a value of an integer in address range, i.e up to the size of a machine word.
  	The object may be either a positive SmallInteger or a LargePositiveInteger of size <= word size."
  	<returnTypeC: #'unsigned long'>
  	<inline: true> "only two callers & one is primitiveNewWithArg"
  	| value bs ok |
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[value := objectMemory integerValueOf: oop.
  		 value < 0 ifTrue: [^self primitiveFail].
  		^value].
  
  	(objectMemory isNonIntegerImmediate: oop) ifTrue:
  		[self primitiveFail.
  		 ^0].
  
  	ok := objectMemory
  			isClassOfNonImm: oop
  			equalTo: (objectMemory splObj: ClassLargePositiveInteger)
  			compactClassIndex: ClassLargePositiveIntegerCompactIndex.
  	ok ifFalse:
  		[self primitiveFail.
  		 ^0].
  	bs := objectMemory numBytesOfBytes: oop.
  	bs > (self sizeof: #'unsigned long') ifTrue:
  		[self primitiveFail.
  		 ^0].
  
+ 	"self cppIf: SPURVM
+ 		ifTrue: [""Memory is 8 byte aligned in Spur and oversized bytes are set to zero, so we can safely fetch 8 bytes""
+ 			^objectMemory byteSwapped64IfBigEndian: (objectMemory fetchLong64: 0 ofObject: oop)]
+ 		ifFalse: ["((self sizeof: #'unsigned long') = 8
+ 			and: [bs > 4])
- 	((self sizeof: #'unsigned long') = 8
- 	and: [bs > 4]) ifTrue:
- 		[^self cppIf: VMBIGENDIAN
- 			ifTrue:
- 				[(objectMemory fetchLong64: 0 ofObject: oop) byteSwap64]
- 			ifFalse:
- 				[objectMemory fetchLong64: 0 ofObject: oop]]
- 		ifFalse:
- 			[^self cppIf: VMBIGENDIAN
  				ifTrue:
+ 					[^objectMemory byteSwapped64IfBigEndian: (objectMemory fetchLong64: 0 ofObject: oop)]
- 					[(self cCoerceSimple: (objectMemory fetchLong32: 0 ofObject: oop) to: #'unsigned int') byteSwap32]
  				ifFalse:
+ 					[^self cCoerceSimple: (objectMemory byteSwapped32IfBigEndian: (objectMemory fetchLong32: 0 ofObject: oop)) to: #'unsigned int']"]"!
- 					[self cCoerceSimple: (objectMemory fetchLong32: 0 ofObject: oop) to: #'unsigned int']]!

Item was changed:
  ----- Method: InterpreterPrimitives>>signed32BitValueOf: (in category 'primitive support') -----
  signed32BitValueOf: oop
  	"Convert the given object into an integer value.
  	The object may be either a positive SmallInteger or a four-byte LargeInteger."
  	| value negative ok magnitude |
  	<inline: false>
  	<returnTypeC: #int>
  	<var: #value type: #int>
  	<var: #magnitude type: #'unsigned int'>
  	<var: #value64 type: #long>
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[objectMemory wordSize = 4
  			ifTrue:
  				[^objectMemory integerValueOf: oop]
  			ifFalse: "Must fail for SmallIntegers with digitLength > 4"
  				[| value64 |
  				 value64 := objectMemory integerValueOf: oop.
  				 (self cCode: [(self cCoerceSimple: value64 to: #int) ~= value64]
  						inSmalltalk: [value64 >> 31 ~= 0 and: [value64 >> 31 ~= -1]]) ifTrue:
  					[self primitiveFail. value64 := 0].
  				 ^value64]].
  
  	(objectMemory isNonIntegerImmediate: oop) ifTrue:
  		[self primitiveFail.
  		 ^0].
  
  	ok := objectMemory
  			isClassOfNonImm: oop
  			equalTo: (objectMemory splObj: ClassLargePositiveInteger)
  			compactClassIndex: ClassLargePositiveIntegerCompactIndex.
  	ok
  		ifTrue: [negative := false]
  		ifFalse:
  			[negative := true.
  			 ok := objectMemory isClassOfNonImm: oop
  							equalTo: (objectMemory splObj: ClassLargeNegativeInteger)
  							compactClassIndex: ClassLargeNegativeIntegerCompactIndex.
  			 ok ifFalse:
  				[self primitiveFail.
  				 ^0]].
  	(objectMemory numBytesOfBytes: oop) > 4 ifTrue:
  		[^self primitiveFail].
  
+ 	magnitude := self cCoerceSimple: (objectMemory byteSwapped32IfBigEndian: (objectMemory fetchLong32: 0 ofObject: oop)) to: #'unsigned int'.
- 	magnitude := self cppIf: VMBIGENDIAN
- 				ifTrue:
- 					[(objectMemory fetchLong32: 0 ofObject: oop) asUnsignedInteger byteSwap32]
- 				ifFalse:
- 					[(objectMemory fetchLong32: 0 ofObject: oop) asUnsignedInteger].
  
  	(negative
  		ifTrue: [magnitude > 16r80000000]
  		ifFalse: [magnitude >= 16r80000000])
  			ifTrue:
  				[self primitiveFail.
  				^0].
  	negative
  		ifTrue: [value := 0 - magnitude]
  		ifFalse: [value := magnitude].
  	^value!

Item was changed:
  ----- Method: InterpreterPrimitives>>signed64BitValueOf: (in category 'primitive support') -----
  signed64BitValueOf: oop
  	"Convert the given object into an integer value.
  	 The object may be either a positive SmallInteger or a eight-byte LargeInteger."
  	| sz value negative ok magnitude |
  	<inline: false>
  	<returnTypeC: #sqLong>
  	<var: #value type: #sqLong>
  	<var: #magnitude type: #usqLong>
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[^self cCoerce: (objectMemory integerValueOf: oop) to: #sqLong].
  
  	(objectMemory isNonIntegerImmediate: oop) ifTrue:
  		[self primitiveFail.
  		 ^0].
  
  	ok := objectMemory isClassOfNonImm: oop
  					equalTo: (objectMemory splObj: ClassLargePositiveInteger)
  					compactClassIndex: ClassLargePositiveIntegerCompactIndex.
  	ok
  		ifTrue: [negative := false]
  		ifFalse:
  			[negative := true.
  			 ok := objectMemory isClassOfNonImm: oop
  							equalTo: (objectMemory splObj: ClassLargeNegativeInteger)
  							compactClassIndex: ClassLargeNegativeIntegerCompactIndex.
  			ok ifFalse:
  				[self primitiveFail.
  				 ^0]].
  	sz := objectMemory numBytesOfBytes: oop.
  	sz > (self sizeof: #sqLong) ifTrue:
  		[self primitiveFail.
  		 ^0].
  
+ 	"self cppIf: SPURVM
- 	self cppIf: VMBIGENDIAN
  		ifTrue:
+ 			[""Memory is 8 byte aligned in Spur and oversized bytes are set to zero, so we can safely fetch 8 bytes""
+ 			magnitude := objectMemory byteSwapped64IfBigEndian: (objectMemory fetchLong64: 0 ofObject: oop)]
- 			[magnitude := sz > 4
- 						ifTrue: [(objectMemory fetchLong64: 0 ofObject: oop) byteSwap64]
- 						ifFalse: [(self cCoerceSimple: (objectMemory fetchLong32: 0 ofObject: oop) to: #'unsigned int') byteSwap32]]
  		ifFalse:
+ 			["sz > 4
+ 				ifTrue: [magnitude := objectMemory byteSwapped64IfBigEndian: (objectMemory fetchLong64: 0 ofObject: oop)]
+ 				ifFalse: [magnitude := self cCoerceSimple: (objectMemory byteSwapped32IfBigEndian: (objectMemory fetchLong32: 0 ofObject: oop)) to: #'unsigned int']"]".
- 			[magnitude := sz > 4
- 						ifTrue: [objectMemory fetchLong64: 0 ofObject: oop]
- 						ifFalse: [self cCoerceSimple: (objectMemory fetchLong32: 0 ofObject: oop) to: #'unsigned int']].
  
  	(negative
  		ifTrue: [magnitude > 16r8000000000000000]
  		ifFalse: [magnitude >= 16r8000000000000000])
  			ifTrue: [self primitiveFail.
  				^0].
  	negative
  		ifTrue: [value := 0 - magnitude]
  		ifFalse: [value := magnitude].
  	^value!

Item was changed:
  ----- Method: InterpreterPrimitives>>signedMachineIntegerValueOf: (in category 'primitive support') -----
  signedMachineIntegerValueOf: oop
  	"Answer a signed value of an integer up to the size of a machine word.
  	The object may be either a positive SmallInteger or a LargeInteger of size <= word size."
  	<returnTypeC: #'long'>
  	| negative ok bs value limit magnitude |
  	<var: #value type: #long>
  	<var: #magnitude type: #usqInt>
  	<var: #limit type: #usqInt>
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[^objectMemory integerValueOf: oop].
  
  	(objectMemory isNonIntegerImmediate: oop) ifTrue:
  		[^self primitiveFail].
  
  	ok := objectMemory isClassOfNonImm: oop
  					equalTo: (objectMemory splObj: ClassLargePositiveInteger)
  					compactClassIndex: ClassLargePositiveIntegerCompactIndex.
  	ok
  		ifTrue: [negative := false]
  		ifFalse:
  			[negative := true.
  			 ok := objectMemory isClassOfNonImm: oop
  							equalTo: (objectMemory splObj: ClassLargeNegativeInteger)
  							compactClassIndex: ClassLargeNegativeIntegerCompactIndex.
  			ok ifFalse: [^self primitiveFail]].
  	bs := objectMemory numBytesOf: oop.
  	bs > (self sizeof: #'unsigned long') ifTrue:
  		[^self primitiveFail].
  
+ 	"self cppIf: SPURVM
+ 		ifTrue:
+ 			[""Memory is 8 byte aligned in Spur and oversized bytes are set to zero, so we can safely fetch 8 bytes""
+ 			magnitude := objectMemory byteSwapped64IfBigEndian: (objectMemory fetchLong64: 0 ofObject: oop)]
- 	((self sizeof: #'unsigned long') = 8
- 	and: [bs > 4]) ifTrue:
- 		[magnitude := self cppIf: VMBIGENDIAN
- 					ifTrue:
- 						[(objectMemory fetchLong64: 0 ofObject: oop) byteSwap64]
- 					ifFalse:
- 						[objectMemory fetchLong64: 0 ofObject: oop]]
  		ifFalse:
+ 			["((self sizeof: #'unsigned long') = 8
+ 			and: [bs > 4])
+ 				ifTrue:
+ 					[magnitude := objectMemory byteSwapped64IfBigEndian: (objectMemory fetchLong64: 0 ofObject: oop)]
+ 				ifFalse:
+ 					[magnitude := self cCoerceSimple: (objectMemory byteSwapped32IfBigEndian: (objectMemory fetchLong32: 0 ofObject: oop)) to: #'unsigned int']"]".
- 			[magnitude := self cppIf: VMBIGENDIAN
- 						ifTrue:
- 							[(objectMemory fetchLong32: 0 ofObject: oop) asUnsignedInteger byteSwap32]
- 						ifFalse:
- 							[(objectMemory fetchLong32: 0 ofObject: oop) asUnsignedInteger]].
  
  	limit := 1 asUnsignedInteger << ((self sizeof: #usqInt) * 8 - 1).
  	(negative
  		ifTrue: [magnitude > limit]
  		ifFalse: [magnitude >= limit])
  			ifTrue: [self primitiveFail.
  				^0].
  	negative
  		ifTrue: [value := 0 - magnitude]
  		ifFalse: [value := magnitude].
  	^value!

Item was added:
+ ----- Method: InterpreterSimulatorLSB>>byteSwapped32IfBigEndian: (in category 'memory access') -----
+ byteSwapped32IfBigEndian: w
+ 	"Accelerate, we now we are not big endian"
+ 	^w bitAnd: 16rFFFFFFFF!

Item was added:
+ ----- Method: InterpreterSimulatorLSB>>byteSwapped64IfBigEndian: (in category 'memory access') -----
+ byteSwapped64IfBigEndian: w
+ 	"Accelerate, we now we are not big endian"
+ 	^w bitAnd: 16rFFFFFFFFFFFFFFFF!

Item was added:
+ ----- Method: InterpreterSimulatorMSB>>byteSwapped32IfBigEndian: (in category 'memory access') -----
+ byteSwapped32IfBigEndian: w
+ 	"Accelerate, we now we are big endian"
+ 	^w byteSwap32!

Item was added:
+ ----- Method: InterpreterSimulatorMSB>>byteSwapped64IfBigEndian: (in category 'memory access') -----
+ byteSwapped64IfBigEndian: w
+ 	"Accelerate, we now we are big endian"
+ 	^w byteSwap64!

Item was added:
+ ----- Method: NewCoObjectMemorySimulatorLSB>>byteSwapped32IfBigEndian: (in category 'memory access') -----
+ byteSwapped32IfBigEndian: w
+ 	"Accelerate, we now we are not big endian"
+ 	^w bitAnd: 16rFFFFFFFF!

Item was added:
+ ----- Method: NewCoObjectMemorySimulatorLSB>>byteSwapped64IfBigEndian: (in category 'memory access') -----
+ byteSwapped64IfBigEndian: w
+ 	"Accelerate, we now we are not big endian"
+ 	^w bitAnd: 16rFFFFFFFFFFFFFFFF!

Item was added:
+ ----- Method: NewCoObjectMemorySimulatorMSB>>byteSwapped32IfBigEndian: (in category 'memory access') -----
+ byteSwapped32IfBigEndian: w
+ 	"Accelerate, we now we are big endian"
+ 	^w byteSwap32!

Item was added:
+ ----- Method: NewCoObjectMemorySimulatorMSB>>byteSwapped64IfBigEndian: (in category 'memory access') -----
+ byteSwapped64IfBigEndian: w
+ 	"Accelerate, we now we are big endian"
+ 	^w byteSwap64!

Item was added:
+ ----- Method: NewObjectMemorySimulatorLSB>>byteSwapped32IfBigEndian: (in category 'memory access') -----
+ byteSwapped32IfBigEndian: w
+ 	"Accelerate, we now we are not big endian"
+ 	^w bitAnd: 16rFFFFFFFF!

Item was added:
+ ----- Method: NewObjectMemorySimulatorLSB>>byteSwapped64IfBigEndian: (in category 'memory access') -----
+ byteSwapped64IfBigEndian: w
+ 	"Accelerate, we now we are not big endian"
+ 	^w bitAnd: 16rFFFFFFFFFFFFFFFF!

Item was added:
+ ----- Method: NewObjectMemorySimulatorMSB>>byteSwapped32IfBigEndian: (in category 'memory access') -----
+ byteSwapped32IfBigEndian: w
+ 	"Accelerate, we now we are big endian"
+ 	^w byteSwap32!

Item was added:
+ ----- Method: NewObjectMemorySimulatorMSB>>byteSwapped64IfBigEndian: (in category 'memory access') -----
+ byteSwapped64IfBigEndian: w
+ 	"Accelerate, we now we are big endian"
+ 	^w byteSwap64!

Item was added:
+ ----- Method: ObjectMemory>>byteSwapped32IfBigEndian: (in category 'memory access') -----
+ byteSwapped32IfBigEndian: w
+ 	"If the VM is big endian, then swap the bytes of w"
+ 	<api>
+ 	<var: 'w' type: #'unsigned int'>
+ 	<returnTypeC: #'unsigned int'>
+ 	self cppIf: VMBIGENDIAN
+ 		ifTrue: [^w byteSwap32]
+ 		ifFalse: [^w bitAnd: 16rFFFFFFFF]!

Item was added:
+ ----- Method: ObjectMemory>>byteSwapped64IfBigEndian: (in category 'memory access') -----
+ byteSwapped64IfBigEndian: w
+ 	"If the VM is big endian, then swap the bytes of w"
+ 	<api>
+ 	<var: 'w' type: #'unsigned long long'>
+ 	<returnTypeC: #'unsigned long long'>
+ 	self cppIf: VMBIGENDIAN
+ 		ifTrue: [^w byteSwap64]
+ 		ifFalse: [^w bitAnd: 16rFFFFFFFFFFFFFFFF]!

Item was changed:
  ----- Method: StackInterpreter>>maybeInlinePositive32BitIntegerFor: (in category 'primitive support') -----
  maybeInlinePositive32BitIntegerFor: integerValue
  	"N.B. will *not* cause a GC.
  	 integerValue is interpreted as POSITIVE, e.g. as the result of Bitmap>at:."
  	<notOption: #Spur64BitMemoryManager>
  	<var: 'integerValue' type: #'unsigned int'>
  	| newLargeInteger |
  	self deny: objectMemory hasSixtyFourBitImmediates.
         "force coercion because slang inliner sometimes incorrectly pass a signed int without converting to unsigned"
         (self cCode: [self cCoerceSimple: integerValue to: #'unsigned int']
  			inSmalltalk: [integerValue bitAnd: 1 << 32 - 1]) <= objectMemory maxSmallInteger ifTrue:
  		[^objectMemory integerObjectOf: integerValue].
  	newLargeInteger := objectMemory
  							eeInstantiateSmallClassIndex: ClassLargePositiveIntegerCompactIndex
  							format: (objectMemory byteFormatForNumBytes: 4)
  							numSlots: 1.
+ 	self cppIf: SPURVM
- 	self cppIf: VMBIGENDIAN
  		ifTrue:
+ 			["Memory is 8 byte aligned in Spur, make sure that oversized bytes are set to zero"
+ 			objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue).
+ 			objectMemory storeLong32: 1 ofObject: newLargeInteger withValue: 0]
+ 		ifFalse: 
+ 			[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue)].
- 			[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: integerValue byteSwap32]
- 		ifFalse:
- 			[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: integerValue].
  	^newLargeInteger!

Item was changed:
  ----- Method: StackInterpreter>>noInlineSigned32BitIntegerFor: (in category 'primitive support') -----
  noInlineSigned32BitIntegerFor: integerValue
  	"Answer a full 32 bit integer object for the given integer value."
  	<notOption: #Spur64BitMemoryManager>
  	| newLargeInteger value largeClass |
  	<inline: false>
  	(objectMemory isIntegerValue: integerValue) ifTrue:
  		[^objectMemory integerObjectOf: integerValue].
  	self deny: objectMemory hasSixtyFourBitImmediates.
  	 integerValue < 0
  		ifTrue: [largeClass := ClassLargeNegativeIntegerCompactIndex.
  				value := 0 - integerValue]
  		ifFalse: [largeClass := ClassLargePositiveIntegerCompactIndex.
  				value := integerValue].
  	newLargeInteger := objectMemory
  							eeInstantiateSmallClassIndex: largeClass
  							format: (objectMemory byteFormatForNumBytes: 4)
  							numSlots: 1.
+ 	self cppIf: SPURVM
- 	self cppIf: VMBIGENDIAN
  		ifTrue:
+ 			["Memory is 8 byte aligned in Spur, make sure that oversized bytes are set to zero"
+ 			objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: integerValue).
+ 			objectMemory storeLong32: 1 ofObject: newLargeInteger withValue: 0]
+ 		ifFalse: 
+ 			[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: value)].
- 			[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: value byteSwap32]
- 		ifFalse:
- 			[objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: value].
  	^newLargeInteger!

Item was changed:
  ----- Method: StackInterpreter>>positive64BitIntegerFor: (in category 'primitive support') -----
  positive64BitIntegerFor: integerValue
  	<api>
  	<var: 'integerValue' type: #usqLong>
  	<var: 'highWord' type: #'unsigned int'>
  	"Answer a Large Positive Integer object for the given integer value.  N.B. will *not* cause a GC."
  	| newLargeInteger highWord sz |
  	objectMemory hasSixtyFourBitImmediates
  		ifTrue:
  			[(self cCode: [integerValue] inSmalltalk: [integerValue bitAnd: 1 << 64 - 1]) <= objectMemory maxSmallInteger ifTrue:
  				[^objectMemory integerObjectOf: integerValue].
  			 sz := 8]
  		ifFalse:
  			[(highWord := integerValue >> 32) = 0 ifTrue:
  				[^self positive32BitIntegerFor: integerValue].
  			 sz := 5.
  			 (highWord := highWord >> 8) = 0 ifFalse:
  				[sz := sz + 1.
  				 (highWord := highWord >> 8) = 0 ifFalse:
  					[sz := sz + 1.
  					 (highWord := highWord >> 8) = 0 ifFalse:[sz := sz + 1]]]].
  	newLargeInteger := objectMemory
  							eeInstantiateSmallClassIndex: ClassLargePositiveIntegerCompactIndex
  							format: (objectMemory byteFormatForNumBytes: sz)
  							numSlots: 8 / objectMemory bytesPerOop.
+ 	objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped64IfBigEndian: integerValue).
- 	self cppIf: VMBIGENDIAN
- 		ifTrue:
- 			[objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: integerValue byteSwap64]
- 		ifFalse:
- 			[objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: integerValue].
  	^newLargeInteger
  !

Item was changed:
  ----- Method: StackInterpreter>>signed64BitIntegerFor: (in category 'primitive support') -----
  signed64BitIntegerFor: integerValue
  	<var: 'integerValue' type: #sqLong>
  	"Answer a Large Integer object for the given integer value.  N.B. will *not* cause a GC."
  	| newLargeInteger magnitude largeClass highWord sz |
  	<inline: false>
  	<var: 'magnitude' type: #usqLong>
  	<var: 'highWord' type: #usqInt>
  
  	integerValue < 0
  		ifTrue:[	integerValue >= objectMemory minSmallInteger ifTrue: [^objectMemory integerObjectOf: integerValue asInteger].
  				largeClass := ClassLargeNegativeIntegerCompactIndex.
  				magnitude := 0 - (self cCoerceSimple: integerValue to: #usqLong)]
  		ifFalse:[	integerValue <= objectMemory maxSmallInteger ifTrue: [^objectMemory integerObjectOf: integerValue asInteger].
  				largeClass := ClassLargePositiveIntegerCompactIndex.
  				magnitude := integerValue].
  
  	objectMemory wordSize = 8
  		ifTrue: [sz := 8]
  		ifFalse: [
  		 (highWord := magnitude >> 32) = 0 
  			ifTrue: [sz := 4] 
  			ifFalse:
  				[sz := 5.
  				 (highWord := highWord >> 8) = 0 ifFalse:
  					[sz := sz + 1.
  					 (highWord := highWord >> 8) = 0 ifFalse:
  						[sz := sz + 1.
  						 (highWord := highWord >> 8) = 0 ifFalse:
  							[sz := sz + 1]]]]].
  
  	newLargeInteger := objectMemory
  							eeInstantiateSmallClassIndex: largeClass
  							format: (objectMemory byteFormatForNumBytes: sz)
  							numSlots: sz + 3 // objectMemory bytesPerOop.
+ 	self cppIf: SPURVM
- 	self cppIf: VMBIGENDIAN
  		ifTrue:
+ 			["Memory is eight byte aligned in SPUR, so we are sure to have room for 64bits word whatever allocated sz"
+ 			objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped64IfBigEndian: magnitude)]
- 			[sz > 4
- 				ifTrue: [objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: magnitude byteSwap64]
- 				ifFalse: [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: magnitude byteSwap32]]
  		ifFalse:
  			[sz > 4
+ 				ifTrue: [objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped64IfBigEndian: magnitude)]
+ 				ifFalse: [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (objectMemory byteSwapped32IfBigEndian: magnitude)]].
- 				ifTrue: [objectMemory storeLong64: 0 ofObject: newLargeInteger withValue: magnitude]
- 				ifFalse: [objectMemory storeLong32: 0 ofObject: newLargeInteger withValue: (self cCode: [magnitude] inSmalltalk: [magnitude bitAnd: 16rFFFFFFFF])]].
  	^newLargeInteger!



More information about the Vm-dev mailing list