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

commits at source.squeak.org commits at source.squeak.org
Thu Jun 18 18:42:37 UTC 2015


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

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

Name: VMMaker.oscog-eem.1362
Author: eem
Time: 18 June 2015, 11:40:39.303 am
UUID: eb2638bd-a092-4dc0-9495-82249a85bfbb
Ancestors: VMMaker.oscog-eem.1361

Fix initialization issues with the array of out-of-line
literals by initializing each literal on allocation rather
than early in a bzero call.

Drop the unused parameter from resetLiterals: and
hide the send of resetLiterals inside the two
allocateOpcodes: methods, rewriting them in more
conventional style, relying on inlining rather than a
C macro to have them inlined into their callers.

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

Item was changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>isSharable (in category 'generate machine code') -----
  isSharable
  	"Hack:  To know if a literal should be unique (not shared) mark the second operand."
  	<inline: true>
  	self assert: opcode = Literal.
+ 	^operands at: 1!
- 	^(operands at: 1) isNil!

Item was changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>isUnique (in category 'generate machine code') -----
  isUnique
  	"Hack:  To know if a literal should be unique (not shared) mark the second operand."
  	<inline: true>
  	self assert: opcode = Literal.
+ 	^(operands at: 1) not!
- 	^(operands at: 1) notNil!

Item was added:
+ ----- Method: CogOutOfLineLiteralsARMCompiler>>setIsSharable (in category 'generate machine code') -----
+ setIsSharable
+ 	"Hack:  To know if a literal should be unique (not shared) mark the second operand."
+ 	<inline: true>
+ 	self assert: opcode = Literal.
+ 	^operands at: 1 put: true!

Item was changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>setIsUnique (in category 'generate machine code') -----
  setIsUnique
  	"Hack:  To know if a literal should be unique (not shared) mark the second operand."
  	<inline: true>
  	self assert: opcode = Literal.
+ 	^operands at: 1 put: false!
- 	^operands at: 1 put: true!

Item was changed:
  ----- Method: Cogit>>allocateOpcodes:bytecodes: (in category 'initialization') -----
  allocateOpcodes: numberOfAbstractOpcodes bytecodes: numberOfBytecodes
  	"Allocate the various arrays needed to compile abstract instructions.
- 	 This needs to be a macro since the arrays are alloca'ed (stack allocated)
- 	 to ensure their being freed when compilation is done.
  	 Notionally we only need as many fixups as there are bytecodes.  But we
  	 reuse fixups to record pc-dependent instructions in generateInstructionsAt:
  	 and so need at least as many as there are abstract opcodes.
  
+ 	 This *must* be inlined since the arrays are alloca'ed (stack allocated)
+ 	 so that they are freed when compilation is done.
+ 
  	 N.B. We do one single alloca to save embarrassing C optimizers that
  	 generate incorrect code as both gcc and the intel compiler do on x86."
+ 	<inline: true>
- 	<cmacro: '(numberOfAbstractOpcodes,numberOfBytecodes) do { \
- 		int opcodeSize = sizeof(AbstractInstruction) * (numAbstractOpcodes = (numberOfAbstractOpcodes)); \
- 		int fixupSize = sizeof(BytecodeFixup) * numAbstractOpcodes; \
- 		abstractOpcodes = alloca(opcodeSize + fixupSize); \
- 		bzero(abstractOpcodes, opcodeSize + fixupSize); \
- 		fixups = (void *)((char *)abstractOpcodes + opcodeSize); \
- 		opcodeIndex = labelCounter = 0; \
- } while (0)'>
  	numAbstractOpcodes := numberOfAbstractOpcodes.
+ 	self
+ 		cCode:
+ 			[| opcodeSize fixupSize|
+ 			 opcodeSize := (self sizeof: CogAbstractInstruction) * numAbstractOpcodes.
+ 			 fixupSize := (self sizeof: CogBytecodeFixup) * numAbstractOpcodes.
+ 			 abstractOpcodes := self alloca: opcodeSize + fixupSize.
+ 			 self b: abstractOpcodes zero: opcodeSize + fixupSize.
+ 			 fixups := (abstractOpcodes asUnsignedInteger + opcodeSize) asVoidPointer]
+ 		inSmalltalk:
+ 			[abstractOpcodes := CArrayAccessor on:
+ 									 ((1 to: numAbstractOpcodes) collect: [:ign| CogCompilerClass for: self]).
+ 			 fixups := CArrayAccessor on:
+ 						((1 to: numAbstractOpcodes) collect: [:ign| self bytecodeFixupClass new])].
+ 	self zeroOpcodeIndex.
+ 	labelCounter := 0!
- 	abstractOpcodes := CArrayAccessor on:
- 						((1 to: numAbstractOpcodes) collect:
- 							[:ign| CogCompilerClass for: self]).
- 	fixups := CArrayAccessor on:
- 						((1 to: numAbstractOpcodes) collect:
- 							[:ign| self bytecodeFixupClass new]).
- 	opcodeIndex := labelCounter := 0!

