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

commits at source.squeak.org commits at source.squeak.org
Mon Nov 18 18:56:39 UTC 2013


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

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

Name: VMMaker.oscog-eem.514
Author: eem
Time: 18 November 2013, 10:53:33.973 am
UUID: f0432404-2a48-4dfd-8d71-05ce4ddfe6e7
Ancestors: VMMaker.oscog-eem.513

Make sure BaseHeaderSize is defined in the Spur cogit.c.

Fix some type errors (tenuringThreshold needs to answer sqInt).
Fix safePrintStringOf:.  Can't have followForwarded: in an expression.

Bring Spur32BitMMLECoSimulator up-to-date.

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

Item was changed:
  ----- Method: CCodeGenerator>>emitCConstantsOn: (in category 'C code generator') -----
  emitCConstantsOn: aStream 
  	"Store the global variable declarations on the given stream."
  	| unused constList |
  	unused := constants keys asSet.
  	"Don't generate any defines for the externally defined constants,
  	 STACKVM, COGVM, COGMTVM et al, unless they're actually used."
  	(VMClass class>>#initializeMiscConstants) literalsDo:
  		[:lit|
  		(lit isVariableBinding and: [lit key isString]) ifTrue:
  			[unused add: lit key]].
  	methods do:
  		[:meth|
  		meth declarations keysDo:
  			[:v|
  			(meth typeFor: v in: self) ifNotNil:
  				[:type| unused remove: type ifAbsent: []]].
  		unused remove: meth returnType ifAbsent: [].
  		meth parseTree nodesDo:
  			[:n| n isConstant ifTrue: [unused remove: n name ifAbsent: []]]].
  	unused copy do:
  		[:const|
  		(variableDeclarations anySatisfy: [:value| value includesSubString: const]) ifTrue:
  			[unused remove: const ifAbsent: []]].
  	unused remove: #BytesPerWord ifAbsent: []. "force inclusion of BytesPerWord declaration"
+ 	unused remove: #BaseHeaderSize ifAbsent: []. "force inclusion of BaseHeaderSize declaration"
  	constList := constants keys reject: [:any| unused includes: any].
  	aStream cr; nextPutAll: '/*** Constants ***/'; cr.
  	(self sortStrings: constList) do:
  		[:varName| | node default value |
  		node := constants at: varName.
  		node name isEmpty ifFalse:
  			["If the definition includes a C comment, take it as is, otherwise convert the value from Smalltalk to C.
  			  Allow the class to provide an alternative definition, either of just the value or the whole shebang."
  			default := (node value isString and: [node value includesSubString: '/*'])
  							ifTrue: [node value]
  							ifFalse: [self cLiteralFor: node value name: varName].
  			value := vmClass
  						ifNotNil:
  							[(vmClass specialValueForConstant: node name default: default)
  								ifNotNil: [:specialDef| specialDef]
  								ifNil: [default]]
  						ifNil: [default].
  			value first ~= $# ifTrue:
  				[aStream nextPutAll: '#define '; nextPutAll: node name; space].
  			aStream nextPutAll: value; cr]].
  	aStream cr!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>checkForLeaks (in category 'accessing') -----
+ checkForLeaks
+ 	^checkForLeaks!

Item was changed:
  Spur32BitCoMemoryManager subclass: #Spur32BitMMLECoSimulator
+ 	instanceVariableNames: 'bootstrapping'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManagerSimulation'!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>bootstrapping (in category 'accessing') -----
+ bootstrapping
+ 	^bootstrapping!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>bootstrapping: (in category 'accessing') -----
+ bootstrapping: aBoolean
+ 	bootstrapping := aBoolean.
+ 	segmentManager initForBootstrap!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>exactFitCompact (in category 'compaction') -----
+ exactFitCompact
+ 	coInterpreter transcript nextPutAll: 'ef compacting...'; flush.
+ 	^super exactFitCompact!

Item was changed:
  ----- Method: Spur32BitMMLECoSimulator>>fetchPointer:ofObject: (in category 'object access') -----
  fetchPointer: fieldIndex ofObject: objOop
  	self assert: (self isForwarded: objOop) not.
+ 	self assert: (fieldIndex >= 0 and: [fieldIndex < (self numSlotsOfAny: objOop)
+ 				or: [fieldIndex = 0 "forwarders and free objs"]]).
- 	self assert: (fieldIndex >= 0 and: [fieldIndex < (self numSlotsOf: objOop)]).
  	^super fetchPointer: fieldIndex ofObject: objOop!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>firstFitCompact (in category 'compaction') -----
+ firstFitCompact
+ 	coInterpreter transcript nextPutAll: 'ff compacting...'; flush.
+ 	^super firstFitCompact!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>freeLists (in category 'spur bootstrap') -----
+ freeLists
+ 	^freeLists!

Item was removed:
- ----- Method: Spur32BitMMLECoSimulator>>freeStart (in category 'accessing') -----
- freeStart
- 	(#(Cogit SimpleStackBasedCogit StackToRegisterMappingCogit) includes: thisContext sender class name) ifTrue:
- 		[self halt].
- 	^super freeStart!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>growOldSpaceByAtLeast: (in category 'growing/shrinking memory') -----
+ growOldSpaceByAtLeast: minAmmount
+ 	"Attempt to grow memory by at least minAmmount.
+ 	 Answer the size of the new segment, or nil if the attempt failed.
+ 	 Override to not grow during the Spur image bootstrap."
+ 	^bootstrapping ifFalse:
+ 		[super growOldSpaceByAtLeast: minAmmount]!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>initialize (in category 'initialization') -----
+ initialize
+ 	super initialize.
+ 	bootstrapping := false!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>isIntegerObject: (in category 'object testing') -----
+ isIntegerObject: oop
+ 	"This list records the valid senders of isIntegerObject: as we replace uses of
+ 	  isIntegerObject: by isImmediate: where appropriate."
+ 	| sel |
+ 	sel := thisContext sender method selector.
+ 	(#(	DoIt
+ 		DoItIn:
+ 		on:do: "from the debugger"
+ 		makeBaseFrameFor:
+ 		quickFetchInteger:ofObject:
+ 		frameOfMarriedContext:
+ 		objCouldBeClassObj:
+ 		isMarriedOrWidowedContext:
+ 		shortPrint:
+ 		bytecodePrimAt
+ 		bytecodePrimAtPut
+ 		commonAt:
+ 		commonAtPut:
+ 		loadFloatOrIntFrom:
+ 		positive32BitValueOf:
+ 		primitiveExternalCall
+ 		checkedIntegerValueOf:
+ 		bytecodePrimAtPut
+ 		commonAtPut:
+ 		primitiveVMParameter
+ 		checkIsStillMarriedContext:currentFP:
+ 		displayBitsOf:Left:Top:Right:Bottom:
+ 		fetchStackPointerOf:
+ 		primitiveContextAt
+ 		primitiveContextAtPut
+ 		subscript:with:storing:format:
+ 		printContext:
+ 		compare31or32Bits:equal:
+ 		signed64BitValueOf:
+ 		primDigitMultiply:negative:
+ 		digitLength:
+ 		isNegativeIntegerValueOf:
+ 		magnitude64BitValueOf:
+ 		primitiveMakePoint
+ 		primitiveAsCharacter
+ 		primitiveInputSemaphore
+ 		baseFrameReturn
+ 		primitiveExternalCall
+ 		primDigitCompare:
+ 		isLiveContext:
+ 		numPointerSlotsOf:
+ 		fileValueOf:
+ 		loadBitBltDestForm
+ 		fetchIntOrFloat:ofObject:ifNil:
+ 		fetchIntOrFloat:ofObject:
+ 		loadBitBltSourceForm
+ 		loadPoint:from:
+ 		primDigitAdd:
+ 		primDigitSubtract:
+ 		positive64BitValueOf:
+ 		digitBitLogic:with:opIndex:
+ 		signed32BitValueOf:
+ 		isNormalized:
+ 		primDigitDiv:negative:
+ 		bytesOrInt:growTo:
+ 		primitiveNewMethod
+ 		isCogMethodReference:
+ 		functionForPrimitiveExternalCall:
+ 		genSpecialSelectorArithmetic
+ 		genSpecialSelectorComparison
+ 		ensureContextHasBytecodePC:
+ 		instVar:ofContext:
+ 		ceBaseFrameReturn:
+ 		inlineCacheTagForInstance:
+ 		primitiveObjectAtPut
+ 		commonVariable:at:put:cacheIndex:
+ 		primDigitBitShiftMagnitude:
+ 		externalInstVar:ofContext:
+ 		primitiveGrowMemoryByAtLeast
+ 		primitiveFileSetPosition) includes: sel) ifFalse:
+ 		[self halt].
+ 	^super isIntegerObject: oop!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>isNonIntegerObject: (in category 'object testing') -----
+ isNonIntegerObject: oop
+ 	"This list records the valid senders of isNonIntegerObject: as we replace uses of
+ 	  isNonIntegerObject: by isNonImmediate: where appropriate."
+ 	(#(	on:do: "from the dbeugger"
+ 		reverseDisplayFrom:to:
+ 		primitiveObjectAtPut
+ 		isCogMethodReference:) includes: thisContext sender method selector) ifFalse:
+ 		[self halt].
+ 	^super isNonIntegerObject: oop!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>markAndTrace: (in category 'gc - global') -----
+ markAndTrace: objOop
+ 	"objOop = 16rB26020 ifTrue: [self halt].
+ 	objOop = 16rB25FD8 ifTrue: [self halt].
+ 	objOop = 16rB26010 ifTrue: [self halt]."
+ 	^super markAndTrace: objOop!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>memoryBaseForImageRead (in category 'snapshot') -----
+ memoryBaseForImageRead
+ 	"Answer the address to read the image into.  Override so that when bootstrapping,
+ 	 the segmentManager's segments are undisturbed in adjustSegmentSwizzlesBy:"
+ 	^bootstrapping
+ 		ifTrue: [0] 
+ 		ifFalse: [super memoryBaseForImageRead]!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>numClassTablePages (in category 'spur bootstrap') -----
+ numClassTablePages
+ 	^numClassTablePages!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>setIsMarkedOf:to: (in category 'header access') -----
+ setIsMarkedOf: objOop to: aBoolean
+ 	"objOop = 16rB26020 ifTrue: [self halt]."
+ 	super setIsMarkedOf: objOop to: aBoolean.
+ 	"(aBoolean
+ 	 and: [(self isContextNonImm: objOop)
+ 	 and: [(coInterpreter
+ 			checkIsStillMarriedContext: objOop
+ 			currentFP: coInterpreter framePointer)
+ 	 and: [(coInterpreter stackPages stackPageFor: (coInterpreter frameOfMarriedContext: objOop)) trace = 0]]]) ifTrue:
+ 		[self halt]"!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>testObjStackDo (in category 'ad-hoc tests') -----
+ testObjStackDo
+ 	| size them seqA seqB seqC rs |
+ 	self initializeWeaklingStack; emptyObjStack: weaklingStack.
+ 	self assert: (self topOfObjStack: weaklingStack) isNil.
+ 	self assert: (self capacityOfObjStack: weaklingStack) >= ObjStackLimit.
+ 	seqA := (1 to: ObjStackLimit * 5 // 2) collect: [:i| self integerObjectOf: i].
+ 	seqA do: [:it| self noCheckPush: it onObjStack: weaklingStack].
+ 	them := Set new.
+ 	size := self objStack: weaklingStack from: 0 do: [:it| them add: it].
+ 	self assert: size = seqA size.
+ 	self assert: (them asSortedCollection asArray = seqA).
+ 	self assert: (self isValidObjStack: weaklingStack).
+ 	seqB := (ObjStackLimit * 5 // 2 + 1 to: ObjStackLimit * 10 // 2) collect: [:i| self integerObjectOf: i].
+ 	self assert: seqA size = seqB size.
+ 	rs := seqB readStream.
+ 	them := Set new.
+ 	size := self objStack: weaklingStack from: 0 do:
+ 				[:it|
+ 				them add: it.
+ 				self noCheckPush: rs next onObjStack: weaklingStack].
+ 	self assert: size = seqA size.
+ 	self assert: rs atEnd.
+ 	self objStack: weaklingStack from: size do:
+ 		[:it| them add: it].
+ 	seqC := (seqA, seqB) sort.
+ 	self assert: them asSortedCollection asArray = seqC!

Item was changed:
  ----- Method: SpurMemoryManager>>safePrintStringOf: (in category 'debug printing') -----
  safePrintStringOf: oop
  	| target |
+ 	(self isOopForwarded: oop)
+ 		ifTrue: [target := self followForwarded: oop]
+ 		ifFalse: [target := oop].
- 	target := (self isOopForwarded: oop)
- 				ifTrue: [self followForwarded: oop]
- 				ifFalse: [oop].
  	^coInterpreter printStringOf: target!

Item was changed:
  ----- Method: SpurMemoryManager>>tenuringThreshold (in category 'accessing') -----
  tenuringThreshold
  	"In the scavenger the tenuring threshold is effectively a number of bytes of objects,
  	 accessed as a proportion of pastSpace from 0 to 1.   In the Squeak image the tenuring
+ 	 threshold is an object count. Marry the two notions by multiplying the proportion by
- 	 threshold is an object count. Marry the two notions  by multiplying the proportion by
  	 the size of pastSpace and dividing by the average object size, as derived from observation."
  	| averageObjectSize |
  	averageObjectSize := 8 * self wordSize.
+ 	^(scavenger scavengerTenuringThreshold * scavenger pastSpaceBytes // averageObjectSize) asInteger!
- 	^scavenger scavengerTenuringThreshold * scavenger pastSpaceBytes // averageObjectSize!



More information about the Vm-dev mailing list