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

commits at source.squeak.org commits at source.squeak.org
Sun Nov 6 13:28:48 UTC 2016


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

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

Name: VMMaker.oscog-nice.1981
Author: nice
Time: 6 November 2016, 2:27:26.75858 pm
UUID: b8675b17-30ec-479d-977d-bc2c6c9aa941
Ancestors: VMMaker.oscog-nice.1980

reportMinimumUnusedHeadroom with %lld format. That's superfluous in 32 bits, but does not hurt, and it works correctly in LLP64 contrarily to %ld. The alternative of using PRIdSQPTR macro would be overkill here.

Review usage of long/unsigned long type hints that should better be replaced with sqInt/usqInt because the intention is to handle a oop, not a target machine address.

Same with senders of asUnsignedLong, some should be replaced with asUnsignedInteger (that is a cast to usqInt), typically after longAt: because longAt: returns an oop (a sqInt).

Let #'sqIntptr_t' #'usqIntptr_t' types be "isFunctional" to allow inlining in C code generator.

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

Item was changed:
  ----- Method: CoInterpreter>>reportMinimumUnusedHeadroom (in category 'debug support') -----
  reportMinimumUnusedHeadroom
  	"Report the stack page size and minimum unused headroom to stdout."
  	<api>
  	self cCode:
+ 			[self pri: 'stack page bytes %lld available headroom %lld minimum unused headroom %lld\n'
+ 				n: self stackPageByteSize asUnsignedLongLong
+ 				t: (self stackPageByteSize - self stackLimitBytes - self stackLimitOffset) asUnsignedLongLong
+ 				f: self minimumUnusedHeadroom asUnsignedLongLong]
- 			[self pri: 'stack page bytes %ld available headroom %ld minimum unused headroom %ld\n'
- 				n: self stackPageByteSize asLong
- 				t: (self stackPageByteSize - self stackLimitBytes - self stackLimitOffset) asLong
- 				f: self minimumUnusedHeadroom asLong]
  		inSmalltalk:
  			["CogVMSimulator new initStackPagesForTests reportMinimumUnusedHeadroom"
  			 self print: 'stack page bytes '; printNum: self stackPageByteSize;
  				print: ' available headroom '; printNum: self stackPageByteSize - self stackLimitBytes - self stackLimitOffset;
  				print: ' minimum unused headroom '; printNum: self minimumUnusedHeadroom;
  				cr]!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeFill32 (in category 'generate machine code') -----
  concretizeFill32
  	<inline: true>
  	| word |
+ 	<var: #word type: #'usqIntptr_t'>
- 	<var: #word type: #'unsigned long'>
  	word := operands at: 0.
  	machineCode at: 0 put: (word bitAnd: 16rFF).
  	machineCode at: 1 put: (word >> 8 bitAnd: 16rFF).
  	machineCode at: 2 put: (word >> 16 bitAnd: 16rFF).
  	machineCode at: 3 put: (word >> 24 bitAnd: 16rFF).
  	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogIA32Compiler>>isQuick: (in category 'testing') -----
  isQuick: operand
+ 	<var: #operand type: #'usqIntptr_t'>
- 	<var: #operand type: #'unsigned long'>
  	^operand signedIntFromLong between: -128 and: 127!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeFill32 (in category 'generate machine code') -----
  concretizeFill32
  	<inline: true>
  	| word |
+ 	<var: #word type: #'usqIntptr_t'>
- 	<var: #word type: #'unsigned long'>
  	word := operands at: 0.
  	machineCode at: 0 put: (word bitAnd: 16rFF).
  	machineCode at: 1 put: (word >> 8 bitAnd: 16rFF).
  	machineCode at: 2 put: (word >> 16 bitAnd: 16rFF).
  	machineCode at: 3 put: (word >> 24 bitAnd: 16rFF).
  	^machineCodeSize := 4!

Item was changed:
  ----- Method: InterpreterPrimitives>>asUnsigned: (in category 'primitive support') -----
  asUnsigned: anInteger
  	<inline: true>
