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

commits at source.squeak.org commits at source.squeak.org
Sun Apr 24 11:39:28 UTC 2016


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

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

Name: VMMaker.oscog-nice.1837
Author: nice
Time: 24 April 2016, 1:37:15.458 pm
UUID: 7c7bd77c-ff12-4085-bbe1-9ba0962b5709
Ancestors: VMMaker.oscog-eem.1834

Extend type inference capabilities from the AST.

Use minimum generality for generated integer constants:
- use int if variable fits in int
- else unsigned int
- else long long (long would be enough for 64bits versions, but long long works for both 32 and 64)
- else unsigned long long
This is to avoid spurious unsigned promotion due to improved type inference.

Protect #pathTo:followWeak: which can currently only work with a signed int, from possibly future spurious unsigned inference (I didn't bissect at which stage exactly this happens, but it happened).

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

Item was changed:
  ----- Method: CCodeGenerator>>cLiteralForInteger:hex: (in category 'C code generator') -----
  cLiteralForInteger: anInteger hex: aBoolean
+ 	"Answer the string for generating a literal integer.
+ 	Use hexadecimal notation as prescribed by aBoolean.
+ 	Use long long suffix (LL) if the integer does not fit on 32 bits.
+ 	Use unsigned suffix (U) if the integer does not fit on a signed integer (resp. long long).
+ 	Correctly generate INT_MIN and LONG_LONG_MIN.
+ 	Indeed -0x8000000 is parsed as - (0x8000000) by C Compiler.
+ 	0x8000000 does not fit on a signed int, it is interpreted as unsigned.
+ 	That makes INT_MIN unsigned which is badly broken..."
+ 	
  	| printString |
  	printString := aBoolean
  		ifTrue: [anInteger positive
  			ifTrue: ['0x' , (anInteger printStringBase: 16)]
  			ifFalse: ['-0x' , (anInteger negated printStringBase: 16)]]
  		ifFalse: [anInteger printString].
+ 	^anInteger positive
+ 		ifTrue: [anInteger > 16r7FFFFFFF "INT_MAX"
+ 			ifTrue: [anInteger > 16rFFFFFFFF "UINT_MAX"
+ 				ifTrue: [anInteger > 16r7FFFFFFFFFFFFFFF "LONG_LONG_MAX"
+ 					ifTrue: [printString , 'ULL']
+ 					ifFalse: [printString , 'LL']]
+ 				ifFalse: [printString , 'U']]
+ 			ifFalse: [printString]]
+ 		ifFalse: [anInteger < -16r8000000
+ 			ifTrue: [anInteger = -16r800000000000000	"LONG_LONG_MIN"
+ 				ifTrue: ['(-0x7FFFFFFFFFFFFFFFLL-1)']
+ 				ifFalse: [printString , 'LL']]
+ 			ifFalse: [anInteger = -16r8000000	"INT_MIN"
+ 				ifTrue: ['(-0x7FFFFFFF-1)']
+ 				ifFalse: [printString]]]!
- 	^anInteger > 16rFFFFFFFF
- 			ifTrue: [printString, ObjectMemory unsignedLongLongSuffix]
- 			ifFalse: [anInteger < 16r7FFFFFFF
- 					ifTrue: [printString]
- 					ifFalse: [printString, ObjectMemory unsignedIntegerSuffix]]!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>pathTo:using:followWeak: (in category 'object access primitives') -----
  pathTo: goal using: stack followWeak: followWeak
  	"Trace objects and frames from the root, marking visited objects, pushing the current path on stack, until goal is found.
  	 If found, unmark, leaving path in stack, and answer 0.  Otherwise answer an error:
  		PrimErrBadArgument if stack is not an Array
  		PrimErrBadIndex if search overflows stack
  		PrimErrNotFound if goal cannot be found"
  	| current index next stackSize stackp freeStartAtStart |
