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

commits at source.squeak.org commits at source.squeak.org
Sun Jul 26 03:56:05 UTC 2020


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

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

Name: VMMaker.oscog-eem.2781
Author: eem
Time: 25 July 2020, 8:55:54.857642 pm
UUID: 8de36fd4-d64f-4396-8948-140acaa8cdb4
Ancestors: VMMaker.oscog-eem.2780

Miscellaneous tweaks.
InterpreterPrimitives: fix some similation slips in canBeImmutable:. Have primitiveHighBit use cppIf:ifTrue:cppIf:ifTrue:ifFalse:.

Sionara asIEEE64BitWord; it's now in trunk.

Harmonise the two simulator primitiveExecuteMethodArgsArray's, adding a useful doit to turn off the halt.

Slang:  add some potentially useful names to namesDefinedAtCompileTime

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

Item was changed:
  ----- Method: CogVMSimulator>>primitiveExecuteMethodArgsArray (in category 'control primitives') -----
  primitiveExecuteMethodArgsArray
  	(InitializationOptions at: #haltOnExecuteMethod ifAbsent: [true]) ifTrue:
  		[self halt: thisContext selector].
+ 	^super primitiveExecuteMethodArgsArray
+ 
+ 	"InitializationOptions at: #haltOnExecuteMethod put: false"!
- 	^super primitiveExecuteMethodArgsArray!

Item was removed:
- ----- Method: Float>>asIEEE64BitWord (in category '*VMMaker-Cog tests') -----
- asIEEE64BitWord
- 	^((self basicAt: 1) bitShift: 32) + (self basicAt: 2)!

Item was changed:
  ----- Method: InterpreterPrimitives>>canBeImmutable: (in category 'object access primitives') -----
  canBeImmutable: oop
  	<option: #IMMUTABILITY>
  	| scheduler processLists |
  	
  	self assert: (objectMemory isNonImmediate: oop).
  	
  	"For now we fail the primitive for contexts to we ensure there are no immutable contexts.
  	Later we can consider having immutable contexts and send cannotReturn callback
  	when returning to an immutable context. That would mean that setting a context 
  	to immutable would require a divorce and returns to immutable context are 
  	necessarily across stack pages"
+ 	(objectMemory isContext: oop) ifTrue: [^ false].
- 	(objectMemory isContext: oop) ifTrue: [ ^ false ].
  	
  	"Weak structures can't be immutable"
  	(objectMemory isEphemeron: oop) ifTrue: [^ false].
  	(objectMemory isWeakNonImm: oop) ifTrue: [^ false].
  	
  	"No clue what is going on for semaphores so they can't be immutable"
  	(objectMemory isSemaphoreObj: oop) ifTrue: [^ false].
  	
  	"Simple version of process management: we forbid Process and LinkedList instances to be immutable 
  	 as well as the Processor and the array of activeProcess"
+ 	scheduler := objectMemory fetchPointer: ValueIndex ofObject: (objectMemory splObj: SchedulerAssociation).
- 	scheduler := self fetchPointer: ValueIndex ofObject: (objectMemory splObj: SchedulerAssociation).
  	processLists := objectMemory fetchPointer: ProcessListsIndex ofObject: scheduler.
+ 	oop = scheduler ifTrue: [^ false].
+ 	oop = processLists ifTrue: [^ false].
- 	oop = scheduler ifTrue: [ ^ false ].
- 	oop = processLists ifTrue: [ ^ false ].
  	"Is it a linkedList ?"
+ 	(objectMemory classIndexOf: (objectMemory fetchPointer: 1 ofObject: processLists)) = (objectMemory classIndexOf: oop) ifTrue: [^ false].
- 	(objectMemory classIndexOf: (objectMemory fetchPointer: 1 ofObject: processLists)) = (objectMemory classIndexOf: oop) ifTrue: [ ^ false ].
  	"is it a Process ?"
+ 	(objectMemory classIndexOf: (objectMemory fetchPointer: ActiveProcessIndex ofObject: scheduler)) =  (objectMemory classIndexOf: oop) ifTrue: [^ false].
- 	(objectMemory classIndexOf: (objectMemory fetchPointer: ActiveProcessIndex ofObject: scheduler)) =  (objectMemory classIndexOf: oop) ifTrue: [ ^ false ].
  	
  	"The rest of the code is relative to process management: the Processor (the active 
  	process scheduler) can't be immutable, as well as all the objects relative to Process management "
  	"scheduler := self fetchPointer: ValueIndex ofObject: (self splObj: SchedulerAssociation).
  	processLists := objectMemory fetchPointer: ProcessListsIndex ofObject: scheduler.
  	((objectMemory formatOf: oop) = objectMemory nonIndexablePointerFormat)
  		ifFalse: 
