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

commits at source.squeak.org commits at source.squeak.org
Tue Feb 28 18:17:26 UTC 2012


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

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

Name: VMMaker.oscog-eem.149
Author: eem
Time: 28 February 2012, 10:15:02.63 am
UUID: 48257b02-cacd-4cc2-b747-c9e6df6e2530
Ancestors: VMMaker.oscog-eem.148

Fix assert failures in mapVMRegisters due to new multiple bytecode
set support.
Report remappable oop and weak root table overflows as errors.
Make the default VM generation scripts methods.

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

Item was changed:
  ----- Method: CoInterpreter>>mapVMRegisters (in category 'object memory support') -----
  mapVMRegisters
  	"Map the oops in the interpreter's vm ``registers'' to their new values 
  	 during garbage collection or a become: operation."
  	"Assume: All traced variables contain valid oops."
  	| mapInstructionPointer |
+ 	"i.e. interpreter instructionPointer in method as opposed to machine code?"
+ 	(mapInstructionPointer := instructionPointer > method) ifTrue:
- 	mapInstructionPointer := instructionPointer > method.
- 	mapInstructionPointer ifTrue:
  		[instructionPointer := instructionPointer - method]. "*rel to method"
+ 	method := (objectMemory remap: method).
- 	self setMethod: (objectMemory remap: method).
  	mapInstructionPointer ifTrue:
  		[instructionPointer := instructionPointer + method]. "*rel to method"
  	messageSelector := objectMemory remap: messageSelector.
  	(objectMemory isIntegerObject: newMethod) ifFalse:
  		[newMethod := objectMemory remap: newMethod].
  	lkupClass := objectMemory remap: lkupClass!

Item was changed:
  ----- Method: NewObjectMemory>>incrementalGC (in category 'garbage collection') -----
  incrementalGC
  	"Do a mark/sweep garbage collection of just the young object
  	area of object memory (i.e., objects above youngStart), using
  	the root table to identify objects containing pointers to
  	young objects from the old object area."
  	| survivorCount weDidGrow |
  	<inline: false>
  
  	rootTableCount >= RootTableSize ifTrue:
  		["root table overflow; cannot do an incremental GC (this should be very rare)"
  		 statRootTableOverflows := statRootTableOverflows + 1.
  		 ^self fullGC].
  
  	self initializeFreeBlocksPreSweep.
  	self runLeakCheckerForFullGC: false.
  
  	self preGCAction: GCModeIncr.
  	"incremental GC and compaction"
  
  	gcStartUsecs := self ioUTCMicrosecondsNow.
  	weakRootCount := 0.
  	statSweepCount := statMarkCount := statMkFwdCount := statCompMoveCount := 0.
  	self markPhase: false.
+ 	weakRootCount <= WeakRootTableSize ifFalse:
+ 		[self error: 'weakRoots table overflow'].
- 	self assert: weakRootCount <= WeakRootTableSize.
  	1 to: weakRootCount do:
  		[:i| self finalizeReference: (weakRoots at: i)].
  	survivorCount := self sweepPhase.
  	self runLeakCheckerForFullGC: false.
  	self incrementalCompaction.
  	statIncrGCs := statIncrGCs + 1.
  	statGCEndUsecs := self ioUTCMicrosecondsNow.
  	statIGCDeltaUsecs := statGCEndUsecs - gcStartUsecs.
  	statIncrGCUsecs := statIncrGCUsecs + statIGCDeltaUsecs.
  	self capturePendingFinalizationSignals.
  	
  	statRootTableCount  := rootTableCount.
  	statSurvivorCount := survivorCount.
  	weDidGrow := false.
  	(((survivorCount > tenuringThreshold)
  	 or: [rootTableCount >= RootTableRedZone])
  	 or: [forceTenureFlag == true]) ifTrue:
  		["move up the young space boundary if
  		  * there are too many survivors:
  			this limits the number of objects that must be
  			processed on future incremental GC's
  		  * we're about to overflow the roots table:
  			this limits the number of full GCs that may be caused
  			by root table overflows in the near future"
  		forceTenureFlag := false.
  		statTenures := statTenures + 1.
  		self clearRootsTable.
  		((self freeSize < growHeadroom)
  		 and: [gcBiasToGrow > 0]) ifTrue:
  			[self biasToGrow.
  			 weDidGrow := true].
  		youngStart := freeStart].
  	self postGCAction.
  	
  	self runLeakCheckerForFullGC: false.
  	weDidGrow ifTrue:
  		[self biasToGrowCheckGCLimit]!

