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

commits at source.squeak.org commits at source.squeak.org
Fri Aug 22 22:58:59 UTC 2014


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

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

Name: Cog-eem.195
Author: eem
Time: 22 August 2014, 11:58:45.028 pm
UUID: 823b7ff0-1e55-4ef7-8503-513c5d0a7fc3
Ancestors: Cog-eem.194

Add support for removals to bootstrap and add a removal for
EncoderForV3>>#computeMethodHeaderForNumArgs:numTemps:numLits:primitive:

=============== Diff against Cog-eem.194 ===============

Item was added:
+ ----- Method: SpurBootstrap class>>EncoderForV3PROTOTYPEcomputeMethodHeaderForNumArgs:numTemps:numLits:primitive: (in category 'method prototypes') -----
+ EncoderForV3PROTOTYPEcomputeMethodHeaderForNumArgs: numArgs numTemps: numTemps numLits: numLits primitive: primitiveIndex
+ 	<remove>!

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 isEphemeronClass)]				-> [#testing].
  			[#(Behavior isImmediateClass)]					-> [#testing].
  			[#(Character identityHash)]						-> [#comparing].
  			[#(Class immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category:)]
  															-> [#'subclass creation'].
  			[#(ClassBuilder superclass:immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category:)]
  															-> [#public].
+ 			[#(CompiledMethod class handleFailingFailingNewMethod:header:)]
+ 															-> [#private].
+ 			[#(CompiledMethod class handleFailingNewMethod:header:)]
+ 															-> [#private].
  			[#(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].
+ 			[#(CompiledMethod class headerFlagForEncoder:)]
+ 															-> [#'method encoding'].
+ 			[#(CompiledMethod class installPrimaryBytecodeSet:)]
+ 															-> [#'class initialization'].
+ 			[#(CompiledMethod class installSecondaryBytecodeSet:)]
+ 															-> [#'class initialization'].
+ 			[#(EncoderForV3PlusClosures genCallPrimitive:)]
+ 															-> [#'bytecode generation'].
+ 			[#(EncoderForV3PlusClosures class callPrimitiveCode)]
+ 															-> [#'bytecode decoding'].
+ 			[#(MethodContext failPrimitiveWith:)]			-> [#'system simulation'].
  			[#(MethodContext class allInstances)]			-> [#enumerating].
  			[#(MethodContext class allInstancesDo:)]		-> [#enumerating].
  			[#(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>>allPrototypeMethods (in category 'method prototypes') -----
  allPrototypeMethods
+ 	^(imageTypes
- 	^imageTypes
  		inject: (SpurBootstrap class organization listAtCategoryNamed: #'method prototypes')
  		into: [:prototypes :type|
+ 				prototypes, (SpurBootstrap class organization listAtCategoryNamed: #'method prototypes ', type)]) reject:
+ 			[:sel| ((SpurBootstrap class >> sel) pragmaAt: #remove) notNil]!
- 			prototypes, (SpurBootstrap class organization listAtCategoryNamed: #'method prototypes ', type)]!

Item was changed:
  ----- Method: SpurBootstrap>>installModifiedMethods (in category 'bootstrap methods') -----
  installModifiedMethods
  	"Install all the methods in the class-side method prototypes protocol in the relevant classes
  	 in the new image.  First use the simulator to get the image to intern all symbols and add
  	 dummy methods under new selectors.  With that done we can manually replace the relevant
  	 methods with the prototypes, mapping selectors and global variables as required."
  	self withExecutableInterpreter: oldInterpreter
  		do: [self internAllSymbols.
  			 self addNewMethods.
+ 			 self removeMethods.
  			 self replaceMethods.
  			 self modifyCharacterMethods]!

Item was added:
+ ----- Method: SpurBootstrap>>removeMethods (in category 'bootstrap methods') -----
+ removeMethods
+ 	"Get the simulator to remove any methods marked with <remove>."
+ 	| removeSym |
+ 	removeSym := self findSymbol: #removeSelectorSilently:.
+ 	removeSym ifNil:
+ 		[removeSym := self findSymbol: #removeSelector:].
+ 	self prototypeClassNameMetaSelectorMethodDo:
+ 		[:className :isMeta :selector :method| | class |
+ 		(method pragmaAt: #remove) ifNotNil:
+ 			[(self findClassNamed: (literalMap at: className)) ifNotNil:
+ 				[:theClass|
+ 				 class := isMeta ifTrue: [oldHeap fetchClassOfNonImm: theClass] ifFalse: [theClass].
+ 				 self interpreter: oldInterpreter
+ 					object: class
+ 					perform: removeSym
+ 					withArguments: {literalMap at: selector}]]]!

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| | class methodReference source definition |
- 		[:className :isMeta :selector :method| | class methodReference source |
  		 class := Smalltalk classNamed: className.
  		 isMeta ifTrue:
  			[class := class class].
  		 methodReference := (class includesSelector: selector) ifTrue:
  								[(class >> selector) methodReference].
  		 (methodReference notNil
  		  and: [methodReference category = Categorizer default]) ifTrue:
  			[methodReference := nil].
  		 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
+ 										className: className
+ 										classIsMeta: isMeta
+ 										selector: selector
+ 										category: (methodReference
+ 													ifNotNil: [methodReference category]
+ 													ifNil: [SpurBootstrap
+ 															categoryForClass: className
+ 															meta: isMeta
+ 															selector: selector])
+ 										timeStamp: method timeStamp
+ 										source: source).
+ 		 (method pragmaAt: #remove) ifNotNil:
+ 			[definition := definition inverse].
  		 (packagesAndPatches
  				at: (methodReference
  						ifNotNil: [PackageOrganizer default packageOfMethod: methodReference]
  						ifNil: [PackageOrganizer default packageOfClass: class])
  				ifAbsentPut: [OrderedCollection new])
+ 			add: definition].
- 			add: (MCAddition of: (MCMethodDefinition
- 									className: className
- 									classIsMeta: isMeta
- 									selector: selector
- 									category: (methodReference
- 												ifNotNil: [methodReference category]
- 												ifNil: [SpurBootstrap
- 														categoryForClass: className
- 														meta: isMeta
- 														selector: selector])
- 									timeStamp: method timeStamp
- 									source: source))].
  	^packagesAndPatches!



More information about the Vm-dev mailing list