Item was changed:
  ----- Method: Cogit>>allocateOpcodes:bytecodes:ifFail: (in category 'initialization') -----
  allocateOpcodes: numberOfAbstractOpcodes bytecodes: numberOfBytecodes ifFail: failBlock
+ 	"Allocate the various arrays needed to compile abstract instructions, failing if the size
+ 	 needed is considered too high.  Notionally we only need as many fixups as there are
+ 	 bytecodes.  But we reuse fixups to record pc-dependent instructions in
+ 	 generateInstructionsAt: and so need at least as many as there are abstract opcodes.
- 	"Allocate the various arrays needed to compile abstract instructions.
- 	 This needs to be a macro since the arrays are alloca'ed (stack allocated)
- 	 to ensure their being freed when compilation is done.
- 	 Notionally we only need as many fixups as there are bytecodes.  But we
- 	 reuse fixups to record pc-dependent instructions in generateInstructionsAt:
- 	 and so need at least as many as there are abstract opcodes.
  
+ 	 This *must* be inlined since the arrays are alloca'ed (stack allocated)
+ 	 so that they are freed when compilation is done.
+ 
  	 N.B. We do one single alloca to save embarrassing C optimizers that
  	 generate incorrect code as both gcc and the intel compiler do on x86."
+ 	<inline: true>
- 	<cmacro: '(numberOfAbstractOpcodes,numberOfBytecodes,failBlock) do { \
- 		int opcodeSize = sizeof(AbstractInstruction) * (numAbstractOpcodes = (numberOfAbstractOpcodes)); \
- 		int fixupSize = sizeof(BytecodeFixup) * numAbstractOpcodes; \
- 		int allocSize = opcodeSize + fixupSize; \
- 		if (allocSize > MaxStackAllocSize) failBlock; \
- 		abstractOpcodes = alloca(allocSize); \
- 		bzero(abstractOpcodes, opcodeSize + fixupSize); \
- 		fixups = (void *)((char *)abstractOpcodes + opcodeSize); \
- 		opcodeIndex = labelCounter = 0; \
- } while (0)'>
  	| opcodeSize fixupSize allocSize |
+ 	numAbstractOpcodes := numberOfAbstractOpcodes.
+ 	opcodeSize := (self sizeof: CogAbstractInstruction) * numAbstractOpcodes.
+ 	fixupSize := (self sizeof: CogBytecodeFixup) * numAbstractOpcodes.
- 	opcodeSize := (self sizeof: CogAbstractInstruction) * numberOfAbstractOpcodes.
- 	fixupSize := (self sizeof: CogBytecodeFixup) * numberOfAbstractOpcodes.
  	allocSize := opcodeSize + fixupSize.
  	allocSize > MaxStackAllocSize ifTrue: [^failBlock value].
+ 	self
+ 		cCode:
+ 			[abstractOpcodes := self alloca: allocSize.
+ 			 self b: abstractOpcodes zero: allocSize.
+ 			 fixups := (abstractOpcodes asUnsignedInteger + opcodeSize) asVoidPointer]
+ 		inSmalltalk:
+ 			[abstractOpcodes := CArrayAccessor on:
+ 									 ((1 to: numAbstractOpcodes) collect: [:ign| CogCompilerClass for: self]).
+ 			 fixups := CArrayAccessor on:
+ 						((1 to: numAbstractOpcodes) collect: [:ign| self bytecodeFixupClass new])].
+ 	self zeroOpcodeIndex.
+ 	labelCounter := 0!
- 	numAbstractOpcodes := numberOfAbstractOpcodes.
- 	abstractOpcodes := CArrayAccessor on:
- 						((1 to: numAbstractOpcodes) collect:
- 							[:ign| CogCompilerClass for: self]).
- 	fixups := CArrayAccessor on:
- 						((1 to: numAbstractOpcodes) collect:
- 							[:ign| self bytecodeFixupClass new]).
- 	opcodeIndex := labelCounter := 0!