Item was changed:
  ----- Method: ObjectMemory>>incrementalGC (in category 'garbage collection') -----
  incrementalGC
  	"Do a mark/sweep garbage collection of just the young object 
  	area of object memory (i.e., objects above youngStart), using 
  	the root table to identify objects containing pointers to 
  	young objects from the old object area."
  	| survivorCount weDidGrow |
  	<inline: false>
  	rootTableCount >= RootTableSize
  		ifTrue: ["root table overflow; cannot do an incremental GC (this should be very rare)"
  			statRootTableOverflows := statRootTableOverflows + 1.
  			^ self fullGC].
  
  	DoAssertionChecks ifTrue:
  		[self reverseDisplayFrom: 8 to: 15.
  		 self checkHeapIntegrity.
  		 self checkInterpreterIntegrity.
  		 self validate].
  
  	self preGCAction: GCModeIncr.
  	"incremental GC and compaction"
  
  	gcStartUsecs := self ioUTCMicrosecondsNow.
  	weakRootCount := 0.
  	statSweepCount := statMarkCount := statMkFwdCount := statCompMoveCount := 0.
  	self markPhase.
+ 	weakRootCount <= WeakRootTableSize ifFalse:
+ 		[self error: 'weakRoots table overflow'].
- 	self assert: weakRootCount <= WeakRootTableSize.
  	1 to: weakRootCount do:[:i| self finalizeReference: (weakRoots at: i)].
  	survivorCount := self sweepPhase.
  	self incrementalCompaction.
  	statAllocationCount := allocationCount.
  	allocationCount := 0.
  	statIncrGCs := statIncrGCs + 1.
  	statGCEndTime := self ioMicroMSecs.
  	statIGCDeltaUsecs := self ioUTCMicrosecondsNow - gcStartUsecs.
  	statIncrGCUsecs := statIncrGCUsecs + statIGCDeltaUsecs.
  	self capturePendingFinalizationSignals.
  
  	self forceInterruptCheck. "Force an an interrupt check ASAP.We could choose to be clever here and only do this under certain time conditions. Keep it simple for now"
  	
  	statRootTableCount  := rootTableCount.
  	statSurvivorCount := survivorCount.
  	weDidGrow := false.
  	(((survivorCount > tenuringThreshold)
  			or: [rootTableCount >= RootTableRedZone])
  			or: [forceTenureFlag == true])
  		ifTrue: ["move up the young space boundary if 
  			* there are too many survivors: 
  			this limits the number of objects that must be 
  			processed on future incremental GC's 
  			* we're about to overflow the roots table 
  			this limits the number of full GCs that may be caused 
  			by root table overflows in the near future"
  			forceTenureFlag := false.
  			statTenures := statTenures + 1.
  			self clearRootsTable.
  			(((self sizeOfFree: freeBlock) < growHeadroom) and: 
  				[gcBiasToGrow > 0]) 
  				ifTrue: [self biasToGrow.
  						weDidGrow := true].
  			youngStart := freeBlock].
  	self postGCAction.
  	DoAssertionChecks ifTrue:
  		[self validate.
  		 self checkHeapIntegrity.
  		 self checkInterpreterIntegrity.
  		 self reverseDisplayFrom: 8 to: 15].
  	weDidGrow ifTrue: [self biasToGrowCheckGCLimit]!

Item was changed:
  ----- Method: ObjectMemory>>pushRemappableOop: (in category 'interpreter access') -----
  pushRemappableOop: oop
  	"Record the given object in a the remap buffer. Objects in this buffer are remapped when a compaction occurs. This facility is used by the interpreter to ensure that objects in temporary variables are properly remapped."
  	<api>
  	self assert: (self addressCouldBeOop: oop).
