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

commits at source.squeak.org commits at source.squeak.org
Mon Dec 9 15:24:11 UTC 2013


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

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

Name: VMMaker.oscog-eem.550
Author: eem
Time: 9 December 2013, 7:21:47.972 am
UUID: 16788219-a25c-487e-bdff-d01a799e4550
Ancestors: VMMaker.oscog-eem.549

Include api methods in conditional expr dead-code removal code.
Rewrite CoInterpreter senders of numRegArgs given they can now
be handled by dead code removal instead of clunky old cppIf:ifTrue:.

Include the classIndex in the longPrintOop: class output.

Fix comments and and remove duplicate alignment in both
compileOpenPIC:numArgs: methods.

Fix comment in genSendTrampolineFor:numArgs:called:arg:arg:arg:

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

Item was added:
+ ----- Method: CCodeGenerator>>isConstantNode:valueInto: (in category 'utilities') -----
+ isConstantNode: aNode valueInto: aBlock
+ 	"Answer if aNode evaluates to a constant, and if so, evaluate aBlock with the value of that constant."
+ 
+ 	aNode isConstant ifTrue:
+ 		[aBlock value: aNode value.
+ 		 ^true].
+ 	aNode isSend ifFalse:
+ 		[^false].
+ 	(self anyMethodNamed: aNode selector) ifNotNil:
+ 		[:m|
+ 		(m statements size = 1
+ 		 and: [m statements last isReturn]) ifTrue:
+ 			[^self isConstantNode: m statements last expression valueInto: aBlock]].
+ 	^false!

Item was changed:
  ----- Method: CCodeGenerator>>isNilConstantReceiverOf: (in category 'utilities') -----
  isNilConstantReceiverOf: sendNode
  	"Answer true if the receiver of the given message send is the constant nil. Used to suppress conditional code when the condition is a translation-time constant."
  
+ 	| val |
  	generateDeadCode ifTrue: [^false].
+ 	^(self isConstantNode: sendNode receiver valueInto: [:v| val := v])
+ 	  and: [val isNil]!
- 	^sendNode receiver isConstant and: [sendNode receiver value isNil]!

Item was changed:
  ----- Method: CCodeGenerator>>nilOrBooleanConstantReceiverOf: (in category 'utilities') -----
  nilOrBooleanConstantReceiverOf: aNode
  	"Answer nil or the boolean constant that is the receiver of the given message send.
  	 Used to suppress conditional code when the condition is a translation-time constant."
  
+ 	| val receiver argument |
  	generateDeadCode ifTrue:[^nil].
