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

commits at source.squeak.org commits at source.squeak.org
Thu Jun 4 05:08:36 UTC 2015


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

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

Name: VMMaker.oscog-eem.1336
Author: eem
Time: 3 June 2015, 10:06:12.601 pm
UUID: a8254ed3-d450-4a8a-aa78-7ae88f6aae1a
Ancestors: VMMaker.oscog-tpr.1335

Merge with VMMaker.oscog-tpr.1335, keeping the -1's
in the cache flush extent calculations.

Fix the hack introduced in VMMaker.oscog-eem.1199
for Sista which merely stopped reclaiming closed
PICs.  In non-Sista VMs do the usual thing of decaying
usage counts on PICs, as with methods, and
reclaiming those least used.
In Sista, retain PICs until teh next cycle, identifying
unused PICs as part of the compaction scan,
reminiscent of tri-colour incremental GC.

Move defaultCogCodeSize into the
CogAbstractInstruction hierarchy so that e.g.
CogARMCompiler can specify a larger default
code zone.

=============== Diff against VMMaker.oscog-tpr.1335 ===============

Item was removed:
- ----- Method: CoInterpreter>>defaultCogCodeSize (in category 'initialization') -----
- defaultCogCodeSize
- 	"Return the default number of bytes to allocate for native code at startup.
- 	 The actual value can be set via vmParameterAt: and/or a preference in the ini file."
- 	<inline: false>
- 	^1024 * 1400!

Item was changed:
  ----- Method: CoInterpreter>>readImageFromFile:HeapSize:StartingAt: (in category 'image save/restore') -----
  readImageFromFile: f HeapSize: desiredHeapSize StartingAt: imageOffset
  	"Read an image from the given file stream, allocating an amount of memory to its object heap.
  	
  	 V3: desiredHeapSize is the total size of the heap.  Fail if the image has an unknown format or
  	 requires more than the specified amount of memory.
  
  	 Spur: desiredHeapSize is ignored; this routine will attempt to provide at least extraVMMemory's
  	 ammount of free space after the image is loaded, taking any free space in teh image into account.
  	 extraVMMemory is stored in the image header and is accessible as vmParameterAt: 23.  If
  	 extraVMMemory is 0, the value defaults to the default grow headroom.  Fail if the image has an
  	 unknown format or if sufficient memory cannot be allocated.
  
  	 Details: This method detects when the image was stored on a machine with the opposite byte
  	 ordering from this machine and swaps the bytes automatically. Furthermore, it allows the header
  	 information to start 512 bytes into the file, since some file transfer programs for the Macintosh
  	 apparently prepend a Mac-specific header of this size. Note that this same 512 bytes of prefix
  	 area could also be used to store an exec command on Unix systems, allowing one to launch
  	 Smalltalk by invoking the image name as a command."
  
  	| swapBytes headerStart headerSize dataSize oldBaseAddr
  	  minimumMemory heapSize bytesRead bytesToShift firstSegSize
  	  hdrNumStackPages hdrEdenBytes hdrCogCodeSize headerFlags hdrMaxExtSemTabSize allocationReserve |
  	<var: #f type: #sqImageFile>
  	<var: #heapSize type: #usqInt>
  	<var: #dataSize type: #'size_t'>
  	<var: #minimumMemory type: #usqInt>
  	<var: #desiredHeapSize type: #usqInt>
  	<var: #allocationReserve type: #usqInt>
  	<var: #headerStart type: #squeakFileOffsetType>
  	<var: #imageOffset type: #squeakFileOffsetType>
  
  	metaclassNumSlots := 6.	"guess Metaclass instSize"
  	classNameIndex := 6.		"guess (Class instVarIndexFor: 'name' ifAbsent: []) - 1"
  	swapBytes := self checkImageVersionFrom: f startingAt: imageOffset.
  	headerStart := (self sqImageFilePosition: f) - 4.  "record header start position"
  
  	headerSize			:= self getWord32FromFile: f swap: swapBytes.
  	dataSize			:= self getLongFromFile: f swap: swapBytes.
  	oldBaseAddr		:= self getLongFromFile: f swap: swapBytes.
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes). "N.B.  not used."
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getWord32FromFile: f swap: swapBytes. "N.B.  ignored in V3."
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default.  Can be changed via vmParameterAt: 43 put: n.
  	 Can be set as a preference (Info.plist, VM.ini, command line etc).
  	 If desiredNumStackPages is already non-zero then it has been
  	 set as a preference.  Ignore (but preserve) the header's default."
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
+ 									ifTrue: [cogit defaultCogCodeSize]
- 									ifTrue: [self defaultCogCodeSize]
  									ifFalse: [hdrCogCodeSize]].
  	hdrEdenBytes		:= self getWord32FromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  
  	"compare memory requirements with availability"
  	allocationReserve := self interpreterAllocationReserveBytes.
  	minimumMemory := cogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ dataSize
  						+ objectMemory newSpaceBytes
  						+ allocationReserve.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[| freeOldSpaceInImage headroom |
  			 freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  			 headroom := objectMemory
  							initialHeadroom: extraVMMemory
  							givenFreeOldSpaceInImage: freeOldSpaceInImage.
  			 heapSize := objectMemory roundUpHeapSize:
  						   cogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
  			[heapSize :=  cogCodeSize "no need to include the stackZone; this is alloca'ed"
  						+ desiredHeapSize
  						+ objectMemory newSpaceBytes
  						+ (desiredHeapSize - dataSize > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve]).
  			 heapSize < minimumMemory ifTrue:
  				[self insufficientMemorySpecifiedError]].
  
  	"allocate a contiguous block of memory for the Squeak heap and ancilliary data structures"
  	objectMemory memory: (self
  								allocateMemory: heapSize
  								minimum: minimumMemory
  								imageFile: f
  								headerSize: headerSize) asUnsignedInteger.
  	objectMemory memory ifNil:
  		[self insufficientMemoryAvailableError].
  
  	heapBase := objectMemory
  					setHeapBase: objectMemory memory + cogCodeSize
  					memoryLimit: objectMemory memory + heapSize
  					endOfMemory: objectMemory memory + cogCodeSize + dataSize.
  
  	"position file after the header"
  	self sqImageFile: f Seek: headerStart + headerSize.
  
  	"read in the image in bulk, then swap the bytes if necessary"
  	bytesRead := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	bytesRead ~= dataSize ifTrue: [self unableToReadImageError].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	"compute difference between old and new memory base addresses"
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.
  	self initializeInterpreter: bytesToShift.  "adjusts all oops to new location"
  	self initializeCodeGenerator.
  	^dataSize!