+ 	remapBuffer at: (remapBufferCount := remapBufferCount + 1) put: oop.
+ 	remapBufferCount <= RemapBufferSize ifFalse:
+ 		[self error: 'remapBuffer overflow'].!
- 	remapBuffer at: (remapBufferCount := remapBufferCount + 1) put: oop.!

Item was removed:
- ----- Method: ObjectMemory>>remapBufferCount: (in category 'accessing') -----
- remapBufferCount: aValue
- 	^remapBufferCount := aValue!

Item was changed:
  ----- Method: StackInterpreter>>mapVMRegisters (in category 'object memory support') -----
  mapVMRegisters
  	"Map the oops in the interpreter's vm ``registers'' to their new values 
  	during garbage collection or a become: operation."
  	"Assume: All traced variables contain valid oops."
  	instructionPointer := instructionPointer - method. "*rel to method"
+ 	method := (objectMemory remap: method).
- 	self setMethod: (objectMemory remap: method).
  	instructionPointer := instructionPointer + method. "*rel to method"
  	(objectMemory isIntegerObject: messageSelector) ifFalse:
  		[messageSelector := objectMemory remap: messageSelector].
  	(objectMemory isIntegerObject: newMethod) ifFalse:
  		[newMethod := objectMemory remap: newMethod].
  	lkupClass := objectMemory remap: lkupClass!

Item was added:
+ ----- Method: VMMaker class>>generateConfiguration (in category 'configurations') -----
+ generateConfiguration
+ 	"VMMaker generateConfiguration"
+ 	| selectors |
+ 	selectors := ((self class organization listAtCategoryNamed: (self class whichCategoryIncludesSelector: thisContext selector)) copyWithout: thisContext selector) sort.
+ 	(UIManager default
+ 			chooseFrom: (selectors collect:
+ 							[:sel| (sel piecesCutWhere: [:a :b| a isLowercase and: [b isUppercase]]) allButFirst
+ 									fold: [:a :b| a, ' ', b]])
+ 			values: selectors) ifNotNil:
+ 		[:choice|
+ 		self perform: choice]!

Item was added:
+ ----- Method: VMMaker class>>generateNewspeakCogVM (in category 'configurations') -----
+ generateNewspeakCogVM
+ 	^VMMaker
+ 		generate: CoInterpreter
+ 		and: StackToRegisterMappingCogit"Cogit chooseCogitClass"
+ 		with: #(NewspeakVM true)
+ 		to: (FileDirectory default pathFromURI: 'oscogvm/nscogsrc')
+ 		platformDir: (FileDirectory default pathFromURI: '../Newspeak/newclosurevm/platforms')
+ 		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DSAPlugin DropPlugin
+ 					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin InflatePlugin JPEGReadWriter2Plugin
+ 					JPEGReaderPlugin LargeIntegersPlugin Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin
+ 					RePlugin SecurityPlugin SocketPlugin SoundPlugin SurfacePlugin ThreadedIA32FFIPlugin
+ 					UUIDPlugin UnixOSProcessPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!

Item was added:
+ ----- Method: VMMaker class>>generateNewspeakInterpreterVM (in category 'configurations') -----
+ generateNewspeakInterpreterVM
+ 	^VMMaker
+ 		generate: NewspeakInterpreter
+ 		to: (FileDirectory default pathFromURI: 'oscogvm/nssrc')
+ 		platformDir: (FileDirectory default pathFromURI: '../Newspeak/newclosurevm/platforms')
+ 		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DSAPlugin DropPlugin
+ 					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin InflatePlugin JPEGReadWriter2Plugin
+ 					JPEGReaderPlugin LargeIntegersPlugin Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin
+ 					RePlugin SecurityPlugin SocketPlugin SoundPlugin SurfacePlugin UUIDPlugin UnixOSProcessPlugin
+ 					VMProfileMacSupportPlugin Win32OSProcessPlugin)!

