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

commits at source.squeak.org commits at source.squeak.org
Tue Aug 26 08:32:54 UTC 2014


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

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

Name: VMMaker.oscog-eem.864
Author: eem
Time: 26 August 2014, 9:28:33.064 am
UUID: 6a9b157d-24d8-47eb-bbc0-0a467b390e26
Ancestors: VMMaker.oscog-eem.863

Sista:
Fix primitiveSistaMethodPICAndCounterData after the
VMMaker.oscog-eem.814 change moving counters to
the heap.  Add several modifications to the current image
facade so we can get the send and branch data for an
in-image compilation.  Fix header printing of counters and
IR caches.

Implement genBinaryConstOpVarInlinePrimitive: &
genBinaryVarOpConstInlinePrimitive: and correct
genBinaryVarOpVarInlinePrimitive: for Slang.

V3:
Fix bug with become where duplicate entries in the input
array would crash the system (thanks Igor).

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

Item was added:
+ ----- Method: CogARMCompiler>>isBigEndian (in category 'testing') -----
+ isBigEndian
+ 	^false!

Item was removed:
- ----- Method: CogIA32Compiler>>counterTargetFromFollowingAddress: (in category 'sista counters') -----
- counterTargetFromFollowingAddress: nextInstructionAddress
- 	"Answer the address of the MoveAw:R or MoveR:Aw: instruction preceeding nextInstructionAddress"
- 	^self literalBeforeFollowingAddress: nextInstructionAddress!

Item was added:
+ ----- Method: Cogit>>cCoerce:to: (in category 'simulation only') -----
+ cCoerce: value to: cTypeString
+ 	"Type coercion for translation only; just return the value when running in Smalltalk."
+ 	<doNotGenerate>
+ 	^value == nil
+ 		ifTrue: [value]
+ 		ifFalse: [value coerceTo: cTypeString sim: objectMemory]!

Item was changed:
  ----- Method: Cogit>>mapFor:bcpc:performUntil:arg: (in category 'method map') -----
  mapFor: cogMethod bcpc: startbcpc performUntil: functionSymbol arg: arg
  	"Machine-code <-> bytecode pc mapping support.  Evaluate functionSymbol
  	 for each mcpc, bcpc pair in the map until the function returns non-zero,
  	 answering that result, or 0 if it fails to.  This works only for frameful methods."
  	<var: #cogMethod type: #'CogBlockMethod *'>
  	<var: #functionSymbol declareC: 'sqInt (*functionSymbol)(BytecodeDescriptor *desc, sqInt isBackwardBranch, char *mcpc, sqInt bcpc, void *arg)'>
  	<var: #arg type: #'void *'>
  	<inline: true>
  	| isInBlock mcpc bcpc endbcpc map mapByte homeMethod aMethodObj result
  	  latestContinuation byte descriptor bsOffset nExts |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #homeMethod type: #'CogMethod *'>
  	self assert: cogMethod stackCheckOffset > 0.
  	"In both CMMethod and CMBlock cases find the start of the map and
  	 skip forward to the bytecode pc map entry for the stack check."
  	cogMethod cmType = CMMethod
  		ifTrue:
  			[isInBlock := false.
  			 homeMethod := self cCoerceSimple: cogMethod to: #'CogMethod *'.
  			 self assert: startbcpc = (coInterpreter startPCOfMethodHeader: homeMethod methodHeader).
  			 map := self mapStartFor: homeMethod.
  			 self assert: ((objectMemory byteAt: map) >> AnnotationShift = IsAbsPCReference
  						 or: [(objectMemory byteAt: map) >> AnnotationShift = IsObjectReference
  						 or: [(objectMemory byteAt: map) >> AnnotationShift = IsRelativeCall
  						 or: [(objectMemory byteAt: map) >> AnnotationShift = IsDisplacementX2N]]]).
  			 latestContinuation := startbcpc.
  			 aMethodObj := homeMethod methodObject.
  			 endbcpc := (objectMemory numBytesOf: aMethodObj) - 1.
  			 bsOffset := self bytecodeSetOffsetForHeader: homeMethod methodHeader]
  		ifFalse:
  			[isInBlock := true.
  			 homeMethod := cogMethod cmHomeMethod.
  			 map := self findMapLocationForMcpc: cogMethod asUnsignedInteger + (self sizeof: CogBlockMethod)
  						inMethod: homeMethod.
  			 self assert: map ~= 0.
  			 self assert: ((objectMemory byteAt: map) >> AnnotationShift = HasBytecodePC "fiducial"
  						 or: [(objectMemory byteAt: map) >> AnnotationShift = IsDisplacementX2N]).
  			 [(objectMemory byteAt: map) >> AnnotationShift ~= HasBytecodePC] whileTrue:
  				[map := map - 1].
  			 map := map - 1. "skip fiducial; i.e. the map entry for the pc immediately following the method header."
  			 aMethodObj := homeMethod methodObject.
  			 bcpc := startbcpc - (self blockCreationBytecodeSizeForHeader: homeMethod methodHeader).
  			 bsOffset := self bytecodeSetOffsetForHeader: homeMethod methodHeader.
  			 byte := (objectMemory fetchByte: bcpc ofObject: aMethodObj) + bsOffset.
  			 descriptor := self generatorAt: byte.
  			 endbcpc := self nextBytecodePCFor: descriptor at: bcpc exts: -1 in: aMethodObj].
  	bcpc := startbcpc.
  	mcpc := cogMethod asUnsignedInteger + cogMethod stackCheckOffset.
  	nExts := 0.
  	"The stack check maps to the start of the first bytecode,
  	 the first bytecode being effectively after frame build."
  	result := self perform: functionSymbol
  					with: nil
  					with: false
  					with: (self cCoerceSimple: mcpc to: #'char *')
  					with: startbcpc
  					with: arg.
  	result ~= 0 ifTrue:
  		[^result].
  	"Now skip up through the bytecode pc map entry for the stack check." 
  	[(objectMemory byteAt: map) >> AnnotationShift ~= HasBytecodePC] whileTrue:
  		[map := map - 1].
  	map := map - 1.
  	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue: "defensive; we exit on bcpc"
  		[mapByte >= FirstAnnotation
  			ifTrue:
  				[| annotation nextBcpc isBackwardBranch |
  				annotation := mapByte >> AnnotationShift.
  				mcpc := mcpc + (mapByte bitAnd: DisplacementMask).
  				(self isPCMappedAnnotation: annotation alternateInstructionSet: bsOffset > 0) ifTrue:
  					[[byte := (objectMemory fetchByte: bcpc ofObject: aMethodObj) + bsOffset.
  					  descriptor := self generatorAt: byte.
  					  isInBlock
  						ifTrue: [bcpc >= endbcpc ifTrue: [^0]]
  						ifFalse:
  							[(descriptor isReturn and: [bcpc >= latestContinuation]) ifTrue: [^0].
  							 (descriptor isBranch or: [descriptor isBlockCreation]) ifTrue:
  								[| targetPC |
  								 targetPC := self latestContinuationPCFor: descriptor at: bcpc exts: nExts in: aMethodObj.
  								 latestContinuation := latestContinuation max: targetPC]].
  					  nextBcpc := self nextBytecodePCFor: descriptor at: bcpc exts: nExts in: aMethodObj.
  					  descriptor isMapped
  					  or: [isInBlock and: [descriptor isMappedInBlock]]] whileFalse:
  						[bcpc := nextBcpc.
  						 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]].
  					isBackwardBranch := descriptor isBranch
  										   and: [self isBackwardBranch: descriptor at: bcpc exts: nExts in: aMethodObj].
  					result := self perform: functionSymbol
  									with: descriptor
  									with: isBackwardBranch
  									with: (self cCoerceSimple: mcpc to: #'char *')
  									with: bcpc
  									with: arg.
  					 result ~= 0 ifTrue:
  						[^result].
  					 bcpc := nextBcpc.
+ 					 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]]]
- 					 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]].
- 				self maybeRememberPrevMap: annotation absPCMcpc: mcpc]
  			ifFalse:
  				[mcpc := mcpc + (mapByte >= DisplacementX2N
  									ifTrue: [mapByte - DisplacementX2N << AnnotationShift]
  									ifFalse: [mapByte])].
  		 map := map - 1].
  	^0!