Item was added:
+ ----- Method: CogARMCompiler>>defaultCogCodeSize (in category 'accessing') -----
+ defaultCogCodeSize
+ 	"Return the default number of bytes to allocate for native code at startup.
+ 	 The actual value can be set via vmParameterAt: and/or a preference in the ini file."
+ 	<api>
+ 	^1024 * 1400!

Item was added:
+ ----- Method: CogAbstractInstruction>>defaultCogCodeSize (in category 'accessing') -----
+ defaultCogCodeSize
+ 	"Return the default number of bytes to allocate for native code at startup.
+ 	 The actual value can be set via vmParameterAt: and/or a preference in the ini file."
+ 	<api>
+ 	^1024 * 1024!

Item was added:
+ ----- Method: CogMethodZone>>clearSavedPICUsageCount: (in category 'compaction') -----
+ clearSavedPICUsageCount: cogMethod
+ 	"For Sista, where we want PICs to last so they can be observed, we need to keep PICs unless
+ 	 they are definitely unused.  So we need to identify unused PICs.  So in planCompact, zero the
+ 	 usage counts of all PICs, saving the actual usage count in blockEntryOffset.  Then in
+ 	 relocateMethodsPreCompaction (actually in relocateIfCallOrMethodReference:mcpc:delta:)
+ 	 restore the usage counts of used PICs.  Finally in compactCompiledCode, clear the blockEntryOffset
+ 	 of the unused PICs; they will then have a zero count and be reclaimed in the next code compaction."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<option: #SistaVM>
+ 	cogMethod cmType = CMClosedPIC ifTrue:
+ 		[cogMethod blockEntryOffset: 0]!

