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

commits at source.squeak.org commits at source.squeak.org
Sat Mar 31 20:39:26 UTC 2012


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

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

Name: VMMaker.oscog-eem.153
Author: eem
Time: 31 March 2012, 1:36:50.547 pm
UUID: 8ace2909-a8c0-4bcf-8274-55850a71487d
Ancestors: VMMaker.oscog-eem.152

Fix header file generation for bytecodeSetSelector.
Make sure BytesPerOop is initialized in initializeWithOptions:.
Add longPrintReferencesTo:.
Search for configurations in package extensions to VMMaker.
Comment fixes.

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

Item was changed:
  ----- Method: CCodeGenerator>>emitGlobalCVariablesOn: (in category 'C code generator') -----
  emitGlobalCVariablesOn: aStream
  	"Store the global variable declarations on the given stream."
  
  	aStream cr; nextPutAll: '/*** Global Variables ***/'; cr.
  	(self sortStrings: (variables select: [:v| vmClass mustBeGlobal: v])) do:
  		[:var | | varString decl |
  		varString := var asString.
  		decl := variableDeclarations at: varString ifAbsent: ['sqInt ' , varString].
+ 		decl first == $# "support cgen var: #bytecodeSetSelector declareC: '#define bytecodeSetSelector 0' hack"
+ 			ifTrue:
+ 				[aStream nextPutAll: decl; cr]
+ 			ifFalse:
+ 				[((decl includesSubString: ' private ')
+ 				  or: [decl beginsWith: 'static']) ifFalse: "work-around hack to prevent localization of variables only referenced once."
+ 					[(decl includes: $=) ifTrue:
+ 						[decl := decl copyFrom: 1 to: (decl indexOf: $=) - 1].
+ 					aStream
+ 						nextPutAll: decl;
+ 						nextPut: $;;
+ 						cr]]].
- 		((decl includesSubString: ' private ')
- 		  or: [decl beginsWith: 'static']) ifFalse: "work-around hack to prevent localization of variables only referenced once."
- 			[(decl includes: $=) ifTrue:
- 				[decl := decl copyFrom: 1 to: (decl indexOf: $=) - 1].
- 			aStream
- 				nextPutAll: decl;
- 				nextPut: $;;
- 				cr]].
  	aStream cr!

Item was changed:
  ----- Method: Interpreter class>>initializeWithOptions: (in category 'initialization') -----
  initializeWithOptions: optionsDictionary
  	"Interpreter initializeWithOptions: Dictionary new"
  
  	super initializeWithOptions: optionsDictionary.  "initialize ObjectMemory constants"
+ 	self initializeMiscConstantsWith: optionsDictionary. "must preceed other initialization."
- 	self initializeMiscConstants. "must preceed other initialization."
  	self initializeAssociationIndex.
  	self initializeBytecodeTable.
  	self initializeCaches.
  	self initializeCharacterIndex.
  	self initializeCharacterScannerIndices.
  	self initializeClassIndices.
  	self initializeCompilerHooks.
  	self initializeContextIndices.
  	self initializeDirectoryLookupResultCodes.
  	self initializeMessageIndices.
  	self initializeMethodIndices.
  	self initializePointIndices.
  	self initializePrimitiveTable.
  	self initializeSchedulerIndices.
  	self initializeSmallIntegers.
  	self initializeStreamIndices!

Item was added:
+ ----- Method: NewObjectMemory>>longPrintReferencesTo: (in category 'debug printing') -----
+ longPrintReferencesTo: anOop
+ 	"Scan the heap long printing the oops of any and all objects that refer to anOop"
+ 	| oop i prntObj |
+ 	<api>
+ 	prntObj := false.
+ 	oop := self firstAccessibleObject.
+ 	[oop = nil] whileFalse:
+ 		[((self isPointers: oop) or: [self isCompiledMethod: oop]) ifTrue:
+ 			[(self isCompiledMethod: oop)
+ 				ifTrue:
+ 					[i := (self literalCountOf: oop) - 1]
+ 				ifFalse:
+ 					[(self isContext: oop)
+ 						ifTrue: [i := CtxtTempFrameStart + (self fetchStackPointerOf: oop) - 1]
+ 						ifFalse: [i := (self lengthOf: oop) - 1]].
+ 			[i >= 0] whileTrue:
+ 				[anOop = (self fetchPointer: i ofObject: oop) ifTrue:
+ 					[self printHex: oop; print: ' @ '; printNum: i; cr.
+ 					 prntObj := true.
+ 					 i := 0].
+ 				 i := i - 1].
+ 			prntObj ifTrue:
+ 				[prntObj := false.
+ 				 coInterpreter longPrintOop: oop]].
+ 		 oop := self accessibleObjectAfter: oop]!