Item was changed:
  ----- Method: Cogit>>printMethodHeader:on: (in category 'disassembly') -----
  printMethodHeader: cogMethod on: aStream
  	<doNotGenerate>
  	self cCode: ''
  		inSmalltalk:
  			[cogMethod isInteger ifTrue:
  				[^self printMethodHeader: (self cogMethodOrBlockSurrogateAt: cogMethod) on: aStream]].
  	aStream ensureCr.
  	cogMethod asInteger printOn: aStream base: 16.
  	aStream crtab.
  	cogMethod cmType = CMMethod ifTrue:
  		[aStream nextPutAll: 'objhdr: '.
  		cogMethod objectHeader printOn: aStream base: 16].
  	cogMethod cmType = CMBlock ifTrue:
  		[aStream nextPutAll: 'homemth: '.
  		cogMethod cmHomeMethod asUnsignedInteger printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'startpc: '; print: cogMethod startpc].
  	aStream
  		crtab; nextPutAll: 'nArgs: ';	print: cogMethod cmNumArgs;
  		tab;    nextPutAll: 'type: ';	print: cogMethod cmType.
  	(cogMethod cmType ~= 0 and: [cogMethod cmType ~= CMBlock]) ifTrue:
  		[aStream crtab; nextPutAll: 'blksiz: '.
  		cogMethod blockSize printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'method: '.
  		cogMethod methodObject printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'mthhdr: '.
  		cogMethod methodHeader printOn: aStream base: 16.
  		aStream crtab; nextPutAll: 'selctr: '.
  		cogMethod selector printOn: aStream base: 16.
  		(coInterpreter lookupAddress: cogMethod selector) ifNotNil:
  			[:string| aStream nextPut: $=; nextPutAll: string].
  		aStream crtab; nextPutAll: 'blkentry: '.
  		cogMethod blockEntryOffset printOn: aStream base: 16.
  		cogMethod blockEntryOffset ~= 0 ifTrue:
  			[aStream nextPutAll: ' => '.
  			 cogMethod asInteger + cogMethod blockEntryOffset printOn: aStream base: 16]].
  	cogMethod cmType = CMClosedPIC
  		ifTrue:
  			[aStream crtab; nextPutAll: 'cPICNumCases: '.
  			 cogMethod cPICNumCases printOn: aStream base: 16.]
  		ifFalse:
  			[aStream crtab; nextPutAll: 'stackCheckOffset: '.
  			 cogMethod stackCheckOffset printOn: aStream base: 16.
  			 cogMethod stackCheckOffset > 0 ifTrue:
  				[aStream nextPut: $/.
  				 cogMethod asInteger + cogMethod stackCheckOffset printOn: aStream base: 16].
  			cogMethod cmType ~= CMBlock ifTrue:
  				[aStream
  					crtab;
  					nextPutAll: 'cmRefersToYoung: ';
  					nextPutAll: (cogMethod cmRefersToYoung ifTrue: ['yes'] ifFalse: ['no'])].
  			cogMethod cmType = CMMethod ifTrue:
  				[([cogMethod nextMethodOrIRCs] on: MessageNotUnderstood do: [:ex| nil]) ifNotNil:
  					[:nmoircs| aStream crtab; nextPutAll: 'nextMethodOrIRCs: '.
+ 						nmoircs = 0 ifTrue: [aStream print: nmoircs] ifFalse: [coInterpreter printHex: nmoircs]].
- 						nmoircs = 0 ifTrue: [aStream print: nmoircs] ifFalse: [self printHex: nmoircs]].
  				 ([cogMethod counters] on: MessageNotUnderstood do: [:ex| nil]) ifNotNil:
  					[:cntrs| aStream crtab; nextPutAll: 'counters: '.
+ 						cntrs = 0 ifTrue: [aStream print: cntrs] ifFalse: [coInterpreter printHex: cntrs]]]].
- 						cntrs = 0 ifTrue: [aStream print: cntrs] ifFalse: [self printHex: cntrs]]]].
  	aStream cr; flush!

Item was changed:
  CogClass subclass: #CurrentImageCoInterpreterFacade
  	instanceVariableNames: 'memory cogit coInterpreter objectMemory objectMap headerToMethodMap cachedObject cachedOop variables'
  	classVariableNames: ''
