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

commits at source.squeak.org commits at source.squeak.org
Thu Jul 17 21:35:49 UTC 2014


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

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

Name: Cog-eem.168
Author: eem
Time: 17 July 2014, 2:35:32.852 pm
UUID: 99b3b7ea-49fe-4a0f-9d64-a9276b5dc560
Ancestors: Cog-eem.167

Add a normative recreateSpecialObejctsArray to the Spur
bootstrap and put it early in the transformed image.

Eliminate compact class init of large integer classes in
Integer>>initialize prototype.

Add a single file monticello package patcher entry-point.

Nuke the empty Cog-Benchmarks category.

=============== Diff against Cog-eem.167 ===============

Item was changed:
  SystemOrganization addCategory: #'Cog-Benchmarks-DeltaBlue'!
  SystemOrganization addCategory: #'Cog-Benchmarks-Richards'!
  SystemOrganization addCategory: #'Cog-Benchmarks-SMark'!
  SystemOrganization addCategory: #'Cog-Benchmarks-Shootout'!
  SystemOrganization addCategory: #'Cog-Bootstrapping'!
  SystemOrganization addCategory: #'Cog-Morphing Bytecode Set'!
  SystemOrganization addCategory: #'Cog-ProcessorPlugins'!
  SystemOrganization addCategory: #'Cog-Processors'!
  SystemOrganization addCategory: #'Cog-Processors-Tests'!
  SystemOrganization addCategory: #'Cog-Scripting'!
  SystemOrganization addCategory: #'Cog-Scripts'!
  SystemOrganization addCategory: #'Cog-Tests'!
- SystemOrganization addCategory: #'Cog-Benchmarks'!

Item was added:
+ ----- Method: SpurBootstrap class>>IntegerclassPROTOTYPEinitialize (in category 'method prototypes') -----
+ IntegerclassPROTOTYPEinitialize
+ 	"Integer initialize"	
+ 	self initializeLowBitPerByteTable!