Item was changed:
  ----- Method: ObjectMemory class>>initializeWithOptions: (in category 'initialization') -----
  initializeWithOptions: optionsDictionary
  	"ObjectMemory initializeWithOptions: Dictionary new"
  
+ 	self initBytesPerWord: (optionsDictionary at: #BytesPerWord ifAbsent: [4]).
+ 	BytesPerOop := optionsDictionary at: #BytesPerOop ifAbsent: [BytesPerWord].
- 	self initBytesPerWord: (optionsDictionary at: #BytesPerWord ifAbsent: [4])..
  
  	"Translation flags (booleans that control code generation via conditional translation):"
  	"generate assertion checks"
  	DoAssertionChecks := optionsDictionary at: #DoAssertionChecks ifAbsent: [false].
  	DoExpensiveAssertionChecks := optionsDictionary at: #DoExpensiveAssertionChecks ifAbsent: [false].
  
  	self initializeSpecialObjectIndices.
  	self initializeCompactClassIndices.
  	self initializePrimitiveErrorCodes.
  	self initializeObjectHeaderConstants.
  
  	NilContext := 1.  "the oop for the integer 0; used to mark the end of context lists"
  
  	RemapBufferSize := 25.
  	RootTableSize := 2500.  	"number of root table entries (4 bytes/entry)"
  	RootTableRedZone := RootTableSize - 100.	"red zone of root table - when reached we force IGC"
  	WeakRootTableSize := RootTableSize + RemapBufferSize + 100.
  
  	"tracer actions"
  	StartField := 1.
  	StartObj := 2.
  	Upward := 3.
  	Done := 4.
  
  	ExtraRootSize := 2048. "max. # of external roots"!

Item was changed:
+ ----- Method: ObjectMemory>>printInstancesOf: (in category 'debug printing') -----
- ----- Method: ObjectMemory>>printInstancesOf: (in category 'memory access') -----
  printInstancesOf: aClassOop
  	"Scan the heap printing the oops of any and all objects that are instances of aClassOop"
  	| oop |
  	<api>
  	oop := self firstAccessibleObject.
  	[oop = nil] whileFalse:
  		[(self fetchClassOfNonInt: oop) = aClassOop ifTrue:
  			[self printHex: oop; cr].
  		 oop := self accessibleObjectAfter: oop]!

Item was changed:
+ ----- Method: ObjectMemory>>printMethodReferencesTo: (in category 'debug printing') -----
- ----- Method: ObjectMemory>>printMethodReferencesTo: (in category 'memory access') -----
  printMethodReferencesTo: anOop
  	"Scan the heap printing the oops of any and all objects that refer to anOop"
  	| oop i |
  	<api>
  	oop := self firstAccessibleObject.
  	[oop = nil] whileFalse:
  		[(self isCompiledMethod: oop) ifTrue:
  			[i := (self literalCountOf: oop) - 1.
  			 [i >= 0] whileTrue:
  				[anOop = (self fetchPointer: i ofObject: oop) ifTrue:
  					[self printHex: oop; print: ' @ '; printNum: i; cr.
  					 i := 0].
  				 i := i - 1]].
  		 oop := self accessibleObjectAfter: oop]!

Item was changed:
+ ----- Method: ObjectMemory>>printReferencesTo: (in category 'debug printing') -----
- ----- Method: ObjectMemory>>printReferencesTo: (in category 'memory access') -----
  printReferencesTo: anOop
  	"Scan the heap printing the oops of any and all objects that refer to anOop"
  	| oop i |
  	<api>
  	oop := self firstAccessibleObject.
  	[oop = nil] whileFalse:
  		[((self isPointers: oop) or: [self isCompiledMethod: oop]) ifTrue:
  			[(self isCompiledMethod: oop)
  				ifTrue:
  					[i := (self literalCountOf: oop) - 1]
  				ifFalse:
  					[(self isContext: oop)
  						ifTrue: [i := CtxtTempFrameStart + (self fetchStackPointerOf: oop) - 1]
  						ifFalse: [i := (self lengthOf: oop) - 1]].
  			[i >= 0] whileTrue:
  				[anOop = (self fetchPointer: i ofObject: oop) ifTrue:
  					[self printHex: oop; print: ' @ '; printNum: i; cr.
  					 i := 0].
  				 i := i - 1]].
  		 oop := self accessibleObjectAfter: oop]!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genMustBeBooleanTrampolineFor:called: (in category 'initialization') -----
  genMustBeBooleanTrampolineFor: boolean called: trampolineName
+ 	"This can be entered in one of two states, depending on SendNumArgsReg. See
+ 	 e.g. genJumpIf:to:.  If SendNumArgsReg is non-zero then this has been entered via
+ 	 the initial test of the counter in the jump executed count (i.e. the counter has
+ 	 tripped).  In this case TempReg contains the boolean to be tested and should not
+ 	 be offset, and ceCounterTripped should be invoked with the unoffset TempReg.
+ 	 If SendNumArgsReg is zero then this has been entered for must-be-boolean
+ 	 processing. TempReg has been offset by boolean and must be corrected and
+ 	 ceSendMustBeBoolean: invoked with the corrected value."
- 	"THis can be entered in one of two states, depending on SendNumArgsReg.
- 	 If SendNumArgsReg is non-zero then this has been entered via the initial test of
- 	 the counted in the jump executed count.  In this case TempReg contains the
- 	 boolean to be tested and should not be offset, and ceCounterTripped should be
- 	 invoked with the unoffset TempReg.
- 	 If SendNumArgsReg is zero then this has been entered for must-be-boolean processing.
- 	 TempReg has been offset by boolean and must be corrected and ceSendMustBeBoolean:
- 	 invoked with the offset value."
  	<var: #trampolineName type: #'char *'>
  	| jumpMBB |
  	<var: #jumpMBB type: #'AbstractInstruction *'>
  	<inline: false>
  	opcodeIndex := 0.
  	self CmpCq: 0 R: SendNumArgsReg.
  	jumpMBB := self JumpZero: 0.
  	self compileTrampolineFor: #ceCounterTripped: asSymbol
  		callJumpBar: true
  		numArgs: 1
  		arg: TempReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		resultReg: nil.
  	"If the objectRepresentation does want true & false to be mobile then we need to record these addresses."
  	self assert: (objectRepresentation shouldAnnotateObjectReference: boolean) not.
  	jumpMBB jmpTarget: (self AddCq: boolean R: TempReg).
  	^self genTrampolineFor: #ceSendMustBeBoolean: asSymbol
  		called: trampolineName
  		callJumpBar: true
  		numArgs: 1
  		arg: TempReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: StackInterpreter>>markContextAsDead: (in category 'frame access') -----
  markContextAsDead: oop
  	"Mark the argument, which must be a context, married, widowed or single, as dead.
  	 For married or widowed contexts this breaks any link to the spouse and makes the context single.
+ 	 For all contexts, marks the context as inactive/having been returned from."
- 	 For all contexts, marks the comtext as inactive/having been returned from."
  	<inline: true>
  	self assert: (self isContext: oop).
  	objectMemory
  		storePointerUnchecked: SenderIndex ofObject: oop withValue: objectMemory nilObject;
  		storePointerUnchecked: InstructionPointerIndex ofObject: oop withValue: objectMemory nilObject!

Item was changed:
  ----- Method: VMMaker class>>generateConfiguration (in category 'configurations') -----
  generateConfiguration
  	"VMMaker generateConfiguration"
+ 	| configCategoryName selectors |
+ 	configCategoryName := self class whichCategoryIncludesSelector: thisContext selector.
+ 	selectors := Set new.
+ 	self class organization categories do:
+ 		[:cat|
+ 		(cat endsWith: configCategoryName) ifTrue:
+ 			[selectors addAll: (self class organization listAtCategoryNamed: cat)]].
+ 	selectors remove: thisContext selector.
+ 	selectors := selectors asArray sort.
- 	| 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]!



More information about the Vm-dev mailing list