[Vm-dev] VM Maker: Cog-eem.222.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Nov 21 00:52:51 UTC 2014


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

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

Name: Cog-eem.222
Author: eem
Time: 20 November 2014, 4:52:34.938 pm
UUID: 1219d9fd-6d24-43ca-a583-6fd362db2b08
Ancestors: Cog-eem.221

Merge with Cog.pharo-EstebanLorenzano.221.
Move Squeak prototype classes under
SpurBootstrapSqueakFamilyPrototypes.  Move
ClassBuilder and InstructionPrinter prototypes
down into SpurBootstrapSqueakFamilyPrototypes.
Add Cog test xray methods to Context.

Happy Birthday Esteban!

=============== Diff against Cog-eem.221 ===============

Item was added:
+ ----- Method: Context>>ContextPROTOTYPEobjectClass: (in category '*Cog-method prototypes') -----
+ ContextPROTOTYPEobjectClass: aReceiver
+ 	<primitive: 111>
+ 	self primitiveFailed!

Item was added:
+ ----- Method: Context>>xray (in category '*Cog-Tests-xrays') -----
+ xray
+ 	"Lift the veil from a context and answer an integer describing its interior state.
+ 	 Used for e.g. VM tests so they can verify they're testing what they think they're testing.
+ 	 0 implies a vanilla heap context.
+ 	 Bit 0 = is or was married to a frame
+ 	 Bit 1 = is still married to a frame
+ 	 Bit 2 = frame is executing machine code
+ 	 Bit 3 = has machine code pc (as opposed to nil or a bytecode pc)
+ 	 Bit 4 = method is currently compiled to machine code"
+ 	<primitive: 213>
+ 	^0 "Can only fail if unimplemented; therefore simply answer 0"!

Item was added:
+ ----- Method: Context>>xrayIsDivorced (in category '*Cog-Tests-xrays') -----
+ xrayIsDivorced
+ 	^(self xray bitAnd: 3) = 1!

Item was added:
+ ----- Method: Context>>xrayIsExecutingMachineCode (in category '*Cog-Tests-xrays') -----
+ xrayIsExecutingMachineCode
+ 	^self xray anyMask: 4!

Item was added:
+ ----- Method: Context>>xrayIsMarried (in category '*Cog-Tests-xrays') -----
+ xrayIsMarried
+ 	^self xray anyMask: 2!

Item was added:
+ ----- Method: Context>>xrayLastExecutedMachineCode (in category '*Cog-Tests-xrays') -----
+ xrayLastExecutedMachineCode
+ 	^self xray anyMask: 8!

Item was added:
+ ----- Method: Context>>xrayMethodIsCompiledToMachineCode (in category '*Cog-Tests-xrays') -----
+ xrayMethodIsCompiledToMachineCode
+ 	^self xray anyMask: 16!

Item was changed:
  ----- Method: SpurBootstrap class>>bootstrapPharoImage: (in category 'utilities') -----
  bootstrapPharoImage: imageFileBaseName
+ 	| oldCompilerClass oldBytecodeBackend |
- 	| oldCompilerClass |
  	
  	oldCompilerClass := SmalltalkImage compilerClass.
+ 	oldBytecodeBackend := CompilationContext bytecodeBackend. 
  	[ 
  		SmalltalkImage compilerClass: Compiler. 
+ 		CompilationContext bytecodeBackend: IRSpurSqueakV3PlusClosuresBytecodeGenerator.
  		self bootstrapImage: imageFileBaseName type: 'pharo' ]
+ 	ensure: [ 
+ 		SmalltalkImage compilerClass: oldCompilerClass.
+ 		CompilationContext bytecodeBackend: oldBytecodeBackend ]!
- 	ensure: [ SmalltalkImage compilerClass: oldCompilerClass ].
- 	!

Item was changed:
  ----- Method: SpurBootstrapPharoPrototypes>>CharacterPROTOTYPEcodePoint (in category 'method prototypes') -----
  CharacterPROTOTYPEcodePoint
  	"Just for ANSI Compliance"	
