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

commits at source.squeak.org commits at source.squeak.org
Tue Apr 7 03:15:29 UTC 2015


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

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

Name: VMMaker.oscog-eem.1166
Author: eem
Time: 6 April 2015, 8:09:36.675 pm
UUID: 7300780d-95c8-42a4-96f2-b0bea69f363d
Ancestors: VMMaker.oscog-eem.1165

Change IA32's genPushRegisterArgsForNumArgs: to
not smash TempReg now that it is used in directed
super send trampolines.

Fix bug in generateMapAt:start:, miswritten for new
annotation extensions, and change it to take nil,
not 0, as the "just measure, don't generate" flag.

Make send table yielding functions test
BytecodeSetHasDirectedSuperSend, not SistaVM.

Fix slip in maybeFreeCounters:.

Optimize StackToRegisterMappingCogit>>genReturnReceiver
to not load ReceiverResultReg if it already contains self.

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

Item was changed:
  ----- Method: CogIA32Compiler>>genPushRegisterArgsForNumArgs: (in category 'smalltalk calling convention') -----
  genPushRegisterArgsForNumArgs: numArgs
  	"Ensure that the register args are pushed before the retpc for arity <= self numRegArgs."
  	"This won't be as clumsy on a RISC.  But putting the receiver and
  	 args above the return address means the CoInterpreter has a
  	 single machine-code frame format which saves us a lot of work."
  	numArgs <= cogit numRegArgs ifTrue:
  		[self assert: cogit numRegArgs <= 2.
+ 		 "N.B. Take great care to /not/ smash TempReg, which is used in directed send marshalling."
+ 		 "Swap the return address with ReceiverResultReg"
+ 		 cogit gen: XCHGMwrR operand: 0 operand: SPReg operand: ReceiverResultReg. "Save return address; replace with receiver"
+ 		 numArgs > 0 ifTrue:
+ 			[cogit PushR: Arg0Reg.
+ 			 numArgs > 1 ifTrue:
+ 				[cogit PushR: Arg1Reg]].
+ 		cogit PushR: ReceiverResultReg.
+ 		"Reload ReceiverResultReg"
+ 		cogit MoveMw: numArgs + 1 * objectMemory wordSize r: SPReg R: ReceiverResultReg]!
- 		 false "these two variants show the same performance on Intel Core i7, but the second one may be shorter."
- 			ifTrue:
- 				[cogit MoveMw: 0 r: SPReg R: TempReg. "Save return address"
- 				 numArgs > 0 ifTrue:
- 					[cogit PushR: Arg0Reg.
- 					 numArgs > 1 ifTrue:
- 						[cogit PushR: Arg1Reg]].
- 				 cogit PushR: TempReg.
- 				 cogit MoveR: ReceiverResultReg Mw: objectMemory wordSize * (1 + numArgs) r: SPReg]
- 			ifFalse:
- 				[cogit MoveMw: 0 r: SPReg R: TempReg. "Save return address"
- 				 cogit MoveR: ReceiverResultReg Mw: 0 r: SPReg.
- 				 numArgs > 0 ifTrue:
- 					[cogit PushR: Arg0Reg.
- 					 numArgs > 1 ifTrue:
- 						[cogit PushR: Arg1Reg]].
- 				cogit PushR: TempReg]] "Restore return address"!

Item was changed:
  ----- Method: Cogit>>generateCogMethod: (in category 'generate machine code') -----
  generateCogMethod: selector
  	"We handle jump sizing simply.  First we make a pass that asks each
  	 instruction to compute its maximum size.  Then we make a pass that
  	 sizes jumps based on the maxmimum sizes.  Then we make a pass
  	 that fixes up jumps.  When fixing up a jump the jump is not allowed to
  	 choose a smaller offset but must stick to the size set in the second pass."
  	<returnTypeC: #'CogMethod *'>
  	| codeSize headerSize mapSize totalSize startAddress result method |
  	<var: #method type: #'CogMethod *'>
  	headerSize := self sizeof: CogMethod.
  	methodLabel address: headerSize negated.
  	self computeMaximumSizes.
  	methodLabel concretizeAt: methodZone freeStart.
  	codeSize := self generateInstructionsAt: methodLabel address + headerSize.
