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

commits at source.squeak.org commits at source.squeak.org
Fri Mar 17 00:04:19 UTC 2017


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

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

Name: VMMaker.oscog-eem.2159
Author: eem
Time: 16 March 2017, 5:03:10.592659 pm
UUID: 68593f06-8e04-4a44-9896-c10f4d35aaa4
Ancestors: VMMaker.oscog-eem.2158

Sista:
Provide a movable allocation threshold in the mehtod zone so that nore space can be made available on a counter trip to avoid reclaiming the method zone and there-by destroying send and branch data as Scorch kicks in.  Allow the threshold to be read and reset via vmParameterAt: 17.  Put this in the SistaMethodZOne subclass of CogMethodZone.  Have the ceCounterTripped: routine set the threshold to 1.0 from its default of 0.5.  Doble the size of the default code zone in Sista VMs.

Spur Cogit:
Fix regression in genNewHashTrampoline.

StackInterpreter:
Simplify the generated code for primitiveVMParameter by using beRootIfOld: instead of storePointer: for the bulk store into the zero args case.  Make the tenuringThreshold: setters use the same convention as other setters, answering the primFailCode.

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

Item was changed:
  ----- Method: CoInterpreter>>ceCounterTripped: (in category 'cog jit support') -----
  ceCounterTripped: condition
  	"Two things are going on here.  The main one is catching a counter trip and attempting
  	 to send the SelectorCounterTripped selector.  In this case we would like to back-up
  	 the pc to the return address of the send that yields the boolean to be tested, so that
  	 after potential optimization, computation proceeds by retrying the jump.  But we cannot,
  	 since there may be no send, just a pop (as in and: [] and or: [] chains).  In this case we also
  	 want to prevent further callbacks until optimization is complete.  So we nil-out the
  	 SelectorCounterTripped entry in the specialSelectorArray.
  
  	 The minor case is that there is an unlikely  possibility that the cointer tripped but condition
  	 is not a boolean, in which case a mustBeBoolean response should occur."
  	<api>
  	<option: #SistaCogit>
  	"Send e.g. thisContext conditionalBranchCounterTrippedOn: boolean."
  	| context counterTrippedSelector classTag classObj |
  	(condition = objectMemory falseObject
  	or: [condition = objectMemory trueObject]) ifFalse:
  		[^self ceSendMustBeBoolean: condition].
  
  	counterTrippedSelector := objectMemory maybeSplObj: SelectorCounterTripped.
  	(counterTrippedSelector isNil
  	or: [counterTrippedSelector = objectMemory nilObject]) ifTrue:
  		[cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  		 ^condition].
  
  	classTag := objectMemory
  					classTagForSpecialObjectsIndex: ClassMethodContext
  					compactClassIndex: ClassMethodContextCompactIndex.
  	(self lookupInMethodCacheSel: counterTrippedSelector classTag: classTag) ifFalse:
  	 	[messageSelector := counterTrippedSelector.
  		 classObj := objectMemory classForClassTag: classTag.
  		 (self lookupOrdinaryNoMNUEtcInClass: classObj) ~= 0 ifTrue:
  			[cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  			 ^condition]].
  
  	(primitiveFunctionPointer ~= 0
  	or: [(self argumentCountOf: newMethod) ~= 1]) ifTrue:
  		[cogit resetCountersIn: (self mframeHomeMethod: framePointer).
  		 ^condition].
  
+ 	cogit setCogCodeZoneThreshold: 1.0.
  	objectMemory splObj: SelectorCounterTripped put: objectMemory nilObject.
  	instructionPointer := self popStack.
  	context := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	self push: context.
  	self push: condition.
  	self ifAppropriateCompileToNativeCode: newMethod selector: counterTrippedSelector.
  	self activateNewMethod.
  	"not reached"
  	^true!

Item was added:
+ ----- Method: CoInterpreter>>getCogCodeZoneThreshold (in category 'internal interpreter access') -----
+ getCogCodeZoneThreshold
+ 	<doNotGenerate>
+ 	<returnTypeC: #double>
+ 	^cogit getCogCodeZoneThreshold!

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]
  									ifFalse: [hdrCogCodeSize]].
+ 	cogCodeSize > cogit maxCogCodeSize ifTrue:
+ 		[cogCodeSize := cogit maxCogCodeSize].
  	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: CoInterpreter>>setCogCodeZoneThreshold: (in category 'internal interpreter access') -----
+ setCogCodeZoneThreshold: threshold
+ 	<doNotGenerate>
+ 	<var: 'threshold' type: #double>
+ 	^cogit setCogCodeZoneThreshold: threshold!