+ 	^self cCode: [anInteger asUnsignedInteger] inSmalltalk: [anInteger bitAnd: objectMemory maxCInteger]!
- 	^self cCode: [anInteger asUnsignedLong] inSmalltalk: [anInteger bitAnd: objectMemory maxCInteger]!

Item was changed:
  ----- Method: LargeIntegersPlugin>>normalizeNegative: (in category 'oop functions') -----
  normalizeNegative: aLargeNegativeInteger 
  	"Check for leading zeroes and return shortened copy if so."
  	"First establish len = significant length."
  	| val val2 sLen digitLen byteLen oldByteLen minVal |
+ 	<var: #val type: #usqInt>
+ 	<var: #val2 type: #usqInt>
+ 	<var: #minVal type: #usqInt>
- 	<var: #val type: #'unsigned long'>
- 	<var: #val2 type: #'unsigned long'>
- 	<var: #minVal type: #'unsigned long'>
  	digitLen := self digitSizeOfLargeInt: aLargeNegativeInteger.
  	[digitLen ~= 0 and: [(self unsafeDigitOfLargeInt: aLargeNegativeInteger at: digitLen) = 0]]
  		whileTrue: [digitLen := digitLen - 1].
  	digitLen = 0 ifTrue: [^ 0 asOop: SmallInteger].
  	"Now check if in SmallInteger range"
  	val := self unsafeDigitOfLargeInt: aLargeNegativeInteger at: digitLen.
  	sLen := interpreterProxy minSmallInteger < -16r40000000
  				ifTrue: [2]
  				ifFalse: [1]. "SmallInteger minVal digitLength"
  	digitLen <= sLen
  		ifTrue: 
  			[minVal := 0 - interpreterProxy minSmallInteger.
  			val2 := val.
  			digitLen > 1 ifTrue: [val2 := val2 << 32 + (self unsafeDigitOfLargeInt: aLargeNegativeInteger at: 1)].
  			val2 <= minVal
  				ifTrue: [^0 -  val2 asOop: SmallInteger]].
  	"Return self, or a shortened copy"
  	byteLen := digitLen * 4.
  	val <= 16rFFFF
  		ifTrue: [byteLen := byteLen - 2]
  		ifFalse: [val := val >> 16].
  	val <= 16rFF
  		ifTrue: [byteLen := byteLen - 1].
  	oldByteLen := self byteSizeOfLargeInt: aLargeNegativeInteger.
  	byteLen < oldByteLen
  		ifTrue: [^ self largeInt: aLargeNegativeInteger growTo: byteLen]
  		ifFalse: [^ aLargeNegativeInteger]!

Item was changed:
  ----- Method: LargeIntegersPlugin>>normalizePositive: (in category 'oop functions') -----
  normalizePositive: aLargePositiveInteger 
  	"Check for leading zeroes and return shortened copy if so."
  	"First establish len = significant length."
  	| val val2 sLen digitLen byteLen oldByteLen maxVal |
