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

commits at source.squeak.org commits at source.squeak.org
Mon Nov 25 22:53:38 UTC 2013


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

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

Name: VMMaker.oscog-eem.520
Author: eem
Time: 25 November 2013, 2:50:47.877 pm
UUID: 15712719-732a-4659-bf8a-6272bc059cc5
Ancestors: VMMaker.oscog-eem.519

Undo the mistake of attempting to place the code zone between
newSpace and oldSpace.  Avoid scavenging Cog methods, which a
simple bounds check would judge as being young, by having
Spur32BitCoMemoryManager>>isReallyYoungObject: filter-out
Cog methods and copyAndForward: using isReallyYoungObject:.

Fix linking for new classes in Spur by having Cogit>>canLinkToYoungClasses
dispatch to the objectRepresentation.  Hence include the methodZone
in the objectRepresentation's inst vars.

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

Item was changed:
  ----- Method: CoInterpreter>>ceSend:super:to:numArgs: (in category 'trampolines') -----
  ceSend: selector super: superNormalBar to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  		
  	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
  	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
  	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
  	because we're out of code memory.
  
  	Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	depending on whether the target method is cogged or not."
  	<api>
  	| classTag canLinkCacheTag errSelIdx cogMethod |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
  	superNormalBar = 0
  		ifTrue: [classTag := objectMemory fetchClassTagOf: rcvr]
  		ifFalse: [classTag := objectMemory classTagForClass: (self superclassOf: (self methodClassOf: (self frameMethodObject: framePointer)))].