+ 	mapSize := self generateMapAt: nil start: methodLabel address + cmNoCheckEntryOffset.
- 	mapSize := self generateMapAt: 0 start: methodLabel address + cmNoCheckEntryOffset.
  	totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize.
  	totalSize > MaxMethodSize ifTrue:
  		[^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  	startAddress := methodZone allocate: totalSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: startAddress + cmNoCheckEntryOffset = noCheckEntry address.
  	result := self outputInstructionsAt: startAddress + headerSize.
  	self assert: startAddress + headerSize + codeSize = result.
  	backEnd padIfPossibleWithNopsFrom: result to: startAddress + totalSize - mapSize.
  	self generateMapAt: startAddress + totalSize - 1 start: startAddress + cmNoCheckEntryOffset.
  	self fillInBlockHeadersAt: startAddress.
  	method := self fillInMethodHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  					size: totalSize
  					selector: selector.
  	postCompileHook notNil ifTrue:
  		[self perform: postCompileHook with: method with: primInvokeLabel.
  		 postCompileHook := nil].
  	processor flushICacheFrom: startAddress to: startAddress + headerSize + codeSize.
  	^method!

Item was changed:
  ----- Method: Cogit>>generateMapAt:start: (in category 'method map') -----
  generateMapAt: addressOrNull start: startAddress
  	"Generate the method map at addressrNull (or compute it if adressOrNull is null).
  	 Answer the length of the map in byes.  Each entry in the map is in two parts.  In the
  	 least signficant bits are a displacement of how far from the start or previous entry,
  	 unless it is an IsAnnotationExtension byte, in which case those bits are the extension.
  	 In the most signficant bits are the type of annotation at the point reached.  A null
  	 byte ends the map."
  	| length location |
  	<var: #annotation type: #'InstructionAnnotation *'>
  	length := 0.
  	location := startAddress.
  	0 to: annotationIndex - 1 do:
  		[:i| | annotation mcpc delta maxDelta mapEntry |
  		 annotation := self addressOf: (annotations at: i).
  		 mcpc := annotation instruction address + annotation instruction machineCodeSize.
  		 [(delta := mcpc - location) > DisplacementMask] whileTrue:
  			[maxDelta := (delta min: MaxX2NDisplacement) bitClear: DisplacementMask.
  			 self assert: maxDelta >> AnnotationShift <= DisplacementMask.
+ 			 addressOrNull ifNotNil:
- 			 addressOrNull ~= 0 ifTrue:
  				[objectMemory
  					byteAt: addressOrNull - length
  					put: maxDelta >> AnnotationShift + DisplacementX2N.
  				 self traceMap: IsDisplacementX2N
  					  byte: maxDelta >> AnnotationShift + DisplacementX2N
  					  at: addressOrNull - length
  					  for: mcpc].
  			 location := location + maxDelta.
  			 length := length + 1].
+ 		 addressOrNull ifNotNil:
- 		 addressOrNull ~= 0 ifTrue:
  			[mapEntry := delta + ((annotation annotation min: IsSendCall) << AnnotationShift).
  			 objectMemory byteAt: addressOrNull - length put: mapEntry.
  			 self traceMap: annotation
  				  byte: mapEntry
  				  at: addressOrNull - length
+ 				  for: mcpc].
+ 		 location := location + delta.
+ 		 length := length + 1.
+ 		 annotation annotation > IsSendCall ifTrue: "Add the necessary IsAnnotationExtension"
+ 			[addressOrNull ifNotNil:
- 				  for: mcpc.
- 			 annotation annotation > IsSendCall ifTrue: "Add the necessary IsAnnotationExtension"
  				[mapEntry := IsAnnotationExtension << AnnotationShift + (annotation annotation - IsSendCall).
+ 				 objectMemory byteAt: addressOrNull - length put: mapEntry.
- 				 objectMemory byteAt: addressOrNull - (length := length + 1) put: mapEntry.
  				 self traceMap: annotation
  					  byte: mapEntry
  					  at: addressOrNull - length
+ 					  for: mcpc].
+ 			 length := length + 1]].
+ 	addressOrNull ifNotNil:
- 					  for: mcpc]].
- 		 location := location + delta.
- 		 length := length + 1].
- 	addressOrNull ~= 0 ifTrue:
  		[objectMemory byteAt: addressOrNull - length put: MapEnd.
  		 self traceMap: MapEnd
  			  byte: MapEnd
  			  at: addressOrNull - length
  			  for: 0].
  	^length + 1!

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."
  	| headerSize codeSize mapSize |
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: 100 bytecodes: 0.
  	"Ned a real selector here so that the map accomodates the annotations for the selector."
  	self compileOpenPIC: (coInterpreter specialSelector: 0) numArgs: self numRegArgs.
  	self computeMaximumSizes.
  	headerSize := self sizeof: CogMethod.
  	methodLabel concretizeAt: methodZoneBase.
  	codeSize := self generateInstructionsAt: methodZoneBase + headerSize.
+ 	mapSize := self generateMapAt: nil start: methodZoneBase + cmNoCheckEntryOffset.
- 	mapSize := self generateMapAt: 0 start: methodZoneBase + cmNoCheckEntryOffset.
  	openPICSize := (methodZone roundUpLength: headerSize + codeSize) + (methodZone roundUpLength: mapSize).
  	"self cCode: ''
  		inSmalltalk:
  			[| end |
  			 end := self outputInstructionsAt: methodZoneBase + headerSize.
  			 self disassembleFrom: methodZoneBase + headerSize to: end - 1.
  			 self halt]"!