+ 	<var: #val type: #usqInt>
+ 	<var: #val2 type: #usqInt>
+ 	<var: #maxVal type: #usqInt>
- 	<var: #val type: #'unsigned long'>
- 	<var: #val2 type: #'unsigned long'>
- 	<var: #maxVal type: #'unsigned long'>
  	digitLen := self digitSizeOfLargeInt: aLargePositiveInteger.
  	[digitLen ~= 0 and: [(self unsafeDigitOfLargeInt: aLargePositiveInteger at: digitLen) = 0]]
  		whileTrue: [digitLen := digitLen - 1].
  	digitLen = 0 ifTrue: [^ 0 asOop: SmallInteger].
  	"Now check if in SmallInteger range"
  	val := self unsafeDigitOfLargeInt: aLargePositiveInteger at: digitLen.
  	sLen := interpreterProxy maxSmallInteger > 16r3FFFFFFF
  				ifTrue: [2]
  				ifFalse: [1]. "SmallInteger maxVal digitLength"
  	digitLen <= sLen
  		ifTrue: 
  			[maxVal := interpreterProxy maxSmallInteger.
  			val2 := val.
  			digitLen > 1 ifTrue: [val2 := val2 << 32 + (self unsafeDigitOfLargeInt: aLargePositiveInteger at: 1)].
  			val2 <= maxVal
  				ifTrue: [^val2 asOop: SmallInteger]].
  	"Return self, or a shortened copy"
  	byteLen := digitLen * 4.
  	val <= 16rFFFF
  		ifTrue: [byteLen := byteLen - 2]
  		ifFalse: [val := val >> 16].
  	val <= 16rFF
  		ifTrue: [byteLen := byteLen - 1].
  	oldByteLen := self byteSizeOfLargeInt: aLargePositiveInteger.
  	byteLen < oldByteLen
  		ifTrue: [^ self largeInt: aLargePositiveInteger growTo: byteLen]
  		ifFalse: [^ aLargePositiveInteger]!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>oldRawNumSlotsOf: (in category 'object access') -----
  oldRawNumSlotsOf: objOop
  	<returnTypeC: #usqInt>
  	<inline: true>
+ 	^(self longAt: objOop) asUnsignedInteger >> self numSlotsFullShift!
- 	^(self longAt: objOop) asUnsignedLong >> self numSlotsFullShift!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>rawOverflowSlotsOf: (in category 'object access') -----
  rawOverflowSlotsOf: objOop
  	<returnTypeC: #usqLong>
  	<inline: true>
  	self flag: #endianness.
  	^self
+ 		cCode: [((self longAt: objOop - self baseHeaderSize) << 8) asUnsignedInteger >> 8]
- 		cCode: [((self longAt: objOop - self baseHeaderSize) << 8) asUnsignedLong >> 8]
  		inSmalltalk: [(self longAt: objOop - self baseHeaderSize) bitAnd: 16rFFFFFFFFFFFFFF]!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>rotateRight: (in category 'interpreter access') -----
  rotateRight: anInteger
+ 	^(self cCode: [anInteger] inSmalltalk: [anInteger bitAnd: 1]) << 63 + (anInteger asUnsignedInteger >> 1)!
- 	^(self cCode: [anInteger] inSmalltalk: [anInteger bitAnd: 1]) << 63 + (anInteger asUnsignedLong >> 1)!