Item was changed:
  ----- Method: CogMethodZone>>allocate: (in category 'allocating') -----
  allocate: numBytes
  	| roundedBytes allocation |
  	roundedBytes := numBytes + 7 bitAnd: -8.
+ 	mzFreeStart + roundedBytes >= self allocationLimit ifTrue:
- 	mzFreeStart + roundedBytes >= (limitAddress - (methodCount * objectMemory wordSize)) ifTrue:
  		[^0].
  	allocation := mzFreeStart.
  	mzFreeStart := mzFreeStart + roundedBytes.
  	methodCount := methodCount + 1.
  	self cCode: '' inSmalltalk:
  		[(cogit breakPC isInteger
  		   and: [cogit breakPC between: allocation and: mzFreeStart]) ifTrue:
  			[cogit singleStep: true]].
  	^allocation!

Item was added:
+ ----- Method: CogMethodZone>>allocationLimit (in category 'allocating') -----
+ allocationLimit
+ 	<inline: true>
+ 	^limitAddress - (methodCount * objectMemory wordSize)!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genNewHashTrampoline (in category 'initialization') -----
  genNewHashTrampoline
  	"In non sista VM this is used only from the identityHash primitive, hence only the result of the trampoline, the hash, should be in ReceiverResultReg, other registers can just be ignored.
  	In the sista VM, the inlined hash operation requires registers to be saved"
  	<inline: true>
  	<option: #SistaVM>
  	^ cogit