Item was changed:
  ----- Method: Cogit>>cogExtendPIC:CaseNMethod:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogExtendPIC: cPIC CaseNMethod: caseNMethod tag: caseNTag isMNUCase: isMNUCase
  	"Extend the cPIC with the supplied case.  If caseNMethod is cogged dispatch direct to
  	 its unchecked entry-point.  If caseNMethod is not cogged, jump to the fast interpreter
  	 dispatch, and if isMNUCase then dispatch to fast MNU invocation and mark the cPIC as
  	 having the MNU case for cache flushing."
   	<var: #cPIC type: #'CogMethod *'>
  	| operand target address size end |
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	coInterpreter
  		compilationBreak: cPIC selector
  		point: (objectMemory numBytesOf: cPIC selector)
  		isMNUCase: isMNUCase.
  	self allocateOpcodes: 8 bytecodes: 0.
- 	literalsManager resetLiterals: 5.
  	methodLabel address: cPIC asUnsignedInteger; dependent: nil. "for pc-relative MoveCw: cPIC R: ClassReg"
  	self assert: (objectRepresentation inlineCacheTagIsYoung: caseNTag) not.
  	"Caller patches to open pic if caseNMethod is young."
  	self assert: (caseNMethod notNil and: [(objectMemory isYoung: caseNMethod) not]).
  	(isMNUCase not
  	 and: [coInterpreter methodHasCogMethod: caseNMethod])
  		ifTrue:
  			[operand := 0.
  			 target := (coInterpreter cogMethodOf: caseNMethod) asInteger + cmNoCheckEntryOffset]
  		ifFalse:
  			[operand := caseNMethod.
  			 isMNUCase
  				ifTrue:
  					[cPIC cpicHasMNUCase: true.
  					 target := cPIC asInteger + (self sizeof: CogMethod)]
  				ifFalse:
  					[target := cPIC asInteger + self picInterpretAbortOffset]].
  	self CmpCw: caseNTag R: TempReg.
  	self MoveUniqueCw: operand R: SendNumArgsReg.
  	self DumpJumpLongZero: target.
  	self MoveCw: cPIC asUnsignedInteger R: ClassReg.
  	self JumpLong: (self cPICMissTrampolineFor: cPIC cmNumArgs).
  	self computeMaximumSizes.
  	address := self addressOfEndOfCase: cPIC cPICNumCases - 1 inCPIC: cPIC.
  	size := self generateInstructionsAt: address.
  	end := self outputInstructionsAt: address.
  	processor flushICacheFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize.
  	cPIC cPICNumCases: cPIC cPICNumCases + 1.
  	^0!

Item was changed:
  ----- Method: Cogit>>cogMNUPICSelector:receiver:methodOperand:numArgs: (in category 'in-line cacheing') -----
  cogMNUPICSelector: selector receiver: rcvr methodOperand: methodOperand numArgs: numArgs
  	<api>
  	"Attempt to create a one-case PIC for an MNU.
  	 The tag for the case is at the send site and so doesn't need to be generated."
  	<returnTypeC: #'CogMethod *'>
  	| startAddress size end |
  	((objectMemory isYoung: selector)
  	 or: [(objectRepresentation inlineCacheTagForInstance: rcvr) = self picAbortDiscriminatorValue]) ifTrue:
  		[^0].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: true.
  	self assert: endCPICCase0 notNil.
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[coInterpreter callForCogCompiledCodeCompaction.
  		 ^0].
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: numPICCases * 9 bytecodes: 0.
- 	literalsManager resetLiterals: numPICCases * 2.
  	methodLabel address: startAddress; dependent: nil. "for pc-relative MoveCw: cPIC R: ClassReg"
  	self compileMNUCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		methodOperand: methodOperand
  		numArgs: numArgs.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: startAddress + (self sizeof: CogMethod).
  	end := self outputInstructionsAt: startAddress + (self sizeof: CogMethod).
  	"The missOffset is the same as the interpretOffset. On RISCs it includes an additional instruction."
  	self assert: missOffset = ((backEnd hasLinkRegister ifTrue: [backEnd callInstructionByteSize] ifFalse: [0])
  								+ picInterpretAbort address + picInterpretAbort machineCodeSize - startAddress).
  	self assert: startAddress + cmEntryOffset = entry address.
  	^self
  		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		numArgs: numArgs
  		numCases: 1
  		hasMNUCase: true
  		selector: selector !