Item was changed:
  ----- Method: SpurMemoryManager>>byteSizeOfInstanceOf:withIndexableSlots:errInto: (in category 'indexing primitive support') -----
  byteSizeOfInstanceOf: classObj withIndexableSlots: nElements errInto: errorBlock
  	| instSpec classFormat numSlots |
  	<var: 'numSlots' type: #usqInt>
  	classFormat := self formatOfClass: classObj.
  	instSpec := self instSpecOfClassFormat: classFormat.
  	instSpec caseOf: {
  		[self arrayFormat]	->
  			[numSlots := nElements].
  		[self indexablePointersFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements].
  		[self weakArrayFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements].
  		[self sixtyFourBitIndexableFormat]	->
  			[numSlots := self bytesPerOop = 4 ifTrue: [nElements * 2] ifFalse: [nElements]].
  		[self firstLongFormat]	->
  			[numSlots := self bytesPerOop = 4 ifTrue: [nElements] ifFalse: [nElements + 1 // 2]].
  		[self firstShortFormat]	->
  			[numSlots := self bytesPerOop = 4 ifTrue: [nElements + 1 // 2] ifFalse: [nElements + 3 // 4]].
  		[self firstByteFormat]	->
  			[numSlots := nElements + (self bytesPerOop - 1) // self bytesPerOop].
  		[self firstCompiledMethodFormat]	-> "Assume nElements is derived from CompiledMethod>>basicSize."
  			[numSlots := nElements + (self bytesPerOop - 1) // self bytesPerOop] }
  		otherwise: [^errorBlock value: PrimErrBadReceiver negated]. "non-indexable"
+ 	numSlots >= (1 asUnsignedInteger << (self bytesPerOop * 8 - self logBytesPerOop)) ifTrue:
- 	numSlots >= (1 asLong << (self bytesPerOop * 8 - self logBytesPerOop)) ifTrue:
  		[^errorBlock value: (nElements < 0 ifTrue: [PrimErrBadArgument] ifFalse: [PrimErrLimitExceeded])].
  	^self objectBytesForSlots: numSlots!

Item was changed:
  ----- Method: StackInterpreter>>positive32BitIntegerFor: (in category 'primitive support') -----
  positive32BitIntegerFor: integerValue
  	"integerValue is interpreted as POSITIVE, e.g. as the result of Bitmap>at:.
  	 N.B.  Returning in each arm separately enables Slang inlining.
  	 /Don't/ return the ifTrue:ifFalse: unless Slang inlining of conditionals is fixed."
  	<inline: true>
  	<var: 'integerValue' type: #'unsigned int'>
  	objectMemory hasSixtyFourBitImmediates
  		ifTrue:
+ 			[^objectMemory integerObjectOf: (integerValue asUnsignedInteger bitAnd: 16rFFFFFFFF)]
- 			[^objectMemory integerObjectOf: (integerValue asUnsignedLong bitAnd: 16rFFFFFFFF)]
  		ifFalse:
  			[^self maybeInlinePositive32BitIntegerFor: integerValue]!

Item was changed:
  ----- Method: StackInterpreter>>putLong:toFile: (in category 'image save/restore') -----
  putLong: aLong toFile: aFile
  	"Append aLong to aFile in this platform's 'natural' byte order.  aLong is either 32 or 64 bits,
  	 depending on ObjectMemory.  (Bytes will be swapped, if necessary, when the image is read
  	 on a different platform.) Set successFlag to false if the write fails."
  
+ 	<var: #aLong type: #sqInt>
- 	<var: #aLong type: #long>
  	<var: #aFile type: #sqImageFile>
  	<inline: false>
  	| objectsWritten |
  	objectsWritten := self
+ 						cCode: [self sq: (self addressOf: aLong) Image: (self sizeof: #sqInt) File: 1 Write: aFile]
- 						cCode: [self sq: (self addressOf: aLong) Image: (self sizeof: #long) File: 1 Write: aFile]
  						inSmalltalk:
  							[| value |
  							 value := aLong.
  							 objectMemory wordSize timesRepeat:
  								[aFile nextPut: (value bitAnd: 16rFF).
  								 value := value >> 8].
  							 1].
  	self success: objectsWritten = 1!

Item was changed:
  ----- Method: TMethod>>isFunctional (in category 'inlining') -----
  isFunctional
  	"Answer true if the receiver is a functional method. That is, if it
  	 consists of a single return statement of an expression that contains
  	 no other returns.
  
  	 Answer false for methods with return types other than the simple
  	 integer types to work around bugs in the inliner."
  
  	parseTree statements isEmpty ifTrue:
  		[^false].
  	parseTree statements last isReturn ifFalse:
  		[^false].
  	parseTree statements size = 1 ifFalse:
  		[(parseTree statements size = 2
  		  and: [parseTree statements first isSend
  		  and: [parseTree statements first selector == #flag:]]) ifFalse:
  			[^false]].
  	parseTree statements last expression nodesDo:
  		[ :n | n isReturn ifTrue: [^false]].
  	^#(int #'unsigned int' #long #'unsigned long' #'long long' #'unsigned long long'
+ 		sqInt usqInt #'sqIntptr_t' #'usqIntptr_t' sqLong usqLong
- 		sqInt usqInt sqLong usqLong
  		#'int *' #'unsigned int *' #'sqInt *' #'usqInt *' #'sqLong *' #'usqLong *' #'CogMethod *' #'char *') includes: returnType!



More information about the Vm-dev mailing list