+ 	^self asciiValue!
- 	^self!

Item was added:
+ ----- Method: SpurBootstrapPharoPrototypes>>CharacterPROTOTYPEshallowCopy (in category 'method prototypes') -----
+ CharacterPROTOTYPEshallowCopy
+ 	"Answer the receiver, because Characters are unique."
+ 	^self!

Item was added:
+ ----- Method: SpurBootstrapPharoPrototypes>>ContextPROTOTYPEobjectClass: (in category 'method prototypes') -----
+ ContextPROTOTYPEobjectClass: aReceiver 
+ 	<indirect>!

Item was removed:
- ----- Method: SpurBootstrapPrototypes>>ClassBuilderPROTOTYPEcomputeFormat:instSize:forSuper:ccIndex: (in category 'method prototypes') -----
- ClassBuilderPROTOTYPEcomputeFormat: type instSize: newInstSize forSuper: newSuper ccIndex: ccIndex
- 	"Compute the new format for making oldClass a subclass of newSuper.
- 	 Answer the format or nil if there is any problem."
- 	| instSize isVar isWords isPointers isWeak |
- 	type == #compiledMethod ifTrue:
- 		[newInstSize > 0 ifTrue:
- 			[self error: 'A compiled method class cannot have named instance variables'.
- 			^nil].
- 		^CompiledMethod format].
- 	instSize := newInstSize + (newSuper ifNil:[0] ifNotNil:[newSuper instSize]).
- 	instSize > 65535 ifTrue:
- 		[self error: 'Class has too many instance variables (', instSize printString,')'.
- 		^nil].
- 	type == #normal ifTrue:[isVar := isWeak := false. isWords := isPointers := true].
- 	type == #bytes ifTrue:[isVar := true. isWords := isPointers := isWeak := false].
- 	type == #words ifTrue:[isVar := isWords := true. isPointers := isWeak := false].
- 	type == #variable ifTrue:[isVar := isPointers := isWords := true. isWeak := false].
- 	type == #weak ifTrue:[isVar := isWeak := isWords := isPointers := true].
- 	type == #ephemeron ifTrue:[isVar := false. isWeak := isWords := isPointers := true].
- 	type == #immediate ifTrue:[isVar := isWeak := isPointers := false. isWords := true].
- 	(isPointers not and: [instSize > 0]) ifTrue:
- 		[self error: 'A non-pointer class cannot have named instance variables'.
- 		^nil].
- 	^self format: instSize variable: isVar words: isWords pointers: isPointers weak: isWeak!

Item was removed:
- ----- Method: SpurBootstrapPrototypes>>ClassBuilderPROTOTYPEformat:variable:words:pointers:weak: (in category 'method prototypes') -----
- ClassBuilderPROTOTYPEformat: nInstVars variable: isVar words: is32BitWords pointers: isPointers weak: isWeak
- 	"Compute the format for the given instance specfication.
- 	 Above Cog Spur the class format is
- 		<5 bits inst spec><16 bits inst size>
- 	 where the 5-bit inst spec is
- 			0	= 0 sized objects (UndefinedObject True False et al)
- 			1	= non-indexable objects with inst vars (Point et al)
- 			2	= indexable objects with no inst vars (Array et al)
- 			3	= indexable objects with inst vars (MethodContext AdditionalMethodState et al)
- 			4	= weak indexable objects with inst vars (WeakArray et al)
- 			5	= weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
- 			6	= unused
- 			7	= immediates (SmallInteger, Character)
- 			8	= unused
- 			9	= reserved for 64-bit indexable
- 		10-11	= 32-bit indexable (Bitmap)
- 		12-15	= 16-bit indexable
- 		16-23	= 8-bit indexable
- 		24-31	= compiled methods (CompiledMethod)"
- 	| instSpec |
- 	instSpec := isWeak
- 					ifTrue:
- 						[isVar
- 							ifTrue: [4]
- 							ifFalse: [5]]
- 					ifFalse:
- 						[isPointers
- 							ifTrue:
- 								[isVar
- 									ifTrue: [nInstVars > 0 ifTrue: [3] ifFalse: [2]]
- 									ifFalse: [nInstVars > 0 ifTrue: [1] ifFalse: [0]]]
- 							ifFalse:
- 								[isVar
- 									ifTrue: [is32BitWords ifTrue: [10] ifFalse: [16]]
- 									ifFalse: [7]]].
- 	^(instSpec bitShift: 16) + nInstVars!