Item was changed:
  ----- Method: Cogit>>cogOpenPICSelector:numArgs: (in category 'in-line cacheing') -----
  cogOpenPICSelector: selector numArgs: numArgs
  	"Create an Open PIC.  Temporarily create a direct call of ceSendFromOpenPIC:.
  	 Should become a probe of the first-level method lookup cache followed by a
  	 call of ceSendFromOpenPIC: if the probe fails."
  	<returnTypeC: #'CogMethod *'>
  	| startAddress codeSize mapSize end |
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: false.
  	startAddress := methodZone allocate: openPICSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	methodLabel
  		address: startAddress;
  		dependent: nil.
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: 100 bytecodes: 0.
- 	literalsManager resetLiterals: 10.
  	self compileOpenPIC: selector numArgs: numArgs.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: startAddress.
  	codeSize := self generateInstructionsAt: startAddress + (self sizeof: CogMethod).
  	mapSize := self generateMapAt: startAddress + openPICSize - 1 start: startAddress + cmNoCheckEntryOffset.
  	self assert: entry address - startAddress = cmEntryOffset.
  	self assert: (methodZone roundUpLength: (self sizeof: CogMethod) + codeSize) + (methodZone roundUpLength: mapSize) <= openPICSize.
  	end := self outputInstructionsAt: startAddress + (self sizeof: CogMethod).
  	^self
  		fillInOPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		numArgs: numArgs
  		selector: selector !