+ 		genTrampolineFor: #ceNewHashOf:
- 		genTrampolineFor: 1
  		called: 'newHashTrampoline'
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		regsToSave: (CallerSavedRegisterMask bitClear: (cogit registerMaskFor: ReceiverResultReg))
  		pushLinkReg: true
  		resultReg: ReceiverResultReg
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  	ProcessorClass ifNil:
  		[Cogit initializeMiscConstants].
  	^(self activeCompilerClass withAllSuperclasses copyUpThrough: CogAbstractInstruction),
  	  {	CogMethodZone.
  		CogBlockStart.
  		CogBytecodeDescriptor.
  		CogBytecodeFixup.
  		CogPrimitiveDescriptor.
  		CogBlockMethod.
  		CogMethod.
  		self activeCompilerClass literalsManagerClass},
  	((options at: #NewspeakVM ifAbsent: [false])
  		ifTrue: [{NewspeakCogMethod. NSSendCache}]
+ 		ifFalse: [#()]),
+ 	((options at: #SistaVM ifAbsent: [false])
+ 		ifTrue: [{SistaMethodZone}]
  		ifFalse: [#()])!

Item was added:
+ ----- Method: Cogit class>>methodZoneClass (in category 'accessing class hierarchy') -----
+ methodZoneClass
+ 	^CogMethodZone!

Item was added:
+ ----- Method: Cogit>>maxCogCodeSize (in category 'accessing') -----
+ maxCogCodeSize
+ 	"We restrict the maximum size of the code zone to 16Mb to allow inter-method
+ 	 calls and jumps to use small offset call and jump instructions if appropriate."
+ 	<api>
+ 	<cmacro: '() (16*1024*1024)'>
+ 	^16*1024*1024!

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"
+ 	methodZone := self class methodZoneClass new.
- 	methodZone := CogMethodZone new.
  	objectRepresentation := objectMemory objectRepresentationClass
  								forCogit: self methodZone: methodZone.
  	methodZone setInterpreter: aCoInterpreter
  				objectRepresentation: objectRepresentation
  				cogit: self.
  	generatorTable := self class generatorTable.
  	processor := ProcessorClass new.
  	simulatedAddresses := Dictionary new.
  	simulatedTrampolines := Dictionary new.
  	simulatedVariableGetters := Dictionary new.
  	simulatedVariableSetters := Dictionary new.
  	traceStores := 0.
  	traceFlags := (self class initializationOptions at: #recordPrimTrace ifAbsent: [true])
  					ifTrue: [8] "record prim trace on by default (see Cogit class>>decareCVarsIn:)"
  					ifFalse: [0].
  	debugPrimCallStackOffset := 0.
  	singleStep := printRegisters := printInstructions := clickConfirm := false.
  	backEnd := CogCompilerClass for: self.
  	methodLabel := CogCompilerClass for: self.
  	(literalsManager := backEnd class literalsManagerClass new) cogit: self.
  	ordinarySendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	superSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	BytecodeSetHasDirectedSuperSend ifTrue:
  		[directedSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
  	NewspeakVM ifTrue:
  		[selfSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		dynamicSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		implicitReceiverSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		outerSendTrampolines := 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.
  
  	extA := numExtB := extB := 0.
  
  	compilationTrace ifNil: [compilationTrace := self class initializationOptions at: #compilationTrace ifAbsent: [0]].
  	debugOpcodeIndices := self class initializationOptions at: #debugOpcodeIndices ifAbsent: [Set new].
  	debugBytecodePointers := self class initializationOptions at: #debugBytecodePointers ifAbsent: [Set new].
  	self class initializationOptions at: #breakPC ifPresent: [:pc| breakPC := pc]!

Item was added:
+ ----- Method: Float>>asUnsignedInteger (in category '*VMMaker-interpreter simulator') -----
+ asUnsignedInteger
+ 	self assert: self >= 0.
+ 	"C conversion from float/double to integer is by dropping the fractional part"
+ 	^self truncated!

Item was changed:
  ----- Method: ObjectMemory>>tenuringThreshold: (in category 'accessing') -----
  tenuringThreshold: aValue
+ 	tenuringThreshold := aValue.
+ 	^0!
- 	^tenuringThreshold := aValue!

Item was added:
+ ----- Method: SistaCogit class>>methodZoneClass (in category 'accessing class hierarchy') -----
+ methodZoneClass
+ 	^SistaMethodZone!

Item was added:
+ ----- Method: SistaCogit>>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>
+ 	^2 * backEnd getDefaultCogCodeSize!

Item was added:
+ ----- Method: SistaCogit>>setCogCodeZoneThreshold: (in category 'accessing') -----
+ setCogCodeZoneThreshold: threshold
+ 	<doNotGenerate>
+ 	^methodZone setCogCodeZoneThreshold: threshold!

Item was added:
+ CogMethodZone subclass: #SistaMethodZone
+ 	instanceVariableNames: 'allocationThreshold thresholdRatio'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: SistaMethodZone class>>declareCVarsIn: (in category 'translation') -----
+ declareCVarsIn: aCCodeGenerator
+ 	aCCodeGenerator
+ 		declareVar: 'allocationThreshold' type: #usqInt;
+ 		var: 'thresholdRatio' declareC: (BytesPerWord = 8 ifTrue: ['double thresholdRatio = 0.5'] ifFalse: ['float thresholdRatio = 0.5f'])!

Item was added:
+ ----- Method: SistaMethodZone>>allocationLimit (in category 'allocating') -----
+ allocationLimit
+ 	<inline: true>
+ 	^super allocationLimit min: allocationThreshold!

Item was added:
+ ----- Method: SistaMethodZone>>computeAllocationThreshold (in category 'initialization') -----
+ computeAllocationThreshold
+ 	<inline: true>
+ 	allocationThreshold := ((limitAddress - baseAddress * thresholdRatio) asUnsignedInteger + (self zoneAlignment - 1) truncateTo: self zoneAlignment) + baseAddress!

Item was added:
+ ----- Method: SistaMethodZone>>getCogCodeZoneThreshold (in category 'accessing') -----
+ getCogCodeZoneThreshold
+ 	<api>
+ 	<returnTypeC: #double>
+ 	^thresholdRatio!

Item was added:
+ ----- Method: SistaMethodZone>>initialize (in category 'initialization') -----
+ initialize
+ 	thresholdRatio := 0.5!

Item was added:
+ ----- Method: SistaMethodZone>>manageFrom:to: (in category 'initialization') -----
+ manageFrom: theStartAddress to: theLimitAddress
+ 	super manageFrom: theStartAddress to: theLimitAddress.
+ 	self computeAllocationThreshold!

Item was added:
+ ----- Method: SistaMethodZone>>setCogCodeZoneThreshold: (in category 'accessing') -----
+ setCogCodeZoneThreshold: ratio
+ 	<api>
+ 	<var: #ratio type: #double>
+ 	self break.
+ 	(ratio >= 0.1 and: [ratio <= 1.0]) ifFalse:
+ 		[^PrimErrBadArgument].
+ 	thresholdRatio := ratio.
+ 	self computeAllocationThreshold.
+ 	^0!

Item was changed:
  ----- Method: SpurMemoryManager>>tenuringThreshold: (in category 'accessing') -----
  tenuringThreshold: threshold
  	"c.f. tenuringThreshold"
+ 	threshold < 0 ifTrue:
+ 		[^PrimErrBadArgument].
  	scavenger scavengerTenuringThreshold:
  		(threshold * self averageObjectSizeInBytes) asFloat
+ 		/ scavenger pastSpaceBytes asFloat.
+ 	^0!
- 		/ scavenger pastSpaceBytes asFloat!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveVMParameter (in category 'system control primitives') -----
(excessive size, no diff calculated)



More information about the Vm-dev mailing list