Item was changed:
  ----- Method: Cogit>>offsetAndSendTableFor:annotation:into: (in category 'in-line cacheing') -----
  offsetAndSendTableFor: entryPoint annotation: annotation into: binaryBlock
  	"Find the relevant sendTable for a linked-send to entryPoint.  Do this based on the
  	 annotation.  c.f. annotationForSendTable:"
  	<inline: true>
  	| offset sendTable |
  	<var: #sendTable type: #'sqInt *'>
  	annotation = IsSendCall ifTrue:
  		[offset := cmEntryOffset.
  		 sendTable := ordinarySendTrampolines] ifFalse:
+ 	[(BytecodeSetHasDirectedSuperSend and: [annotation = IsDirectedSuperSend]) ifTrue:
- 	[(SistaVM and: [annotation = IsDirectedSuperSend]) ifTrue:
  		[offset := cmNoCheckEntryOffset.
  		 sendTable := directedSuperSendTrampolines] ifFalse:
  	[(NewspeakVM and: [annotation = IsNSSelfSend]) ifTrue:
  		[offset := cmEntryOffset.
  		 sendTable := selfSendTrampolines] ifFalse:
  	[(NewspeakVM and: [annotation = IsNSSelfSend]) ifTrue:
  		[offset := cmEntryOffset.
  		 sendTable := selfSendTrampolines] ifFalse:
  	[(NewspeakVM and: [annotation = IsNSSelfSend]) ifTrue:
  		[offset := cmEntryOffset.
  		 sendTable := selfSendTrampolines] ifFalse:
  	[self assert: annotation = IsSuperSend.
  	 offset := cmNoCheckEntryOffset.
  	 sendTable := superSendTrampolines]]]]].
  
  	binaryBlock
  		value: offset
  		value: sendTable!

Item was changed:
  ----- Method: Cogit>>targetMethodAndSendTableFor:annotation:into: (in category 'in-line cacheing') -----
  targetMethodAndSendTableFor: entryPoint annotation: annotation into: binaryBlock
  	"Evaluate binaryBlock with the targetMethod and relevant send table for a linked-send
  	 to entryPoint.  Do so based on the alignment of entryPoint.  N.B.  For Newspeak sends
  	 we don't need to distinguish between ceImplicitReceiver and the other sends since
  	 ceImplicitReceiver will never appear to be linked, so only three cases here."
  	<inline: true>
  	| targetMethod sendTable |
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #sendTable type: #'sqInt *'>
  
  	annotation = IsSendCall ifTrue:
  		[targetMethod := self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *'.
  		 sendTable := ordinarySendTrampolines] ifFalse:
+ 	[(BytecodeSetHasDirectedSuperSend and: [annotation = IsDirectedSuperSend]) ifTrue:
- 	[(SistaVM and: [annotation = IsDirectedSuperSend]) ifTrue:
  		[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  		 sendTable := directedSuperSendTrampolines] ifFalse:
  	[(NewspeakVM and: [annotation = IsNSSelfSend]) ifTrue:
  		[targetMethod := self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *'.
  		 sendTable := selfSendTrampolines] ifFalse:
  	[(NewspeakVM and: [annotation = IsNSSelfSend]) ifTrue:
  		[targetMethod := self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *'.
  		 sendTable := selfSendTrampolines] ifFalse:
  	[(NewspeakVM and: [annotation = IsNSSelfSend]) ifTrue:
  		[targetMethod := self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *'.
  		 sendTable := selfSendTrampolines] ifFalse:
  	[self assert: annotation = IsSuperSend.
  	 targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  	 sendTable := superSendTrampolines]]]]].
  
  	binaryBlock
  		value: targetMethod
  		value: sendTable!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>maybeFreeCounters (in category 'compile abstract instructions') -----
  maybeFreeCounters
  	<inline: true>
  	counters ~= 0 ifTrue:
+ 		[objectRepresentation freeCounters: counters]!
- 		[objectMemory freeCounters: counters]!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genReturnReceiver (in category 'bytecode generators') -----
+ genReturnReceiver
+ 	"In a frameless method ReceiverResultReg already contains self.
+ 	 In a frameful method, ReceiverResultReg /may/ contain self."
+ 	needsFrame ifTrue:
+ 		[(optStatus isReceiverResultRegLive
+ 		  and: [optStatus ssEntry = (self addressOf: simSelf)]) ifFalse:
+ 			[self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg]].
+ 	^self genUpArrowReturn!



More information about the Vm-dev mailing list