Item was removed:
- ----- Method: SpurBootstrapPrototypes>>ClassBuilderPROTOTYPEsuperclass:immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'method prototypes') -----
- ClassBuilderPROTOTYPEsuperclass: aClass
- 	immediateSubclass: t instanceVariableNames: f 
- 	classVariableNames: d poolDictionaries: s category: cat
- 	"This is the standard initialization message for creating a
- 	 new immediate class as a subclass of an existing class."
- 	| env |
- 	aClass instSize > 0
- 		ifTrue: [^self error: 'cannot make an immediate subclass of a class with named fields'].
- 	aClass isVariable
- 		ifTrue: [^self error: 'cannot make an immediate subclass of a class with indexed instance variables'].
- 	aClass isPointers
- 		ifFalse: [^self error: 'cannot make an immediate subclass of a class without pointer fields'].
- 	"Cope with pre-environment and environment versions. Simplify asap."
- 	env := (Smalltalk classNamed: #EnvironmentRequest)
- 				ifNil: [aClass environment]
- 				ifNotNil: [:erc| erc signal ifNil: [aClass environment]].
- 	^self 
- 		name: t
- 		inEnvironment: env
- 		subclassOf: aClass
- 		type: #immediate
- 		instanceVariableNames: f
- 		classVariableNames: d
- 		poolDictionaries: s
- 		category: cat!

Item was removed:
- ----- Method: SpurBootstrapPrototypes>>ClassBuilderPROTOTYPEupdate:to: (in category 'method prototypes') -----
- ClassBuilderPROTOTYPEupdate: oldClass to: newClass
- 	"Convert oldClass, all its instances and possibly its meta class into newClass,
- 	 instances of newClass and possibly its meta class. The process is surprisingly
- 	 simple in its implementation and surprisingly complex in its nuances and potentially
- 	 bad side effects.
- 	 We can rely on two assumptions (which are critical):
- 		#1: The method #updateInstancesFrom: will not create any lasting pointers to
- 			 'old' instances ('old' is quote on quote since #updateInstancesFrom: will do
- 			 a become of the old vs. the new instances and therefore it will not create
- 			 pointers to *new* instances before the #become: which are *old* afterwards)
- 		#2: The non-preemptive execution of the critical piece of code guarantees that
- 			 nobody can get a hold by 'other means' (such as process interruption and
- 			 reflection) on the old instances.
- 	 Given the above two, we know that after #updateInstancesFrom: there are no pointers
- 	 to any old instances. After the forwarding become there will be no pointers to the old
- 	 class or meta class either.
- 	 Andreas Raab, 2/27/2003 23:42"
- 	| meta |
- 	meta := oldClass isMeta.
- 	"Note: Everything from here on will run without the ability to get interrupted
- 	to prevent any other process to create new instances of the old class."
- 	["Note: The following removal may look somewhat obscure and needs an explanation.
- 	  When we mutate the class hierarchy we create new classes for any existing subclass.
- 	  So it may look as if we don't have to remove the old class from its superclass. However,
- 	  at the top of the hierarchy (the first class we reshape) that superclass itself is not newly
- 	  created so therefore it will hold both the oldClass and newClass in its (obsolete or not)
- 	  subclasses. Since the #become: below will transparently replace the pointers to oldClass
- 	  with newClass the superclass would have newClass in its subclasses TWICE. With rather
- 	  unclear effects if we consider that we may convert the meta-class hierarchy itself (which
- 	  is derived from the non-meta class hierarchy).
- 	  Due to this problem ALL classes are removed from their superclass just prior to converting
- 	  them. Here, breaking the superclass/subclass invariant really doesn't matter since we will
- 	  effectively remove the oldClass (becomeForward:) just a few lines below."
- 
- 		oldClass superclass removeSubclass: oldClass.
- 		oldClass superclass removeObsoleteSubclass: oldClass.
- 
- 		"make sure that the VM cache is clean"
- 		oldClass methodDict do: [:cm | cm flushCache].
- 		
- 		"Convert the instances of oldClass into instances of newClass"
- 		newClass updateInstancesFrom: oldClass.
- 
- 		meta
- 			ifTrue:
- 				[oldClass becomeForward: newClass.
- 				 oldClass updateMethodBindingsTo: oldClass binding]
- 			ifFalse:
- 				[{oldClass. oldClass class} elementsForwardIdentityTo: {newClass. newClass class}.
- 				 oldClass updateMethodBindingsTo: oldClass binding.
- 				 oldClass class updateMethodBindingsTo: oldClass class binding].
- 
- 		"eem 5/31/2014 07:22 At this point there used to be a garbage collect whose purpose was
- 		 to ensure no old instances existed after the becomeForward:.  Without the GC it was possible
- 		 to resurrect old instances using e.g. allInstancesDo:.  This was because the becomeForward:
- 		 updated references from the old objects to new objects but didn't destroy the old objects.
- 		 But as of late 2013/early 2014 becomeForward: has been modified to free all the old objects."]
- 			valueUnpreemptively!

Item was removed:
- ----- Method: SpurBootstrapPrototypes>>InstructionPrinterPROTOTYPEcallPrimitive: (in category 'method prototypes') -----
- InstructionPrinterPROTOTYPEcallPrimitive: index
- 	"Print the callPrimitive."
- 
- 	self print: 'callPrimtive: ' , index printString!

Item was changed:
+ SpurBootstrapSqueakFamilyPrototypes subclass: #SpurBootstrapSqueak43Prototypes
- SpurBootstrapPrototypes subclass: #SpurBootstrapSqueak43Prototypes
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Cog-Bootstrapping'!

Item was added:
+ SpurBootstrapPrototypes subclass: #SpurBootstrapSqueakFamilyPrototypes
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Cog-Bootstrapping'!

Item was added:
+ ----- Method: SpurBootstrapSqueakFamilyPrototypes>>ClassBuilderPROTOTYPEcomputeFormat:instSize:forSuper:ccIndex: (in category 'method prototypes') -----
+ ClassBuilderPROTOTYPEcomputeFormat: type instSize: newInstSize forSuper: newSuper ccIndex: ccIndex
+ 	"Compute the new format for making oldClass a subclass of newSuper.
+ 	 Answer the format or nil if there is any problem."
+ 	| instSize isVar isWords isPointers isWeak |
+ 	type == #compiledMethod ifTrue:
+ 		[newInstSize > 0 ifTrue:
+ 			[self error: 'A compiled method class cannot have named instance variables'.
+ 			^nil].
+ 		^CompiledMethod format].
+ 	instSize := newInstSize + (newSuper ifNil:[0] ifNotNil:[newSuper instSize]).
+ 	instSize > 65535 ifTrue:
+ 		[self error: 'Class has too many instance variables (', instSize printString,')'.
+ 		^nil].
+ 	type == #normal ifTrue:[isVar := isWeak := false. isWords := isPointers := true].
+ 	type == #bytes ifTrue:[isVar := true. isWords := isPointers := isWeak := false].
+ 	type == #words ifTrue:[isVar := isWords := true. isPointers := isWeak := false].
+ 	type == #variable ifTrue:[isVar := isPointers := isWords := true. isWeak := false].
+ 	type == #weak ifTrue:[isVar := isWeak := isWords := isPointers := true].
+ 	type == #ephemeron ifTrue:[isVar := false. isWeak := isWords := isPointers := true].
+ 	type == #immediate ifTrue:[isVar := isWeak := isPointers := false. isWords := true].
+ 	(isPointers not and: [instSize > 0]) ifTrue:
+ 		[self error: 'A non-pointer class cannot have named instance variables'.
+ 		^nil].
+ 	^self format: instSize variable: isVar words: isWords pointers: isPointers weak: isWeak!

Item was added:
+ ----- Method: SpurBootstrapSqueakFamilyPrototypes>>ClassBuilderPROTOTYPEformat:variable:words:pointers:weak: (in category 'method prototypes') -----
+ ClassBuilderPROTOTYPEformat: nInstVars variable: isVar words: is32BitWords pointers: isPointers weak: isWeak
+ 	"Compute the format for the given instance specfication.
+ 	 Above Cog Spur the class format is
+ 		<5 bits inst spec><16 bits inst size>
+ 	 where the 5-bit inst spec is
+ 			0	= 0 sized objects (UndefinedObject True False et al)
+ 			1	= non-indexable objects with inst vars (Point et al)
+ 			2	= indexable objects with no inst vars (Array et al)
+ 			3	= indexable objects with inst vars (MethodContext AdditionalMethodState et al)
+ 			4	= weak indexable objects with inst vars (WeakArray et al)
+ 			5	= weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 			6	= unused
+ 			7	= immediates (SmallInteger, Character)
+ 			8	= unused
+ 			9	= reserved for 64-bit indexable
+ 		10-11	= 32-bit indexable (Bitmap)
+ 		12-15	= 16-bit indexable
+ 		16-23	= 8-bit indexable
+ 		24-31	= compiled methods (CompiledMethod)"
+ 	| instSpec |
+ 	instSpec := isWeak
+ 					ifTrue:
+ 						[isVar
+ 							ifTrue: [4]
+ 							ifFalse: [5]]
+ 					ifFalse:
+ 						[isPointers
+ 							ifTrue:
+ 								[isVar
+ 									ifTrue: [nInstVars > 0 ifTrue: [3] ifFalse: [2]]
+ 									ifFalse: [nInstVars > 0 ifTrue: [1] ifFalse: [0]]]
+ 							ifFalse:
+ 								[isVar
+ 									ifTrue: [is32BitWords ifTrue: [10] ifFalse: [16]]
+ 									ifFalse: [7]]].
+ 	^(instSpec bitShift: 16) + nInstVars!

Item was added:
+ ----- Method: SpurBootstrapSqueakFamilyPrototypes>>ClassBuilderPROTOTYPEsuperclass:immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category: (in category 'method prototypes') -----
+ ClassBuilderPROTOTYPEsuperclass: aClass
+ 	immediateSubclass: t instanceVariableNames: f 
+ 	classVariableNames: d poolDictionaries: s category: cat
+ 	"This is the standard initialization message for creating a
+ 	 new immediate class as a subclass of an existing class."
+ 	| env |
+ 	aClass instSize > 0
+ 		ifTrue: [^self error: 'cannot make an immediate subclass of a class with named fields'].
+ 	aClass isVariable
+ 		ifTrue: [^self error: 'cannot make an immediate subclass of a class with indexed instance variables'].
+ 	aClass isPointers
+ 		ifFalse: [^self error: 'cannot make an immediate subclass of a class without pointer fields'].
+ 	"Cope with pre-environment and environment versions. Simplify asap."
+ 	env := (Smalltalk classNamed: #EnvironmentRequest)
+ 				ifNil: [aClass environment]
+ 				ifNotNil: [:erc| erc signal ifNil: [aClass environment]].
+ 	^self 
+ 		name: t
+ 		inEnvironment: env
+ 		subclassOf: aClass
+ 		type: #immediate
+ 		instanceVariableNames: f
+ 		classVariableNames: d
+ 		poolDictionaries: s
+ 		category: cat!

Item was added:
+ ----- Method: SpurBootstrapSqueakFamilyPrototypes>>ClassBuilderPROTOTYPEupdate:to: (in category 'method prototypes') -----
+ ClassBuilderPROTOTYPEupdate: oldClass to: newClass
+ 	"Convert oldClass, all its instances and possibly its meta class into newClass,
+ 	 instances of newClass and possibly its meta class. The process is surprisingly
+ 	 simple in its implementation and surprisingly complex in its nuances and potentially
+ 	 bad side effects.
+ 	 We can rely on two assumptions (which are critical):
+ 		#1: The method #updateInstancesFrom: will not create any lasting pointers to
+ 			 'old' instances ('old' is quote on quote since #updateInstancesFrom: will do
+ 			 a become of the old vs. the new instances and therefore it will not create
+ 			 pointers to *new* instances before the #become: which are *old* afterwards)
+ 		#2: The non-preemptive execution of the critical piece of code guarantees that
+ 			 nobody can get a hold by 'other means' (such as process interruption and
+ 			 reflection) on the old instances.
+ 	 Given the above two, we know that after #updateInstancesFrom: there are no pointers
+ 	 to any old instances. After the forwarding become there will be no pointers to the old
+ 	 class or meta class either.
+ 	 Andreas Raab, 2/27/2003 23:42"
+ 	| meta |
+ 	meta := oldClass isMeta.
+ 	"Note: Everything from here on will run without the ability to get interrupted
+ 	to prevent any other process to create new instances of the old class."
+ 	["Note: The following removal may look somewhat obscure and needs an explanation.
+ 	  When we mutate the class hierarchy we create new classes for any existing subclass.
+ 	  So it may look as if we don't have to remove the old class from its superclass. However,
+ 	  at the top of the hierarchy (the first class we reshape) that superclass itself is not newly
+ 	  created so therefore it will hold both the oldClass and newClass in its (obsolete or not)
+ 	  subclasses. Since the #become: below will transparently replace the pointers to oldClass
+ 	  with newClass the superclass would have newClass in its subclasses TWICE. With rather
+ 	  unclear effects if we consider that we may convert the meta-class hierarchy itself (which
+ 	  is derived from the non-meta class hierarchy).
+ 	  Due to this problem ALL classes are removed from their superclass just prior to converting
+ 	  them. Here, breaking the superclass/subclass invariant really doesn't matter since we will
+ 	  effectively remove the oldClass (becomeForward:) just a few lines below."
+ 
+ 		oldClass superclass removeSubclass: oldClass.
+ 		oldClass superclass removeObsoleteSubclass: oldClass.
+ 
+ 		"make sure that the VM cache is clean"
+ 		oldClass methodDict do: [:cm | cm flushCache].
+ 		
+ 		"Convert the instances of oldClass into instances of newClass"
+ 		newClass updateInstancesFrom: oldClass.
+ 
+ 		meta
+ 			ifTrue:
+ 				[oldClass becomeForward: newClass.
+ 				 oldClass updateMethodBindingsTo: oldClass binding]
+ 			ifFalse:
+ 				[{oldClass. oldClass class} elementsForwardIdentityTo: {newClass. newClass class}.
+ 				 oldClass updateMethodBindingsTo: oldClass binding.
+ 				 oldClass class updateMethodBindingsTo: oldClass class binding].
+ 
+ 		"eem 5/31/2014 07:22 At this point there used to be a garbage collect whose purpose was
+ 		 to ensure no old instances existed after the becomeForward:.  Without the GC it was possible
+ 		 to resurrect old instances using e.g. allInstancesDo:.  This was because the becomeForward:
+ 		 updated references from the old objects to new objects but didn't destroy the old objects.
+ 		 But as of late 2013/early 2014 becomeForward: has been modified to free all the old objects."]
+ 			valueUnpreemptively!

Item was added:
+ ----- Method: SpurBootstrapSqueakFamilyPrototypes>>InstructionPrinterPROTOTYPEcallPrimitive: (in category 'method prototypes') -----
+ InstructionPrinterPROTOTYPEcallPrimitive: index
+ 	"Print the callPrimitive."
+ 
+ 	self print: 'callPrimtive: ' , index printString!

Item was changed:
+ SpurBootstrapSqueakFamilyPrototypes subclass: #SpurBootstrapSqueakPrototypes
- SpurBootstrapPrototypes subclass: #SpurBootstrapSqueakPrototypes
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Cog-Bootstrapping'!



More information about the Vm-dev mailing list