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

commits at source.squeak.org commits at source.squeak.org
Fri May 29 23:48:54 UTC 2015


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

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

Name: Cog-eem.268
Author: eem
Time: 29 May 2015, 4:48:40.605 pm
UUID: c91565e3-8964-404c-b95f-45e1669c87a2
Ancestors: Cog-eem.267

Spur Bootstrap:
Get the category right for the inadvertent *Scorch
override of callPrimitive:.

=============== Diff against Cog-eem.267 ===============

Item was changed:
  ----- Method: SpurBootstrap class>>categoryForClass:meta:selector: (in category 'method prototype categorization') -----
  categoryForClass: className meta: isMeta selector: selector 
  	^(isMeta
  			ifTrue: [{ className. #class. selector }]
  			ifFalse: [{ className. selector }])
  		caseOf: {
  			[#(Behavior allInstancesOrNil)]					-> [#enumerating].
  			[#(Behavior byteSizeOfInstance)]				-> [#'accessing instances and variables'].
  			[#(Behavior byteSizeOfInstanceOfSize:)]		-> [#'accessing instances and variables'].
  			[#(Behavior elementSize)]						-> [#'accessing instances and variables'].
  			[#(Behavior handleFailingBasicNew)]			-> [#private].
  			[#(Behavior handleFailingBasicNew:)]			-> [#private].
  			[#(Behavior handleFailingFailingBasicNew)]		-> [#private].
  			[#(Behavior handleFailingFailingBasicNew:)]		-> [#private].
  			[#(Behavior identityHash)]						-> [#comparing].
  			[#(Behavior isCompiledMethodClass)]			-> [#testing].
  			[#(Behavior isEphemeronClass)]				-> [#testing].
  			[#(Behavior isImmediateClass)]					-> [#testing].
  			[#(BoxedFloat64 class basicNew)]				-> [#'instance creation'].
  			[#(BoxedFloat64 class basicNew:)]				-> [#'instance creation'].
  			[#(Character identityHash)]						-> [#comparing].
  			[#(Character setValue:)]						-> [#accessing].
  			[#(Class immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category:)]
  															-> [#'subclass creation'].
  			[#(ClassBuilder superclass:immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category:)]
  															-> [#public].
  			[#(CompiledMethod bytecodeSetName)]		-> [#accessing].
  			[#(CompiledMethod class handleFailingFailingNewMethod:header:)]
  															-> [#private].
  			[#(CompiledMethod class handleFailingNewMethod:header:)]
  															-> [#private].
  			[#(CompiledMethod class headerFlagForEncoder:)]
  															-> [#'method encoding'].
  			[#(CompiledMethod class installPrimaryBytecodeSet:)]
  															-> [#'class initialization'].
  			[#(CompiledMethod class installSecondaryBytecodeSet:)]
  															-> [#'class initialization'].
  			[#(Context class allInstances)]					-> [#enumerating].
  			[#(Context class allInstancesDo:)]				-> [#enumerating].
  			[#(Context failPrimitiveWith:)]					-> [#'system simulation'].
  			[#(Context isPrimFailToken:)]					-> [#private].
  			[#(Context send:to:with:lookupIn:)]				-> [#controlling].
  			[#(ContextPart isPrimFailToken:)]				-> [#private].
  			[#(ContextPart send:to:with:lookupIn:)]			-> [#controlling].
  			[#(EncoderForV3 computeMethodHeaderForNumArgs:numTemps:numLits:primitive:)]
  															-> [#'method encoding'].
  			[#(EncoderForV3PlusClosures genCallPrimitive:)]
  															-> [#'bytecode generation'].
  			[#(EncoderForV3PlusClosures class callPrimitiveCode)]
  															-> [#'bytecode decoding'].
+ 			[#(InstructionClient callPrimitive:)]				-> [#'instruction decoding'].
  			[#(MethodContext failPrimitiveWith:)]			-> [#'system simulation'].
  			[#(MethodContext class allInstances)]			-> [#enumerating].
  			[#(MethodContext class allInstancesDo:)]		-> [#enumerating].
  			[#(Object isPinned)]							-> [#'system primitives'].
  			[#(Object pin)]									-> [#'system primitives'].
  			[#(Object setPinned:)]							-> [#'system primitives'].
  			[#(Object unpin)]								-> [#'system primitives'].
  			[#(SmallFloat64 class basicNew)]				-> [#'instance creation'].
  			[#(SmallFloat64 class basicNew:)]				-> [#'instance creation'].
  			[#(SmallFloat64 clone)]							-> [#copying].
  			[#(SmallFloat64 copy)]							-> [#copying].
  			[#(SmallFloat64 deepCopy)]					-> [#copying].
  			[#(SmallFloat64 identityHash)]					-> [#comparing].
  			[#(SmallFloat64 shallowCopy)]					-> [#copying].
  			[#(SmallFloat64 veryDeepCopyWith:)]			-> [#copying].
  			[#(SmallInteger asCharacter)]					-> [#converting].
  			[#(SmalltalkImage growMemoryByAtLeast:)]	-> [#'memory space'].
  			[#(SmalltalkImage maxIdentityHash)]			-> [#'system attributes'].
  			[#(SystemDictionary growMemoryByAtLeast:)]	-> [#'memory space'].
  			[#(SystemDictionary maxIdentityHash)]			-> [#'system attributes'].
  			[#(SystemDictionary setGCParameters)]		-> [#'snapshot and quit'].
  			[#(SystemNavigation allObjects)]				-> [#query].
  			[#(SystemNavigation allObjectsOrNil)]			-> [#query].
  			 }
  		otherwise:
  			[Transcript nextPutAll: className.
  			 isMeta ifTrue: [Transcript nextPutAll: ' class'].
  			 Transcript nextPutAll: '>>'; store: selector; nextPutAll: ' is unclassified'; cr; flush.
  			 ^Categorizer default]!

Item was changed:
  ----- Method: SpurBootstrap>>fileOutPrototypesFor: (in category 'public access') -----
  fileOutPrototypesFor: imageTypeOrArrayOfTypes
  	"SpurBootstrap new fileOutPrototypesFor: 'squeak'"
  	| internalStream |
  	imageTypes := imageTypeOrArrayOfTypes isString
  						ifTrue: [{imageTypeOrArrayOfTypes}]
  						ifFalse: [imageTypeOrArrayOfTypes asArray].
  	internalStream := WriteStream on: (String new: 1000).
  	internalStream header; timeStamp.
  	self prototypeClassNameMetaSelectorMethodDo:
  		[:className :isMeta :selector :method| | classNameString class category preamble source |
  		class := Smalltalk classNamed: className.
  		isMeta
  			ifTrue: [class := class class. classNameString := className, ' class']
  			ifFalse: [classNameString := className].
  		(method pragmaAt: #remove)
  			ifNil:
+ 				[category := class ifNotNil: [class organization categoryOfElement: selector].
+ 				 (category notNil and: [category first = $*]) ifTrue:
+ 					[category := nil].
+ 				 category ifNil:
+ 					[category := self class categoryForClass: className meta: isMeta selector: selector].
- 				[category := (class ifNotNil: [class organization categoryOfElement: selector]) ifNil:
- 								[self class categoryForClass: className meta: isMeta selector: selector].
  				preamble := classNameString, ' methodsFor: ' , category asString printString, ' stamp: ''', method timeStamp, ''''.
  				internalStream nextPut: $!!; nextChunkPut: preamble; cr.
  				source := method getSourceFromFile asString.
  				source := source copyFrom: (source indexOfSubCollection: 'PROTOTYPE') + 9 to: source size.
  				(self selectorForPrototypeMethod: method) isBinary ifTrue:
  					[source := (self selectorForPrototypeMethod: method), (source copyFrom: (source indexOf: Character space) to: source size)].
  				internalStream nextChunkPut: source; space; nextPut: $!!; cr; cr]
  			ifNotNil:
  				[source := classNameString, ' removeSelector: ', selector storeString.
  				 internalStream nextChunkPut: source; cr; cr]].
  	internalStream trailer.
  
  	FileStream
  		writeSourceCodeFrom: internalStream
  		baseName: ('SpurBootstrapPrototypes-', (imageTypes fold: [:a :b| a, '-', b]) replaceAll: Character space with: $_)
  		isSt: true
  		useHtml: false!

Item was changed:
  ----- Method: SpurBootstrapMonticelloPackagePatcher>>packagesAndPatches (in category 'private-accessing') -----
  packagesAndPatches
  	"SpurBootstrapMonticelloPackagePatcher new packagesAndPatches"
  	| spurBootstrap |
  	packagesAndPatches ifNotNil:
  		[^packagesAndPatches].
  	packagesAndPatches := Dictionary new.
  	spurBootstrap := SpurBootstrap new.
  	imageTypes ifNotNil:
  		[spurBootstrap imageTypes: imageTypes].
  	spurBootstrap prototypeClassNameMetaSelectorMethodDo:
  		[:className :isMeta :selector :method| | package category source definition |
  		 (Smalltalk classNamed: className)
  			ifNil: [package := self packageForMissingClassNamed: className]
  			ifNotNil:
  				[:behavior| | class methodReference |
  				 class := isMeta ifTrue: [behavior class] ifFalse: [behavior].
  				 (class includesSelector: selector) ifTrue:
  					[methodReference := (class >> selector) methodReference.
+ 					 category := methodReference category.
+ 					 category first = $* ifTrue:
+ 						[category := nil]].
- 					 category := methodReference category].
  				 package := (methodReference isNil
  							  or: [methodReference category = Categorizer default
  							  or: [methodReference category first = $*]]) "This for Scorch's override of InstructionClient>>classPrimitive:"
  								ifTrue: [PackageOrganizer default packageOfClass: class]
  								ifFalse: [PackageOrganizer default packageOfMethod: methodReference]].
  		 source := method getSourceFromFile asString allButFirst: method selector size - selector size.
  		 source first ~= selector first ifTrue:
  			[source replaceFrom: 1 to: selector size with: selector startingAt: 1].
  		 definition := MCAddition of: (MCMethodDefinition new
  										initializeWithClassName: className
  										classIsMeta: isMeta
  										selector: selector
  										category: (category ifNil: [SpurBootstrap
  																	categoryForClass: className
  																	meta: isMeta
  																	selector: selector])
  										timeStamp: method timeStamp
  										source: source).
  		 (method pragmaAt: #remove) ifNotNil:
  			[definition := definition inverse].
  		 (packagesAndPatches at: package ifAbsentPut: [OrderedCollection new])
  			add: definition].
  	^packagesAndPatches!



More information about the Vm-dev mailing list