Item was added:
+ ----- Method: VMMaker class>>generateNewspeakStackVM (in category 'configurations') -----
+ generateNewspeakStackVM
+ 	^VMMaker
+ 		generate: StackInterpreter
+ 		with: #(NewspeakVM true)
+ 		to: (FileDirectory default pathFromURI: 'oscogvm/nsstacksrc')
+ 		platformDir: (FileDirectory default pathFromURI: '../Newspeak/newclosurevm/platforms')
+ 		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DSAPlugin DropPlugin
+ 					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin InflatePlugin JPEGReadWriter2Plugin
+ 					JPEGReaderPlugin LargeIntegersPlugin Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin
+ 					RePlugin SecurityPlugin SocketPlugin SoundPlugin SurfacePlugin UUIDPlugin UnixOSProcessPlugin
+ 					VMProfileMacSupportPlugin Win32OSProcessPlugin)!

Item was added:
+ ----- Method: VMMaker class>>generateSqueakCogSistaVM (in category 'configurations') -----
+ generateSqueakCogSistaVM
+ 	^VMMaker
+ 		generate: (Smalltalk at: ([:choices| choices at: (UIManager default chooseFrom: choices) ifAbsent: [^self]]
+ 									value: #(CoInterpreter CoInterpreterMT)))
+ 		and: SistaStackToRegisterMappingCogit
+ 		to: (FileDirectory default pathFromURI: 'cogvm/sistasrc')
+ 		platformDir: (FileDirectory default pathFromURI: 'cogvm/platforms')
+ 		excluding:#(BrokenPlugin DShowVideoDecoderPlugin NewsqueakIA32ABIPlugin NewsqueakIA32ABIPluginAttic
+ 					CroquetPlugin HostWindowPlugin SoundPlugin
+ 					QuicktimePlugin QVideoCodecPlugin QwaqMediaPlugin SlangTestPlugin TestOSAPlugin
+ 					FFIPlugin ThreadedARMFFIPlugin ThreadedFFIPlugin ThreadedPPCBEFFIPlugin
+ 					ReentrantARMFFIPlugin ReentrantFFIPlugin ReentrantIA32FFIPlugin ReentrantPPCBEFFIPlugin)!

Item was added:
+ ----- Method: VMMaker class>>generateSqueakCogVM (in category 'configurations') -----
+ generateSqueakCogVM
+ 	^VMMaker
+ 		generate: (Smalltalk at: ([:choices| choices at: (UIManager default chooseFrom: choices) ifAbsent: [^self]]
+ 									value: #(CoInterpreter CoInterpreterMT)))
+ 		and: StackToRegisterMappingCogit
+ 		to: (FileDirectory default pathFromURI: 'oscogvm/src')
+ 		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
+ 		including:#(	ADPCMCodecPlugin AsynchFilePlugin BalloonEnginePlugin B3DAcceleratorPlugin
+ 					BMPReadWriterPlugin BitBltSimulation BochsIA32Plugin CroquetPlugin DSAPlugin
+ 					DeflatePlugin DropPlugin FT2Plugin FFTPlugin FileCopyPlugin FilePlugin FloatArrayPlugin
+ 					FloatMathPlugin GeniePlugin HostWindowPlugin IA32ABIPlugin InternetConfigPlugin
+ 					JPEGReadWriter2Plugin JPEGReaderPlugin JoystickTabletPlugin KlattSynthesizerPlugin
+ 					LargeIntegersPlugin LocalePlugin MIDIPlugin MacMenubarPlugin Matrix2x3Plugin
+ 					MiscPrimitivePlugin Mpeg3Plugin QuicktimePlugin RePlugin SecurityPlugin SerialPlugin
+ 					SocketPlugin SoundCodecPlugin SoundGenerationPlugin SoundPlugin ThreadedIA32FFIPlugin
+ 					StarSqueakPlugin UUIDPlugin UnixOSProcessPlugin Win32OSProcessPlugin VMProfileMacSupportPlugin)!

Item was added:
+ ----- Method: VMMaker class>>generateSqueakStackVM (in category 'configurations') -----
+ generateSqueakStackVM
+ 	"No primitives since we can use those for the Cog VM"
+ 	^VMMaker
+ 		generate: StackInterpreter
+ 		to: (FileDirectory default pathFromURI: 'oscogvm/stacksrc')
+ 		platformDir: (FileDirectory default pathFromURI: 'cogvm/platforms')
+ 		excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])!



More information about the Vm-dev mailing list