+ 	poolDictionaries: 'VMBasicConstants VMObjectIndices VMSqueakClassIndices'
- 	poolDictionaries: 'VMBasicConstants VMObjectIndices'
  	category: 'VMMaker-Support'!
  
  !CurrentImageCoInterpreterFacade commentStamp: 'eem 8/6/2014 14:59' prior: 0!
  A CurrentImageCoInterpreterFacade is a stand-in for an object memory (ObjectMemory, SpurMemoryManager, etc) that allows the Cogits to access image objects as if they were in the simulator VM's heap.  hence it allows the Cogits to generate code for methdos in the current image, for testing, etc.
  
  Instance Variables
  	cachedObject:			<Object>
  	cachedOop:			<Integer>
  	coInterpreter:			<CoInterpreter>
  	cogit:					<Cogit>
  	headerToMethodMap:	<Dictionary>
  	memory:				<ByteArray>
  	objectMap:				<IdentityDictionary>
  	objectMemory:			<NewObjectMemory|SpurMemoryManager>
  	variables:				<Dictionary>
  
  cachedObject
  	- the object matching cachedOop, to speed-up oop to obejct mapping
  
  cachedOop
  	- the last used oop
  
  coInterpreter
  	- the CoInterpreter simulator used by the cogit.
  
  cogit
  	- the code egnerator in use
  
  headerToMethodMap
  	- a map from header to CompiledMethod
  
  memory
  	- a rump memory for holding various interpreter variables (e.g. stackLimit) that are accessed as memory locations by generated code
  
  objectMap
  	- map from objects to their oops
  
  objectMemory
  	- the object memory used to encode various values, answer queries, etc
  
  variables
  	- a map from the names of variables to their addresses in memory
  !

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>addressForLabel: (in category 'labels') -----
  addressForLabel: l
+ 	^variables at: l ifAbsentPut: [variables size * 4 + self variablesBase]!
- 	^variables at: l ifAbsentPut: [variables size * 4 + 131072]!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>byteAt: (in category 'accessing') -----
  byteAt: index
+ 	^objectMemory byteAt: index!
- 	^memory at: index + 1!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>byteAt:put: (in category 'accessing') -----
  byteAt: index put: value
+ 	^objectMemory byteAt: index put: value!
- 	^memory at: index + 1 put: value!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>cogCodeSize (in category 'accessing') -----
  cogCodeSize