+ 	canLinkCacheTag := cogit canLinkToYoungClasses or: [(objectMemory isYoungObject: classTag) not].
- 	canLinkCacheTag := objectMemory hasSpurMemoryManagerAPI
- 						or: [(objectMemory isYoungObject: classTag) not or: [cogit canLinkToYoungClasses]].
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[messageSelector := selector.
  			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  				[(canLinkCacheTag
  				  and: [errSelIdx = SelectorDoesNotUnderstand
  				  and: [(cogMethod := cogit cogMNUPICSelector: messageSelector
  											methodOperand: (self mnuMethodOrNilFor: rcvr)
  											numArgs: argumentCount) asUnsignedInteger
  						> cogit minCogMethodAddress]]) ifTrue:
  						[cogit
  							linkSendAt: (stackPages longAt: stackPointer)
  							in: (self mframeHomeMethod: framePointer)
  							to: cogMethod
  							offset: (superNormalBar = 0
  									ifTrue: [cogit entryOffset]
  									ifFalse: [cogit noCheckEntryOffset])
  							receiver: rcvr].
  				self handleMNU: errSelIdx
  					InMachineCodeTo: rcvr
  					classForMessage: (objectMemory classForClassTag: classTag).
  				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it.  The receiver's class may be young.
  	 If the Cogit can't store young classes in inline caches we can link to an open PIC instead."
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[cogMethod := self cogMethodOf: newMethod.
  		 cogMethod selector = objectMemory nilObject
  			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
  			ifFalse:
  				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the
  				  correct selector.  If not, try and compile a new method with the correct selector."
  				 cogMethod selector ~= selector ifTrue:
  					[(cogit cog: newMethod selector: selector) ifNotNil:
  						[:newCogMethod| cogMethod := newCogMethod]]].
  		 (cogMethod selector = selector
  		  and: [canLinkCacheTag])
  			ifTrue:
  				[cogit
  					linkSendAt: (stackPages longAt: stackPointer)
  					in: (self mframeHomeMethod: framePointer)
  					to: cogMethod
  					offset: (superNormalBar = 0
  								ifTrue: [cogit entryOffset]
  								ifFalse: [cogit noCheckEntryOffset])
  					receiver: rcvr]
  			ifFalse: "If patchToOpenPICFor:.. returns we're out of code memory"
  				[cogit
  					patchToOpenPICFor: selector
  					numArgs: numArgs
  					receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>initializeCodeGenerator (in category 'initialization') -----
  initializeCodeGenerator
+ 	cogit
+ 		initializeCodeZoneFrom: (self cCode: [objectMemory memory] inSmalltalk: [Cogit guardPageSize])
+ 		upTo: (self cCode: [objectMemory memory] inSmalltalk: [Cogit guardPageSize]) + cogCodeSize!
- 	objectMemory hasSpurMemoryManagerAPI
- 		ifTrue:
- 			[cogit
- 				initializeCodeZoneFrom: objectMemory newSpaceLimit
- 				upTo: objectMemory newSpaceLimit + cogCodeSize]
- 		ifFalse:
- 			[cogit
- 				initializeCodeZoneFrom: (self cCode: [objectMemory memory] inSmalltalk: [Cogit guardPageSize])
- 				upTo: (self cCode: [objectMemory memory] inSmalltalk: [Cogit guardPageSize]) + cogCodeSize]!

Item was changed:
  ----- Method: CoInterpreter>>isCogMethodReference: (in category 'compiled methods') -----
  isCogMethodReference: methodHeader
  	<api>
  	self assert: ((objectMemory isIntegerObject: methodHeader)
+ 				or: [methodHeader asUnsignedInteger < objectMemory startOfMemory
- 				 or: [methodHeader asUnsignedInteger < cogit maxCogMethodAddress
  					and: [methodHeader asUnsignedInteger >= cogit minCogMethodAddress]]).
  	^objectMemory isNonIntegerObject: methodHeader!

Item was changed:
  ----- Method: CoInterpreterStackPages>>initializeStack:numSlots:pageSize: (in category 'initialization') -----
  initializeStack: theStackPages numSlots: stackSlots pageSize: slotsPerPage
  	"Initialize the stack pages.  In the C VM theStackPages will be alloca'ed memory to hold the
  	 stack pages on the C stack.  In the simulator they are housed in the memory between the
  	 cogMethodZone and the heap."
  
  	<var: #theStackPages type: #'char *'>
  	<returnTypeC: #void>
  	| numPages page structStackPageSize pageStructBase count |
  	<var: #page type: #'StackPage *'>
  	<var: #pageStructBase type: #'char *'>
  	self cCode: []
  		inSmalltalk:
+ 			[self assert: objectMemory startOfMemory - coInterpreter cogCodeSize - Cogit guardPageSize - coInterpreter methodCacheSize - coInterpreter primTraceLogSize - coInterpreter rumpCStackSize
+ 					= (stackSlots * BytesPerWord roundUpTo: objectMemory allocationUnit)].
- 			[objectMemory hasSpurMemoryManagerAPI
- 				ifTrue:
- 					[self assert: objectMemory oldSpaceStart - objectMemory newSpaceLimit - coInterpreter cogCodeSize - coInterpreter methodCacheSize - coInterpreter primTraceLogSize - coInterpreter rumpCStackSize - Cogit guardPageSize
- 					= (stackSlots * BytesPerWord roundUpTo: objectMemory allocationUnit)]
- 				ifFalse:
- 					[self assert: objectMemory startOfMemory - coInterpreter cogCodeSize - coInterpreter methodCacheSize - coInterpreter primTraceLogSize - coInterpreter rumpCStackSize - Cogit guardPageSize
- 					= (stackSlots * BytesPerWord roundUpTo: objectMemory allocationUnit)]].
  	structStackPageSize := coInterpreter sizeof: InterpreterStackPage.
  	bytesPerPage := slotsPerPage * BytesPerWord.
  	numPages := coInterpreter numStkPages.
  
  	"Because stack pages grow down baseAddress is at the top of a stack page and so to avoid
  	 subtracting BytesPerWord from baseAddress and lastAddress in the init loop below we simply
  	 push the stackPage array up one word to avoid the overlap.  This word is extraStackBytes."
  	pageStructBase := theStackPages + (numPages * bytesPerPage) + BytesPerWord.
  	pages := self cCode: [self cCoerceSimple: pageStructBase to: #'StackPage *']
  				  inSmalltalk:
  					[pageMap := Dictionary new.
  					 ((0 to: numPages - 1) collect:
  						[:i|
  						 InterpreterStackPage surrogateClass new
  							address: pageStructBase + (i * structStackPageSize)
  							simulator: coInterpreter
  							zoneBase: coInterpreter stackZoneBase
  							zoneLimit: objectMemory startOfMemory])
  						do: [:pageSurrogate|
  							pageMap at: pageSurrogate address put: pageSurrogate];
  						yourself].
  	"make sure there's enough headroom"
  	self assert: coInterpreter stackPageByteSize - coInterpreter stackLimitBytes - coInterpreter stackLimitOffset
  				>= coInterpreter stackPageHeadroom.
  	0 to: numPages - 1 do:
  		[:index|
  		 page := self stackPageAt: index.
  		 page
  			lastAddress: theStackPages + (index * bytesPerPage);
  			baseAddress: page lastAddress + bytesPerPage;
  			stackLimit: page baseAddress - coInterpreter stackLimitBytes;
  			realStackLimit: page stackLimit;
  			baseFP: 0;
  			nextPage: (self stackPageAt: (index = (numPages - 1) ifTrue: [0] ifFalse: [index + 1]));
  			prevPage: (self stackPageAt: (index = 0 ifTrue: [numPages - 1] ifFalse: [index - 1]))].
  
  	"Now compute stackBasePlus1 so that the pageIndexFor: call maps all addresses from
  	 aPage baseAddress to aBase limitAddress + 1 to the same index (stacks grow down)"
  	stackBasePlus1 := (self cCoerceSimple: theStackPages to: #'char *') + 1.
  	self cCode: []
  		inSmalltalk:
  			[minStackAddress := theStackPages.
  			 maxStackAddress := theStackPages + (numPages * bytesPerPage) + BytesPerWord - 1].
  
  	"The overflow limit is the amount of stack to retain when moving frames from an overflowing
  	 stack to reduce thrashing.  See stackOverflowOrEvent:mayContextSwitch:"
  	page := self stackPageAt: 0.
  	overflowLimit := page baseAddress - page realStackLimit * 3 // 5.
  	0 to: numPages - 1 do:
  		[:index|
  		 page := self stackPageAt: index.
  		 self assert: (self pageIndexFor: page baseAddress) == index.
  		 self assert: (self pageIndexFor: page baseAddress - (slotsPerPage - 1 * BytesPerWord)) == index.
  		 self assert: (self stackPageFor: page baseAddress) == page.
  		 self assert: (self stackPageFor: page stackLimit) == page.
  		 self cCode: []
  			inSmalltalk:
  				[| memIndex |
  				 memIndex := index * slotsPerPage + 1. "this is memIndex in the block above"
  				 self assert: (self memIndexFor: (self oopForPointer: page baseAddress))
  							== (memIndex + slotsPerPage - 1).
  				 index < (numPages - 1) ifTrue:
  					[self assert: (self stackPageFor: page baseAddress + BytesPerWord) == (self stackPageAt: index + 1)]].
  		coInterpreter initializePageTraceToInvalid: page].
  
  	mostRecentlyUsedPage := self stackPageAt: 0.
  	page := mostRecentlyUsedPage.
  	count := 0.
  	[| theIndex |
  	 count := count + 1.
  	 theIndex := self pageIndexFor: page baseAddress.
  	 self assert: (self stackPageAt: theIndex) == page.
  	 self assert: (self pageIndexFor: page baseAddress) == theIndex.
  	 self assert: (self pageIndexFor: page stackLimit) == theIndex.
  	 self assert: (self pageIndexFor: page lastAddress + 1) == theIndex.
  	 (page := page nextPage) ~= mostRecentlyUsedPage] whileTrue.
  	self assert: count == numPages.
  	self assert: self pageListIsWellFormed!

Item was changed:
  CogClass subclass: #CogObjectRepresentation
+ 	instanceVariableNames: 'cogit methodZone objectMemory ceStoreCheckTrampoline'
- 	instanceVariableNames: 'cogit objectMemory ceStoreCheckTrampoline'
  	classVariableNames: ''
  	poolDictionaries: 'CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices'
  	category: 'VMMaker-JIT'!
  
  !CogObjectRepresentation commentStamp: '<historical>' prior: 0!
  I am an abstract superclass for object representations whose job it is to generate abstract instructions for accessing objects.  It is hoped that this level of indirection between the Cogit code generator and object access makes it easier to adapt the code generator to different garbage collectors, object representations and languages.!

Item was removed:
- ----- Method: CogObjectRepresentation class>>for: (in category 'instance creation') -----
- for: aCogit
- 	^self new setCogit: aCogit!

Item was added:
+ ----- Method: CogObjectRepresentation class>>forCogit:methodZone: (in category 'instance creation') -----
+ forCogit: aCogit methodZone: methodZone
+ 	^self new setCogit: aCogit methodZone: methodZone!

Item was removed:
- ----- Method: CogObjectRepresentation>>setCogit: (in category 'initialization') -----
- setCogit: aCogit
- 	<doNotGenerate>
- 	cogit := aCogit.
- 	objectMemory := (aCogit coInterpreter isKindOf: ObjectMemory)
- 						ifTrue: [aCogit coInterpreter]
- 						ifFalse: [aCogit coInterpreter objectMemory]!

Item was added:
+ ----- Method: CogObjectRepresentation>>setCogit:methodZone: (in category 'initialization') -----
+ setCogit: aCogit methodZone: aMethodZone
+ 	<doNotGenerate>
+ 	cogit := aCogit.
+ 	methodZone := aMethodZone.
+ 	objectMemory := (aCogit coInterpreter isKindOf: StackInterpreter)
+ 						ifTrue: [aCogit coInterpreter objectMemory]
+ 						ifFalse: [aCogit coInterpreter]!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>canLinkToYoungClasses (in category 'in-line cacheing') -----
+ canLinkToYoungClasses
+ 	<api>
+ 	<cmacro: '() true'>
+ 	^true!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>canLinkToYoungClasses (in category 'in-line cacheing') -----
+ canLinkToYoungClasses
+ 	<api>
+ 	^methodZone roomOnYoungReferrersList!

Item was changed:
  ----- Method: CogVMSimulator>>stackZoneBase (in category 'stack pages') -----
  stackZoneBase
  	"In the simulator the stack zone starts immediately after the code zone."
+ 	^cogit cogCodeBase + cogCodeSize!
- 	^objectMemory cogCodeBase + cogCodeSize!

Item was changed:
  ----- Method: Cogit>>canLinkToYoungClasses (in category 'jit - api') -----
  canLinkToYoungClasses
+ 	<doNotGenerate>
+ 	^objectRepresentation canLinkToYoungClasses!
- 	<api>
- 	^methodZone roomOnYoungReferrersList!

Item was changed:
  ----- Method: Cogit>>setInterpreter: (in category 'initialization') -----
  setInterpreter: aCoInterpreter
  	"Initialization of the code generator in the simulator.
  	 These objects already exist in the generated C VM
  	 or are used only in the simulation."
  	<doNotGenerate>
  	coInterpreter := aCoInterpreter.
  	objectMemory := aCoInterpreter objectMemory.
  	threadManager := aCoInterpreter threadManager. "N.B. may be nil"
- 	objectRepresentation := objectMemory objectRepresentationClass for: self.
  	methodZone := CogMethodZone new.
+ 	objectRepresentation := objectMemory objectRepresentationClass
+ 								forCogit: self methodZone: methodZone.
  	methodZone setInterpreter: aCoInterpreter
  				objectRepresentation: objectRepresentation
  				cogit: self.
  	generatorTable := self class generatorTable.
  	primitiveGeneratorTable := self class primitiveTable.
  	processor := ProcessorClass new.
  	simulatedAddresses := Dictionary new.
  	simulatedTrampolines := Dictionary new.
  	simulatedVariableGetters := Dictionary new.
  	simulatedVariableSetters := Dictionary new.
  	traceStores := 0.
  	traceFlags := 8. "record prim trace on by default (see Cogit class>>decareCVarsIn:)"
  	debugPrimCallStackOffset := 0.
  	singleStep := printRegisters := printInstructions := clickConfirm := false.
  	breakBlock ifNil: [self breakPC: breakPC].
  	(backEnd := processor abstractInstructionCompilerClass new) cogit: self.
  	(methodLabel := processor abstractInstructionCompilerClass new) cogit: self.
  	sendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	superSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	NewspeakVM ifTrue:
  		[dynamicSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
  	"debug metadata"
  	objectReferencesInRuntime := CArrayAccessor on: (Array new: NumObjRefsInRuntime).
  	runtimeObjectRefIndex := 0.
  	"debug metadata"
  	trampolineAddresses := CArrayAccessor on: (Array new: NumTrampolines * 2).
  	trampolineTableIndex := 0.
  
  	compilationTrace ifNil: [compilationTrace := 0].
  	extA := extB := 0!

Item was changed:
  ----- Method: Cogit>>simulateCogCodeAt: (in category 'simulation only') -----
  simulateCogCodeAt: address "<Integer>"
  	<doNotGenerate>
  	| stackZoneBase |
  	stackZoneBase := coInterpreter stackZoneBase.
  	processor pc: address.
  	[[[singleStep ifTrue:
  		[[processor sp < stackZoneBase ifTrue: [self halt].
  		  self recordProcessing.
  		  (breakPC isInteger
  			ifTrue:
  				[processor pc = breakPC
  				 and: [breakBlock value: self]]
  			ifFalse:
  				[breakBlock value: self]) ifTrue:
  			["printRegisters := printInstructions := true"
  			 "self reportLastNInstructions"
  			 "coInterpreter printExternalHeadFrame"
  			 "coInterpreter printFrameAndCallers: coInterpreter framePointer SP: coInterpreter stackPointer"
  			 "coInterpreter shortPrintFrameAndCallers: coInterpreter framePointer"
  			 "coInterpreter printFrame: processor fp WithSP: processor sp"
  			 "coInterpreter printFrameAndCallers: processor fp SP: processor sp"
  			 "coInterpreter shortPrintFrameAndCallers: processor fp"
  			"self disassembleMethodFor: processor pc"
  			 coInterpreter changed: #byteCountText.
  			 self halt: 'machine code breakpoint at ',
  						(breakPC isInteger
  							ifTrue: [breakPC hex]
  							ifFalse: [String streamContents: [:s| breakBlock decompile printOn: s indent: 0]])]] value]. "So that the Debugger's Over steps over all this"
  	   singleStep
  		ifTrue: [processor
  					singleStepIn: coInterpreter memory
  					minimumAddress: guardPageSize
+ 					readOnlyBelow: methodZone zoneEnd]
- 					executableAndReadOnlyFrom: codeBase
- 					to: methodZone zoneEnd]
  		ifFalse: [processor
  					runInMemory: coInterpreter memory
  					minimumAddress: guardPageSize
+ 					readOnlyBelow: methodZone zoneEnd].
- 					executableAndReadOnlyFrom: codeBase
- 					to: methodZone zoneEnd].
  	   ((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
  	 	[(self confirm: 'continue?') ifFalse:
  			[self halt]].
  	   true] whileTrue]
  		on: ProcessorSimulationTrap
  		do: [:ex| self handleSimulationTrap: ex].
  	 true] whileTrue!

Item was changed:
  ----- Method: Cogit>>simulateLeafCallOf: (in category 'simulation only') -----
  simulateLeafCallOf: someFunction
  	"Simulate execution of machine code that leaf-calls someFunction,
  	 answering the result returned by someFunction."
  	<doNotGenerate>
  	| spOnEntry |
  	self recordRegisters.
  	processor
  		simulateLeafCallOf: someFunction
  		nextpc: 16rBADF00D5
  		memory: coInterpreter memory.
  	spOnEntry := processor sp.
  	self recordInstruction: {'(simulated call of '. someFunction. ')'}.
+ 	[[processor pc between: 0 and: methodZone zoneEnd] whileTrue:
- 	[[processor pc between: codeBase and: methodZone zoneEnd] whileTrue:
  		[singleStep
  			ifTrue: [self recordProcessing.
  					processor
  						singleStepIn: coInterpreter memory
  						minimumAddress: guardPageSize
+ 						readOnlyBelow: methodZone zoneEnd]
- 						executableAndReadOnlyFrom: codeBase
- 						to: methodZone zoneEnd]
  			ifFalse: [processor
  						runInMemory: coInterpreter memory
  						minimumAddress: guardPageSize
+ 						readOnlyBelow: methodZone zoneEnd]]]
- 						executableAndReadOnlyFrom: codeBase
- 						to: methodZone zoneEnd]]]
  		on: ProcessorSimulationTrap
  		do: [:ex| | retpc |
  			"If the ip is out of bounds the return has already occurred."
+ 			((processor pc between: 0 and: methodZone zoneEnd)
- 			((processor pc between: codeBase and: methodZone zoneEnd)
  			 and: [processor sp <= spOnEntry]) ifTrue:
  				[retpc := processor leafRetpcIn: coInterpreter memory.
  				 self assert: retpc = 16rBADF00D5.
  				 self recordInstruction: {'(simulated return to '. retpc. ')'.
  				 processor simulateLeafReturnIn: coInterpreter memory}.
  				 self recordRegisters]].
  	^processor cResultRegister!

Item was changed:
  ----- Method: NewCoObjectMemorySimulator>>cogCodeBase (in category 'simulation only') -----
  cogCodeBase
+ 	^Cogit guardPageSize!
- 	^0!

Item was changed:
  ----- Method: ObjectMemory>>setHeapBase:memoryLimit:endOfMemory: (in category 'initialization') -----
  setHeapBase: heapBase memoryLimit: memLimit endOfMemory: memEnd
+ 	"Set the dimensions of the heap, answering the start of oldSpace."
- 	"Set the dimentions of the heap, answering the start of oldSpace."
  	self setMemoryLimit: memLimit.
  	self setEndOfMemory: memEnd.
  	^heapBase!

Item was changed:
  Spur32BitMemoryManager subclass: #Spur32BitCoMemoryManager
  	instanceVariableNames: 'cogit'
  	classVariableNames: ''
  	poolDictionaries: 'CogMethodConstants'
  	category: 'VMMaker-SpurMemoryManager'!
  
+ !Spur32BitCoMemoryManager commentStamp: 'eem 11/25/2013 14:47' prior: 0!
+ Spur32BitCoMemoryManager is a refinement of Spur32BitMemoryManager that supports the CoInterpreter/Cogit just-in-time compiler.  The significant difference from Spur32BitMemoryManager is the memory layout.  Spur32BitCoMemoryManager adds the cogCodeZone beneath newSpace:
- !Spur32BitCoMemoryManager commentStamp: 'eem 11/20/2013 13:45' prior: 0!
- Spur32BitCoMemoryManager is a refinement of Spur32BitMemoryManager that supports the CoInterpreter/Cogit just-in-time compiler.  The signifiant difference from Spur32BitMemoryManager is the memory layout.  Spur32BitCoMemoryManager adds the cgCodeZone between newSpace and the firts oldSpace segment:
  
  low address:
- 	newSpace:
- 		past/future survivor space
- 		future/past survivor space
- 		eden
  	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 Spur32BitCoMemoryManager ocerrides isReallyYoungObject: to filter-out Cog methods for copyAndForward:.
+ 
  Instance Variables
  	cogit:		<SimpleStackBasedCogit or subclass>
  
  cogit
+ 	- the just-in-time compiler!
- 	- the just-in-time compiler
- !

Item was changed:
  ----- Method: Spur32BitCoMemoryManager>>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 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: Spur32BitCoMemoryManager>>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 changed:
  ----- Method: Spur32BitCoMemoryManager>>setHeapBase:memoryLimit:endOfMemory: (in category 'snapshot') -----
  setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd
  	"Set the dimensions of the heap, answering the start of oldSpace.
+ 	 Override to position the cog code zone beneath the heap."
+ 	^super setHeapBase: coInterpreter cogCodeSize memoryLimit: memLimit endOfMemory: memEnd!
- 	 Override to position oldSpace above the cog code zone."
- 	super setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd.
- 	^oldSpaceStart := newSpaceLimit + coInterpreter cogCodeSize!

Item was changed:
  ----- Method: Spur32BitMMLECoSimulator>>cogCodeBase (in category 'simulation only') -----
  cogCodeBase
+ 	^Cogit guardPageSize!
- 	^newSpaceLimit!

Item was changed:
  ----- Method: Spur32BitMMLECoSimulator>>setHeapBase:memoryLimit:endOfMemory: (in category 'initialization') -----
  setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd
  	"Set the dimensions of the heap, answering the start of oldSpace.
+ 	 Override to add a guard page beneath the code zone.  We can't use
+ 	 super; we need to skip over the super implementation."
+ 	^self
+ 		perform: #setHeapBase:memoryLimit:endOfMemory:
+ 		withArguments: {	baseOfHeap.
+ 							memLimit.
+ 							memEnd }
+ 		inSuperclass: Spur32BitMemoryManager!
- 	 Override to add a guard page beneath the heap."
- 	"As invoked by CogVMSimulator>>openOn:extraBytes: baseOfHeap contains the combined
- 	 zone sizes for cog methods, stack zone, etc.  The memory map in SqueakV3 looks like
- 		0:	cogCode
- 			stackZone
- 			methodCache
- 			primTraceLog
- 			rumpCStack
- 		heapBase:
- 			nilObj etc
- 	 But here in Spur we want
- 		0:	guardPage
- 		guardPageSize:
- 			newSpace:
- 				past/future survivor space
- 				past/future survivor space
- 				eden
- 		M:
- 			cogCode
- 			stackZone
- 			methodCache
- 			primTraceLog
- 			rumpCStack
- 		heapBase:
- 			nilObj etc"
- 	super setHeapBase: Cogit guardPageSize memoryLimit: memLimit endOfMemory: memEnd.
- 	^oldSpaceStart := newSpaceLimit + baseOfHeap!

Item was changed:
  ----- Method: SpurGenerationScavenger>>scavengeReferentsOf: (in category 'scavenger') -----
  scavengeReferentsOf: referrer
  	"scavengeReferentsOf: referrer inspects all the pointers in referrer.  If
  	 any are new objects, it has them moved to FutureSurvivorSpace, and
  	 answers truth. If there are no new referents, it answers falsity. To handle
  	 weak arrays, if the referrer is weak only scavenge strong slots and answer
  	 true so that it won't be removed from the remembered set until later."
  	| foundNewReferent |
  	"forwarding objects should be followed by callers,
  	 unless the forwarder is a root in the remembered table."
  	self assert: ((manager isForwarded: referrer) not
  				or: [manager isRemembered: referrer]).
  	"unscanned ephemerons should be scanned later."
  	self assert: ((manager isEphemeron: referrer) not
  				or: [(self isScavengeSurvivor: (manager keyOfEphemeron: referrer))
  				or: [self is: referrer onWeaklingList: ephemeronList]]).
  	foundNewReferent := false.
  	0 to: (manager numStrongSlotsOf: referrer ephemeronInactiveIf: #isScavengeSurvivor:) - 1
  	   do: [:i| | referent newLocation |
  		referent := manager fetchPointer: i ofMaybeForwardedObject: referrer.
  		(manager isNonImmediate: referent) ifTrue:
  			["a forwarding pointer could be because of become: or scavenging."
  			 (manager isForwarded: referent) ifTrue:
  				[referent := manager followForwarded: referent].
+ 			 (manager isReallyYoungObject: referent)
- 			 (manager isYoung: referent)
  				ifTrue: "if target is already in future space forwarding pointer was due to a become:."
  					[(manager isInFutureSpace: referent)
  						ifTrue: [newLocation := referent. foundNewReferent := true]
  						ifFalse:
  							[newLocation := self copyAndForward: referent.
  							 (manager isYoung: newLocation) ifTrue:
  								[foundNewReferent := true]].
  					 manager storePointerUnchecked: i ofMaybeForwardedObject: referrer withValue: newLocation]
  				ifFalse:
  					[manager storePointerUnchecked: i ofMaybeForwardedObject: referrer withValue: referent]]].
  	^foundNewReferent or: [manager isWeakNonImm: referrer]!

Item was changed:
  ----- Method: SpurMemoryManager>>allocateMemoryOfSize:newSpaceSize:stackSize:codeSize: (in category 'spur bootstrap') -----
  allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceBytes stackSize: stackBytes codeSize: codeBytes
  	"Intialize the receiver for bootsraping an image.
  	 Set up a large oldSpace and an empty newSpace and set-up freeStart and scavengeThreshold
  	 to allocate in oldSpace.  Later on (in initializePostBootstrap) freeStart and scavengeThreshold
  	 will be set to sane values."
  	<doNotGenerate>
  	self assert: (memoryBytes \\ self allocationUnit = 0
  				and: [newSpaceBytes \\ self allocationUnit = 0
  				and: [codeBytes \\ self allocationUnit = 0]]).
  	memory := (self endianness == #little
  					ifTrue: [LittleEndianBitmap]
  					ifFalse: [Bitmap]) new: (memoryBytes + newSpaceBytes + codeBytes + stackBytes) // 4.
- 	"N.B. This layout does NOT reflect the layout of SpurCoMemoryManager"
  	newSpaceStart := codeBytes + stackBytes.
  	endOfMemory := freeOldSpaceStart := memoryBytes + newSpaceBytes + codeBytes + stackBytes.
  	"leave newSpace empty for the bootstrap"
  	freeStart := newSpaceBytes + newSpaceStart.
  	oldSpaceStart := newSpaceLimit := newSpaceBytes + newSpaceStart.
  	scavengeThreshold := memory size * 4. "Bitmap is a 4-byte per word array"
  	scavenger := SpurGenerationScavengerSimulator new.
  	scavenger manager: self.
  	scavenger newSpaceStart: newSpaceStart
  				newSpaceBytes: newSpaceBytes
  				edenBytes: newSpaceBytes * self scavengerDenominator
  						- self numSurvivorSpaces // self scavengerDenominator!

Item was changed:
  ----- Method: SpurMemoryManager>>cheapIsInMemory: (in category 'plugin support') -----
  cheapIsInMemory: address
  	"Answer if the given address is in ST object memory.  For simulation only."
  	<doNotGenerate>
+ 	^address >= newSpaceStart and: [address < endOfMemory]!
- 	^(address < newSpaceLimit and: [address >= newSpaceStart])
- 	 or: [address >= oldSpaceStart and: [address < endOfMemory]]!

Item was changed:
  ----- Method: SpurMemoryManager>>checkHeapIntegrity: (in category 'debug support') -----
  checkHeapIntegrity: excludeUnmarkedNewSpaceObjs
  	"Perform an integrity/leak check using the heapMap.  Assume
  	 clearLeakMapAndMapAccessibleObjects has set a bit at each
  	 object's header.  Scan all objects in the heap checking that every
  	 pointer points to a header.  Scan the rootTable, remapBuffer and
  	 extraRootTable checking that every entry is a pointer to a header.
  	 Check that the number of roots is correct and that all rootTable
  	 entries have their rootBit set. Answer if all checks pass."
  	| ok numRememberedRootsInHeap |
  	<inline: false>
  	ok := true.
  	numRememberedRootsInHeap := 0.
  	self allHeapEntitiesDo:
  		[:obj| | containsYoung fieldOop classIndex classOop |
  		((self isFreeObject: obj)
  		 or: [(self isYoungObject: obj) and: [(self isMarked: obj) not and: [excludeUnmarkedNewSpaceObjs]]]) ifFalse:
  			[containsYoung := false.
  			 (self isRemembered: obj) ifTrue:
  				[numRememberedRootsInHeap := numRememberedRootsInHeap + 1.
  				 (scavenger isInRememberedSet: obj) ifFalse:
  					[coInterpreter print: 'remembered object '; printHex: obj; print: ' is not in remembered table'; cr.
  					 self eek.
  					 ok := false]].
  			 (self isForwarded: obj)
  				ifTrue:
  					[fieldOop := self fetchPointer: 0 ofMaybeForwardedObject: obj.
  					 (heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  						[coInterpreter print: 'object leak in forwarder '; printHex: obj; print: ' to unmapped '; printHex: fieldOop; cr.
  						 self eek.
  						 ok := false].
  					 (self isYoung: fieldOop) ifTrue:
  						[containsYoung := true]]
  				ifFalse:
  					[classOop := self classAtIndex: (classIndex := self classIndexOf: obj).
  					 ((classOop isNil or: [classOop = nilObj])
  					  and: [(self isHiddenObj: obj) not]) ifTrue:
  						[coInterpreter print: 'object leak in '; printHex: obj; print: ' invalid class index '; printHex: classIndex; print: ' -> '; print: (classOop ifNil: ['nil'] ifNotNil: ['nilObj']); cr.
  						 self eek.
  						 ok := false].
  					 self baseHeaderSize to: (self lastPointerOf: obj) by: BytesPerOop do:
  						[:ptr|
  						 fieldOop := self longAt: obj + ptr.
  						 (self isNonImmediate: fieldOop) ifTrue:
  							[| fi |
  							 fi := ptr - self baseHeaderSize / self wordSize.
  							 (fieldOop bitAnd: self wordSize - 1) ~= 0
  								ifTrue:
  									[coInterpreter print: 'misaligned oop in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
  									 self eek.
  									 ok := false]
  								ifFalse:
  									[(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  										[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
  										 self eek.
  										 ok := false].
+ 									 "don't be misled by CogMethods; they appear to be young, but they're not"
+ 									 ((self isYoung: fieldOop)
+ 									  and: [self oop: fieldOop isGreaterThanOrEqualTo: newSpaceStart]) ifTrue:
- 									 (self isYoung: fieldOop) ifTrue:
  										[containsYoung := true]]]]].
  					(containsYoung and: [(self isYoung: obj) not]) ifTrue:
  						[(self isRemembered: obj) ifFalse:
  							[coInterpreter print: 'unremembered object '; printHex: obj; print: ' contains young oop(s)'; cr.
  							 self eek.
  							 ok := false]]]].
  	numRememberedRootsInHeap ~= scavenger rememberedSetSize ifTrue:
  		[coInterpreter
  			print: 'root count mismatch. #heap roots ';
  			printNum: numRememberedRootsInHeap;
  			print: '; #roots ';
  			printNum: scavenger rememberedSetSize;
  			cr.
  		self eek.
  		"But the system copes with overflow..."
  		self flag: 'no support for remembered set overflow yet'.
  		"ok := rootTableOverflowed and: [needGCFlag]"].
  	scavenger rememberedSetWithIndexDo:
  		[:obj :i|
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned oop in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
  					ifTrue:
  						[coInterpreter print: 'object leak in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  						 self eek.
  						 ok := false]
  					ifFalse:
  						[(self isYoung: obj) ifTrue:
  							[coInterpreter print: 'non-root in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  							 self eek.
  							 ok := false]]]].
  	1 to: remapBufferCount do:
  		[:ri| | obj |
  		obj := remapBuffer at: ri.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned remapRoot @ '; printNum: ri; print: ' = '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
  					[coInterpreter print: 'object leak in remapRoots @ '; printNum: ri; print: ' = '; printHex: obj; cr.
  					 self eek.
  					 ok := false]]].
  	1 to: extraRootCount do:
  		[:ri| | obj |
  		obj := (extraRoots at: ri) at: 0.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned extraRoot @ '; printNum: ri; print: ' => '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
  					[coInterpreter print: 'object leak in extraRoots @ '; printNum: ri; print: ' => '; printHex: obj; cr.
  					 self eek.
  					 ok := false]]].
  	^ok!

Item was changed:
  ----- Method: SpurMemoryManager>>setHeapBase:memoryLimit:endOfMemory: (in category 'snapshot') -----
  setHeapBase: baseOfHeap memoryLimit: memLimit endOfMemory: memEnd
  	"Set the dimensions of the heap, answering the start of oldSpace."
  	"Transcript
  		cr; nextPutAll: 'heapBase: '; print: baseOfHeap; nextPut: $/; nextPutAll: baseOfHeap hex;
  		nextPutAll: ' memLimit '; print: memLimit; nextPut: $/; nextPutAll: memLimit hex;
  		nextPutAll: ' memEnd '; print: memEnd; nextPut: $/; nextPutAll: memEnd hex; cr; flush."
  	"This is a little counter-intuitive.  Eden must include interpreterAllocationReserveBytes."
  	newSpaceStart := baseOfHeap.
  	newSpaceLimit := baseOfHeap
  					 + self newSpaceBytes
  					 + coInterpreter interpreterAllocationReserveBytes.
  	scavenger
  		newSpaceStart: newSpaceStart
  		newSpaceBytes: newSpaceLimit - newSpaceStart
  		edenBytes: newSpaceLimit - newSpaceStart
  				   * (self scavengerDenominator - self numSurvivorSpaces) // self scavengerDenominator.
  	freeStart := scavenger eden start.
  	pastSpaceStart := scavenger pastSpace start.
  
+ 	oldSpaceStart := newSpaceLimit.
  	freeOldSpaceStart := memEnd.
  	endOfMemory := memLimit.
+ 	^baseOfHeap!
- 	oldSpaceStart := newSpaceLimit.
- 	^oldSpaceStart!



More information about the Vm-dev mailing list