Item was changed:
  ----- Method: CogMethodZone>>compactCompiledCode (in category 'compaction') -----
  compactCompiledCode
  	| objectHeaderValue source dest bytes |
  	<var: #source type: #'CogMethod *'>
  	<var: #dest type: #'CogMethod *'>
  	objectHeaderValue := objectMemory nullHeaderForMachineCodeMethod.
  	source := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	openPICList := nil.
  	methodCount := 0.
  	self cppIf: NewspeakVM ifTrue: [unpairedMethodList := nil].
  	[source < self limitZony
  	 and: [source cmType ~= CMFree]] whileTrue:
  		[self assert: (cogit cogMethodDoesntLookKosher: source) = 0.
  		 source objectHeader: objectHeaderValue.
  		 source cmUsageCount > 0 ifTrue:
  			[source cmUsageCount: source cmUsageCount // 2].
  		 self cppIf: NewspeakVM ifTrue:
  				[(source cmType = CMMethod
  				  and: [(coInterpreter rawHeaderOf: source methodObject) asInteger ~= source asInteger]) ifTrue:
  					[source nextMethodOrIRCs: unpairedMethodList.
  					 unpairedMethodList := source asUnsignedInteger]].
+ 		 SistaVM ifTrue:
+ 			[self clearSavedPICUsageCount: source].
  		 source cmType = CMOpenPIC ifTrue:
  			[source nextOpenPIC: openPICList asUnsignedInteger.
  			 openPICList := source].
  		 methodCount := methodCount + 1.
  		 source := self methodAfter: source].
  	source >= self limitZony ifTrue:
  		[^self halt: 'no free methods; cannot compact.'].
  	dest := source.
  	[source < self limitZony] whileTrue:
  		[self assert: (cogit maybeFreeCogMethodDoesntLookKosher: source) = 0.
  		 bytes := source blockSize.
  		 source cmType ~= CMFree ifTrue:
  			[methodCount := methodCount + 1.
  			 objectMemory mem: dest mo: source ve: bytes.
  			 dest objectHeader: objectHeaderValue.
  			 dest cmType = CMMethod
  				ifTrue:
  					["For non-Newspeak there should be a one-to-one mapping between bytecoded and
  					  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  					"Only update the original method's header if it is referring to this CogMethod."
  					 (coInterpreter rawHeaderOf: dest methodObject) asInteger = source asInteger
  						ifTrue:
  							[coInterpreter rawHeaderOf: dest methodObject put: dest asInteger]
  						ifFalse:
  							[self assert: (cogit noAssertMethodClassAssociationOf: dest methodObject) = objectMemory nilObject.
  							 self cppIf: NewspeakVM ifTrue:
  								[dest nextMethodOrIRCs: unpairedMethodList.
  								 unpairedMethodList := dest asUnsignedInteger]]]
  				ifFalse:
+ 					[SistaVM ifTrue:
+ 						[self clearSavedPICUsageCount: dest].
+ 					dest cmType = CMOpenPIC ifTrue:
- 					[dest cmType = CMOpenPIC ifTrue:
  						[dest nextOpenPIC: openPICList asUnsignedInteger.
  						 openPICList := dest]].
  			 dest cmUsageCount > 0 ifTrue:
  				[dest cmUsageCount: dest cmUsageCount // 2].
  			 dest := coInterpreter
  								cCoerceSimple: dest asUnsignedInteger + bytes
  								to: #'CogMethod *'].
  		 source := coInterpreter
  							cCoerceSimple: source asUnsignedInteger + bytes
  							to: #'CogMethod *'].
  	mzFreeStart := dest asUnsignedInteger.
  	methodBytesFreedSinceLastCompaction := 0!

Item was changed:
  ----- Method: CogMethodZone>>freeOlderMethodsForCompaction (in category 'compaction') -----
  freeOlderMethodsForCompaction
+ 	"Free methods, preferring older methods for compaction, up to some fraction, currently a quarter."
- 	"Free methods, preferring older methods for compaction, up to some fraction."
  	| zoneSize amountToFree initialFreeSpace freedSoFar freeableUsage cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	zoneSize := limitAddress - baseAddress.
  	initialFreeSpace := limitAddress - mzFreeStart + methodBytesFreedSinceLastCompaction.
  	freedSoFar := initialFreeSpace.
  	amountToFree := zoneSize // 4. "4 needs to be e.g. a start-up parameter"
  	freeableUsage := 0.
  	[self cCode: ''
  		inSmalltalk: [coInterpreter transcript nextPutAll: 'freeing methods with usage '; print: freeableUsage; cr; flush].
+ 	 cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
- 	 cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	 [cogMethod asUnsignedInteger < mzFreeStart
  	  and: [freedSoFar < amountToFree]] whileTrue:
+ 		[(self shouldFreeMethod: cogMethod given: freeableUsage) ifTrue:
- 		[(cogMethod cmType = CMMethod
- 		  and: [cogMethod cmUsageCount <= freeableUsage]) ifTrue:
  			[self freeMethod: cogMethod.
  			 freedSoFar := freedSoFar + cogMethod blockSize].
  		 cogMethod := self methodAfter: cogMethod].
  	 freedSoFar < amountToFree
  	 and: [(freeableUsage := freeableUsage + 1) < CMMaxUsageCount]] whileTrue.
  	self cCode: ''
  		inSmalltalk: [coInterpreter transcript
  						nextPutAll: 'Compaction freeing '; print: freedSoFar;
  						nextPutAll: ' of '; print: zoneSize;
  						nextPutAll: ' (target: '; print: amountToFree;
  						nextPutAll: ' (newly freed: '; print: freedSoFar - initialFreeSpace;
  						cr; flush]!

Item was changed:
  ----- Method: CogMethodZone>>planCompaction (in category 'compaction') -----
  planCompaction
+ 	"Some methods have been freed.  Compute how much each survivor needs to
+ 	 move during the ensuing compaction and record it in the objectHeader field.
+ 
+ 	 For Sista, where we want PICs to last so they can be observed, we need to keep PICs unless
+ 	 they are definitely unused.  So we need to identify unused PICs.  So in planCompact, zero the
+ 	 usage counts of all PICs, saving the actual usage count in blockEntryOffset.  Then in
+ 	 relocateMethodsPreCompaction (actually in relocateIfCallOrMethodReference:mcpc:delta:)
+ 	 restore the usage counts of used PICs.  Finally in compactCompiledCode, clear the blockEntryOffset
+ 	 of the unused PICs; they will then have a zero count and be reclaimed in the next code compaction."
- 	"Some metods have been freed.  Compute how much each survivor needs to
- 	 move during the ensuing compaction and record it in the objectHeader field."
  	| delta cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	delta := 0.
+ 	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
- 	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod asUnsignedInteger < mzFreeStart] whileTrue:
  		[cogMethod cmType = CMFree
  			ifTrue: [delta := delta - cogMethod blockSize]
  			ifFalse:
  				[self assert: (cogit cogMethodDoesntLookKosher: cogMethod) = 0.
+ 				 cogMethod objectHeader: delta.
+ 				 SistaVM ifTrue:
+ 					[self savePICUsageCount: cogMethod]].
- 				 cogMethod objectHeader: delta].
  		 cogMethod := self methodAfter: cogMethod]!

Item was added:
+ ----- Method: CogMethodZone>>relocateMethodsPreCompaction (in category 'compaction') -----
+ relocateMethodsPreCompaction
+ 	"All surviving methods have had the amount they are going to relocate by
+ 	 stored in their objectHeader fields.  Relocate all relative calls so that after
+ 	 the compaction of both the method containing each call and the call target
+ 	 the calls invoke the same target."
+ 	| cogMethod |
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
+ 	[cogMethod < mzFreeStart] whileTrue:
+ 		[cogMethod cmType ~= CMFree ifTrue:
+ 			[cogMethod cmType = CMClosedPIC
+ 				ifTrue: [cogit relocateCallsInClosedPIC: cogMethod]
+ 				ifFalse: [cogit relocateCallsAndSelfReferencesInMethod: cogMethod]].
+ 		 cogMethod := self methodAfter: cogMethod].
+ 	self relocateAndPruneYoungReferrers.
+ 	^true!

Item was added:
+ ----- Method: CogMethodZone>>restorePICUsageCount: (in category 'compaction') -----
+ restorePICUsageCount: cogMethod
+ 	"For Sista, where we want PICs to last so they can be observed, we need to keep PICs unless
+ 	 they are definitely unused.  So we need to identify unused PICs.  So in planCompact, zero the
+ 	 usage counts of all PICs, saving the actual usage count in blockEntryOffset.  Then in
+ 	 relocateMethodsPreCompaction (actually in relocateIfCallOrMethodReference:mcpc:delta:)
+ 	 restore the usage counts of used PICs.  Finally in compactCompiledCode, clear the blockEntryOffset
+ 	 of the unused PICs; they will then have a zero count and be reclaimed in the next code compaction."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<option: #SistaVM>
+ 	(cogMethod cmType = CMClosedPIC
+ 	 and: [cogMethod blockEntryOffset ~= 0]) ifTrue:
+ 		[cogMethod
+ 			cmUsageCount: cogMethod blockEntryOffset;
+ 			blockEntryOffset: 0]!

Item was added:
+ ----- Method: CogMethodZone>>savePICUsageCount: (in category 'compaction') -----
+ savePICUsageCount: cogMethod
+ 	"For Sista, where we want PICs to last so they can be observed, we need to keep PICs unless
+ 	 they are definitely unused.  So we need to identify unused PICs.  So in planCompact, zero the
+ 	 usage counts of all PICs, saving the actual usage count in blockEntryOffset.  Then in
+ 	 relocateMethodsPreCompaction (actually in relocateIfCallOrMethodReference:mcpc:delta:)
+ 	 restore the usage counts of used PICs.  Finally in compactCompiledCode, clear the blockEntryOffset
+ 	 of the unused PICs; they will then have a zero count and be reclaimed in the next code compaction."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<option: #SistaVM>
+ 	cogMethod cmType = CMClosedPIC ifTrue:
+ 		[cogMethod
+ 			blockEntryOffset: cogMethod cmUsageCount;
+ 			cmUsageCount: 0]!

Item was added:
+ ----- Method: CogMethodZone>>shouldFreeMethod:given: (in category 'compaction') -----
+ shouldFreeMethod: cogMethod given: freeableUsage
+ 	"Answer if cogMethod should be freed in the current pass of freeOlderMethodsForCompaction.
+ 
+ 	 For Sista, where we want PICs to last so they can be observed, we need to keep PICs unless
+ 	 they are definitely unused.  So we need to identify unused PICs.  So in planCompact, zero the
+ 	 usage counts of all PICs, saving the actual usage count in blockEntryOffset.  Then in
+ 	 relocateMethodsPreCompaction (actually in relocateIfCallOrMethodReference:mcpc:delta:)
+ 	 restore the usage counts of used PICs.  Finally in compactCompiledCode, clear the blockEntryOffset
+ 	 of the unused PICs; they will then have a zero count and be reclaimed in the next code compaction."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	<inline: true>
+ 	^SistaVM
+ 		ifTrue:
+ 			[cogMethod cmType = CMMethod
+ 			 	ifTrue: [cogMethod cmUsageCount <= freeableUsage]
+ 				ifFalse: [cogMethod cmType ~= CMFree
+ 						  and: [cogMethod cmUsageCount = 0]]]
+ 		ifFalse:
+ 			[cogMethod cmType ~= CMFree
+ 			  and: [cogMethod cmUsageCount <= freeableUsage]]!

Item was changed:
  ----- Method: CogVMSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  	"CogVMSimulator new openOn: 'clone.im' extraMemory: 100000"
  
  	| f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes
  	  headerFlags firstSegSize heapSize
  	  hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize
  	  hdrCogCodeSize stackZoneSize methodCacheSize primTraceLogSize allocationReserve |
  	"open image file and read the header"
  
  	f := FileStream readOnlyFileNamed: fileName.
  	f ifNil: [^self error: 'no image found'].
  
  	["begin ensure block..."
  	imageName := f fullName.
  	f binary.
  
  	version := self getWord32FromFile: f swap: false.  "current version: 16r1968 (=6504) vive la revolucion!!"
  	(self readableFormat: version)
  		ifTrue: [swapBytes := false]
  		ifFalse: [(version := objectMemory byteSwapped: version) = self imageFormatVersion
  					ifTrue: [swapBytes := true]
  					ifFalse: [self error: 'incomaptible image format']].
  	headerSize := self getWord32FromFile: f swap: swapBytes.
  	dataSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  	oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getWord32FromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default. Can be changed via vmParameterAt: 43 put: n"
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	stackZoneSize := self computeStackZoneSize.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
+ 									ifTrue: [cogit defaultCogCodeSize]
- 									ifTrue: [self defaultCogCodeSize]
  									ifFalse: [hdrCogCodeSize]].
  	desiredCogCodeSize := hdrCogCodeSize.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]).
  	hdrEdenBytes	:= self getWord32FromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [48] ifFalse: [72]).
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"For Open PICs to be able to probe the method cache during
  	 simulation the methodCache must be relocated to memory."
  	methodCacheSize := methodCache size * objectMemory wordSize.
  	primTraceLogSize := primTraceLog size * objectMemory wordSize.
  	"allocate interpreter memory. This list is in address order, low to high.
  	 In the actual VM the stack zone exists on the C stack."
  	heapBase := (Cogit guardPageSize
  				+ cogCodeSize
  				+ stackZoneSize
  				+ methodCacheSize
  				+ primTraceLogSize
  				+ self rumpCStackSize) roundUpTo: objectMemory allocationUnit.
  	"compare memory requirements with availability"
  	allocationReserve := self interpreterAllocationReserveBytes.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[| freeOldSpaceInImage headroom |
  			 freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  			 headroom := objectMemory
  							initialHeadroom: extraVMMemory
  							givenFreeOldSpaceInImage: freeOldSpaceInImage.
  			 heapSize := objectMemory roundUpHeapSize:
  						   dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
  			[heapSize :=  dataSize
  						+ extraBytes
  						+ objectMemory newSpaceBytes
  						+ (extraBytes > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])].
  	heapBase := objectMemory
  					setHeapBase: heapBase
  					memoryLimit:  heapBase + heapSize
  					endOfMemory: heapBase + dataSize.
  
  	self assert: cogCodeSize \\ 4 = 0.
  	self assert: objectMemory memoryLimit \\ 4 = 0.
  	self assert: self rumpCStackSize \\ 4 = 0.
  	"read in the image in bulk, then swap the bytes if necessary"
  	f position: headerSize.
  	objectMemory memory: ((cogit processor endianness == #little
  					ifTrue: [LittleEndianBitmap]
  					ifFalse: [Bitmap]) new: objectMemory memoryLimit // 4).
  	count := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
  	count ~= dataSize ifTrue: [self halt].
  	]
  		ensure: [f close].
  	self moveMethodCacheToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize.
  	self movePrimTraceLogToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize + methodCacheSize.
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
  	Utilities
  		informUser: 'Relocating object pointers...'
  		during: [self initializeInterpreter: bytesToShift].
  	self initializeCodeGenerator!

Item was changed:
  ----- Method: Cogit>>ceSICMiss: (in category 'in-line cacheing') -----
  ceSICMiss: receiver
  	"An in-line cache check in a method has failed.  The failing entry check has jumped
  	 to the ceMethodAbort abort call at the start of the method which has called this routine.
  	 If possible allocate a closed PIC for the current and existing classes.
  	 The stack looks like:
  			receiver
  			args
  			sender return address
  	  sp=>	ceMethodAbort call return address
  	 So we can find the method that did the failing entry check at
  		ceMethodAbort call return address - missOffset
  	 and we can find the send site from the outer return address."
  	<api>
  	| pic innerReturn outerReturn entryPoint targetMethod newTargetMethodOrNil errorSelectorOrNil cacheTag extent result |
  	<var: #pic type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #callerMethod type: #'CogMethod *'>
  	"Whether we can relink to a PIC or not we need to pop off the inner return and identify the target method."
  	innerReturn := coInterpreter popStack asUnsignedInteger.
  	targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'.
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	outerReturn := coInterpreter stackTop asUnsignedInteger.
  	self assert: (outerReturn between: methodZoneBase and: methodZone freeStart).
  	entryPoint := backEnd callTargetFromReturnAddress: outerReturn.
  
  	self assert: targetMethod selector ~= objectMemory nilObject.
  	self cppIf: NewspeakVM ifTrue:
  		[| callerMethod annotation |
  		 self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  		 callerMethod := coInterpreter mframeHomeMethod: coInterpreter getFramePointer.
  		 self assert: (outerReturn
  						between: callerMethod asUnsignedInteger + cmNoCheckEntryOffset
  						and: callerMethod asUnsignedInteger + callerMethod blockSize).
  		 annotation := self annotationForMcpc: outerReturn in: callerMethod.
  		 self assert: annotation >= IsSendCall.
  		 "Avoid the effort of implementing PICs for the relatively high dynamic frequency
  		  self send and simply rebind the send site (for now)."
  		 annotation = IsNSSelfSend ifTrue:
  			[^coInterpreter
  				ceSelfSend: targetMethod selector
  				to: receiver
  				numArgs: targetMethod cmNumArgs].
  		 "Avoid the effort of implementing PICs for the relatively low dynamic frequency
  		  dynamic super send and simply rebind the send site."
  		 annotation = IsNSDynamicSuperSend ifTrue:
  			[^coInterpreter
  				ceDynamicSuperSend: targetMethod selector
  				to: receiver
  				numArgs: targetMethod cmNumArgs]].
  	self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  
  	self lookup: targetMethod selector
  		for: receiver
  		methodAndErrorSelectorInto:
  			[:method :errsel|
  			newTargetMethodOrNil := method.
  			errorSelectorOrNil := errsel].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	((errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [(backEnd inlineCacheTagAt: outerReturn) = self picAbortDiscriminatorValue
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]]) ifTrue:
  		[result := self patchToOpenPICFor: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	"See if an Open PIC is already available."
  	pic := methodZone openPICWithSelector: targetMethod selector.
  	pic isNil ifTrue:
  		["otherwise attempt to create a closed PIC for the two cases."
  		 pic := self cogPICSelector: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					Case0Method: targetMethod
  					Case1Method: newTargetMethodOrNil
  					tag: cacheTag
  					isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
  		 (pic asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory.
  			  Continue as if this is an unlinked send."
  			 pic asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  		 processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize].
  	"Relink the send site to the pic.  If to an open PIC then reset the cache tag to the selector,
  	 for the benefit of the cacheTag assert check in checkIfValidObjectRef:pc:cogMethod:."
  	extent := pic cmType = CMOpenPIC
  				ifTrue:
  					[backEnd
  						rewriteInlineCacheAt: outerReturn
  						tag: targetMethod selector
  						target: pic asInteger + cmEntryOffset]
  				ifFalse:
  					[backEnd
  						rewriteCallAt: outerReturn
  						target: pic asInteger + cmEntryOffset].
+ 	processor flushICacheFrom: outerReturn asUnsignedInteger - 1 - extent to: outerReturn asUnsignedInteger - 1.
- 	processor flushICacheFrom: outerReturn  - extent to: outerReturn .
  	"Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)"
  	coInterpreter
  		executeCogPIC: pic
  		fromLinkedSendWithReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: Cogit>>compactCogCompiledCode (in category 'jit - api') -----
  compactCogCompiledCode
  	<api>
  	self assert: self noCogMethodsMaximallyMarked.
  	coInterpreter markActiveMethodsAndReferents.
  	methodZone freeOlderMethodsForCompaction.
  	self freePICsWithFreedTargets.
  	methodZone planCompaction.
  	coInterpreter updateStackZoneReferencesToCompiledCodePreCompaction.
+ 	methodZone relocateMethodsPreCompaction.
- 	self relocateMethodsPreCompaction.
  	methodZone compactCompiledCode.
  	self assert: self allMethodsHaveCorrectHeader.
  	self assert: methodZone kosherYoungReferrers.
+ 	processor
+ 		flushICacheFrom: methodZoneBase asUnsignedInteger
+ 		to: methodZone freeStart asUnsignedInteger!
- 	processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone freeStart asUnsignedInteger!

Item was added:
+ ----- Method: Cogit>>defaultCogCodeSize (in category 'accessing') -----
+ defaultCogCodeSize
+ 	"Return the default number of bytes to allocate for native code at startup.
+ 	 The actual value can be set via vmParameterAt: and/or a preference in the ini file."
+ 	<doNotGenerate>
+ 	^backEnd defaultCogCodeSize!

Item was changed:
  ----- Method: Cogit>>linkSendAt:in:to:offset:receiver: (in category 'in-line cacheing') -----
  linkSendAt: callSiteReturnAddress in: sendingMethod to: targetMethod offset: theEntryOffset receiver: receiver
  	<api>
  	<var: #sendingMethod type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	| inlineCacheTag address extent |
  	self assert: (theEntryOffset = cmEntryOffset or: [theEntryOffset = cmNoCheckEntryOffset]).
  	self assert: (callSiteReturnAddress between: methodZoneBase and: methodZone freeStart).
  	inlineCacheTag := theEntryOffset = cmNoCheckEntryOffset
  						ifTrue: [targetMethod selector "i.e. no change"]
  						ifFalse: [objectRepresentation inlineCacheTagForInstance: receiver].
  	(objectRepresentation inlineCacheTagIsYoung: inlineCacheTag) ifTrue:
  		[methodZone ensureInYoungReferrers: sendingMethod].
  	address := targetMethod asInteger + theEntryOffset.
  	extent := backEnd
  				rewriteInlineCacheAt: callSiteReturnAddress
  				tag: inlineCacheTag
  				target: address.
  	processor
+ 		flushICacheFrom: callSiteReturnAddress asUnsignedInteger - 1 - extent
+ 		to: callSiteReturnAddress asUnsignedInteger - 1!
- 		flushICacheFrom: callSiteReturnAddress asUnsignedInteger - extent
- 		to: callSiteReturnAddress asUnsignedInteger!

Item was changed:
  ----- Method: Cogit>>patchToOpenPICFor:numArgs:receiver: (in category 'in-line cacheing') -----
  patchToOpenPICFor: selector numArgs: numArgs receiver: receiver
  	"Code entry closed PIC full or miss to an instance of a young class or to a young target method.
  	 Attempt to patch the send site to an open PIC.  Answer if the attempt succeeded; in fact it will
  	 only return if the attempt failed.
  	 The stack looks like:
  			receiver
  			args
  	 sp=>	sender return address"
  	<api>
  	| oPIC outerReturn extent |
  	<var: #oPIC type: #'CogMethod *'>
  	outerReturn := coInterpreter stackTop.
  	"See if an Open PIC is already available."
  	oPIC := methodZone openPICWithSelector: selector.
  	oPIC isNil ifTrue:
  		["otherwise attempt to create an Open PIC."
  		oPIC := self cogOpenPICSelector: selector numArgs: numArgs.
  		(oPIC asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory."
  			oPIC asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^false]].
  	extent := backEnd
  				rewriteInlineCacheAt: outerReturn
  				tag: selector
  				target: oPIC asInteger + cmEntryOffset.
  	processor
+ 		flushICacheFrom: outerReturn asUnsignedInteger - 1 - extent to: outerReturn asUnsignedInteger - 1;
+ 		flushICacheFrom: oPIC asUnsignedInteger to: oPIC asUnsignedInteger + openPICSize.
- 		flushICacheFrom: outerReturn asUnsignedInteger - extent to: outerReturn asUnsignedInteger;
- 		flushICacheFrom: oPIC asInteger to: oPIC asInteger + openPICSize.
  	"Jump into the oPIC at its entry"
  	coInterpreter executeCogMethod: oPIC fromLinkedSendWithReceiver: receiver.
  	"NOTREACHED"
  	^true!

Item was changed:
  ----- Method: Cogit>>relocateIfCallOrMethodReference:mcpc:delta: (in category 'compaction') -----
  relocateIfCallOrMethodReference: annotation mcpc: mcpc delta: delta
  	<var: #mcpc type: #'char *'>
  	| entryPoint targetMethod unlinkedRoutine |
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  
  	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			["Retrieve the send cache before relocating the stub call. Fetching the send
  			  cache asserts the stub call points below all the cogged methods, but
  			  until this method is actually moved, the adjusted stub call may appear to
  			  point to somewhere in the method zone."
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  
  			"Fix call to trampoline. This method is moving [delta] bytes, and calls are
  			 relative, so adjust the call by -[delta] bytes"
  			backEnd relocateCallBeforeReturnPC: mcpc asInteger by: delta negated.
  
  			nsSendCache target ~= 0 ifTrue: "Send is linked"
  				[entryPoint := nsSendCache target.
  				targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				targetMethod cmType = CMMethod
  					ifTrue: "send target not freed; just relocate. The cache has an absolute
  							target, so only adjust by the target method's displacement."
  						[nsSendCache target: entryPoint + targetMethod objectHeader]
  					ifFalse: "send target was freed, unlink"
  						[self voidNSSendCache: nsSendCache]].
  			^0]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		entryPoint <= methodZoneBase ifTrue: "send is not linked; just relocate"
  			[backEnd relocateCallBeforeReturnPC: mcpc asInteger by: delta negated.
  			 ^0].
  		"It's a linked send; find which kind."
  		self
  			offsetAndSendTableFor: entryPoint
  			annotation: annotation
  			into: [:offset :sendTable|
  				 targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
+ 				 targetMethod cmType ~= CMFree ifTrue: "send target not freed; just relocate."
- 				 targetMethod cmType = CMMethod ifTrue: "send target not freed; just relocate."
  					[backEnd
  						relocateCallBeforeReturnPC: mcpc asInteger
  						by: (delta - targetMethod objectHeader) negated.
+ 					 SistaVM ifTrue: "See comment in planCompaction"
+ 						[methodZone restorePICUsageCount: targetMethod].
  					 ^0].
  				 "Target was freed; map back to an unlinked send; but include this method's reocation"
  				 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
  				 unlinkedRoutine := unlinkedRoutine - delta.
  				 backEnd
  					rewriteInlineCacheAt: mcpc asInteger
  					tag: targetMethod selector
  					target: unlinkedRoutine.
  				 ^0]].
  
  	annotation = IsRelativeCall ifTrue:
  		[backEnd relocateCallBeforeReturnPC: mcpc asInteger by: delta negated.
  		 ^0].
  
  	annotation = IsAbsPCReference ifTrue:
  		[backEnd relocateMethodReferenceBeforeAddress: mcpc asInteger by: delta].
  
  	^0 "keep scanning"!

Item was removed:
- ----- Method: Cogit>>relocateMethodsPreCompaction (in category 'compaction') -----
- relocateMethodsPreCompaction
- 	"All surviving methods have had the amount they are going to relocate by
- 	 stored in their objectHeader fields.  Relocate all relative calls so that after
- 	 the compaction of both the method containing each call and the call target
- 	 the calls invoke the same target."
- 	| cogMethod |
- 	<var: #cogMethod type: #'CogMethod *'>
- 	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
- 	[cogMethod < methodZone limitZony] whileTrue:
- 		[cogMethod cmType ~= CMFree ifTrue:
- 			[cogMethod cmType = CMClosedPIC
- 				ifTrue: [self relocateCallsInClosedPIC: cogMethod]
- 				ifFalse: [self relocateCallsAndSelfReferencesInMethod: cogMethod]].
- 		 cogMethod := methodZone methodAfter: cogMethod].
- 	methodZone relocateAndPruneYoungReferrers.
- 	^true!



More information about the Vm-dev mailing list