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

commits at source.squeak.org commits at source.squeak.org
Fri Jul 12 22:54:43 UTC 2013


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

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

Name: VMMaker.oscog-eem.302
Author: eem
Time: 12 July 2013, 3:52:19.037 pm
UUID: 2ac39432-ac54-4584-964e-b129c90792f4
Ancestors: VMMaker.oscog-tpr.301

Fix bug when assigning to some context inst vars from generated
methods.  Add accessors to document the context inst var access
scheme.
Fix a compiler warning comparing an error code in cog:selector:

=============== Diff against VMMaker.oscog-tpr.301 ===============

Item was changed:
  ----- Method: Cogit>>cog:selector: (in category 'jit - api') -----
  cog: aMethodObj selector: aSelectorOop
  	"Attempt to produce a machine code method for the bytecode method
  	 object aMethodObj.  N.B. If there is no code memory available do *NOT*
  	 attempt to reclaim the method zone.  Certain clients (e.g. ceSICMiss:)
  	 depend on the zone remaining constant across method generation."
  	<api>
  	<returnTypeC: #'CogMethod *'>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	self assert: ((coInterpreter methodHasCogMethod: aMethodObj) not
  				or: [(self noAssertMethodClassAssociationOf: aMethodObj) = objectMemory nilObject]).
  	"coInterpreter stringOf: aSelectorOop"
  	coInterpreter
  		compilationBreak: aSelectorOop
  		point: (objectMemory lengthOf: aSelectorOop).
  	aMethodObj = breakMethod ifTrue: [self halt: 'Compilation of breakMethod'].
  	self cppIf: NewspeakVM
  		ifTrue: [cogMethod := methodZone findPreviouslyCompiledVersionOf: aMethodObj with: aSelectorOop.
  				cogMethod ifNotNil:
  					[(coInterpreter methodHasCogMethod: aMethodObj) not ifTrue:
  						[self assert: (coInterpreter rawHeaderOf: aMethodObj) = cogMethod methodHeader.
  						 cogMethod methodObject: aMethodObj.
  						 coInterpreter rawHeaderOf: aMethodObj put: cogMethod asInteger].
  					^cogMethod]].
  	"If the generators for the alternate bytecode set are missing then interpret."
  	(coInterpreter methodUsesAlternateBytecodeSet: aMethodObj)
  		ifTrue:
  			[(self numElementsIn: generatorTable) <= 256 ifTrue:
  				[^nil].
  			 bytecodeSetOffset := 256]
  		ifFalse:
  			[bytecodeSetOffset := 0].
  	extA := extB := 0.
  	methodObj := aMethodObj.
  	cogMethod := self compileCogMethod: aSelectorOop.
  	(cogMethod asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
+ 		[cogMethod asInteger = InsufficientCodeSpace ifTrue:
- 		[cogMethod asUnsignedInteger = InsufficientCodeSpace ifTrue:
  			[coInterpreter callForCogCompiledCodeCompaction].
  		"Right now no errors should be reported, so nothing more to do."
  		"self reportError: (self cCoerceSimple: cogMethod to: #sqInt)."
  		 ^nil].
  	"self cCode: ''
  		inSmalltalk:
  			[coInterpreter printCogMethod: cogMethod.
  			 ""coInterpreter symbolicMethod: aMethodObj.""
  			 self assertValidMethodMap: cogMethod."
  			 "self disassembleMethod: cogMethod."
  			 "printInstructions := clickConfirm := true""]."
  	^cogMethod!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>doubleExtendedDoAnythingBytecode (in category 'bytecode generators') -----
  doubleExtendedDoAnythingBytecode
  	"Replaces the Blue Book double-extended send [132], in which the first byte was wasted on 8 bits of argument count. 
  	Here we use 3 bits for the operation sub-type (opType),  and the remaining 5 bits for argument count where needed. 
  	The last byte give access to 256 instVars or literals. 
  	See also secondExtendedSendBytecode"
  	| opType |
  	opType := byte1 >> 5.
  	opType = 0 ifTrue:
  		[^self genSend: (self getLiteral: byte2) numArgs: (byte1 bitAnd: 31)].
  	opType = 1 ifTrue:
  		[^self genSendSuper: (self getLiteral: byte2) numArgs: (byte1 bitAnd: 31)].
  	"We need a map entry for this bytecode for correct parsing.
  	 The sends will get an IsSend entry anyway.  The other cases need a
  	 fake one.  We could of course special case the scanning but that's silly."
  	opType caseOf: {
+ 			[2]	->	[(coInterpreter isReadMediatedContextInstVarIndex: byte2)
- 			[2]	->	[byte2 <= StackPointerIndex
  						ifTrue: [self genPushMaybeContextReceiverVariable: byte2]
  						ifFalse: [self genPushReceiverVariable: byte2]].
  			[3]	->	[self genPushLiteralIndex: byte2].
  			[4]	->	[self genPushLiteralVariable: byte2].
  			[7]	->	[self genStorePop: false LiteralVariable: byte2] }
  		otherwise: "5 & 6"
+ 			[(coInterpreter isWriteMediatedContextInstVarIndex: byte2)
- 			[byte2 <= StackPointerIndex
  				ifTrue: [self genStorePop: opType = 6 MaybeContextReceiverVariable: byte2]
  				ifFalse: [self genStorePop: opType = 6 ReceiverVariable: byte2]].
  	"We need a map entry for this bytecode for correct parsing (if the method builds a frame).
  	 We could of course special case the scanning but that's silly."
  	needsFrame ifTrue:
  		[self annotateBytecode: self Label].
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtPushReceiverVariableBytecode (in category 'bytecode generators') -----
  genExtPushReceiverVariableBytecode
  	"226		11100010	i i i i i i i i	Push Receiver Variable #iiiiiiii (+ Extend A * 256)"
  	| index |
  	index := byte1 + (extA << 8).
  	extA := 0.
+ 	^(coInterpreter isReadMediatedContextInstVarIndex: index)
+ 		ifTrue: [self genPushMaybeContextReceiverVariable: index]
+ 		ifFalse: [self genPushReceiverVariable: index]!
- 	^index > StackPointerIndex
- 		ifTrue: [self genPushReceiverVariable: index]
- 		ifFalse: [self genPushMaybeContextReceiverVariable: index]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtStoreAndPopReceiverVariableBytecode (in category 'bytecode generators') -----
  genExtStoreAndPopReceiverVariableBytecode
  	"235		11101011	i i i i i i i i	Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)"
  	| index |
  	index := byte1 + (extA << 8).
  	extA := 0.
+ 	^(coInterpreter isWriteMediatedContextInstVarIndex: index)
+ 		ifTrue: [self genStorePop: true MaybeContextReceiverVariable: index]
+ 		ifFalse: [self genStorePop: true ReceiverVariable: index]!
- 	^index > StackPointerIndex
- 		ifTrue: [self genStorePop: true ReceiverVariable: index]
- 		ifFalse: [self genStorePop: true MaybeContextReceiverVariable: index]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtStoreReceiverVariableBytecode (in category 'bytecode generators') -----
  genExtStoreReceiverVariableBytecode
  	"232		11101000	i i i i i i i i	Store Receiver Variable #iiiiiii (+ Extend A * 256)"
  	| index |
  	index := byte1 + (extA << 8).
  	extA := 0.
+ 	^(coInterpreter isWriteMediatedContextInstVarIndex: index)
+ 		ifTrue: [self genStorePop: false MaybeContextReceiverVariable: index]
+ 		ifFalse: [self genStorePop: false ReceiverVariable: index]!
- 	^index > StackPointerIndex
- 		ifTrue: [self genStorePop: false ReceiverVariable: index]
- 		ifFalse: [self genStorePop: false MaybeContextReceiverVariable: index]!

Item was changed:
  ----- Method: StackInterpreter class>>initializeContextIndices (in category 'initialization') -----
  initializeContextIndices
  	"Class MethodContext"
  	| contextFixedSizePlusHeader |
  	SenderIndex := 0.
  	InstructionPointerIndex := 1.
  	StackPointerIndex := 2.
  	MethodIndex := 3.
+ 	ClosureIndex := 4. "N.B. Called receiverMap in old images, closureOrNil in newer images."
- 	ClosureIndex := 4. "N.B. Called receiverMap in the image."
  	ReceiverIndex := 5.
  	CtxtTempFrameStart := 6.
  
  	"Class BlockClosure"
  	ClosureOuterContextIndex := 0.
  	ClosureStartPCIndex := 1.
  	ClosureNumArgsIndex := 2.
  	ClosureFirstCopiedValueIndex := 3.
  	ClosureCopiedValuesIndex := 3.
  
  	contextFixedSizePlusHeader := CtxtTempFrameStart + 1.
  	SmallContextSize := contextFixedSizePlusHeader + 16 * BytesPerWord.  "16 indexable fields"
+ 	"Large contexts have 56 indexable fields.  Max with single header word."
- 	"Large contexts have 56 indexable fileds.  Max with single header word."
  	"However note that in 64 bits, for now, large contexts have 3-word headers"
  	LargeContextSize := contextFixedSizePlusHeader + 56 * BytesPerWord!

Item was added:
+ ----- Method: StackInterpreter>>isReadMediatedContextInstVarIndex: (in category 'frame access') -----
+ isReadMediatedContextInstVarIndex: index
+ 	"Reading the sender, instructionPointer and stackPointer inst vars of a context must take
+ 	 account of potentially married contexts and fetch the state from the frame. method,
+ 	 closureOrNil and receiver can safely be fetched from the context without checking."
+ 	<api>
+ 	<inline: true>
+ 	^index <= StackPointerIndex!

Item was added:
+ ----- Method: StackInterpreter>>isWriteMediatedContextInstVarIndex: (in category 'frame access') -----
+ isWriteMediatedContextInstVarIndex: index
+ 	"Wrining any inst vars of a context must take account of potentially married contexts
+ 	 and set the state in the frame. Inst vars in subclasses don't need mediation; subclasses
+ 	 can't marry."
+ 	<api>
+ 	<inline: true>
+ 	^index <= ReceiverIndex!

Item was changed:
  ----- Method: StackInterpreter>>pushMaybeContextReceiverVariable: (in category 'stack bytecodes') -----
  pushMaybeContextReceiverVariable: fieldIndex
  	"Must trap accesses to married and widowed contexts.
  	 But don't want to check on all inst var accesses.  This
  	 method is only used by the long-form bytecodes, evading
  	 the cost. Note that the method, closure and receiver fields
  	 of married contexts are correctly initialized so they don't
  	 need special treatment on read.  Only sender, instruction
  	 pointer and stack pointer need to be intercepted on reads."
  	| rcvr |
  	<inline: true>
  	rcvr := self receiver.
+ 	((self isReadMediatedContextInstVarIndex: fieldIndex)
- 	(fieldIndex < MethodIndex
  	and: [objectMemory isContextNonInt: rcvr])
  		ifTrue:
  			[self internalPush: (self instVar: fieldIndex ofContext: rcvr)]
  		ifFalse:
  			[self internalPush: (objectMemory fetchPointer: fieldIndex ofObject: rcvr)]!

Item was changed:
  ----- Method: StackInterpreter>>storeMaybeContextReceiverVariable:withValue: (in category 'stack bytecodes') -----
  storeMaybeContextReceiverVariable: fieldIndex withValue: anObject
  	"Must trap accesses to married and widowed contexts.
  	 But don't want to check on all inst var accesses.  This
  	 method is only used by the long-form bytecodes, evading the cost."
  	| rcvr |
  	rcvr := self receiver.
+ 	((self isWriteMediatedContextInstVarIndex: fieldIndex)
- 	(fieldIndex <= ReceiverIndex
  	and: [(objectMemory isContextNonInt: rcvr)
  	and: [self isMarriedOrWidowedContext: rcvr]])
  		ifTrue:
  			[self instVar: fieldIndex ofContext: rcvr put: anObject]
  		ifFalse:
  			[objectMemory storePointer: fieldIndex ofObject: rcvr withValue: anObject]
  !

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>doubleExtendedDoAnythingBytecode (in category 'bytecode generators') -----
  doubleExtendedDoAnythingBytecode
  	"Replaces the Blue Book double-extended send [132], in which the first byte was wasted on 8 bits of argument count. 
  	Here we use 3 bits for the operation sub-type (opType),  and the remaining 5 bits for argument count where needed. 
  	The last byte give access to 256 instVars or literals. 
  	See also secondExtendedSendBytecode"
  	| opType |
  	opType := byte1 >> 5.
  	opType = 0 ifTrue:
  		[^self genSend: (self getLiteral: byte2) numArgs: (byte1 bitAnd: 31)].
  	opType = 1 ifTrue:
  		[^self genSendSuper: (self getLiteral: byte2) numArgs: (byte1 bitAnd: 31)].
  	"We need a map entry for this bytecode for correct parsing.
  	 The sends will get an IsSend entry anyway.  The other cases need a
  	 fake one.  We could of course special case the scanning but that's silly."
  	opType caseOf: {
+ 			[2]	->	[(coInterpreter isReadMediatedContextInstVarIndex: byte2)
- 			[2]	->	[byte2 <= StackPointerIndex
  						ifTrue: [self genPushMaybeContextReceiverVariable: byte2]
  						ifFalse: [self genPushReceiverVariable: byte2.
  								self ssTop annotateUse: true.
  								^0]].
  			[3]	->	[self genPushLiteralIndex: byte2.
  					 self ssTop annotateUse: true.
  					 ^0].
  			[4]	->	[self genPushLiteralVariable: byte2.].
  			[7]	->	[self genStorePop: false LiteralVariable: byte2] }
  		otherwise: "5 & 6"
+ 			[(coInterpreter isWriteMediatedContextInstVarIndex: byte2)
- 			[byte2 <= StackPointerIndex
  				ifTrue: [self genStorePop: opType = 6 MaybeContextReceiverVariable: byte2]
  				ifFalse: [self genStorePop: opType = 6 ReceiverVariable: byte2]].
  	"We need a map entry for this bytecode for correct parsing (if the method builds a frame).
  	 We could of course special case the scanning but that's silly (or is it?)."
  	self assert: needsFrame.
  	"genPushMaybeContextInstVar, pushListVar, store & storePop all generate code"
  	self assert: self prevInstIsPCAnnotated not.
  	self annotateBytecode: self Label.
  	^0!



More information about the Vm-dev mailing list