Item was changed:
  ----- Method: Cogit>>cogPICSelector:numArgs:Case0Method:Case1Method:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogPICSelector: selector numArgs: numArgs Case0Method: case0CogMethod Case1Method: case1MethodOrNil tag: case1Tag isMNUCase: isMNUCase
  	"Attempt to create a two-case PIC for case0CogMethod and  case1Method,case1Tag.
  	 The tag for case0CogMethod is at the send site and so doesn't need to be generated.
  	 case1Method may be any of
  		- a Cog method; link to its unchecked entry-point
  		- a CompiledMethod; link to ceInterpretMethodFromPIC:
  		- a CompiledMethod; link to ceMNUFromPICMNUMethod:receiver:"
  	<var: #case0CogMethod type: #'CogMethod *'>
  	<returnTypeC: #'CogMethod *'>
  	| startAddress size end |
  	(objectMemory isYoung: selector) ifTrue:
  		[^self cCoerceSimple: YoungSelectorInPIC to: #'CogMethod *'].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: isMNUCase.
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: numPICCases * 9 bytecodes: 0.
- 	literalsManager resetLiterals: numPICCases * 2.
  	methodLabel address: startAddress; dependent: nil. "for pc-relative MoveCw: cPIC R: ClassReg"
  	self compileCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		Case0: case0CogMethod
  		Case1Method: case1MethodOrNil
  		tag: case1Tag
  		isMNUCase: isMNUCase
  		numArgs: numArgs.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: startAddress + (self sizeof: CogMethod).
  	end := self outputInstructionsAt: startAddress + (self sizeof: CogMethod).
  	"The missOffset is the same as the interpretOffset. On RISCs it includes an additional instruction."
  	self assert: missOffset = ((backEnd hasLinkRegister ifTrue: [backEnd callInstructionByteSize] ifFalse: [0])
  								+ picInterpretAbort address + picInterpretAbort machineCodeSize - startAddress).
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: endCPICCase0 address = (startAddress + firstCPICCaseOffset).
  	self assert: endCPICCase1 address = (startAddress + firstCPICCaseOffset + cPICCaseSize).
  	^self
  		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		numArgs: numArgs
  		numCases: 2
  		hasMNUCase: isMNUCase
  		selector: selector !

Item was changed:
  ----- Method: Cogit>>compileCogMethod: (in category 'compile abstract instructions') -----
  compileCogMethod: selector
  	<returnTypeC: #'CogMethod *'>
  	| numBytecodes numBlocks numCleanBlocks result extra |
  	hasYoungReferent := (objectMemory isYoungObject: methodObj)
  						  or: [objectMemory isYoung: selector].
  	methodOrBlockNumArgs := coInterpreter argumentCountOf: methodObj.
  	inBlock := false.
  	postCompileHook := nil.
  	maxLitIndex := -1.
  	extra := ((primitiveIndex := coInterpreter primitiveIndexOf: methodObj) > 0
  			and: [(coInterpreter isQuickPrimitiveIndex: primitiveIndex) not])
  				ifTrue: [30]
  				ifFalse: [10].
  	initialPC := coInterpreter startPCOfMethod: methodObj.
  	"initial estimate.  Actual endPC is determined in scanMethod."
  	endPC := (coInterpreter isQuickPrimitiveIndex: primitiveIndex)
  					ifTrue: [initialPC - 1]
  					ifFalse: [objectMemory numBytesOf: methodObj].
  	numBytecodes := endPC - initialPC + 1.
  	self allocateOpcodes: (numBytecodes + extra) * self estimateOfAbstractOpcodesPerBytecodes
  		bytecodes: numBytecodes
  		ifFail: [^coInterpreter cCoerceSimple: MethodTooBig to: #'CogMethod *'].
- 	literalsManager resetLiterals: (objectMemory literalCountOf: methodObj).
  	(numBlocks := self scanMethod) < 0 ifTrue:
  		[^coInterpreter cCoerceSimple: numBlocks to: #'CogMethod *'].
  	numCleanBlocks := self scanForCleanBlocks.
  	self allocateBlockStarts: numBlocks + numCleanBlocks.
  	blockCount := 0.
  	numCleanBlocks > 0 ifTrue:
  		[self addCleanBlockStarts].
  	(self maybeAllocAndInitCounters
  	 and: [self maybeAllocAndInitIRCs]) ifFalse: "Inaccurate error code, but it'll do.  This will likely never fail."
  		[^coInterpreter cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	
  	blockEntryLabel := nil.
  	methodLabel dependent: nil.
  	(result := self compileEntireMethod) < 0 ifTrue:
  		[^coInterpreter cCoerceSimple: result to: #'CogMethod *'].
  	^self generateCogMethod: selector!

Item was changed:
  ----- Method: Cogit>>computeEntryOffsets (in category 'initialization') -----
  computeEntryOffsets
  	"Generate the entry code for a method to determine cmEntryOffset and cmNoCheckEntryOffset.  We
  	 need cmNoCheckEntryOffset up front to be able to generate the map starting from cmNoCheckEntryOffset"
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	| sendMissCall |
  	<var: 'sendMissCall' type: #'AbstractInstruction *'>
  	self allocateOpcodes: 24 bytecodes: 0.
- 	literalsManager resetLiterals: 5.
  	methodOrBlockNumArgs := 0.
  	sendMissCall := self compileAbort.
  	self compileEntry.
  	self computeMaximumSizes.
  	self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod).
  	cmEntryOffset := entry address - methodZoneBase.
  	cmNoCheckEntryOffset := noCheckEntry address - methodZoneBase.
  	missOffset := sendMissCall address + sendMissCall machineCodeSize - methodZoneBase.
  	entryPointMask := objectMemory wordSize - 1.
  	[(cmEntryOffset bitAnd: entryPointMask) = (cmNoCheckEntryOffset bitAnd: entryPointMask)] whileTrue:
  		[entryPointMask := entryPointMask + entryPointMask + 1].
  	entryPointMask >= (methodZone roundUpLength: 1) ifTrue:
  		[self error: 'cannot differentiate checked and unchecked entry-points with current cog method alignment'].
  	checkedEntryAlignment := cmEntryOffset bitAnd: entryPointMask.
  	uncheckedEntryAlignment := cmNoCheckEntryOffset bitAnd: entryPointMask.
  	self assert: checkedEntryAlignment ~= uncheckedEntryAlignment!

Item was changed:
  ----- Method: Cogit>>genGetLeafCallStackPointer (in category 'initialization') -----
  genGetLeafCallStackPointer
  	"Generate a routine that answers the stack pointer immedately
  	 after a leaf call, used for checking stack pointer alignment."
  	| startAddress |
  	<inline: false>
  	self allocateOpcodes: 32 bytecodes: 0.
- 	literalsManager resetLiterals: 5.
  	initialPC := 0.
  	endPC := numAbstractOpcodes - 1.
  	startAddress := methodZoneBase.
  	backEnd genGetLeafCallStackPointerFunction.
  	self outputInstructionsForGeneratedRuntimeAt: startAddress.
  	self recordGeneratedRunTime: 'ceGetSP' address: startAddress.
  	^startAddress!

Item was changed:
  ----- Method: Cogit>>generateCaptureCStackPointers: (in category 'initialization') -----
  generateCaptureCStackPointers: captureFramePointer
  	"Generate the routine that writes the current values of the C frame and stack pointers into
  	 variables.  These are used to establish the C stack in trampolines back into the C run-time.
  
  	 This is a presumptuous quick hack for x86.  It is presumptuous for two reasons.  Firstly
  	 the system's frame and stack pointers may differ from those we use in generated code,
  	 e.g. on register-rich RISCs.  Secondly the ABI may not support a simple frameless call
  	 as written here (for example 128-bit stack alignment on Mac OS X)."
  	| startAddress |
  	<inline: false>
  	self allocateOpcodes: 32 bytecodes: 0.
- 	literalsManager resetLiterals: 5.
  	initialPC := 0.
  	endPC := numAbstractOpcodes - 1.
  	startAddress := methodZoneBase.
  	captureFramePointer ifTrue:
  		[self MoveR: FPReg Aw: self cFramePointerAddress].
  	"Capture the stack pointer prior to the call."
  	backEnd leafCallStackPointerDelta = 0
  		ifTrue: [self MoveR: SPReg Aw: self cStackPointerAddress]
  		ifFalse: [self MoveR: SPReg R: TempReg.
  				self AddCq: backEnd leafCallStackPointerDelta R: TempReg.
  				self MoveR: TempReg Aw: self cStackPointerAddress].
  	self RetN: 0.
  	self outputInstructionsForGeneratedRuntimeAt: startAddress.
  	processor flushICacheFrom: startAddress asUnsignedInteger to: methodZoneBase asUnsignedInteger.
  	self recordGeneratedRunTime: 'ceCaptureCStackPointers' address: startAddress.
  	ceCaptureCStackPointers := self cCoerceSimple: startAddress to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>generateClosedPICPrototype (in category 'initialization') -----
  generateClosedPICPrototype
  	"Generate the prototype ClosedPIC to determine how much space as full PIC takes.
  	 When we first allocate a closed PIC it only has one or two cases and we want to grow it.
  	 So we have to determine how big a full one is before hand."
  	numPICCases := 6.
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: numPICCases * 9 bytecodes: 0.
- 	literalsManager resetLiterals: numPICCases * 2.
  	methodLabel address: methodZoneBase; dependent: nil. "for pc-relative MoveCw: cPIC R: ClassReg"
  	self compileClosedPICPrototype.
  	self computeMaximumSizes.
  	closedPICSize := (self sizeof: CogMethod) + (self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod)).
  	firstCPICCaseOffset := endCPICCase0 address - methodZoneBase.
  	cPICCaseSize := endCPICCase1 address - endCPICCase0 address.
  	cPICEndSize := closedPICSize - (numPICCases - 1 * cPICCaseSize + firstCPICCaseOffset).
  	closedPICSize := methodZone roundUpLength: closedPICSize.
  	self assert: picInterpretAbort address = (methodLabel address + self picInterpretAbortOffset)
  	"self cCode: ''
  		inSmalltalk:
  			[| end |
  			 end := self outputInstructionsAt: methodZoneBase + headerSize.
  			 self disassembleFrom: methodZoneBase + headerSize to: end - 1.
  			 self halt]"!

Item was changed:
  ----- Method: Cogit>>generateOpenPICPrototype (in category 'initialization') -----
  generateOpenPICPrototype
  	"Generate the prototype ClosedPIC to determine how much space as full PIC takes.
  	 When we first allocate a closed PIC it only has one or two cases and we want to grow it.
  	 So we have to determine how big a full one is before hand."
  	| codeSize mapSize |
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: 100 bytecodes: 0.
- 	literalsManager resetLiterals: 10.
  	methodLabel
  		address: methodZoneBase;
  		dependent: nil.
  	"Need a real selector here so that the map accomodates the annotations for the selector.
  	 Use self numRegArgs to generate the longest possible code sequence due to
  	 genPushRegisterArgsForNumArgs:"
  	self compileOpenPIC: (coInterpreter specialSelector: 0) numArgs: self numRegArgs.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: methodZoneBase.
  	codeSize := self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod).
  	mapSize := self generateMapAt: nil start: methodZoneBase + cmNoCheckEntryOffset.
  	openPICSize := (methodZone roundUpLength: (self sizeof: CogMethod) + codeSize) + (methodZone roundUpLength: mapSize).
  	"self cCode: ''
  		inSmalltalk:
  			[| end |
  			 end := self outputInstructionsAt: methodZoneBase + headerSize.
  			 self disassembleFrom: methodZoneBase + (self sizeof: CogMethod) to: end - 1.
  			 self halt]"!

Item was changed:
  ----- Method: Cogit>>initializeBackend (in category 'initialization') -----
  initializeBackend
  	methodLabel machineCodeSize: 0.
  	methodLabel opcode: Label.
  	methodLabel operands at: 0 put: 0.
  	methodLabel operands at: 1 put: 0. "label offset"
  	callerSavedRegMask := backEnd callerSavedRegisterMask.
  	backEnd hasVarBaseRegister ifTrue:
  		[self assert: ((self registerMaskFor: VarBaseReg) noMask: callerSavedRegMask)].
+ 	literalsManager allocateLiterals: 4; resetLiterals!
- 	literalsManager allocateLiterals: 4; resetLiterals: 4!

Item was changed:
  ----- Method: Cogit>>maybeGenerateCheckFeatures (in category 'initialization') -----
  maybeGenerateCheckFeatures
  	| startAddress |
  	<inline: false>
  	backEnd numCheckFeaturesOpcodes = 0 ifTrue:
  		[^nil].
  	self allocateOpcodes: backEnd numCheckFeaturesOpcodes bytecodes: 0.
- 	literalsManager resetLiterals: 1.
  	initialPC := 0.
  	endPC := numAbstractOpcodes - 1.
  	startAddress := methodZoneBase.
  	backEnd generateCheckFeatures.
  	self outputInstructionsForGeneratedRuntimeAt: startAddress.
  	self recordGeneratedRunTime: 'ceCheckFeaturesFunction' address: startAddress.
  	ceCheckFeaturesFunction := self cCoerceSimple: startAddress to: #'unsigned long (*)(void)'!

Item was changed:
  ----- Method: Cogit>>maybeGenerateICacheFlush (in category 'initialization') -----
  maybeGenerateICacheFlush
  	| startAddress |
  	<inline: false>
  	backEnd numICacheFlushOpcodes = 0 ifTrue:
  		[^nil].
  	self allocateOpcodes: backEnd numICacheFlushOpcodes bytecodes: 0.
- 	literalsManager resetLiterals: 1.
  	initialPC := 0.
  	endPC := numAbstractOpcodes - 1.
  	startAddress := methodZoneBase.
  	backEnd generateICacheFlush.
  	self outputInstructionsForGeneratedRuntimeAt: startAddress.
  	self recordGeneratedRunTime: 'ceFlushICache' address: startAddress.
  	ceFlushICache := self cCoerceSimple: startAddress to: #'void (*)(unsigned long,unsigned long)'!

Item was changed:
  ----- Method: Cogit>>zeroOpcodeIndex (in category 'accessing') -----
  zeroOpcodeIndex
  	"Access for the object representations when they need to prepend code to trampolines."
  	opcodeIndex := 0.
+ 	literalsManager resetLiterals!
- 	literalsManager resetLiterals: 1!

Item was added:
+ ----- Method: InLineLiteralsManager>>resetLiterals (in category 'initialization') -----
+ resetLiterals
+ 	<inline: true>!

Item was removed:
- ----- Method: InLineLiteralsManager>>resetLiterals: (in category 'initialization') -----
- resetLiterals: numLiteralsHint
- 	<inline: true>!

Item was changed:
  ----- Method: OutOfLineLiteralsManager>>allocateLiteral: (in category 'compile abstract instructions') -----
  allocateLiteral: aLiteral
+ 	"Allocate an unsharable Literal instruction for the literal and answer it."
- 	"Allocate a n unsharable Literal instruction for the literal and answer it."
  	<returnTypeC: #'AbstractInstruction *'>
  	<inline: true>
  	| litInst |
  	<var: 'litInst' type: #'AbstractInstruction *'>
  	nextLiteralIndex >= literalsSize ifTrue:
  		[self allocateLiterals: literalsSize + 8].
  	litInst := self literalInstructionAt: nextLiteralIndex.
  	litInst
  		opcode: Literal;
  		operand0: aLiteral;
  		setIsUnique;
+ 		setLiteralOpcodeIndex: -1; "means as-yet-unassigned; see literalInstructionInRange:"
+ 		dependent: nil.
- 		setLiteralOpcodeIndex: -1. "means as-yet-unassigned; see literalInstructionInRange:"
  	nextLiteralIndex := nextLiteralIndex + 1.
  	"Record the opcodeIndex of the first dependent instruction (the first instruction that references an out-of-line literal)"
  	firstOpcodeIndex > cogit getOpcodeIndex ifTrue:
  		[firstOpcodeIndex := cogit getOpcodeIndex - 1].
  	^litInst!

Item was changed:
  ----- Method: OutOfLineLiteralsManager>>locateLiteral: (in category 'compile abstract instructions') -----
  locateLiteral: aLiteral
  	"Search for a Literal instruction that is in-range and answer it.  Otherwise
+ 	 allocate a new sharable Literal instruction for the literal and answer it."
- 	 allocate a new Literal instruction for the literal and answer it."
  	<returnTypeC: #'AbstractInstruction *'>
  	<inline: false>
  	| litInst |
  	<var: 'litInst' type: #'AbstractInstruction *'>
  	0 to: nextLiteralIndex - 1 do:
  		[:i|
  		litInst := self literalInstructionAt: i.
  		((litInst operands at: 0) = aLiteral
  		 and: [litInst isSharable
  		 and: [self literalInstructionInRange: litInst]]) ifTrue:
  			[^litInst]].
  	nextLiteralIndex >= literalsSize ifTrue:
  		[self allocateLiterals: literalsSize + 8].
  	litInst := self literalInstructionAt: nextLiteralIndex.
  	litInst
  		opcode: Literal;
  		operand0: aLiteral;
+ 		setIsSharable;
+ 		setLiteralOpcodeIndex: -1; "means as-yet-unassigned; see literalInstructionInRange:"
+ 		dependent: nil.
- 		setLiteralOpcodeIndex: -1. "means as-yet-unassigned; see literalInstructionInRange:"
  	nextLiteralIndex := nextLiteralIndex + 1.
  	"Record the opcodeIndex of the first dependent instruction (the first instruction that references an out-of-line literal)"
  	firstOpcodeIndex > cogit getOpcodeIndex ifTrue:
  		[firstOpcodeIndex := cogit getOpcodeIndex - 1].
  	^litInst!

Item was changed:
+ ----- Method: OutOfLineLiteralsManager>>resetForBlockCompile (in category 'initialization') -----
- ----- Method: OutOfLineLiteralsManager>>resetForBlockCompile (in category 'compile abstract instructions') -----
  resetForBlockCompile
  	firstOpcodeIndex := savedFirstOpcodeIndex.
  	nextLiteralIndex := savedNextLiteralIndex.
  	lastDumpedLiteralIndex := savedLastDumpedLiteralIndex!

Item was added:
+ ----- Method: OutOfLineLiteralsManager>>resetLiterals (in category 'initialization') -----
+ resetLiterals
+ 	<inline: true>
+ 	firstOpcodeIndex := 1 << 16. "an impossibly high value"
+ 	nextLiteralIndex := lastDumpedLiteralIndex := 0!

Item was removed:
- ----- Method: OutOfLineLiteralsManager>>resetLiterals: (in category 'initialization') -----
- resetLiterals: numLiteralsHint
- 	<inline: true>
- 	self cCode:
- 			[self me: literals ms: 0 et: literalsSize * (self sizeof: CogAbstractInstruction)]
- 		inSmalltalk:
- 			[0 to: literalsSize - 1 do: [:i| literals at: i put: nil]].
- 	firstOpcodeIndex := 1 << 16. "an impossibly high value"
- 	nextLiteralIndex := lastDumpedLiteralIndex := 0!

Item was changed:
+ ----- Method: OutOfLineLiteralsManager>>saveForBlockCompile (in category 'initialization') -----
- ----- Method: OutOfLineLiteralsManager>>saveForBlockCompile (in category 'compile abstract instructions') -----
  saveForBlockCompile
  	savedFirstOpcodeIndex := firstOpcodeIndex.
  	savedNextLiteralIndex := nextLiteralIndex.
  	savedLastDumpedLiteralIndex := lastDumpedLiteralIndex!



More information about the Vm-dev mailing list