+ 	<var: #index type: #sqInt> "Force the sign because typeInference does not seem to work"
  	(objectMemory isArray: stack) ifFalse:
  		[^PrimErrBadArgument].
  	self assert: objectMemory allObjectsUnmarked.
  	freeStartAtStart := objectMemory freeStart. "check no allocations during search"
  	objectMemory beRootIfOld: stack. "so no store checks are necessary on stack"
  	stackSize := objectMemory lengthOf: stack.
  	objectMemory mark: stack.
  	"no need. the current context is not reachable from the active process (suspendedContext is nil)"
  	"objectMemory mark: self activeProcess."
  	current := objectMemory specialObjectsOop.
  	objectMemory mark: current.
  	index := objectMemory lengthOf: current.
  	stackp := 0.
  	[[(index := index - 1) >= -1] whileTrue:
  		[(stackPages couldBeFramePointer: current)
  			ifTrue:
  				[next := index >= 0
  							ifTrue: [self field: index ofFrame: (self cCoerceSimple: current to: #'char *')]
  							ifFalse: [objectMemory nilObject]]
  			ifFalse:
  				[index >= 0
  					ifTrue:
  						[next := (objectMemory isContextNonImm: current)
  									ifTrue: [self fieldOrSenderFP: index ofContext: current]
  									ifFalse: [objectMemory fetchPointer: index ofObject: current]]
  					ifFalse:
  						[next := objectMemory fetchClassOfNonImm: current]].
  		 (stackPages couldBeFramePointer: next)
  			ifTrue: [self assert: (self isFrame: (self cCoerceSimple: next to: #'char *')
  										onPage: (stackPages stackPageFor: (self cCoerceSimple: next to: #'char *')))]
  			ifFalse:
  				[next >= heapBase ifTrue: "exclude Cog methods"
  					[self assert: (self checkOkayOop: next)]].
  		 next = goal ifTrue:
  			[self assert: freeStartAtStart = objectMemory freeStart.
  			 self unmarkAfterPathTo.
  			 objectMemory storePointer: stackp ofObject: stack withValue: current.
  			 self pruneStack: stack stackp: stackp.
  			 ^0].
  		 ((objectMemory isNonIntegerObject: next)
  		  and: [(stackPages couldBeFramePointer: next)
  				ifTrue: [(self frameIsMarked: next) not]
  				ifFalse:
  					[next >= heapBase "exclude Cog methods"
  					  and: [(objectMemory isMarked: next) not
  					  and: [((objectMemory isPointers: next) or: [objectMemory isCompiledMethod: next])
  					  and: [followWeak or: [(objectMemory isWeakNonImm: next) not]]]]]])
  			ifTrue:
  				[stackp + 2 > stackSize ifTrue:
  					[self assert: freeStartAtStart = objectMemory freeStart.
  					 self unmarkAfterPathTo.
  					 objectMemory nilFieldsOf: stack.
  					 ^PrimErrBadIndex]. "PrimErrNoMemory ?"
  				 objectMemory
  					storePointerUnchecked: stackp ofObject: stack withValue: current;
  					storePointerUnchecked: stackp + 1 ofObject: stack withValue: (objectMemory integerObjectOf: index).
  				 stackp := stackp + 2.
  				 (stackPages couldBeFramePointer: (self cCoerceSimple: next to: #'char *'))
  					ifTrue:
  						[self markFrame: next.
  						index := self fieldsInFrame: (self cCoerceSimple: next to: #'char *')]
  					ifFalse:
  						[objectMemory mark: next.
  						 (objectMemory isCompiledMethod: next)
  							ifTrue: [index := (objectMemory literalCountOf: next) + LiteralStart]
  							ifFalse: [index := objectMemory lengthOf: next]].
  				 current := next]].
  		 current = objectMemory specialObjectsOop ifTrue:
  			[self assert: freeStartAtStart = objectMemory freeStart.
  			 self unmarkAfterPathTo.
  			 objectMemory nilFieldsOf: stack.
  			^PrimErrNotFound].
  		 index := objectMemory integerValueOf: (objectMemory fetchPointer: stackp - 1 ofObject: stack).
  		 current := objectMemory fetchPointer: stackp - 2 ofObject: stack.
  		 stackp := stackp - 2] repeat!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>pathTo:using:followWeak: (in category 'object access primitives') -----
  pathTo: goal using: stack followWeak: followWeak
  	"Trace objects and frames from the root, marking visited objects, pushing the current path on stack, until goal is found.
  	 If found, unmark, leaving path in stack, and answer 0.  Otherwise answer an error:
  		PrimErrBadArgument if stack is not an Array
  		PrimErrBadIndex if search overflows stack
  		PrimErrNotFound if goal cannot be found"
+ 	<var: #index type: #sqInt> "beware, must be signed"
  	| current index next stackSize stackp freeStartAtStart |
  	(objectMemory isArray: stack) ifFalse:
  		[^PrimErrBadArgument].
  	self assert: objectMemory allObjectsUnmarked.
  	freeStartAtStart := objectMemory freeStart. "check no allocations during search"
  	objectMemory beRootIfOld: stack. "so no store checks are necessary on stack"
  	stackSize := objectMemory lengthOf: stack.
  	objectMemory mark: stack.
  	"no need. the current context is not reachable from the active process (suspendedContext is nil)"
  	"objectMemory mark: self activeProcess."
  	current := objectMemory specialObjectsOop.
  	objectMemory mark: current.
  	index := objectMemory lengthOf: current.
  	stackp := 0.
  	[[(index := index - 1) >= -1] whileTrue:
  		[(stackPages couldBeFramePointer: current)
  			ifTrue:
  				[next := index >= 0
  							ifTrue: [self field: index ofFrame: (self cCoerceSimple: current to: #'char *')]
  							ifFalse: [objectMemory nilObject]]
  			ifFalse:
  				[index >= 0
  					ifTrue:
  						[next := (objectMemory isContextNonImm: current)
  									ifTrue: [self fieldOrSenderFP: index ofContext: current]
  									ifFalse: [objectMemory fetchPointer: index ofObject: current]]
  					ifFalse:
  						[next := objectMemory fetchClassOfNonImm: current]].
  		 (stackPages couldBeFramePointer: next)
  			ifTrue: [self assert: (self isFrame: (self cCoerceSimple: next to: #'char *')
  									onPage: (stackPages stackPageFor: (self cCoerceSimple: next to: #'char *')))]
  			ifFalse: [self assert: (self checkOkayOop: next)].
  		 next = goal ifTrue:
  			[self assert: freeStartAtStart = objectMemory freeStart.
  			 self unmarkAfterPathTo.
  			 objectMemory storePointer: stackp ofObject: stack withValue: current.
  			 self pruneStack: stack stackp: stackp.
  			 ^0].
  		 ((objectMemory isNonIntegerObject: next)
  		  and: [(stackPages couldBeFramePointer: next)
  				ifTrue: [(self frameIsMarked: next) not]
  				ifFalse:
  					[(objectMemory isMarked: next) not
  					  and: [((objectMemory isPointers: next) or: [objectMemory isCompiledMethod: next])
  					  and: [followWeak or: [(objectMemory isWeakNonImm: next) not]]]]])
  			ifTrue:
  				[stackp + 2 > stackSize ifTrue:
  					[self assert: freeStartAtStart = objectMemory freeStart.
  					 self unmarkAfterPathTo.
  					 objectMemory nilFieldsOf: stack.
  					 ^PrimErrBadIndex]. "PrimErrNoMemory ?"
  				 objectMemory
  					storePointerUnchecked: stackp ofObject: stack withValue: current;
  					storePointerUnchecked: stackp + 1 ofObject: stack withValue: (objectMemory integerObjectOf: index).
  				 stackp := stackp + 2.
  				 (stackPages couldBeFramePointer: (self cCoerceSimple: next to: #'char *'))
  					ifTrue:
  						[self markFrame: next.
  						index := self fieldsInFrame: (self cCoerceSimple: next to: #'char *')]
  					ifFalse:
  						[objectMemory mark: next.
  						 (objectMemory isCompiledMethod: next)
  							ifTrue: [index := (objectMemory literalCountOf: next) + LiteralStart]
  							ifFalse: [index := objectMemory lengthOf: next]].
  				 current := next]].
  		 current = objectMemory specialObjectsOop ifTrue:
  			[self assert: freeStartAtStart = objectMemory freeStart.
  			 self unmarkAfterPathTo.
  			 objectMemory nilFieldsOf: stack.
  			^PrimErrNotFound].
  		 index := objectMemory integerValueOf: (objectMemory fetchPointer: stackp - 1 ofObject: stack).
  		 current := objectMemory fetchPointer: stackp - 2 ofObject: stack.
  		 stackp := stackp - 2] repeat!

Item was added:
+ ----- Method: TAssignmentNode>>typeOrNilFrom:in: (in category 'type inference') -----
+ typeOrNilFrom: aCodeGenerator in: aTMethod
+ 	"This is the default type in case of doubt"
+ 	^variable typeOrNilFrom: aCodeGenerator in: aTMethod!

Item was added:
+ ----- Method: TConstantNode>>typeOrNilFrom:in: (in category 'type inference') -----
+ typeOrNilFrom: aCodeGenerator in: aTMethod
+ 	"For integers, answer int unless the value does not fit into a 32bits signed int.
+ 	In that case, answer the shortest architecture independant integer type that could hold the constant.
+ 	This method must be consistent with CCodeGenerator>>cLiteralFor:"
+ 	| hb |
+ 	value isInteger
+ 		ifTrue:
+ 			[value positive
+ 				ifTrue:
+ 					[hb := value highBit.
+ 					hb < 32 ifTrue: [^#int].
+ 					hb = 32 ifTrue: [^#'unsigned int'].
+ 					hb = 64 ifTrue: [^#'unsigned long long'].
+ 					^#'long long']
+ 				ifFalse:
+ 					[hb := value bitInvert highBit.
+ 					hb < 32 ifTrue: [^#int].
+ 					^#'long long']].
+ 	value isFloat ifTrue: [^#double].
+ 	(#(nil true false) includes: value) ifTrue: [^#int].
+ 	^nil!

Item was added:
+ ----- Method: TInlineNode>>typeOrNilFrom:in: (in category 'type inference') -----
+ typeOrNilFrom: aCodeGenerator in: aTMethod
+ 	^method returnType!

Item was added:
+ ----- Method: TReturnNode>>typeOrNilFrom:in: (in category 'type inference') -----
+ typeOrNilFrom: aCodeGenerator in: aTMethod
+ 	^expression typeOrNilFrom: aCodeGenerator in: aTMethod!

Item was added:
+ ----- Method: TStmtListNode>>typeOrNilFrom:in: (in category 'type inference') -----
+ typeOrNilFrom: aCodeGenerator in: aTMethod
+ 	statements isEmpty ifTrue: [^nil].
+ 	^statements last typeOrNilFrom: aCodeGenerator in: aTMethod!



More information about the Vm-dev mailing list