Item was added:
+ ----- Method: SpurBootstrap class>>SmalltalkImagePROTOTYPErecreateSpecialObjectsArray (in category 'method prototypes') -----
+ SmalltalkImagePROTOTYPErecreateSpecialObjectsArray
+ 	"Smalltalk recreateSpecialObjectsArray"
+ 	
+ 	"To external package developers:
+ 	**** DO NOT OVERRIDE THIS METHOD.  *****
+ 	If you are writing a plugin and need additional special object(s) for your own use, 
+ 	use addGCRoot() function and use own, separate special objects registry "
+ 	
+ 	"The Special Objects Array is an array of objects used by the Squeak virtual machine.
+ 	 Its contents are critical and accesses to it by the VM are unchecked, so don't even
+ 	 think of playing here unless you know what you are doing."
+ 	| newArray |
+ 	newArray := Array new: 58.
+ 	"Nil false and true get used throughout the interpreter"
+ 	newArray at: 1 put: nil.
+ 	newArray at: 2 put: false.
+ 	newArray at: 3 put: true.
+ 	"This association holds the active process (a ProcessScheduler)"
+ 	newArray at: 4 put: (self specialObjectsArray at: 4) "(self bindingOf: #Processor) but it answers an Alias".
+ 	"Numerous classes below used for type checking and instantiation"
+ 	newArray at: 5 put: Bitmap.
+ 	newArray at: 6 put: SmallInteger.
+ 	newArray at: 7 put: ByteString.
+ 	newArray at: 8 put: Array.
+ 	newArray at: 9 put: Smalltalk.
+ 	newArray at: 10 put: Float.
+ 	newArray at: 11 put: MethodContext.
+ 	newArray at: 12 put: BlockContext.
+ 	newArray at: 13 put: Point.
+ 	newArray at: 14 put: LargePositiveInteger.
+ 	newArray at: 15 put: Display.
+ 	newArray at: 16 put: Message.
+ 	newArray at: 17 put: CompiledMethod.
+ 	newArray at: 18 put: (self specialObjectsArray at: 18). "(low space Semaphore)"
+ 	newArray at: 19 put: Semaphore.
+ 	newArray at: 20 put: Character.
+ 	newArray at: 21 put: #doesNotUnderstand:.
+ 	newArray at: 22 put: #cannotReturn:.
+ 	newArray at: 23 put: nil. "This is the process signalling low space."
+ 	"An array of the 32 selectors that are compiled as special bytecodes,
+ 	 paired alternately with the number of arguments each takes."
+ 	newArray at: 24 put: #(	#+ 1 #- 1 #< 1 #> 1 #<= 1 #>= 1 #= 1 #~= 1
+ 							#* 1 #/ 1 #\\ 1 #@ 1 #bitShift: 1 #// 1 #bitAnd: 1 #bitOr: 1
+ 							#at: 1 #at:put: 2 #size 0 #next 0 #nextPut: 1 #atEnd 0 #== 1 #class 0
+ 							#blockCopy: 1 #value 0 #value: 1 #do: 1 #new 0 #new: 1 #x 0 #y 0 ).
+ 	"An array of the 255 Characters in ascii order.
+ 	 Cog inlines table into machine code at: prim so do not regenerate it.
+ 	 This is nil in Spur, which has immediate Characters."
+ 	newArray at: 25 put: (self specialObjectsArray at: 25).
+ 	newArray at: 26 put: #mustBeBoolean.
+ 	newArray at: 27 put: ByteArray.
+ 	newArray at: 28 put: Process.
+ 	"An array of up to 31 classes whose instances will have compact headers; an empty array in Spur"
+ 	newArray at: 29 put: self compactClassesArray.
+ 	newArray at: 30 put: (self specialObjectsArray at: 30). "(delay Semaphore)"
+ 	newArray at: 31 put: (self specialObjectsArray at: 31). "(user interrupt Semaphore)"
+ 	"Entries 32 - 34 unreferenced. Previously these contained prototype instances to be copied for fast initialization"
+ 	newArray at: 32 put: nil. "was the prototype Float"
+ 	newArray at: 33 put: nil. "was the prototype 4-byte LargePositiveInteger"
+ 	newArray at: 34 put: nil. "was the prototype Point"
+ 	newArray at: 35 put: #cannotInterpret:.
+ 	newArray at: 36 put: nil. "was the prototype MethodContext"
+ 	newArray at: 37 put: BlockClosure.
+ 	newArray at: 38 put: nil. "was the prototype BlockContext"
+ 	"array of objects referred to by external code"
+ 	newArray at: 39 put: (self specialObjectsArray at: 39).	"external semaphores"
+ 	newArray at: 40 put: nil. "Reserved for Mutex in Cog VMs"
+ 	newArray at: 41 put: ((self specialObjectsArray at: 39) ifNil: [LinkedList new]). "Reserved for a LinkedList instance for overlapped calls in CogMT"
+ 	newArray at: 42 put: ((self specialObjectsArray at: 42) ifNil: [Semaphore new]). "finalization Semaphore"
+ 	newArray at: 43 put: LargeNegativeInteger.
+ 	"External objects for callout.
+ 	 Note: Written so that one can actually completely remove the FFI."
+ 	newArray at: 44 put: (self at: #ExternalAddress ifAbsent: []).
+ 	newArray at: 45 put: (self at: #ExternalStructure ifAbsent: []).
+ 	newArray at: 46 put: (self at: #ExternalData ifAbsent: []).
+ 	newArray at: 47 put: (self at: #ExternalFunction ifAbsent: []).
+ 	newArray at: 48 put: (self at: #ExternalLibrary ifAbsent: []).
+ 	newArray at: 49 put: #aboutToReturn:through:.
+ 	newArray at: 50 put: #run:with:in:.
+ 	"51 reserved for immutability message"
+ 	newArray at: 51 put: #attemptToAssign:withIndex:.
+ 	newArray at: 52 put: #(nil "nil => generic error" #'bad receiver'
+ 							#'bad argument' #'bad index'
+ 							#'bad number of arguments'
+ 							#'inappropriate operation'  #'unsupported operation'
+ 							#'no modification' #'insufficient object memory'
+ 							#'insufficient C memory' #'not found' #'bad method'
+ 							#'internal error in named primitive machinery'
+ 							#'object may move' #'resource limit exceeded'
+ 							#'object is pinned' #'primitive write beyond end of object').
+ 	"53 to 55 are for Alien"
+ 	newArray at: 53 put: (self at: #Alien ifAbsent: []).
+ 	newArray at: 54 put: #invokeCallbackContext::. "use invokeCallback:stack:registers:jmpbuf: for old Alien callbacks."
+ 	newArray at: 55 put: (self at: #UnsafeAlien ifAbsent: []).
+ 
+ 	"Used to be WeakFinalizationList for WeakFinalizationList hasNewFinalization, obsoleted by ephemeron support."
+ 	newArray at: 56 put: nil.
+ 
+ 	"reserved for foreign callback process"
+ 	newArray at: 57 put: (self specialObjectsArray at: 57 ifAbsent: []).
+ 
+ 	newArray at: 58 put: #unusedBytecode.
+ 
+ 	"Now replace the interpreter's reference in one atomic operation"
+ 	self specialObjectsArray becomeForward: newArray!

Item was changed:
  ----- Method: SpurBootstrap>>allPrototypeMethodSymbols (in category 'method prototypes') -----
  allPrototypeMethodSymbols
  	"self basicNew allPrototypeMethodSymbols"
  	| symbols |
  	symbols := Set new.
  	self prototypeClassNameMetaSelectorMethodDo:
+ 		[:className :isMeta :selector :method | | adder |
- 		[:className :isMeta :selector :method |
  		symbols
  			add: className;
+ 			add: selector.	
+ 		adder := [:lit|
+ 				   (lit isSymbol and: [lit ~~ method selector]) ifTrue: [symbols add: lit].
+ 				   lit isArray ifTrue: [lit do: adder]].
+ 		method literals do: adder].
- 			add: selector;
- 			addAll: (method literals select: [:l| l isSymbol and: [l ~~ method selector]])].
  	^symbols!

Item was changed:
  ----- Method: SpurBootstrap>>bootstrapImageUsingFileDirectory: (in category 'public access') -----
  bootstrapImageUsingFileDirectory: imageName
  	| dirName baseName dir |
  	dirName := FileDirectory dirPathFor: imageName.
  	baseName := (imageName endsWith: '.image')
  					ifTrue: [FileDirectory baseNameFor: imageName]
  					ifFalse: [FileDirectory localNameFor: imageName].
+ 	dir := dirName isEmpty ifTrue: [FileDirectory default] ifFalse: [FileDirectory on: dirName].
- 	dir := FileDirectory on: dirName.
  	self on: (dir fullNameFor: baseName, '.image').
  	[self transform]
  		on: Halt
  		do: [:ex|
  			"suppress halts from the usual suspects (development time halts)"
  			(#(fullGC compactImage) includes: ex signalerContext sender selector)
  				ifTrue: [ex resume]
  				ifFalse: [ex pass]].
  	self writeSnapshot: (dir fullNameFor: baseName, '-spur.image')
  		ofTransformedImage: newHeap
  		headerFlags: oldInterpreter getImageHeaderFlags
  		screenSize: oldInterpreter savedWindowSize.
  	dir copyFileNamed: (dir fullNameFor: baseName, '.changes')
  		toFileNamed: (dir fullNameFor: baseName, '-spur.changes')!

Item was changed:
  ----- Method: SpurBootstrap>>cloneArrayLiteral: (in category 'bootstrap methods') -----
  cloneArrayLiteral: anArray
  	"Currently serves only to clone the #(0 0) literal in SpaceTallyPROTOTYPEspaceForInstancesOf:"
  	| array |
  	array := oldHeap instantiateClass: (oldHeap splObj: ClassArray) indexableSize: anArray size.
  	1 to: anArray size do:
  		[:i| | lit |
  		lit := anArray at: i.
  		lit class caseOf: {
  			[SmallInteger] -> [oldHeap
  									storePointerUnchecked: i - 1
  									ofObject: array
+ 									withValue: (oldHeap integerObjectOf: lit)].
+ 			[ByteSymbol] -> [oldHeap
+ 									storePointer: i - 1
+ 									ofObject: array
+ 									withValue: (self findSymbol: lit)].
+ 			[UndefinedObject] -> [oldHeap
+ 									storePointerUnchecked: i - 1
+ 									ofObject: array
+ 									withValue: oldHeap nilObject] }].
- 									withValue: (oldHeap integerObjectOf: lit)] }].
  	^array
  !

Item was changed:
  ----- Method: SpurBootstrap>>cloneObjects (in category 'bootstrap image') -----
  cloneObjects
+ 	| specialObjectsArray characterClass characterTable compactClasses oldObj oldClass |
+ 	specialObjectsArray := oldHeap specialObjectsOop.
- 	| characterClass characterTable compactClasses oldObj oldClass |
  	characterClass := oldHeap classCharacter.
  	characterTable := oldHeap characterTable.
  	compactClasses := oldHeap splObj: CompactClasses.
+ 	self clone: specialObjectsArray
+ 		classIndex: (classToIndex at: (oldHeap fetchClassOfNonImm: specialObjectsArray)).
  	oldObj := oldHeap objectAfter: oldHeap trueObject.
  	[oldObj < oldHeap freeStart] whileTrue:
  		[oldClass := oldHeap fetchClassOfNonImm: oldObj.
  		 (oldObj ~= characterTable
+ 		 and: [oldObj ~= specialObjectsArray
  		 and: [oldObj ~= compactClasses
+ 		 and: [oldClass ~= characterClass]]]) ifTrue:
- 		 and: [oldClass ~= characterClass]]) ifTrue:
  			[self clone: oldObj classIndex: (classToIndex at: oldClass)].
  		 oldObj := oldHeap objectAfter: oldObj].
  	newHeap
  		specialObjectsOop: (map at: oldHeap specialObjectsOop);
  		lastHash: oldHeap lastHash!

Item was changed:
  ----- Method: SpurBootstrap>>findSymbol: (in category 'bootstrap methods') -----
  findSymbol: aString
  	"Find the Symbol equal to aString in oldHeap."
  	| symbolClass |
+ 	(literalMap at: aString ifAbsent: nil) ifNotNil:
+ 		[:oop| ^oop].
  	symbolClass := self symbolClass.
  	oldHeap allObjectsDo:
+ 		[:obj|
+ 		(symbolClass = (oldHeap fetchClassOfNonImm: obj)
+ 		 and: [(oldHeap byteLengthOf: obj) = aString size
+ 		 and: [aString = (oldHeap stringOf: obj)]]) ifTrue:
+ 			[^obj]].
- 		[:o|
- 		(symbolClass = (oldHeap fetchClassOfNonImm: o)
- 		 and: [(oldHeap byteLengthOf: o) = aString size
- 		 and: [aString = (oldHeap stringOf: o)]]) ifTrue:
- 			[^o]].
  	^nil!

Item was changed:
  ----- Method: SpurBootstrap>>interpreter:object:perform:withArguments: (in category 'bootstrap methods') -----
  interpreter: sim object: receiver perform: selector withArguments: arguments
  	"Interpret an expression in oldHeap using oldInterpreter.
  	 Answer the result."
  	| fp savedpc savedsp result startByteCount |
  	savedpc := sim localIP.
  	savedsp := sim localSP.
  	sim internalPush: receiver.
  	arguments do: [:arg| sim internalPush: arg].
  	sim
  		argumentCount: arguments size;
  		messageSelector: selector.
  	fp := sim localFP.
  	startByteCount := sim byteCount.
  	"sim byteCount = 66849 ifTrue: [self halt]."
  	sim normalSend.
  	sim incrementByteCount. "otherwise, send is not counted"
+ 	["sim printFrame: sim localFP WithSP: sim localSP"
+ 	 "sim setBreakSelector: #elementsForwardIdentityTo:"
+ 	 "sim byteCount = 66849 ifTrue: [self halt]."
- 	["sim byteCount = 66849 ifTrue: [self halt]."
  	 "(sim byteCount > 7508930 and: [sim localFP = -16r27894]) ifTrue:
  		[self halt]."
  	 fp = sim localFP] whileFalse:
  		[sim singleStep].
  	result := sim internalPopStack.
  	self assert: savedsp = sim localSP.
  	self assert: sim localIP - 1 = savedpc.
  	sim localIP: savedpc.
  	^result!

Item was added:
+ ----- Method: SpurBootstrap>>recreateSpecialObjectsArray (in category 'bootstrap image') -----
+ recreateSpecialObjectsArray
+ 	"This is tricky.  We want to recreate the specialObjectsArray according to
+ 	 the class side SmalltalkImagePROTOTYPErecreateSpecialObjectsArray.
+ 	 But that version destroys the CompactClassesArray upon which the V3
+ 	 image depends.  The bootstrap will get rid of it later.  So save it before
+ 	 the recreation and restore it."
+ 	self withExecutableInterpreter: oldInterpreter
+ 		do: [| compactClassesArray |
+ 			compactClassesArray := oldHeap splObj: CompactClasses.
+ 			self
+ 				interpreter: oldInterpreter
+ 				object: (oldHeap splObj: 8)
+ 				perform: (self findSymbol: #recreateSpecialObjectsArray)
+ 				withArguments: #().
+ 			oldHeap splObj: CompactClasses put: compactClassesArray]!

Item was changed:
  ----- Method: SpurBootstrap>>transform (in category 'bootstrap image') -----
  transform
  	self rememberRehashSymbol.
  	self findRequiredGlobals.
  	self installModifiedMethods.
+ 	self recreateSpecialObjectsArray.
  	self bootstrapImage.
  	self validate.
  	self rememberRehashSymbol.
  	self rehashImage.
  	self followForwardingPointers.
  	self scavengeImage.
  	self freeForwarders.
  	self compactImage.
  	self reportSizes!

Item was added:
+ ----- Method: SpurBootstrapMonticelloPackagePatcher>>patchFile: (in category 'patching') -----
+ patchFile: packageFile
+ 	"(SpurBootstrapMonticelloPackagePatcher new
+ 			from: '/Users/eliot/oscogvm/image/package-cache'
+ 			to: '/Users/eliot/oscogvm/image/spurpackages')
+ 		patchFile: 'Collections-ul.573(nice.572).mcd'"
+ 	
+ 	sourceDir exists ifFalse:
+ 		[self error: 'source directory doest not exist'].
+ 	destDir assureExistence.
+ 	self packagesAndPatches keysAndValuesDo:
+ 		[:package :patches|
+ 		 ((packageFile beginsWith: package name)
+ 		  and: [(packageFile at: package name size + 1) isLetter not]) ifTrue:
+ 			[self patchPackage: packageFile with: patches for: package]]!



More information about the Vm-dev mailing list