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

commits at source.squeak.org commits at source.squeak.org
Fri Dec 5 02:32:28 UTC 2014


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

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

Name: VMMaker.oscog-eem.965
Author: eem
Time: 4 December 2014, 6:29:43.217 pm
UUID: e8fc6a7f-6a04-4e57-a9f7-2ca56387d4d8
Ancestors: VMMaker.oscog-eem.964

Fix in-image PC mapping testing.

Add Spur64BitCoMemoryManager.

Nuke the now obsolete withoutForwardingOn:and:sendToCogit:

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

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade class>>forCogit: (in category 'instance creation') -----
  forCogit: aCogit
  	| class |
  	class := self allSubclasses
+ 				detect: [:subclass|
+ 						aCogit class objectMemoryClass objectRepresentationClass
+ 						== subclass objectRepresentationClass]
- 				detect: [:subclass| aCogit class objectMemoryClass = subclass objectRepresentationClass objectMemoryClass]
  				ifNone: [self error: 'cannot find subclass for the Cogit''s objectRepresentation and/or objectMemory'].
  	^class new
  		cogit: aCogit;
  		yourself!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>bytesPerOop (in category 'accessing') -----
+ bytesPerOop
+ 	^objectMemory bytesPerOop!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>initialize (in category 'initialize-release') -----
  initialize
  	memory := (VMBIGENDIAN
  					ifTrue: [Bitmap]
  					ifFalse: [LittleEndianBitmap]) new: 1024*1024/4.
  	objectMemory := self class objectMemoryClass simulatorClass new.
+ 	objectMemory memory: memory.
  	objectMemory
  		initializeFreeSpaceForFacadeFrom: self startOfMemory
  		to: self variablesBase.
- 	objectMemory memory: memory.
  	coInterpreter := CoInterpreter new.
  	coInterpreter
  		instVarNamed: 'objectMemory'
  			put: objectMemory;
  		instVarNamed: 'primitiveTable'
  			put: (CArrayAccessor on: CoInterpreter primitiveTable copy).
  	variables := Dictionary new.
  	#('stackLimit') do:
  		[:l| self addressForLabel: l].
  	self initializeObjectMap!

Item was removed:
- ----- Method: NewCoObjectMemory>>withoutForwardingOn:and:sendToCogit: (in category 'cog jit support') -----
- withoutForwardingOn: obj1 and: obj2 sendToCogit: selector
- 	"For the purposes of become: send selector to the cogit with obj1 and obj2 and
- 	 answer the result. Undo forwarding for the selector, but redo forwarding after since
- 	 become:'s restoreHeadersAfter*Become* methods expect to be able to restore."
- 	<api>
- 	<var: #selector declareC: 'sqInt (*selector)(sqInt,sqInt)'>
- 	| savedHeaderA savedHeaderB result |
- 	savedHeaderA := self baseHeader: obj1.
- 	self baseHeader: obj1 put: (self headerWhileForwardingOf: obj1).
- 	savedHeaderB := self baseHeader: obj2.
- 	self baseHeader: obj2 put: (self headerWhileForwardingOf: obj2).
- 
- 	result := cogit perform: selector with: obj1 with: obj2.
- 
- 	self baseHeader: obj1 put: savedHeaderA.
- 	self baseHeader: obj2 put: savedHeaderB.
- 	^result!

Item was removed:
- ----- Method: Spur32BitCoMemoryManager>>withoutForwardingOn:and:sendToCogit: (in category 'cog jit support') -----
- withoutForwardingOn: obj1 and: obj2 sendToCogit: selector
- 	"For the purposes of become: send selector to the cogit with obj1 and obj2
- 	 and answer the result.  Undo forwarding for the selector."
- 	<api>
- 	<var: #selector declareC: 'sqInt (*selector)(sqInt,sqInt)'>
- 	| targetA targetB |
- 	targetA := self followForwarded: obj1.
- 	targetB := self followForwarded: obj2.
- 	^cogit perform: selector with: targetA with: targetB!