+ 	^memory byteSize / 4!
- 	^memory size / 2!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>cogit: (in category 'initialize-release') -----
  cogit: aCogit
  	cogit := aCogit.
  	coInterpreter cogit: aCogit.
  	(objectMemory respondsTo: #cogit:) ifTrue:
+ 		[objectMemory cogit: aCogit].
+ 	(objectMemory respondsTo: #coInterpreter:) ifTrue:
+ 		[objectMemory coInterpreter: coInterpreter]!
- 		[objectMemory cogit: aCogit]!

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

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

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>long32At:put: (in category 'accessing') -----
  long32At: index put: value
+ 	^objectMemory long32At: index put: value!
- 	^memory longAt: index + 1 put: value bigEndian: false!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>longAt: (in category 'accessing') -----
+ longAt: index
+ 	^objectMemory longAt: index!
- longAt: index 
- 	^memory unsignedLongAt: index + 1!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>longAt:put: (in category 'accessing') -----
  longAt: index put: value
+ 	^objectMemory longAt: index put: value!
- 	^memory longAt: index + 1 put: value bigEndian: false!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>methodCacheAddress (in category 'accessing') -----
  methodCacheAddress
+ 	"Use the top half of memory for variables, methodcache and rumpCStack,
+ 	 and the bottom half for allocating code and objects:
+ 
+ 		0 - 256k:			code zone
+ 		256k to 512k		object zone
+ 		512k to 768k		variables
+ 		768k to 1023k		method cache
+ 		 1023k to 1024k	rump C stack"
+ 	^memory byteSize * 3 / 4!
- 	^memory size * 3 / 4!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>numSlotsOf: (in category 'accessing') -----
+ numSlotsOf: objOop
- numSlotsOf: objOop 
  	"Answer the number of slots in the given non-immediate object.
  	 Does not adjust the size of contexts by stackPointer."
  	| obj elementSize wordSize |
  	obj := self objectForOop: objOop.
+ 	obj = objOop ifTrue:
+ 		[^objectMemory numSlotsOf: objOop].
  	self deny: ([obj class isImmediateClass]
  				on: MessageNotUnderstood
  				do: [:ex| obj class == SmallInteger]).
  	wordSize := Smalltalk wordSize.
  	elementSize := 
  		[obj class elementSize]
  			on: MessageNotUnderstood
  			do: [:ex| obj class isBytes ifTrue: [1] ifFalse: [wordSize]].
  	wordSize = 4 ifTrue:
  		[^elementSize caseOf: {
  			[1]	->	[obj basicSize + 3 // wordSize].
  			[2]	->	[obj basicSize * 2 + 3 // wordSize].
  			[4]	->	[obj basicSize + obj class instSize] }].
  	^elementSize caseOf: {
  		[1]	->	[obj basicSize + (wordSize - 1) // wordSize].
  		[2]	->	[obj basicSize * 2 + (wordSize - 1) // wordSize].
  		[4]	->	[obj basicSize * 2 + (wordSize - 1) // wordSize].
  		[8]	->	[obj basicSize + obj class instSize] }!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>printHex: (in category 'printing') -----
+ printHex: anInteger
+ 	coInterpreter printHex: anInteger!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>rumpCStackAddress (in category 'accessing') -----
  rumpCStackAddress
+ 	"Use the top half of memory for variables, methodcache and rumpCStack,
+ 	 and the bottom half for allocating code and objects:
+ 
+ 		0 - 256k:			code zone
+ 		256k to 512k		object zone
+ 		512k to 768k		variables
+ 		768k to 1023k		method cache
+ 		 1023k to 1024k	rump C stack"
+ 	^memory byteSize - 1024!
- 	^memory size / 4 * 3 + 1024!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>startOfMemory (in category 'accessing') -----
  startOfMemory
+ 	"Use the top half of memory for variables, methodcache and rumpCStack,
+ 	 and the bottom half for allocating code and objects:
+ 
+ 		0 - 256k:			code zone
+ 		256k to 512k		object zone
+ 		512k to 768k		variables
+ 		768k to 1023k		method cache
+ 		 1023k to 1024k	rump C stack"
+ 	^memory byteSize / 4!
- 	^memory size!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacade>>unalignedLongAt: (in category 'accessing') -----
- unalignedLongAt: index 
- 	^memory unsignedLongAt: index + 1!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>variablesBase (in category 'private') -----
+ variablesBase
+ 	"Use the top half of memory for variables, methodcache and rumpCStack, and the bottom half for allocating code and objects:
+ 
+ 		0 - 256k:			code zone
+ 		256k to 512k		object zone
+ 		512k to 768k		variables
+ 		768k to 1023k		method cache
+ 		 1023k to 1024k	rump C stack"
+ 	^memory byteSize / 2!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>wordSize (in category 'accessing') -----
  wordSize
+ 	^objectMemory wordSize!
- 	^self memMgr wordSize!

Item was changed:
  CurrentImageCoInterpreterFacade subclass: #CurrentImageCoInterpreterFacadeForSpurObjectRepresentation
+ 	instanceVariableNames: 'hiddenRoots'
- 	instanceVariableNames: 'memMgr hiddenRoots'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-Support'!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>allocatePinnedSlots: (in category 'cog jit support') -----
+ allocatePinnedSlots: nSlots
+ 	^(objectMemory allocatePinnedSlots: nSlots)
+ 		ifNil: [nil]
+ 		ifNotNil:
+ 			[:objOop |
+ 			 objectMap at: objOop put: objOop]!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>classIndexMask (in category 'accessing') -----
  classIndexMask
+ 	^objectMemory classIndexMask!
- 	^self memMgr classIndexMask!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>classTableRootObj (in category 'accessing') -----
  classTableRootObj
  	hiddenRoots ifNil:
+ 		[hiddenRoots := Array new: objectMemory classTableRootSlots + objectMemory hiddenRootSlots].
- 		[hiddenRoots := Array new: self memMgr classTableRootSlots + self memMgr hiddenRootSlots].
  	^self oopForObject: hiddenRoots!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>eeInstantiateClassIndex:format:numSlots: (in category 'cog jit support') -----
+ eeInstantiateClassIndex: knownClassIndex format: objFormat numSlots: numSlots
+ 	self assert: knownClassIndex = ClassArrayCompactIndex.
+ 	^self oopForObject: (Array new: numSlots)!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>initialize (in category 'initialize-release') -----
+ initialize
+ 	super initialize.
+ 	objectMemory
+ 		initializeFreeSpaceForFacadeFrom: self startOfMemory
+ 		to: self variablesBase!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>memMgr (in category 'accessing') -----
- memMgr
- 	^memMgr ifNil:
- 		[memMgr := Spur32BitCoMemoryManager new]!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>memMgr: (in category 'accessing') -----
- memMgr: aSpurMemoryManagerSubclassInstance
- 	memMgr := aSpurMemoryManagerSubclassInstance!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>tagMask (in category 'testing') -----
  tagMask
+ 	^objectMemory tagMask!
- 	^self memMgr tagMask!

Item was added:
+ ----- Method: NewCoObjectMemory>>coInterpreter (in category 'accessing') -----
+ coInterpreter
+ 	<doNotGenerate>
+ 	^coInterpreter!

Item was added:
+ ----- Method: NewCoObjectMemory>>coInterpreter: (in category 'accessing') -----
+ coInterpreter: aCoInterpreter
+ 	<doNotGenerate>
+ 	coInterpreter := aCoInterpreter!

Item was added:
+ ----- Method: NewCoObjectMemory>>headerIndicatesAlternateBytecodeSet: (in category 'simulation') -----
+ headerIndicatesAlternateBytecodeSet: methodHeader
+ 	"this is here only for in-image compilation"
+ 	<doNotGenerate>
+ 	"A negative header selects the alternate bytecode set."
+ 	^methodHeader signedIntFromLong < 0!

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

Item was changed:
  ----- Method: NewObjectMemory>>initForwardBlock:mapping:to:withBackPtr: (in category 'gc -- compaction') -----
+ initForwardBlock: fwdBlock mapping: objOop to: newOop withBackPtr: backFlag
- initForwardBlock: fwdBlock mapping: oop to: newOop withBackPtr: backFlag 
  	"Initialize the given forwarding block to map oop to newOop, 
+ 	and replace oop's header with a pointer to the fowarding block."
- 	and replace oop's header with a pointer to the fowarding 
- 	block. "
  	"Details: The mark bit is used to indicate that an oop is 
  	forwarded. When an oop is forwarded, its header (minus the 
  	mark bit) contains the address of its forwarding block. (The 
  	forwarding block address is actually shifted right by one bit 
  	so that its top-most bit does not conflict with the header's 
  	mark bit; since fowarding blocks are stored on word 
  	boundaries, the low two bits of the address are always zero.) 
  	The first word of the forwarding block is the new oop; the 
  	second word is the oop's orginal header. In the case of a 
  	forward become, a four-word block is used, with the third 
  	field being a backpointer to the old oop (for header fixup), 
  	and the fourth word is unused. The type bits of the 
  	forwarding header are the same as those of the original 
  	header. "
  	| originalHeader originalHeaderType |
  	<inline: true>
+ 	<asmLabel: false>
- 	<asmLabel: false> 
- 	originalHeader := self longAt: oop.
  	self assert: fwdBlock ~= nil. "ran out of forwarding blocks in become"
+ 	self deny: (self hasForwardingBlock: objOop). "'object already has a forwarding table entry"
+ 	originalHeader := self longAt: objOop.
- 	self assert: (originalHeader bitAnd: MarkBit) = 0. "'object already has a forwarding table entry"
  	originalHeaderType := originalHeader bitAnd: TypeMask.
  	self longAt: fwdBlock put: newOop.
  	self longAt: fwdBlock + BytesPerWord put: originalHeader.
+ 	backFlag ifTrue: [self longAt: fwdBlock + (BytesPerWord*2) put: objOop].
+ 	self longAt: objOop put: (fwdBlock >> 1 bitOr: (MarkBit bitOr: originalHeaderType))!
- 	backFlag ifTrue: [self longAt: fwdBlock + (BytesPerWord*2) put: oop].
- 	self longAt: oop put: (fwdBlock >> 1 bitOr: (MarkBit bitOr: originalHeaderType))!

Item was changed:
  ----- Method: NewObjectMemory>>prepareForwardingTableForBecoming:with:twoWay: (in category 'become') -----
  prepareForwardingTableForBecoming: array1 with: array2 twoWay: twoWayFlag 
  	"Ensure that there are enough forwarding blocks to 
  	accomodate this become, then prepare forwarding blocks for 
  	the pointer swap. Return true if successful."
  	"Details: Doing a GC might generate enough space for 
  	forwarding blocks if we're short. However, this is an 
  	uncommon enough case that it is better handled by primitive 
  	fail code at the Smalltalk level."
  
  	"Important note on multiple references to same object  - since the preparation of
  	fwdBlocks is NOT idempotent we get VM crashes if the same object is referenced more
  	than once in such a way as to require multiple fwdBlocks.
  	oop1 forwardBecome: oop1 is ok since only a single fwdBlock is needed.
  	oop1 become: oop1 would fail because the second fwdBlock woudl not have the actual object
  	header but rather the mutated ref to the first fwdBlock.
  	Further problems can arise with an array1 or array2 that refer multiply to the same 
  	object. This would notbe expected input for programmer writen code but might arise from
  	automatic usage such as in ImageSegment loading.
  	To avoid the simple and rather common case of oop1 become*: oop1, we skip such pairs
  	and simply avoid making fwdBlocks - it is redundant anyway"
  	| entriesNeeded entriesAvailable fieldOffset oop1 oop2 fwdBlock fwdBlkSize |
  	entriesNeeded := (self lastPointerOf: array1) // BytesPerWord. "need enough entries for all oops"
  	"Note: Forward blocks must be quadword aligned - see fwdTableInit:."
  	twoWayFlag
  		ifTrue: ["Double the number of blocks for two-way become"
  			entriesNeeded := entriesNeeded * 2.
  			fwdBlkSize := BytesPerWord * 2]
  		ifFalse: ["One-way become needs backPointers in fwd blocks."
  			fwdBlkSize := BytesPerWord * 4].
  	entriesAvailable := self fwdTableInit: fwdBlkSize.
  	entriesAvailable < entriesNeeded ifTrue:
  		[self initializeMemoryFirstFree: freeStart.
  		 "re-initialize the free block"
  		 ^false].
  	fieldOffset := self lastPointerOf: array1.
  	[fieldOffset >= BaseHeaderSize] whileTrue:
  		[oop1 := self longAt: array1 + fieldOffset.
  		 oop2 := self longAt: array2 + fieldOffset.
  		 "if oop1 == oop2, no need to do any work for this pair.
  		  May still be other entries in the arrays though so keep looking"
+ 		 oop1 ~= oop2 ifTrue:
+ 			[(self hasForwardingBlock: oop1) ifFalse: "Don't allocate multiple forwarding entries for duplicates."
- 		 oop1 = oop2 ifFalse:
- 			[fwdBlock := self fwdBlockGet: fwdBlkSize.
- 			 self
- 				initForwardBlock: fwdBlock
- 				mapping: oop1
- 				to: oop2
- 				withBackPtr: twoWayFlag not.
- 			twoWayFlag ifTrue: "Second block maps oop2 back to oop1 for two-way become"
  				[fwdBlock := self fwdBlockGet: fwdBlkSize.
  				 self
  					initForwardBlock: fwdBlock
+ 					mapping: oop1
+ 					to: oop2
+ 					withBackPtr: twoWayFlag not].
+ 			 (twoWayFlag
+ 			  and: [(self hasForwardingBlock: oop2) not]) ifTrue: "Again don't get confused by duplicates"
+ 				["Second block maps oop2 back to oop1 for two-way become"
+ 						fwdBlock := self fwdBlockGet: fwdBlkSize.
+ 						self
+ 							initForwardBlock: fwdBlock
+ 							mapping: oop2
+ 							to: oop1
+ 							withBackPtr: twoWayFlag not]].
- 					mapping: oop2
- 					to: oop1
- 					withBackPtr: twoWayFlag not]].
  		fieldOffset := fieldOffset - BytesPerWord].
  	^true!

Item was added:
+ ----- Method: ObjectMemory>>hasForwardingBlock: (in category 'header access') -----
+ hasForwardingBlock: objOop
+ 	^self isMarked: objOop!

Item was changed:
  ----- Method: ObjectMemory>>prepareForwardingTableForBecoming:with:twoWay: (in category 'become') -----
  prepareForwardingTableForBecoming: array1 with: array2 twoWay: twoWayFlag 
  	"Ensure that there are enough forwarding blocks to 
  	accomodate this become, then prepare forwarding blocks for 
  	the pointer swap. Return true if successful."
  	"Details: Doing a GC might generate enough space for 
  	forwarding blocks if we're short. However, this is an 
  	uncommon enough case that it is better handled by primitive 
  	fail code at the Smalltalk level."
  
  	"Important note on multiple references to same object  - since the preparation of
  	fwdBlocks is NOT idempotent we get VM crashes if the same object is referenced more
  	than once in such a way as to require multiple fwdBlocks.
  	oop1 forwardBecome: oop1 is ok since only a single fwdBlock is needed.
  	oop1 become: oop1 would fail because the second fwdBlock woudl not have the actual object
  	header but rather the mutated ref to the first fwdBlock.
  	Further problems can arise with an array1 or array2 that refer multiply to the same 
  	object. This would notbe expected input for programmer writen code but might arise from
  	automatic usage such as in ImageSegment loading.
  	To avoid the simple and rather common case of oop1 become*: oop1, we skip such pairs
  	and simply avoid making fwdBlocks - it is redundant anyway"
  	| entriesNeeded entriesAvailable fieldOffset oop1 oop2 fwdBlock fwdBlkSize |
  	entriesNeeded := (self lastPointerOf: array1) // BytesPerWord. "need enough entries for all oops"
  	"Note: Forward blocks must be quadword aligned - see fwdTableInit:."
  	twoWayFlag
  		ifTrue: ["Double the number of blocks for two-way become"
  			entriesNeeded := entriesNeeded * 2.
  			fwdBlkSize := BytesPerWord * 2]
  		ifFalse: ["One-way become needs backPointers in fwd blocks."
  			fwdBlkSize := BytesPerWord * 4].
  	entriesAvailable := self fwdTableInit: fwdBlkSize.
  	entriesAvailable < entriesNeeded
  		ifTrue: [self initializeMemoryFirstFree: freeBlock.
  			"re-initialize the free block"
  			^ false].
  	fieldOffset := self lastPointerOf: array1.
  	[fieldOffset >= BaseHeaderSize]
  		whileTrue: [oop1 := self longAt: array1 + fieldOffset.
  			oop2 := self longAt: array2 + fieldOffset.
  			"if oop1 == oop2, no need to do any work for this pair.
  			May still be other entries in the arrays though so keep looking"
+ 			oop1 ~= oop2 ifTrue:
+ 				[(self hasForwardingBlock: oop1) ifFalse: "Don't allocate multiple forwarding entries for duplicates."
+ 					[fwdBlock := self fwdBlockGet: fwdBlkSize.
+ 					 self
- 			oop1 = oop2
- 				ifFalse: [fwdBlock := self fwdBlockGet: fwdBlkSize.
- 					self
  						initForwardBlock: fwdBlock
  						mapping: oop1
  						to: oop2
+ 						withBackPtr: twoWayFlag not].
+ 				 (twoWayFlag
+ 				  and: [(self hasForwardingBlock: oop2) not]) ifTrue: "Again don't get confused by duplicates"
+ 					["Second block maps oop2 back to oop1 for two-way become"
- 						withBackPtr: twoWayFlag not.
- 					twoWayFlag
- 						ifTrue: ["Second block maps oop2 back to oop1 for two-way become"
  							fwdBlock := self fwdBlockGet: fwdBlkSize.
  							self
  								initForwardBlock: fwdBlock
  								mapping: oop2
  								to: oop1
  								withBackPtr: twoWayFlag not]].
  			fieldOffset := fieldOffset - BytesPerWord].
  	^ true!

Item was changed:
  StackToRegisterMappingCogit subclass: #SistaStackToRegisterMappingCogit
+ 	instanceVariableNames: 'picDataIndex picData numCounters counters counterIndex initialCounterValue ceClassTrapTrampoline'
- 	instanceVariableNames: 'picDataIndex picData numCounters counters counterIndex initialCounterValue prevMapAbsPCMcpc ceClassTrapTrampoline'
  	classVariableNames: 'CounterBytes MaxCounterValue'
  	poolDictionaries: 'VMSqueakClassIndices'
  	category: 'VMMaker-JIT'!
  
  !SistaStackToRegisterMappingCogit commentStamp: 'eem 4/7/2014 12:23' prior: 0!
  A SistaStackToRegisterMappingCogit is a refinement of StackToRegisterMappingCogit that generates code suitable for dynamic optimization by Sista, the Speculative Inlining Smalltalk Architecture, a project by Clément Bera and Eliot Miranda.  Sista is an optimizer that exists in the Smalltalk image, /not/ in the VM,  and optimizes by substituting normal bytecoded methods by optimized bytecoded methods that may use special bytecodes for which the Cogit can generate faster code.  These bytecodes eliminate overheads such as bounds checks or polymorphic code (indexing Array, ByteArray, String etc).  But the bulk of the optimization performed is in inlining blocks and sends for the common path.
  
  The basic scheme is that SistaStackToRegisterMappingCogit generates code containing performance counters.  When these counters trip, a callback into the image is performed, at which point Sista analyses some portion of the stack, looking at performance data for the methods on the stack, and optimises based on the stack and performance data.  Execution then resumes in the optimized code.
  
  SistaStackToRegisterMappingCogit adds counters to conditional branches.  Each branch has an executed and a taken count, implemented at the two 16-bit halves of a single 32-bit word.  Each counter pair is initialized with initialCounterValue.  On entry to the branch the executed count is decremented and if the count goes below zero the ceMustBeBooleanAdd[True|False] trampoline called.  The trampoline distinguishes between true mustBeBoolean and counter trips because in the former the register temporarily holding the counter value will contain zero.  Then the condition is tested, and if the branch is taken the taken count is decremented.  The two counter values allow an optimizer to collect basic block execution paths and to know what are the "hot" paths through execution that are worth agressively optimizing.  Since conditional branches are about 1/6 as frequent as sends, and since they can be used to determine the hot path through code, they are a better choice to count than, for example, method or block entry.
  
  SistaStackToRegisterMappingCogit implements picDataFor:into: that fills an Array with the state of the counters in a method and the state of each linked send in a method.  This is used to implement a primitive used by the optimizer to answer the branch and send data for a method as an Array.
  
  Instance Variables
  	counterIndex:			<Integer>
  	counterMethodCache:	<CogMethod>
  	counters:				<Array of AbstractInstruction>
  	initialCounterValue:		<Integer>
  	numCounters:			<Integer>
  	picData:				<Integer Oop>
  	picDataIndex:			<Integer>
  	prevMapAbsPCMcpc:	<Integer>
  
  counterIndex
  	- xxxxx
  
  counterMethodCache
  	- xxxxx
  
  counters
  	- xxxxx
  
  initialCounterValue
  	- xxxxx
  
  numCounters
  	- xxxxx
  
  picData
  	- xxxxx
  
  picDataIndex
  	- xxxxx
  
  prevMapAbsPCMcpc
  	- xxxxx
  !

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>mapFor:bcpc:performUntil:arg: (in category 'method map') -----
- mapFor: cogMethod bcpc: startbcpc performUntil: functionSymbol arg: arg
- 	"as a hack for collecting counters, remember the prev mcpc in a static variable."
- 	prevMapAbsPCMcpc := 0.
- 	^super mapFor: cogMethod bcpc: startbcpc performUntil: functionSymbol arg: arg!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>maybeRememberPrevMap:absPCMcpc: (in category 'method map') -----
- maybeRememberPrevMap: annotation absPCMcpc: mcpc
- 	"Remember the previous IsAbsPCReference's mcpc for collecting send and branch data."
- 	<inline: true>
- 	annotation = IsAbsPCReference ifTrue:
- 		[self assert: mcpc ~= 0.
- 		 prevMapAbsPCMcpc := mcpc]!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>picDataFor:IsBackwardBranch:Mcpc:Bcpc:Method: (in category 'method introspection') -----
  picDataFor: descriptor IsBackwardBranch: IsBackwardBranch Mcpc: mcpc Bcpc: bcpc Method: cogMethodArg
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #mcpc type: #'char *'>
  	<var: #cogMethodArg type: #'void *'>
+ 	| entryPoint tuple counter |
+ 	<var: #counter type: #'unsigned long'>
+ 
- 	| entryPoint tuple |
  	descriptor isNil ifTrue:
  		[^0].
  	descriptor isBranch ifTrue:
  		["it's a branch; conditional?"
  		 (descriptor isBranchTrue or: [descriptor isBranchFalse]) ifTrue:
+ 			[counter := (self
+ 							cCoerce: ((self
+ 											cCoerceSimple: cogMethodArg
+ 											to: #'CogMethod *') counters)
+ 							to: #'unsigned long *')
+ 								at: counterIndex.
+ 			 tuple := self picDataForCounter: counter at: bcpc + 1.
- 			[tuple := self picDataForConditionalBranch: prevMapAbsPCMcpc at: bcpc + descriptor numBytes.
  			 tuple = 0 ifTrue: [^PrimErrNoMemory].
  			 objectMemory storePointer: picDataIndex ofObject: picData withValue: tuple.
+ 			 picDataIndex := picDataIndex + 1.
+ 			 counterIndex := counterIndex + 1].
- 			 picDataIndex := picDataIndex + 1].
  		 ^0].
  	"infer it's a send; alas we can't just test the descriptor because of the bloody
  	 doubleExtendedDoAnythingBytecode which does sends as well as other things."
  	(backEnd isCallPreceedingReturnPC: mcpc asUnsignedInteger) ifFalse:
  		[^0].
  	entryPoint := backEnd callTargetFromReturnAddress: mcpc asUnsignedInteger.
  	entryPoint <= methodZoneBase ifTrue: "send is not linked, or is not a send"
  		[^0].
  	self targetMethodAndSendTableFor: entryPoint into: "It's a linked send; find which kind."
  		[:targetMethod :sendTable|
  		 tuple := self picDataForSendTo: targetMethod
  					methodClassIfSuper: (sendTable = superSendTrampolines ifTrue:
  												[coInterpreter methodClassOf:
  													(self cCoerceSimple: cogMethodArg to: #'CogMethod *') methodObject])
  					at: mcpc
  					bcpc: bcpc + 1].
  	tuple = 0 ifTrue: [^PrimErrNoMemory].
  	objectMemory storePointer: picDataIndex ofObject: picData withValue: tuple.
  	picDataIndex := picDataIndex + 1.
  	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>picDataFor:into: (in category 'method introspection') -----
  picDataFor: cogMethod into: arrayObj
  	"Collect the branch and send data for cogMethod, storing it into arrayObj."
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	| errCode |
  	cogMethod stackCheckOffset = 0 ifTrue:
  		[^0].
+ 	picDataIndex := counterIndex := 0.
- 	picDataIndex := 0.
  	picData := arrayObj.
  	errCode := self
  					mapFor: (self cCoerceSimple: cogMethod to: #'CogBlockMethod *')
  					bcpc: (coInterpreter startPCOfMethod: cogMethod methodObject)
  					performUntil: #picDataFor:IsBackwardBranch:Mcpc:Bcpc:Method:
  					arg: cogMethod asVoidPointer.
  	errCode ~= 0 ifTrue:
  		[self assert: errCode = PrimErrNoMemory.
  		 ^-1].
  	cogMethod blockEntryOffset ~= 0 ifTrue:
  		[errCode := self blockDispatchTargetsFor: cogMethod
  						perform: #picDataForBlockEntry:Method:
  						arg: cogMethod asInteger.
  		 errCode ~= 0 ifTrue:
  			[self assert: errCode = PrimErrNoMemory.
  			 ^-1]].
  	^picDataIndex!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>picDataForConditionalBranch:at: (in category 'method introspection') -----
- picDataForConditionalBranch: counterReferenceMcpc at: bcpc
- 	| address counter executedCount tuple untakenCount |
- 	<var: #counter type: #'unsigned long'>
- 	tuple := objectMemory
- 				eeInstantiateClassIndex: ClassArrayCompactIndex
- 				format: objectMemory arrayFormat
- 				numSlots: 3.
- 	tuple = 0 ifTrue:
- 		[^0].
- 	self assert: CounterBytes = 4.
- 	address := backEnd counterTargetFromFollowingAddress: counterReferenceMcpc.
- 	counter := objectMemory longAt: address.
- 	executedCount := initialCounterValue - (counter >> 16).
- 	untakenCount := initialCounterValue - (counter bitAnd: 16rFFFF).
- 	objectMemory
- 		storePointerUnchecked: 0 ofObject: tuple withValue: (objectMemory integerObjectOf: bcpc);
- 		storePointerUnchecked: 1 ofObject: tuple withValue: (objectMemory integerObjectOf: executedCount);
- 		storePointerUnchecked: 2 ofObject: tuple withValue: (objectMemory integerObjectOf: untakenCount).
- 	^tuple!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>picDataForCounter:at: (in category 'method introspection') -----
+ picDataForCounter: counter at: bcpc
+ 	| executedCount tuple untakenCount |
+ 	<var: #counter type: #'unsigned long'>
+ 	tuple := objectMemory
+ 				eeInstantiateClassIndex: ClassArrayCompactIndex
+ 				format: objectMemory arrayFormat
+ 				numSlots: 3.
+ 	tuple = 0 ifTrue:
+ 		[^0].
+ 	self assert: CounterBytes = 4.
+ 	executedCount := initialCounterValue - (counter >> 16).
+ 	untakenCount := initialCounterValue - (counter bitAnd: 16rFFFF).
+ 	objectMemory
+ 		storePointerUnchecked: 0 ofObject: tuple withValue: (objectMemory integerObjectOf: bcpc);
+ 		storePointerUnchecked: 1 ofObject: tuple withValue: (objectMemory integerObjectOf: executedCount);
+ 		storePointerUnchecked: 2 ofObject: tuple withValue: (objectMemory integerObjectOf: untakenCount).
+ 	^tuple!

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

Item was changed:
  ----- Method: SpurMemoryManager>>initializeFreeSpacePostLoad: (in category 'snapshot') -----
  initializeFreeSpacePostLoad: freeListObj
  	"Reinitialize the free list info.  The freeLists object needs to be swizzled
  	 because its neither a free, nor a pointer object.  Free objects have already
  	 been swizzled in adjustAllOopsBy:"
  	
  	self assert: (self numSlotsOf: freeListObj) = self numFreeLists.
+ 	self assert: (self formatOf: freeListObj) = self wordIndexableFormat.
- 	self assert: (self formatOf: freeListObj) = (self wordSize = 4
- 													ifTrue: [self firstLongFormat]
- 													ifFalse: [self sixtyFourBitIndexableFormat]).
  	freeLists := self firstIndexableField: freeListObj.
  	freeListsMask := 0.
  	0 to: self numFreeLists - 1 do:
  		[:i|
  		(freeLists at: i) ~= 0 ifTrue:
  			[freeListsMask := freeListsMask bitOr: (1 << i).
  			 freeLists at: i put: (segmentManager swizzleObj: (freeLists at: i))]]!

Item was added:
+ ----- Method: SpurSegmentManager>>initSegmentForInImageCompilationFrom:to: (in category 'simulation') -----
+ initSegmentForInImageCompilationFrom: base to: limit
+ 	| bridge |
+ 	self allocateOrExtendSegmentInfos.
+ 	numSegments := 1.
+ 	bridge := manager initSegmentBridgeWithBytes: manager memory byteSize - limit at: limit - manager bridgeSize.
+ 	segments := {SpurSegmentInfo new
+ 						segStart: base;
+ 						segSize: limit - base;
+ 						yourself}.
+ 	segments := CArrayAccessor on: segments!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genBinaryConstOpVarInlinePrimitive: (in category 'inline primitive generators') -----
+ genBinaryConstOpVarInlinePrimitive: prim
+ 	"Const op var version of binary inline primitives."
+ 	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
+ 	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
+ 	| ra val untaggedVal |
+ 	(ra := backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
+ 		[self ssAllocateRequiredReg:
+ 			(ra := optStatus isReceiverResultRegLive
+ 					ifTrue: [Arg0Reg]
+ 					ifFalse: [ReceiverResultReg])].
+ 	ra = ReceiverResultReg ifTrue:
+ 		[optStatus isReceiverResultRegLive: false].
+ 	self ssTop popToReg: ra.
+ 	self ssPop: 1.
+ 	val := self ssTop constant.
+ 	self ssPop: 1.
+ 	untaggedVal := val - objectMemory smallIntegerTag.
+ 	prim caseOf: {
+ 		"0 through 6, +, -, *, /, //, \\, quo:, SmallInteger op SmallInteger => SmallInteger, no overflow"
+ 		[0]	->	[self AddCq: untaggedVal R: ra].
+ 		[1]	->	[self SubCq: untaggedVal R: ra].
+ 		[2]	->	[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ra.
+ 				 self MoveCq: (objectMemory integerValueOf: val) R: TempReg.
+ 				 self MulR: TempReg R: ra.
+ 				 objectRepresentation genAddSmallIntegerTagsTo: ra].
+ 
+ 		"16 through 19, bitAnd:, bitOr:, bitXor, bitShift:, SmallInteger op SmallInteger => SmallInteger, no overflow"
+ 
+ 		"32	through 37, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
+ 
+ 		"64	through 68, Pointer Object>>at:, Byte Object>>at:, Short16 Word Object>>at: LongWord32 Object>>at: Quad64Word Object>>at:. obj op 0-rel SmallInteger => oop"
+ 
+ 		"80	through 84, Pointer Object>>at:put:, Byte Object>>at:put:, Short16 Word Object>>at:put: LongWord32 Object>>at:put: Quad64Word Object>>at:put:. obj op 0-rel SmallInteger => oop"
+ 
+ 	}
+ 	otherwise: [^EncounteredUnknownBytecode].
+ 	self ssPushRegister: ra.
+ 	^0!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genBinaryVarOpConstInlinePrimitive: (in category 'inline primitive generators') -----
+ genBinaryVarOpConstInlinePrimitive: prim
+ 	"Var op const version of inline binary inline primitives."
+ 	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
+ 	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
+ 	| rr val untaggedVal |
+ 	(rr := backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
+ 		[self ssAllocateRequiredReg:
+ 			(rr := optStatus isReceiverResultRegLive
+ 					ifTrue: [Arg0Reg]
+ 					ifFalse: [ReceiverResultReg])].
+ 	rr = ReceiverResultReg ifTrue:
+ 		[optStatus isReceiverResultRegLive: false].
+ 	val := self ssTop constant.
+ 	self ssPop: 1.
+ 	self ssTop popToReg: rr.
+ 	self ssPop: 1.
+ 	untaggedVal := val - objectMemory smallIntegerTag.
+ 	prim caseOf: {
+ 		"0 through 6, +, -, *, /, //, \\, quo:, SmallInteger op SmallInteger => SmallInteger, no overflow"
+ 		[0]	->	[self AddCq: untaggedVal R: rr].
+ 		[1]	->	[self SubCq: untaggedVal R: rr].
+ 		[2]	->	[self flag: 'could use MulCq:R'.
+ 				 objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: rr.
+ 				 self MoveCq: (objectMemory integerValueOf: val) R: TempReg.
+ 				 self MulR: TempReg R: rr.
+ 				 objectRepresentation genAddSmallIntegerTagsTo: rr].
+ 
+ 		"16 through 19, bitAnd:, bitOr:, bitXor, bitShift:, SmallInteger op SmallInteger => SmallInteger, no overflow"
+ 
+ 		"32	through 37, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
+ 
+ 		"64	through 68, Pointer Object>>at:, Byte Object>>at:, Short16 Word Object>>at: LongWord32 Object>>at: Quad64Word Object>>at:. obj op 0-rel SmallInteger => oop"
+ 
+ 		"80	through 84, Pointer Object>>at:put:, Byte Object>>at:put:, Short16 Word Object>>at:put: LongWord32 Object>>at:put: Quad64Word Object>>at:put:. obj op 0-rel SmallInteger => oop"
+ 
+ 	}
+ 	otherwise: [^EncounteredUnknownBytecode].
+ 	self ssPushRegister: rr.
+ 	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genBinaryVarOpVarInlinePrimitive: (in category 'inline primitive generators') -----
  genBinaryVarOpVarInlinePrimitive: prim
+ 	"Var op var version of binary inline primitives."
  	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
  	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
  	| ra rr |
+ 	(rr := backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
+ 		[self ssAllocateRequiredReg:
+ 			(rr := optStatus isReceiverResultRegLive
- 	rr := (backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
- 			[self ssAllocateRequiredReg:
- 				(optStatus isReceiverResultRegLive
  					ifTrue: [Arg0Reg]
  					ifFalse: [ReceiverResultReg])].
+ 	(ra := backEnd availableRegisterOrNilFor: (self liveRegisters bitOr: (self registerMaskFor: rr))) ifNil:
+ 		[self ssAllocateRequiredReg: (rr := Arg1Reg)].
- 	ra := (backEnd availableRegisterOrNilFor: (self liveRegisters bitOr: (self registerMaskFor: rr))) ifNil:
- 			[self ssAllocateRequiredReg: Arg1Reg].
  	(rr = ReceiverResultReg or: [ra = ReceiverResultReg]) ifTrue:
  		[optStatus isReceiverResultRegLive: false].
  	self ssTop popToReg: ra.
  	self ssPop: 1.
  	self ssTop popToReg: rr.
  	self ssPop: 1.
  	prim caseOf: {
  		"0 through 6, +, -, *, /, //, \\, quo:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  		[0]	->	[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ra.
  				 self AddR: ra R: rr].
  		[1]	->	[self SubR: ra R: rr.
  				 objectRepresentation genAddSmallIntegerTagsTo: rr].
  		[2]	->	[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: rr.
  				 objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ra.
  				 self MulR: ra R: rr.
  				 objectRepresentation genAddSmallIntegerTagsTo: rr].
  
  		"16 through 19, bitAnd:, bitOr:, bitXor, bitShift:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  
  		"32	through 37, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
  
  		"64	through 68, Pointer Object>>at:, Byte Object>>at:, Short16 Word Object>>at: LongWord32 Object>>at: Quad64Word Object>>at:. obj op 0-rel SmallInteger => oop"
  
  		"80	through 84, Pointer Object>>at:put:, Byte Object>>at:put:, Short16 Word Object>>at:put: LongWord32 Object>>at:put: Quad64Word Object>>at:put:. obj op 0-rel SmallInteger => oop"
  
  	}
  	otherwise: [^EncounteredUnknownBytecode].
  	self ssPushRegister: rr.
  	^0!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genTrinaryInlinePrimitive: (in category 'inline primitive generators') -----
+ genTrinaryInlinePrimitive: prim
+ 	"Unary inline primitives."
+ 	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
+ 	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
+ 	"not yet implemented"
+ 	^EncounteredUnknownBytecode!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genUnaryInlinePrimitive: (in category 'inline primitive generators') -----
+ genUnaryInlinePrimitive: prim
+ 	"Unary inline primitives."
+ 	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
+ 	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
+ 	"not yet implemented"
+ 	^EncounteredUnknownBytecode!



More information about the Vm-dev mailing list