+ 	((self isConstantNode: aNode valueInto: [:v| val := v])
+ 	 and: [#(true false) includes: val]) ifTrue:
+ 		[^val].
- 	(aNode isConstant
- 	 and: [#(true false) includes: aNode value]) ifTrue:
- 		[^aNode value].
  	aNode isSend ifTrue:
  		[((#(or: and:) includes: aNode selector)
  		 and: [aNode args last isStmtList
  		 and: [aNode args last statements size = 1]]) ifTrue:
  			[(self nilOrBooleanConstantReceiverOf: aNode receiver) ifNotNil:
  				[:rcvr|
  				(self nilOrBooleanConstantReceiverOf: aNode args last statements first) ifNotNil:
  					[:arg|
  					^rcvr perform: aNode selector with: [arg]]]].
  		 ((#(= ~= < > <= >=) includes: aNode selector)
+ 		  and: [(self isConstantNode: aNode receiver valueInto: [:v| receiver := v])
+ 		  and: [receiver isInteger
+ 		  and: [(self isConstantNode: aNode args first valueInto: [:v| argument := v])
+ 		  and: [argument isInteger]]]]) ifTrue:
+ 			[^receiver perform: aNode selector with: argument]].
+ 	^nil!
- 		  and: [(aNode receiver isConstant and: [aNode receiver value isInteger])
- 		  and: [(aNode args first isConstant and: [aNode args first value isInteger])]]) ifTrue:
- 			[^aNode receiver value perform: aNode selector with: aNode args first value].
- 		(self methodNamed: aNode selector) ifNotNil:
- 			[:m|
- 			(m statements size = 1
- 			 and: [m statements last isReturn]) ifTrue:
- 				[^self nilOrBooleanConstantReceiverOf: m statements last expression]]].
- 	^nil
- !

Item was changed:
  ----- Method: CoInterpreter>>activateCoggedNewMethod: (in category 'message sending') -----
  activateCoggedNewMethod: inInterpreter
  	"Activate newMethod when newMethod has been cogged, i.e. create a machine-code frame and (re)enter machine-code."
  	| methodHeader cogMethod rcvr numTemps errorCode switched |
  	<var: #cogMethod type: #'CogMethod *'>
  
  	methodHeader := self rawHeaderOf: newMethod.
  	self assert: (self isCogMethodReference: methodHeader).
  
  	cogMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  	methodHeader := cogMethod methodHeader.
  	rcvr := self stackValue: cogMethod cmNumArgs. "could new rcvr be set at point of send?"
  	self push: instructionPointer.
  	cogMethod stackCheckOffset = 0 ifTrue:
  		["frameless method; nothing to activate..."
+ 		(cogit numRegArgs > 0
+ 		 and: [cogMethod cmNumArgs <= cogit numRegArgs]) ifTrue:
+ 			[self enterRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr].
- 		 self
- 			cppIf: cogit numRegArgs > 0
- 		  	ifTrue:
- 				[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
- 					[self enterRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr]].
  		 self push: cogMethod asInteger + cogit noCheckEntryOffset.
  		 self push: rcvr.
  		 cogit ceEnterCogCodePopReceiverReg.
  		 self error: 'should not be reached'].
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: cogMethod asInteger.
  	self push: objectMemory nilObject. "FxThisContext field"
  	self push: rcvr.
  
  	"clear remaining temps to nil"
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	cogMethod cmNumArgs + 1 to: numTemps do:
  		[:i | self push: objectMemory nilObject].
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		[| initialPC |
  		 "Store the error code if the method starts with a long store temp.  No instructionPointer skip because we're heading for machine code."
  		 initialPC := (self initialPCForHeader: methodHeader method: newMethod) + (self sizeOfCallPrimitiveBytecode: methodHeader).
  		 primFailCode ~= 0 ifTrue:
  			[(objectMemory byteAt: initialPC) = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	stackPointer >= stackLimit ifTrue:
  		[self assert: cogMethod stackCheckOffset > cogit noCheckEntryOffset.
  		 self push: cogMethod asInteger + cogMethod stackCheckOffset.
  		 self push: rcvr.
  		 cogit ceEnterCogCodePopReceiverReg.
  		 self error: 'should not be reached'].
  	instructionPointer := cogMethod asInteger + cogMethod stackCheckOffset.
  	switched := self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader).
  	self returnToExecutive: inInterpreter postContextSwitch: switched!

Item was changed:
  ----- Method: CoInterpreter>>enterRegisterArgCogMethod:at:receiver: (in category 'enilopmarts') -----
  enterRegisterArgCogMethod: cogMethod at: entryOffset receiver: rcvr
  	"convert
  	 		rcvr	base
  			arg(s)
  			retpc	<- sp
  	 to
  			retpc	base
  			entrypc
  			rcvr
  			arg(s)	<- sp
  	 and then enter at either the checked or the unchecked entry-point."
  	<var: #cogMethod type: #'CogMethod *'>
+ 	self assert: (cogit numRegArgs > 0 and: [cogit numRegArgs <= 2 and: [cogMethod cmNumArgs <= cogit numRegArgs]]).
+ 	cogMethod cmNumArgs = 2 ifTrue:
+ 		[self stackValue: 3 put: self stackTop. "retpc"
+ 		 self push: (self stackValue: 1). "last arg"
+ 		 self stackValue: 1 put: (self stackValue: 3). "first arg"
+ 		 self stackValue: 2 put: rcvr.
+ 		 self stackValue: 3 put: cogMethod asInteger + entryOffset.
+ 		 cogit ceEnterCogCodePopReceiverArg1Arg0Regs
+ 		"NOTREACHED"].
+ 	cogMethod cmNumArgs = 1 ifTrue:
+ 		[self stackValue: 2 put: self stackTop. "retpc"
+ 		 self push: (self stackValue: 1). "arg"
+ 		 self stackValue: 1 put: rcvr.
+ 		 self stackValue: 2 put: cogMethod asInteger + entryOffset.
+ 		 cogit ceEnterCogCodePopReceiverArg0Regs
+ 		"NOTREACHED"].
+ 	self assert: cogMethod cmNumArgs = 0.
+ 	self stackValue: 1 put: self stackTop. "retpc"
+ 	self stackValue: 0 put: cogMethod asInteger + entryOffset.
+ 	self push: rcvr.
+ 	cogit ceEnterCogCodePopReceiverReg
+ 	"NOTREACHED"!
- 	self cppIf: cogit numRegArgs > 0
- 		ifTrue:
- 			[self assert: (cogit numRegArgs > 0 and: [cogit numRegArgs <= 2]).
- 			 cogMethod cmNumArgs = 2 ifTrue:
- 				[self stackValue: 3 put: self stackTop. "retpc"
- 				 self push: (self stackValue: 1). "last arg"
- 				 self stackValue: 1 put: (self stackValue: 3). "first arg"
- 				 self stackValue: 2 put: rcvr.
- 				 self stackValue: 3 put: cogMethod asInteger + entryOffset.
- 				 cogit ceEnterCogCodePopReceiverArg1Arg0Regs
- 				"NOTREACHED"].
- 			 cogMethod cmNumArgs = 1 ifTrue:
- 				[self stackValue: 2 put: self stackTop. "retpc"
- 				 self push: (self stackValue: 1). "arg"
- 				 self stackValue: 1 put: rcvr.
- 				 self stackValue: 2 put: cogMethod asInteger + entryOffset.
- 				 cogit ceEnterCogCodePopReceiverArg0Regs
- 				"NOTREACHED"].
- 			 self assert: cogMethod cmNumArgs = 0.
- 			 self stackValue: 1 put: self stackTop. "retpc"
- 			 self stackValue: 0 put: cogMethod asInteger + entryOffset.
- 			 self push: rcvr.
- 			 cogit ceEnterCogCodePopReceiverReg
- 			 "NOTREACHED"]
- 		ifFalse:
- 			[self assert: false]!

Item was changed:
  ----- Method: CoInterpreter>>executeCogMethodFromLinkedSend:withReceiver: (in category 'enilopmarts') -----
  executeCogMethodFromLinkedSend: cogMethod withReceiver: rcvr
  	<api>
  	"Execute a CogMethod from a linked send.  The receiver,
  	 arguments and return address are on the Smalltalk stack.  First
  	 push the entry-point and finally the register argument(s).  Then write
  	 back the frame pointers and call the routine that will pop off the register
  	 argument(s) and jump to the entry by executing a return instruction.
  
  	 In the simple jit only the receiver gets passed in registers, so only the
  	 receiver gets pushed."
  	<var: #cogMethod type: #'CogMethod *'>
  	cogit assertCStackWellAligned.
  	self assert: (self isMachineCodeFrame: framePointer).
  	self assertValidExecutionPointe: self stackTop r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
+ 	(cogit numRegArgs > 0
+ 	 and: [cogMethod cmNumArgs <= cogit numRegArgs]) ifTrue:
+ 		[self enterRegisterArgCogMethod: cogMethod at: cogit entryOffset receiver: rcvr].
  	self
- 		cppIf: cogit numRegArgs > 0
- 		ifTrue:
- 			[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
- 				[self enterRegisterArgCogMethod: cogMethod at: cogit entryOffset receiver: rcvr]].
- 	self
  		push: cogMethod asInteger + cogit entryOffset;
  		push: rcvr.
  	cogit ceEnterCogCodePopReceiverReg
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>executeCogMethodFromLinkedSend:withReceiver:andCacheTag: (in category 'enilopmarts') -----
  executeCogMethodFromLinkedSend: cogMethod withReceiver: rcvr andCacheTag: cacheTag
  	<api>
  	"Execute a CogMethod from a linked send.  The receiver,
  	 arguments and return address are on the Smalltalk stack.  First
  	 push the entry-point and finally the register argument(s).  Then write
  	 back the frame pointers and call the routine that will pop off the register
  	 argument(s) and jump to the entry by executing a return instruction.
  
  	 In the simple jit only the receiver gets passed in registers, so only the
  	 receiver gets pushed."
  	<var: #cogMethod type: #'CogMethod *'>
  	cogit assertCStackWellAligned.
  	self assert: (self isMachineCodeFrame: framePointer).
  	self assertValidExecutionPointe: self stackTop r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
  	self push: cogMethod asInteger + cogit entryOffset.
+ 	cogit numRegArgs > 0 ifTrue:
+ 		[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
+ 			[self assert: cogit numRegArgs <= 2.
+ 			 self push: cacheTag.
+ 			 cogMethod cmNumArgs = 0 ifTrue:
+ 				[cogit ceEnter0ArgsPIC].
+ 			 cogMethod cmNumArgs = 1 ifTrue:
+ 				[cogit ceEnter1ArgsPIC].
+ 			 cogMethod cmNumArgs = 2 ifTrue:
+ 				[cogit ceEnter2ArgsPIC].
+ 			 self error: 'not reached']].
  	self
- 		cppIf: cogit numRegArgs > 0
- 		ifTrue:
- 			[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
- 				[self assert: cogit numRegArgs <= 2.
- 				 self push: cacheTag.
- 				 cogMethod cmNumArgs = 0 ifTrue:
- 					[cogit ceEnter0ArgsPIC].
- 				 cogMethod cmNumArgs = 1 ifTrue:
- 					[cogit ceEnter1ArgsPIC].
- 				 cogMethod cmNumArgs = 2 ifTrue:
- 					[cogit ceEnter2ArgsPIC].
- 				 self error: 'not reached']].
- 	self
  		push: rcvr;
  		push: cacheTag.
  	cogit ceEnterCogCodePopReceiverAndClassRegs
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>executeCogMethodFromUnlinkedSend:withReceiver: (in category 'enilopmarts') -----
  executeCogMethodFromUnlinkedSend: cogMethod withReceiver: rcvr
  	"Execute a CogMethod from an unlinked send.  The receiver,
  	 arguments and return address are on the Smalltalk stack.  First
  	 push the entry-point and finally the register argument(s).  Then write
  	 back the frame pointers and call the routine that will pop off the register
  	 argument(s) and jump to the entry by executing a return instruction.
  
  	 In the simple jit only the receiver gets passed in registers, so only the
  	 receiver gets pushed."
  	<var: #cogMethod type: #'CogMethod *'>
  	cogit assertCStackWellAligned.
  	self assert: (self isMachineCodeFrame: framePointer).
  	self assertValidExecutionPointe: self stackTop r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
+ 	(cogit numRegArgs > 0
+ 	 and: [cogMethod cmNumArgs <= cogit numRegArgs]) ifTrue:
+ 		[self enterRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr].
  	self
- 		cppIf: cogit numRegArgs > 0
- 		ifTrue:
- 			[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
- 				[self enterRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr]].
- 	self
  		push: cogMethod asInteger + cogit noCheckEntryOffset;
  		push: rcvr.
  	cogit ceEnterCogCodePopReceiverReg
  	"NOTREACHED"!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileOpenPIC:numArgs: (in category 'in-line cacheing') -----
  compileOpenPIC: selector numArgs: numArgs
  	"Compile the code for an open PIC.  Perform a probe of the first-level method
  	 lookup cache followed by a call of ceSendFromInLineCacheMiss: if the probe fails."
  	| jumpSelectorMiss jumpClassMiss itsAHit jumpBCMethod routine |
  	<var: #jumpSelectorMiss type: #'AbstractInstruction *'>
  	<var: #jumpClassMiss type: #'AbstractInstruction *'>
  	<var: #itsAHit type: #'AbstractInstruction *'>
  	<var: #jumpBCMethod type: #'AbstractInstruction *'>
  	self compilePICProlog: numArgs.
+ 	entry := objectRepresentation genGetClassTagOf: ReceiverResultReg into: ClassReg scratchReg: TempReg.
- 	self AlignmentNops: (BytesPerWord max: 8).
- 	entry := self Label.
- 	objectRepresentation genGetClassTagOf: ReceiverResultReg into: ClassReg scratchReg: TempReg.
  
+ 	"Do first of three probes.  See CoInterpreter>>lookupInMethodCacheSel:classTag:"
+ 	self flag: #lookupInMethodCacheSel:classTag:. "so this method shows up as a sender of lookupInMethodCacheSel:class:"
- 	"Do first of three probes.  See CoInterpreter>>lookupInMethodCacheSel:class:"
- 	self flag: #lookupInMethodCacheSel:classTag:. "so this method shows up as a sender of lookupInMethodCacheSel:classTag:"
  	self MoveR: ClassReg R: SendNumArgsReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	self LogicalShiftLeftCq: ShiftForWord R: ClassReg.
  	self AndCq: MethodCacheMask << ShiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	jumpClassMiss := self JumpNonZero: 0.
  
  	itsAHit := self Label.
  	"Fetch the method.  The interpret trampoline requires the bytecoded method in SendNumArgsReg"
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheMethod << ShiftForWord)
  		r: ClassReg
  		R: SendNumArgsReg.
  	"If the method is compiled jump to its unchecked entry-point, otherwise interpret it."
  	objectRepresentation
  		genLoadSlot: HeaderIndex sourceReg: SendNumArgsReg destReg: TempReg.
  	self MoveR: TempReg R: ClassReg.
  	jumpBCMethod := objectRepresentation genJumpSmallIntegerInScratchReg: TempReg.
  	jumpBCMethod jmpTarget: interpretCall.
  	self AddCq: cmNoCheckEntryOffset R: ClassReg.
  	self JumpR: ClassReg.
  
  	"First probe missed.  Do second of three probes.  Shift hash right one and retry."
  	jumpSelectorMiss jmpTarget: (jumpClassMiss jmpTarget: self Label).
  	self MoveR: SendNumArgsReg R: ClassReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	self LogicalShiftLeftCq: ShiftForWord - 1 R: ClassReg.
  	self AndCq: MethodCacheMask << ShiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	self JumpZero: itsAHit.
  
  	"Second probe missed.  Do last probe.  Shift hash right two and retry."
  	jumpSelectorMiss jmpTarget: self Label.
  	self MoveR: SendNumArgsReg R: ClassReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	ShiftForWord > 2 ifTrue:
  		[self LogicalShiftLeftCq: ShiftForWord - 1 R: ClassReg].
  	self AndCq: MethodCacheMask << ShiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	self JumpZero: itsAHit.
  
  	"Last probe missed.  Call ceSendFromInLineCacheMiss: to do the full lookup."
  	jumpSelectorMiss jmpTarget: self Label.
  	self genSaveStackPointers.
  	self genLoadCStackPointers.
  	methodLabel addDependent: (self annotateAbsolutePCRef: (self MoveCw: methodLabel asInteger R: SendNumArgsReg)).
  	cStackAlignment > BytesPerWord ifTrue:
  		[backEnd
  			genAlignCStackSavingRegisters: false
  			numArgs: 1
  			wordAlignment: cStackAlignment / BytesPerWord].
  	backEnd genPassReg: SendNumArgsReg asArgument: 0.
  	routine := self cCode: '(sqInt)ceSendFromInLineCacheMiss'
  					inSmalltalk: [self simulatedAddressFor: #ceSendFromInLineCacheMiss:].
  	self annotateCall: (self Call: routine)
  	"Note that this call does not return."!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>numRegArgs (in category 'testing') -----
  numRegArgs
  	<api>
- 	"Use of the macro allows the compiler to avoid the call and test in cointerpreter.c"
- 	<cmacro: '() 0'>
  	^0!

Item was changed:
  ----- Method: StackInterpreter>>longPrintOop: (in category 'debug printing') -----
  longPrintOop: oop
  	<api>
  	| fmt lastIndex startIP bytecodesPerLine column |
  	((objectMemory isImmediate: oop)
  	 or: [(objectMemory addressCouldBeObj: oop) not
  	 or: [(oop bitAnd: objectMemory allocationUnit - 1) ~= 0
  	 or: [(objectMemory isFreeObject: oop)
  	 or: [objectMemory isForwarded: oop]]]]) ifTrue:
  		[self printOop: oop.
  		 ^self].
  	self printHex: oop.
  	(objectMemory fetchClassOfNonImm: oop)
  		ifNil: [self print: ' has a nil class!!!!']
  		ifNotNil: [:class|
  			self print: ': a(n) '; printNameOfClass: class count: 5;
+ 				print: ' ('.
+ 			objectMemory hasSpurMemoryManagerAPI ifTrue:
+ 				[self printHexnp: (objectMemory compactClassIndexOf: oop); print: '=>'].
+ 			self printHexnp: class; print: ')'].
- 				print: ' ('; printHex: class; print: ')'].
  	fmt := objectMemory formatOf: oop.
  	self print: ' format '; printHexnp: fmt.
  	fmt > objectMemory lastPointerFormat
  		ifTrue: [self print: ' nbytes '; printNum: (objectMemory byteLengthOf: oop)]
  		ifFalse: [(objectMemory isIndexableFormat: fmt) ifTrue:
  					[| len |
  					len := objectMemory lengthOf: oop.
  					self print: ' size '; printNum: len - (objectMemory fixedFieldsOf: oop format: fmt length: len)]].
  	objectMemory printHeaderTypeOf: oop.
  	self print: ' hash '; printHexnp: (objectMemory rawHashBitsOf: oop).
  	self cr.
  	(fmt between: objectMemory firstByteFormat and: objectMemory firstCompiledMethodFormat - 1) ifTrue:
  		[^self printStringOf: oop; cr].
  	(fmt between: objectMemory firstLongFormat and: objectMemory firstByteFormat - 1) ifTrue:
  		[^self].
  	"this is nonsense.  apologies."
  	startIP := (objectMemory lastPointerOf: oop) + BytesPerOop - objectMemory baseHeaderSize / BytesPerOop.
  	lastIndex := 256 min: startIP.
  	lastIndex > 0 ifTrue:
  		[1 to: lastIndex do:
  			[:i| | fieldOop |
  			fieldOop := objectMemory fetchPointer: i - 1 ofObject: oop.
  			self space; printNum: i - 1; space; printHex: fieldOop; space.
  			(i = 1 and: [objectMemory isCompiledMethod: oop])
  				ifTrue: [self printMethodHeaderOop: fieldOop]
  				ifFalse: [self cCode: [self printOopShort: fieldOop]
  							inSmalltalk: [self print: (self shortPrint: fieldOop)]].
  			self cr]].
  	(objectMemory isCompiledMethod: oop)
  		ifFalse:
  			[startIP > 64 ifTrue: [self print: '...'; cr]]
  		ifTrue:
  			[startIP := startIP * BytesPerWord + 1.
  			 lastIndex := objectMemory lengthOf: oop.
  			 lastIndex - startIP > 100 ifTrue:
  				[lastIndex := startIP + 100].
  			 bytecodesPerLine := 8.
  			 column := 1.
  			 startIP to: lastIndex do:
  				[:index| | byte |
  				column = 1 ifTrue:
  					[self cCode: 'printf("0x%08x: ", oop+BaseHeaderSize+index-1)'
  						inSmalltalk: [self print: (oop+BaseHeaderSize+index-1) hex; print: ': ']].
  				byte := objectMemory fetchByte: index - 1 ofObject: oop.
  				self cCode: 'printf(" %02x/%-3d", byte,byte)'
  					inSmalltalk: [self space; print: (byte radix: 16); printChar: $/; printNum: byte].
  				column := column + 1.
  				column > bytecodesPerLine ifTrue:
  					[column := 1. self cr]].
  			column = 1 ifFalse:
  				[self cr]]!

Item was changed:
  ----- Method: StackToRegisterMapping2RegArgsCogit>>numRegArgs (in category 'calling convention') -----
  numRegArgs
  	<api>
- 	"Use of the macro allows the compiler to avoid the call and test in cointerpreter.c"
- 	<cmacro: '() 2'>
  	^2!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>compileOpenPIC:numArgs: (in category 'in-line cacheing') -----
  compileOpenPIC: selector numArgs: numArgs
  	"Compile the code for an open PIC.  Perform a probe of the first-level method
  	 lookup cache followed by a call of ceSendFromInLineCacheMiss: if the probe fails.
  	 Override to push the register args when calling ceSendFromInLineCacheMiss:"
  	| jumpSelectorMiss jumpClassMiss itsAHit jumpBCMethod routine |
  	<var: #jumpSelectorMiss type: #'AbstractInstruction *'>
  	<var: #jumpClassMiss type: #'AbstractInstruction *'>
  	<var: #itsAHit type: #'AbstractInstruction *'>
  	<var: #jumpBCMethod type: #'AbstractInstruction *'>
  	self compilePICProlog: numArgs.
  	entry := objectRepresentation genGetClassTagOf: ReceiverResultReg into: ClassReg scratchReg: TempReg.
  
  	"Do first of three probes.  See CoInterpreter>>lookupInMethodCacheSel:classTag:"
  	self flag: #lookupInMethodCacheSel:classTag:. "so this method shows up as a sender of lookupInMethodCacheSel:class:"
  	self MoveR: ClassReg R: SendNumArgsReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	self LogicalShiftLeftCq: ShiftForWord R: ClassReg.
  	self AndCq: MethodCacheMask << ShiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	jumpClassMiss := self JumpNonZero: 0.
  
  	itsAHit := self Label.
  	"Fetch the method.  The interpret trampoline requires the bytecoded method in SendNumArgsReg"
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheMethod << ShiftForWord)
  		r: ClassReg
  		R: SendNumArgsReg.
  	"If the method is compiled jump to its unchecked entry-point, otherwise interpret it."
  	objectRepresentation
  		genLoadSlot: HeaderIndex sourceReg: SendNumArgsReg destReg: TempReg.
  	self MoveR: TempReg R: ClassReg.
  	jumpBCMethod := objectRepresentation genJumpSmallIntegerInScratchReg: TempReg.
  	jumpBCMethod jmpTarget: interpretCall.
  	self AddCq: cmNoCheckEntryOffset R: ClassReg.
  	self JumpR: ClassReg.
  
  	"First probe missed.  Do second of three probes.  Shift hash right one and retry."
  	jumpSelectorMiss jmpTarget: (jumpClassMiss jmpTarget: self Label).
  	self MoveR: SendNumArgsReg R: ClassReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	self LogicalShiftLeftCq: ShiftForWord - 1 R: ClassReg.
  	self AndCq: MethodCacheMask << ShiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	self JumpZero: itsAHit.
  
  	"Second probe missed.  Do last probe.  Shift hash right two and retry."
  	jumpSelectorMiss jmpTarget: self Label.
  	self MoveR: SendNumArgsReg R: ClassReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	ShiftForWord > 2 ifTrue:
  		[self LogicalShiftLeftCq: ShiftForWord - 1 R: ClassReg].
  	self AndCq: MethodCacheMask << ShiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	self JumpZero: itsAHit.
  
+ 	"Last probe missed.  Call ceSendFromInLineCacheMiss: to do the full lookup."
- 	"Last probe missed.  Call ceSendFromOpenPIC: to do the full lookup."
  	jumpSelectorMiss jmpTarget: self Label.
  	self genPushRegisterArgsForNumArgs: numArgs.
  	self genSaveStackPointers.
  	self genLoadCStackPointers.
  	methodLabel addDependent: (self annotateAbsolutePCRef: (self MoveCw: methodLabel asInteger R: SendNumArgsReg)).
  	cStackAlignment > BytesPerWord ifTrue:
  		[backEnd
  			genAlignCStackSavingRegisters: false
  			numArgs: 1
  			wordAlignment: cStackAlignment / BytesPerWord].
  	backEnd genPassReg: SendNumArgsReg asArgument: 0.
  	routine := self cCode: '(sqInt)ceSendFromInLineCacheMiss'
  					inSmalltalk: [self simulatedAddressFor: #ceSendFromInLineCacheMiss:].
  	self annotateCall: (self Call: routine)
  	"Note that this call does not return."!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendTrampolineFor:numArgs:called:arg:arg:arg: (in category 'initialization') -----
  genSendTrampolineFor: aRoutine numArgs: numArgs called: aString arg: regOrConst0 arg: regOrConst1 arg: regOrConst2
+ 	"Generate a trampoline with three arguments.
- 	"Generate a trampoline with four arguments.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	| startAddress |
  	<inline: false>
  	startAddress := methodZoneBase.
  	opcodeIndex := 0.
  	self genPushRegisterArgsForNumArgs: numArgs.
  	self genTrampolineFor: aRoutine
  		called: aString
  		callJumpBar: true
  		numArgs: 3
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: nil
  		saveRegs: false
  		resultReg: nil
  		appendOpcodes: true.
  	^startAddress!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>numRegArgs (in category 'compile abstract instructions') -----
  numRegArgs
  	<api>
- 	"Use of the macro allows the compiler to avoid the call and test in cointerpreter.c"
- 	<cmacro: '() 1'>
  	^1!



More information about the Vm-dev mailing list