Item was added:
+ Spur64BitMemoryManager subclass: #Spur64BitCoMemoryManager
+ 	instanceVariableNames: 'cogit'
+ 	classVariableNames: ''
+ 	poolDictionaries: 'CogMethodConstants'
+ 	category: 'VMMaker-SpurMemoryManager'!
+ 
+ !Spur64BitCoMemoryManager commentStamp: 'eem 11/25/2013 14:47' prior: 0!
+ Spur64BitCoMemoryManager is a refinement of Spur64BitMemoryManager that supports the CoInterpreter/Cogit just-in-time compiler.  The significant difference from Spur64BitMemoryManager is the memory layout.  Spur64BitCoMemoryManager adds the cogCodeZone beneath newSpace:
+ 
+ low address:
+ 	cogCodeZone:
+ 		generated run-time
+ 		cog methods
+ 		free space
+ 		young referrers
+ 	newSpace:
+ 		past/future survivor space
+ 		future/past survivor space
+ 		eden
+ 	first oldSpace segment
+ 	...
+ 	subsequent oldSpace segment
+ high address:
+ 
+ It would be convenient if the code zone were placed between newSpace and oldSpace; then Cog methods could be onsidered neither old nor young, filtering them out of copyAndForward: and the store check with single bounds checks.  But the CoInterpreter already assumes Cog methods are less than all objects (e.g. in its isMachineCodeFrame:).  If the dynamic frequency of isMachineCodeFrame: is higher (likely because this is used in e.g. scanning for unwind protects in non-local return) then it should keep the single bounds check.  So the coder zone remains beneath newSpace and Spur64BitCoMemoryManager ocerrides isReallyYoungObject: to filter-out Cog methods for copyAndForward:.
+ 
+ Instance Variables
+ 	cogit:		<SimpleStackBasedCogit or subclass>
+ 
+ cogit
+ 	- the just-in-time compiler!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager class>>exportAPISelectors: (in category 'translation') -----
+ exportAPISelectors: options
+ 	^(Set withAll: (self exportAPISelectorsFor: self))
+ 		addAll: (SpurGenerationScavenger exportAPISelectors: options);
+ 		yourself!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager class>>objectRepresentationClass (in category 'accessing class hierarchy') -----
+ objectRepresentationClass
+ 	^CogObjectRepresentationFor64BitSpur!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager class>>simulatorClass (in category 'simulation only') -----
+ simulatorClass
+ 	^Spur64BitMMLECoSimulator!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>assimilateNewSegment: (in category 'growing/shrinking memory') -----
+ assimilateNewSegment: segInfo
+ 	"Update after adding a segment.
+ 	 Here we make sure the new segment is not executable."
+ 	<var: #segInfo type: #'SpurSegmentInfo *'>
+ 	super assimilateNewSegment: segInfo.
+ 	coInterpreter sqMakeMemoryNotExecutableFrom: segInfo segStart To: segInfo segLimit!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>ceClassAtIndex: (in category 'trampolines') -----
+ ceClassAtIndex: classIndex
+ 	<api>
+ 	| result |
+ 	result := self classAtIndex: classIndex.
+ 	self assert: (coInterpreter addressCouldBeClassObj: result).
+ 	^result!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>ceSheduleScavenge (in category 'trampolines') -----
+ ceSheduleScavenge
+ 	<api>
+ 	self assert: freeStart >= scavengeThreshold.
+ 	self scheduleScavenge!

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

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>checkMemoryMap (in category 'debug support') -----
+ checkMemoryMap
+ 	"Override to check that Cog methods are considered neither young nor old.
+ 	 Being young would cause them to be scavenged.
+ 	 Being old would cause them to be remembered if stored into (but wait, they don't get stored into)."
+ 
+ 	self assert: (self isYoungObject: newSpaceStart).
+ 	self assert: (self isYoungObject: newSpaceLimit - self wordSize).
+ 	self assert: (self isOldObject: newSpaceStart) not.
+ 	self assert: (self isOldObject: newSpaceLimit - self wordSize) not.
+ 	self assert: (self isYoungObject: newSpaceLimit) not.
+ 	self assert: (self isYoungObject: oldSpaceStart) not.
+ 	self assert: (self isYoungObject: endOfMemory) not.
+ 	self assert: (self isOldObject: oldSpaceStart).
+ 	self assert: (self isOldObject: endOfMemory).
+ 
+ 	"we would like the following to be true, but we either choose one boundary check for
+ 	 cogMethods vs objects (isMachineCodeFrame: et al) or one boundary check for
+ 	 copyAndForward:.  We can't have both, and the former is likely the highest dynamic
+ 	 frequency."
+ 	false ifTrue:
+ 		[self assert: (self isYoungObject: cogit minCogMethodAddress) not.
+ 		 self assert: (self isYoungObject: cogit maxCogMethodAddress) not].
+ 	self assert: (self isOldObject: cogit minCogMethodAddress) not.
+ 	self assert: (self isOldObject: cogit maxCogMethodAddress) not!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>clearLeakMapAndMapAccessibleObjects (in category 'debug support') -----
+ clearLeakMapAndMapAccessibleObjects
+ 	"Perform an integrity/leak check using the heapMap.  Set a bit at each object's header.
+ 	 Override to set a bit at each Cog method"
+ 	super clearLeakMapAndMapAccessibleObjects.
+ 	cogit addCogMethodsToHeapMap!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>ensureNoForwardedLiteralsIn: (in category 'cog jit support') -----
+ ensureNoForwardedLiteralsIn: aMethodObj
+ 	"Ensure there are no forwarded literals in the argument."
+ 	<api>
+ 	self followForwardedObjectFields: aMethodObj toDepth: 0!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>freeStart: (in category 'cog jit support') -----
+ freeStart: aValue
+ 	self assert: (aValue >= scavenger eden start and: [aValue < (scavengeThreshold + 1024)]).
+ 	self assert: (scavengeThreshold max: aValue) + coInterpreter interpreterAllocationReserveBytes <= scavenger eden limit.
+ 	^freeStart := aValue!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>freeStartAddress (in category 'trampoline support') -----
+ freeStartAddress
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^self cCode: [(self addressOf: freeStart) asUnsignedInteger]
+ 		inSmalltalk: [cogit simulatedReadWriteVariableAddress: #freeStart in: self]!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>getScavengeThreshold (in category 'cog jit support') -----
+ getScavengeThreshold
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^scavengeThreshold!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>headerWhileForwardingOf: (in category 'garbage collection') -----
+ headerWhileForwardingOf: aCompiledMethodObjOop
+ 	"Answer the header of the argument even though
+ 	 it may have its header word in a forwarding block
+ 	 (which shouldn't happen with Spur)."
+ 	self assert: (self isForwarded: aCompiledMethodObjOop) not.
+ 	^self baseHeader: aCompiledMethodObjOop!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>ifAProxy:updateCopy: (in category 'image segment in/out') -----
+ ifAProxy: objOop updateCopy: copy
+ 	"If the obejct being copied to the segment is weird and has exotic state,
+ 	 i.e. a married context or a jitted method, update the copy with the vanilla state."
+ 
+ 	super ifAProxy: objOop updateCopy: copy.
+ 	(self isCompiledMethod: objOop) ifTrue:
+ 		[| methodHeader |
+ 		 methodHeader := coInterpreter rawHeaderOf: objOop.
+ 		 (coInterpreter isCogMethodReference: methodHeader) ifTrue:
+ 			[self storePointerUnchecked: HeaderIndex
+ 				ofObject: copy
+ 				withValue: (coInterpreter cCoerceSimple: methodHeader to: #'CogMethod *') methodHeader]]!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>initializeFreeSpaceForFacadeFrom:to: (in category 'simulation only') -----
+ initializeFreeSpaceForFacadeFrom: base to: limit
+ 	"c.f. initializeFreeSpacePostLoad: freeListObj."
+ 	| freeListObj freeBytes |
+ 	newSpaceLimit := oldSpaceStart := freeStart := base.
+ 	endOfMemory := scavengeThreshold := limit.
+ 	segmentManager initSegmentForInImageCompilationFrom: base to: limit.
+ 	freeListObj := self allocateSlots: self numFreeLists
+ 						format: self wordIndexableFormat
+ 						classIndex: self wordSizeClassIndexPun.
+ 	freeLists := self firstIndexableField: freeListObj.
+ 	freeListsMask := 0.
+ 	0 to: self numFreeLists - 1 do:
+ 		[:i|
+ 		(freeLists at: i) ~= 0 ifTrue:
+ 			[freeListsMask := freeListsMask bitOr: (1 << i).
+ 			 freeLists at: i put: (segmentManager swizzleObj: (freeLists at: i))]].
+ 	freeBytes := segmentManager lastSegment segLimit - self bridgeSize - freeStart.
+ 	freeLists at: 0 put: (self initFreeChunkWithBytes: freeBytes at: freeStart).
+ 	totalFreeOldSpace := freeBytes!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>isForwardedClassIndex: (in category 'class table') -----
+ isForwardedClassIndex: maybeClassIndex
+ 	"A lenient tester of forwarded class indices for inline cache management in the Cogit."
+ 	<api>
+ 	| classTablePage entry |
+ 	maybeClassIndex asUnsignedInteger >= self classTableRootSlots ifTrue:
+ 		[^false].
+ 	classTablePage := self fetchPointer: maybeClassIndex >> self classTableMajorIndexShift
+ 							ofObject: hiddenRootsObj.
+ 	classTablePage = nilObj ifTrue:
+ 		[^false].
+ 	entry := self
+ 				fetchPointer: (maybeClassIndex bitAnd: self classTableMinorIndexMask)
+ 				ofObject: classTablePage.
+ 	^self isForwarded: entry!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>isImmediateClass: (in category 'cog jit support') -----
+ isImmediateClass: classObj
+ 	<api>
+ 	^(self instSpecOfClass: classObj) = self instSpecForImmediateClasses!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>isReallyYoungObject: (in category 'object testing') -----
+ isReallyYoungObject: objOop
+ 	<api>
+ 	"Answer if obj is young. Require that obj is non-immediate. Override to filter-out Cog methods"
+ 	self assert: (self isNonImmediate: objOop).
+ 	^(self oop: objOop isLessThan: newSpaceLimit)
+ 	  and: [self oop: objOop isGreaterThanOrEqualTo: newSpaceStart]!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>methodHeaderOf: (in category 'growing/shrinking memory') -----
+ methodHeaderOf: methodObj
+ 	"Answer the method header of a CompiledMethod object.
+ 	 If the method has been cogged then the header is a pointer to
+ 	 the CogMethod and the real header will be stored in the CogMethod."
+ 	<api>
+ 	<inline: true>
+ 	| header |
+ 	self assert: (self isCompiledMethod: methodObj).
+ 	header := self fetchPointer: HeaderIndex ofObject: methodObj.
+ 	^(self isIntegerObject: header)
+ 		ifTrue: [header]
+ 		ifFalse:
+ 			[self assert: header asUnsignedInteger < newSpaceStart.
+ 			 self assert: (coInterpreter cCoerceSimple: header to: #'CogMethod *') objectHeader
+ 						= self nullHeaderForMachineCodeMethod..
+ 			(coInterpreter cCoerceSimple: header to: #'CogMethod *') methodHeader]!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>nullHeaderForMachineCodeMethod (in category 'garbage collection') -----
+ nullHeaderForMachineCodeMethod
+ 	<api>
+ 	<returnTypeC: #sqLong>
+ 	^(self firstLongFormat << self formatShift)
+ 	+ (1 << self markedBitFullShift)
+ 	+ ClassBitmapCompactIndex!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>remember: (in category 'cog jit support') -----
+ remember: objOop
+ 	<doNotGenerate>
+ 	^scavenger remember: objOop!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>scavengeThresholdAddress (in category 'trampoline support') -----
+ scavengeThresholdAddress
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^self cCode: [(self addressOf: scavengeThreshold) asUnsignedInteger]
+ 		inSmalltalk: [cogit simulatedReadWriteVariableAddress: #getScavengeThreshold in: self]!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>smallIntegerTag (in category 'cog jit support') -----
+ smallIntegerTag
+ 	<api>
+ 	^1!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>startOfMemory (in category 'accessing') -----
+ startOfMemory
+ 	"Return the start of object memory.  This is immediately after the native code zone.
+ 	 N.B. the stack zone is alloca'ed. Use a macro so as not to punish the debug VM."
+ 	<api>
+ 	<cmacro: '() heapBase'>
+ 	<returnTypeC: #usqInt>
+ 	^coInterpreter heapBase!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>unalignedLongAt: (in category 'simulation only') -----
+ unalignedLongAt: byteAddress
+ 	<doNotGenerate>
+ 	| rem |
+ 	self shouldBeImplemented.
+ 	rem := byteAddress \\ 4.
+ 	^rem = 0
+ 		ifTrue: [self longAt: byteAddress]
+ 		ifFalse: [((self longAt: byteAddress - rem) + ((self longAt: byteAddress - rem + 4) bitShift: 32) bitShift: rem * -8) bitAnd: 16rFFFFFFFF]!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>unalignedLongAt:put: (in category 'simulation only') -----
+ unalignedLongAt: byteAddress put: aLong
+ 	<doNotGenerate>
+ 	| rem mask |
+ 	self shouldBeImplemented.
+ 	rem := byteAddress \\ 4.
+ 	^rem = 0
+ 		ifTrue: [self longAt: byteAddress put: aLong]
+ 		ifFalse:
+ 			[mask := 16rFFFFFFFF bitAnd: (-1 bitShift: rem * 8).
+ 			 self longAt: byteAddress - rem
+ 				put: ((self longAt: byteAddress - rem) bitAnd: mask bitInvert)
+ 					+ ((aLong bitShift: rem * 8) bitAnd: mask).
+ 			 self longAt: byteAddress - rem + 4
+ 				put: ((self longAt: byteAddress - rem + 4) bitAnd: mask)
+ 					+ ((aLong bitShift: 4 - rem * -8) bitAnd: mask bitInvert).
+ 			 aLong]!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>withoutForwardingOn:and:with:sendToCogit: (in category 'cog jit support') -----
+ withoutForwardingOn: obj1 and: obj2 with: aBool sendToCogit: selector
+ 	"For the purposes of become: send selector to the cogit with obj1, obj2
+ 	 and aBool and answer the result.  Undo forwarding for the selector."
+ 	<api>
+ 	<var: #selector declareC: 'sqInt (*selector)(sqInt,sqInt,sqInt)'>
+ 	| targetA targetB |
+ 	targetA := self followForwarded: obj1.
+ 	targetB := self followForwarded: obj2.
+ 	^cogit perform: selector with: targetA with: targetB with: aBool!



More information about the Vm-dev mailing list