+ 			[ (objectMemory isArrayNonImm: oop) ifFalse: [^ true].
- 			[ (objectMemory isArrayNonImm: oop) ifFalse: [ ^ true ].
  			  ^ (oop = processLists) not ].
+ 	(objectMemory numSlotsOf: oop) >= 2 ifFalse: [^ true].
- 	(objectMemory numSlotsOf: oop) >= 2 ifFalse: [ ^ true ].
  	""is the oop the scheduler itself ?""
+ 	oop = scheduler ifTrue: [^ false].
- 	oop = scheduler ifTrue: [ ^ false ].
  	1 to: (objectMemory numSlotsOf: processLists) do: [ :i |
  		""is the oop one of the linked lists ?""
  		(list := processLists at: i) = oop ifTrue: [^ false].
  		""is the oop one of the runnable process ?""
  		first := objectMemory fetchPointer: FirstLinkIndex ofObject: list.
  		first = objectMemory nilObject ifFalse: 
  			[ last := objectMemory fetchPointer: LastLinkIndex ofObject: list.
  			  link := first.
  			  [ link = last ] whileFalse: 
+ 				[ link = oop ifTrue: [^ false]. 
- 				[ link = oop ifTrue: [ ^ false ]. 
  				  link := objectMemory fetchPointer: NextLinkIndex ofObject: link. ] ] ]."
  	^ true!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveHighBit (in category 'arithmetic integer primitives') -----
  primitiveHighBit
  	| integerReceiverOop leadingZeroCount highestBitZeroBased |
  	integerReceiverOop := self stackTop.
  	"Convert the receiver Oop to use a single tag bit"
  	objectMemory numSmallIntegerTagBits > 1 ifTrue:
  		[integerReceiverOop := (integerReceiverOop >>> (objectMemory numSmallIntegerTagBits-1) bitOr: 1)].
  	self cppIf: #'__GNUC__' defined
  		ifTrue:
  			["Note: in gcc, result is undefined if input is zero (for compatibility with BSR fallback when no CLZ instruction available).
  			but input is never zero because we pass the oop with tag bits set, so we are safe"
  			objectMemory wordSize = 4
  				ifTrue: [leadingZeroCount := self __builtin_clz: integerReceiverOop]
  				ifFalse: [leadingZeroCount := self __builtin_clzll: integerReceiverOop].
+ 			leadingZeroCount = 0 ifTrue: "highBit is not defined for negative Integer"
+ 				[self primitiveFail].
+ 			"Nice bit trick: 1-based high-bit is (32 - clz) - 1 to account for tag bit.
+ 			 This is like two-complement - clz - 1 on 5 bits, or in other words a bit-invert operation clz ^16r1F"
+ 			self pop: 1 thenPushInteger: (leadingZeroCount bitXor: (BytesPerWord * 8 - 1))]
+ 		cppIf: #'_MSC_VER' defined | #'__ICC' defined
- 			leadingZeroCount = 0
- 				ifTrue:
- 					["highBit is not defined for negative Integer"
- 					self primitiveFail]
- 				ifFalse:
- 					["Nice bit trick: 1-based high-bit is (32 - clz) - 1 to account for tag bit.
- 					This is like two-complement - clz - 1 on 5 bits, or in other words a bit-invert operation clz ^16r1F"
- 					self pop: 1 thenPushInteger: (leadingZeroCount bitXor: (BytesPerWord * 8 - 1))].
- 			^self].
- 	self cppIf: #'__GNUC__' defined not & (#'_MSC_VER' defined | #'__ICC' defined)
  		ifTrue:
  			["In MSVC, _lzcnt and _lzcnt64 builtins do not fallback to BSR when not supported by CPU
  			Instead of messing with __cpuid() we always use the BSR intrinsic"
  			
  			"Trick: we test the oop sign rather than the integerValue. Assume oop are signed (so far, they are, sqInt are signed)"
+ 			integerReceiverOop < 0 ifTrue:
+ 				[^self primitiveFail].
- 			integerReceiverOop < 0 ifTrue: [self primitiveFail] ifFalse: [		
  			"Setting this variable is useless, but VMMaker will generate an automatic initialization at a worse place if this isn't initialized explicitly."
  			highestBitZeroBased := 0.
  			"We do not even test the return value, because integerReceiverOop is never zero"
+ 			objectMemory wordSize = 4
- 			self cCode: [objectMemory wordSize = 4
  					ifTrue: [self _BitScanReverse: (self addressOf: highestBitZeroBased) _: integerReceiverOop]
+ 					ifFalse: [self _BitScanReverse64: (self addressOf: highestBitZeroBased) _: integerReceiverOop].
- 					ifFalse: [self _BitScanReverse64: (self addressOf: highestBitZeroBased) _: integerReceiverOop]]
- 				inSmalltalk: [highestBitZeroBased := integerReceiverOop highBit - 1].
  			"thanks to the tag bit, the +1 operation for getting 1-based rank is not necessary"
+ 			self pop: 1 thenPushInteger: highestBitZeroBased]
+ 		ifFalse:
+ 			["not gcc/clang, nor MSVC/ICC, you have to implement if your compiler provides useful builtins"
- 			self pop: 1 thenPushInteger: highestBitZeroBased].
- 			^self].
- 	self cppIf:  #'__GNUC__' defined not & #'_MSC_VER' defined not & #'__ICC' defined not
- 		ifTrue:
- 			["not gcc/clang, nor MSVC/ICC, you have to implement if your compiler provide useful builtins"
  			self cCode:
  					[self primitiveFail]
+ 				inSmalltalk: "Simulate so that the simulator is closer to the actual VM"
+ 					[integerReceiverOop < 0 ifTrue:
+ 						[^self primitiveFail].
+ 					 self pop: 1 thenPushInteger: integerReceiverOop highBit - 1]]!
- 				inSmalltalk: "Simulate so that the simulatror is closer to the actual VM"
- 					[integerReceiverOop < 0
- 						ifTrue: [self primitiveFail]
- 						ifFalse: [self pop: 1 thenPushInteger: integerReceiverOop highBit - 1]]]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>primitiveExecuteMethodArgsArray (in category 'control primitives') -----
  primitiveExecuteMethodArgsArray
+ 	(InitializationOptions at: #haltOnExecuteMethod ifAbsent: [true]) ifTrue:
+ 		[self halt: thisContext selector].
+ 	^super primitiveExecuteMethodArgsArray
+ 
+ 	"InitializationOptions at: #haltOnExecuteMethod put: false"!
- 	self halt: thisContext selector.
- 	"(objectMemory isOopCompiledMethod: self stackTop) ifFalse:
- 		[self halt]."
- 	^super primitiveExecuteMethodArgsArray!

Item was changed:
  ----- Method: VMBasicConstants class>>namesDefinedAtCompileTime (in category 'C translation') -----
  namesDefinedAtCompileTime
  	"Answer the set of names for variables that should be defined at compile time.
  	 Some of these get default values during simulation, and hence get defaulted in
  	 the various initializeMiscConstants methods.  But that they have values should
  	 /not/ cause the code generator to do dead code elimination based on their
  	 default values.  In particular, methods marked with <option: ANameDefinedAtCompileTime>
+ 	 will be emitted within #if defined(ANameDefinedAtCompileTime)...#endif.
+ 
+ 	And of course this is backwards.  We'd like to define names that are defined at translation time."
+ 	^#(VMBIGENDIAN
- 	 will be emitted within #if defined(ANameDefinedAtCompileTime)...#endif."
- 	^#(	VMBIGENDIAN
  		IMMUTABILITY
  		STACKVM COGVM COGMTVM SPURVM
  		PharoVM								"Pharo vs Squeak"
  		TerfVM									"Terf vs Squeak"
  		EnforceAccessControl					"Newspeak"
  		CheckRememberedInTrampoline		"IMMUTABILITY"
  		BIT_IDENTICAL_FLOATING_POINT
  		LLDB									"As of lldb-370.0.42 Swift-3.1, passing function parameters to printOopsSuchThat fails with Internal error [IRForTarget]: Couldn't rewrite one of the arguments of a function call.  Turning off link time optimization with -fno-lto has no effect.  hence we define some debugging functions as being <option: LLDB>"
  
  		"processor related"
  		__ARM_ARCH__ __arm__ __arm32__ ARM32 __arm64__ ARM64
  		_M_I386 _X86_ i386 i486 i586 i686 __i386__ __386__ X86 I386
  		x86_64 __amd64 __x86_64 __amd64__ __x86_64__ _M_AMD64 _M_X64
+ 		__mips__ __mips
+ 		__powerpc __powerpc__ __powerpc64__ __POWERPC__
+ 		__ppc__ __ppc64__ __PPC__ __PPC64__
+ 		__sparc__ __sparc __sparc_v8__ __sparc_v9__ __sparcv8 __sparcv9
  
  		"Compiler brand related"
+ 		__ACK__
+ 		__CC_ARM
+ 		__clang__
  		__GNUC__
  		_MSC_VER
  		__ICC
+ 		__SUNPRO_C
  		
  		"os related"
  		ACORN
+ 		_AIX
+ 		__ANDROID__
+ 		__BEOS__
  		__linux__
  		__MINGW32__
+ 		__FreeBSD__ __NetBSD__ __OpenBSD__
- 		__OpenBSD__
  		__osf__
+ 		EPLAN9
+ 		__unix__ __unix UNIX
- 		UNIX
  		WIN32 _WIN32 _WIN32_WCE
  		WIN64 _WIN64 _WIN64_WCE)!



More information about the Vm-dev mailing list