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

commits at source.squeak.org commits at source.squeak.org
Thu Aug 22 02:03:11 UTC 2013


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

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

Name: VMMaker.oscog-eem.331
Author: eem
Time: 21 August 2013, 7:00:38.722 pm
UUID: 37d2e4b0-2f37-4e2d-8313-c63637785e59
Ancestors: VMMaker.oscog-eem.330

Speed-up Newspeak significantly (e.g. -28% in one compile-intensive benchmark)
by maintaining unpaired methods (compilations of anonymous accessors) on a
linked list instead of searching the entire method zone.

Do this by adding a NewspeakCogMethod and surrogates that add a nextMethod
field.  Update surrogate accessor generation so that accessors can answer and
receive surrogates and nils.  Also add a nop before the dynSuperEntry so as to
change its alignment now that (in the Newspeak VM) CogMethod has changed size
in gaining a field.

Send fetchClassOf: to the right receiver in
explicitOuterReceiver:withObject:withMixin:

Slang: fix various bugs in header and typedef generation so that only one CogMethod
typedef is produced.

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

Item was changed:
  ----- Method: CoInterpreter class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  	"Answer any extra classes to be included in the translation."
  	^((super ancilliaryClasses: options) copyWithout: InterpreterStackPages),
  	   {	CoInterpreterStackPages.
+ 		CogBlockMethod },
+ 	((Cogit ancilliaryClasses: options) select: [:class| class inheritsFrom: CogBlockMethod])!
- 		CogBlockMethod.
- 		CogMethod }!

Item was changed:
  ----- Method: CoInterpreter class>>shouldGenerateTypedefFor: (in category 'translation') -----
  shouldGenerateTypedefFor: aStructClass
  	"Hack to work-around multiple definitions.  Sometimes a type has been defined in an include."
+ 	^({ CogBlockMethod. CogMethod. NewspeakCogMethod. SistaCogMethod. VMCallbackContext } includes: aStructClass) not!
- 	^({ CogBlockMethod. CogMethod. SistaCogMethod. VMCallbackContext } includes: aStructClass) not!

Item was changed:
  ----- Method: CogBlockMethod class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a CogMethod or CogBlockMethod struct."
  
  	self allInstVarNames do:
  		[:ivn|
  		"Notionally objectHeader is in a union with homeOffset and startpc but
  		 we don't have any convenient support for unions.  So hack, hack, hack, hack."
  		((self == CogBlockMethod
  			ifTrue: [#('objectHeader')]
  			ifFalse: [#('homeOffset' 'startpc' 'padToWord')]) includes: ivn) ifFalse:
  				[aBinaryBlock
  					value: ivn
  					value: (ivn caseOf: {
  								['cmNumArgs']				-> [#(unsigned ' : 8')]. "SqueakV3 needs only 5 bits"
  								['cmType']					-> [#(unsigned ' : 3')].
  								['cmRefersToYoung']		-> [#(unsigned #Boolean ' : 1')].
  								['cpicHasMNUCase']		-> [#(unsigned #Boolean ' : 1')].
  								['cmUsageCount']			-> [#(unsigned ' : 3')]. "see CMMaxUsageCount in initialize"
  								['cmUsesPenultimateLit']	-> [#(unsigned #Boolean ' : 1')].
  								['cmUnusedFlags']			-> [#(unsigned ' : 3')].
  								['stackCheckOffset']		-> [#(unsigned ' : 12')]. "See MaxStackCheckOffset in initialize. a.k.a. cPICNumCases"
  								['blockSize']				-> [#'unsigned short']. "See MaxMethodSize in initialize"
  								['blockEntryOffset']			-> [#'unsigned short'].
  								['homeOffset']				-> [#'unsigned short'].
  								['startpc']					-> [#'unsigned short'].
+ 								['padToWord']				-> [#(#BytesPerWord 8 'unsigned int')].
+ 								['nextMethod']				-> ['struct _CogMethod *']} "see NewspeakCogMethod"
- 								['padToWord']				-> [#(#BytesPerWord 8 'unsigned int')]}
  							otherwise:
  								[#sqInt])]]!

Item was changed:
  CogClass subclass: #CogMethodZone
+ 	instanceVariableNames: 'youngReferrers methodCount openPICList mzFreeStart baseAddress limitAddress methodBytesFreedSinceLastCompaction coInterpreter objectRepresentation cogit objectMemory unpairedMethodList'
- 	instanceVariableNames: 'youngReferrers methodCount openPICList mzFreeStart baseAddress limitAddress methodBytesFreedSinceLastCompaction coInterpreter objectRepresentation cogit objectMemory'
  	classVariableNames: ''
  	poolDictionaries: 'CogMethodConstants VMBasicConstants'
  	category: 'VMMaker-JIT'!
  
  !CogMethodZone commentStamp: '<historical>' prior: 0!
  I am a simple allocator/deallocator for the native code zone.  I also manage the youngReferers list, which contains methods that may refer to one or more young objects, and the openPICList which is a linked list of all open PICs in the zone.!

Item was changed:
  ----- Method: CogMethodZone class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	aCCodeGenerator
  		removeVariable: 'coInterpreter';
  		removeVariable: 'objectRepresentation'.
  	
  	self declareC: #(youngReferrers mzFreeStart baseAddress limitAddress)
  			as: #usqInt
+ 				in: aCCodeGenerator.
+ 	aCCodeGenerator var: 'unpairedMethodList' type: #'CogMethod *'!
- 				in: aCCodeGenerator!

Item was added:
+ ----- Method: CogMethodZone>>addToUnpairedMethodList: (in category 'accessing') -----
+ addToUnpairedMethodList: aCogMethod
+ 	<var: #aCogMethod type: #'CogMethod *'>
+ 	self assert: aCogMethod cmType = CMMethod.
+ 	self assert: (unpairedMethodList == nil
+ 				or: [unpairedMethodList cmType = CMMethod]).
+ 	aCogMethod nextMethod: unpairedMethodList.
+ 	unpairedMethodList := aCogMethod!

Item was changed:
  ----- Method: CogMethodZone>>compactCompiledCode: (in category 'compaction') -----
  compactCompiledCode: objectHeaderValue
  	| source dest bytes |
  	<var: #source type: #'CogMethod *'>
  	<var: #dest type: #'CogMethod *'>
  	source := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	openPICList := nil.
  	methodCount := 0.
+ 	self cppIf: NewspeakVM ifTrue: [unpairedMethodList := nil].
  	[source < self limitZony
  	 and: [source cmType ~= CMFree]] whileTrue:
  		[self assert: (cogit cogMethodDoesntLookKosher: source) = 0.
  		 source objectHeader: objectHeaderValue.
  		 source cmUsageCount > 0 ifTrue:
  			[source cmUsageCount: source cmUsageCount // 2].
+ 		 self cppIf: NewspeakVM ifTrue:
+ 				[(coInterpreter rawHeaderOf: source methodObject) asInteger ~= source asInteger ifTrue:
+ 					[source nextMethod: unpairedMethodList.
+ 					 unpairedMethodList := source]].
  		 source cmType = CMOpenPIC ifTrue:
  			[source nextOpenPIC: openPICList asUnsignedInteger.
  			 openPICList := source].
  		 methodCount := methodCount + 1.
  		 source := self methodAfter: source].
  	source >= self limitZony ifTrue:
  		[^self halt: 'no free methods; cannot compact.'].
  	dest := source.
  	[source < self limitZony] whileTrue:
  		[self assert: (cogit maybeFreeCogMethodDoesntLookKosher: source) = 0.
  		 bytes := source blockSize.
  		 source cmType ~= CMFree ifTrue:
  			[methodCount := methodCount + 1.
  			 self mem: dest mo: source ve: bytes.
  			 dest objectHeader: objectHeaderValue.
  			 dest cmType = CMMethod
  				ifTrue:
+ 					["For non-Newspeak there should be a one-to-one mapping between bytecoded and
- 					["For non-Newspeak there should be a one-to-one mapping metween bytecoded and
  					  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  					"Only update the original method's header if it is referring to this CogMethod."
  					 (coInterpreter rawHeaderOf: dest methodObject) asInteger = source asInteger
  						ifTrue: [coInterpreter rawHeaderOf: dest methodObject put: dest asInteger]
+ 						ifFalse:
+ 							[self assert: (cogit noAssertMethodClassAssociationOf: dest methodObject) = objectMemory nilObject.
+ 							 self cppIf: NewspeakVM
+ 								ifTrue: [dest nextMethod: unpairedMethodList.
+ 										unpairedMethodList := dest]]]
- 						ifFalse: [self assert: (cogit noAssertMethodClassAssociationOf: dest methodObject) = objectMemory nilObject]]
  				ifFalse:
  					[dest cmType = CMOpenPIC ifTrue:
  						[dest nextOpenPIC: openPICList asUnsignedInteger.
  						 openPICList := dest]].
  			 dest cmUsageCount > 0 ifTrue:
  				[dest cmUsageCount: dest cmUsageCount // 2].
  			 dest := coInterpreter
  								cCoerceSimple: dest asUnsignedInteger + bytes
  								to: #'CogMethod *'].
  		 source := coInterpreter
  							cCoerceSimple: source asUnsignedInteger + bytes
  							to: #'CogMethod *'].
  	mzFreeStart := dest asUnsignedInteger.
  	methodBytesFreedSinceLastCompaction := 0!

Item was changed:
  ----- Method: CogMethodZone>>findPreviouslyCompiledVersionOf:with: (in category 'accessing') -----
  findPreviouslyCompiledVersionOf: aMethodObj with: aSelectorOop
  	"Newspeak uses a set of methods to implement accessors, a setter and a getter for
  	 each inst var offset (e.g. 0 to 255).  These accessors are installed under the relevant
  	 selectors in different method dictionaries as required.  These methods effectively
  	 have multiple selectors.  The current inline cache design stores the selector of a
  	 linked send in the header of the target method.  So this requires a one-to-many
  	 mapping of bytecoded method to cog method, with the bytecoded method referring
  	 directly to only one cog method, which will have a specific selector, not necessarily
+ 	 the right one.  It is therefore worth-while searching for a cog method on this bytecoded
+ 	 method that has the right selector.  To speed up the search we maintain all such unpaired
+ 	 methods on the unpairedMethodList."
- 	 the right one.  It is therefore worth-while searching for a cog method on this method
- 	 that has the right selector.
- 	 We could revisit this:
- 		- a send site could have two loads, one for the selector and one for the class,
- 		  eliminating the need to store the selector in the header of a cog method
- 		  (although it would still be needed in a PIC, because open PICs are shared)
- 		- a set of unpaired cog methods could be maintained to speed up the search. since
- 		  the methodHeader field is effectively unused in an unpaired method the list could
- 		  link through this field (c.f. the openPICList linked through the methodObject field)."
  	<returnTypeC: #'CogMethod *'>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	((coInterpreter methodHasCogMethod: aMethodObj)
+ 	 and: [(coInterpreter methodClassAssociationOf: aMethodObj) = objectMemory nilObject]) ifTrue:
+ 		[cogMethod := unpairedMethodList.
+ 		[cogMethod notNil] whileTrue:
+ 			[self assert: cogMethod cmType = CMMethod.
+ 			 (cogMethod selector = aSelectorOop
+ 			  and: [cogMethod methodObject = aMethodObj]) ifTrue:
- 	and: [(coInterpreter methodClassAssociationOf: aMethodObj) = objectMemory nilObject]) ifTrue:
- 		[cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
- 		[cogMethod < self limitZony] whileTrue:
- 			[(cogMethod cmType = CMMethod
- 			  and: [cogMethod selector = aSelectorOop
- 			  and: [cogMethod methodObject = aMethodObj]]) ifTrue:
  				[^cogMethod].
+ 			 cogMethod := cogMethod nextMethod]].
- 			 cogMethod := self methodAfter: cogMethod]].
  	^nil!

Item was changed:
  ----- Method: CogMethodZone>>freeMethod: (in category 'compaction') -----
  freeMethod: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false>
  	self assert: cogMethod cmType ~= CMFree.
  	self assert: (cogit cogMethodDoesntLookKosher: cogMethod) = 0.
  	cogMethod cmType = CMMethod ifTrue:
  		["For non-Newspeak there should ne a one-to-one mapping between bytecoded and
  		  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  		"Only reset the original method's header if it is referring to this CogMethod."
  		 (coInterpreter rawHeaderOf: cogMethod methodObject) asInteger = cogMethod asInteger
  			ifTrue:
  				[coInterpreter rawHeaderOf: cogMethod methodObject put: cogMethod methodHeader]
  			ifFalse:
+ 				[self assert: (cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject.
+ 				 self cppIf: NewspeakVM ifTrue:
+ 					[self removeFromUnpairedMethodList: cogMethod]].
- 				[self assert: (cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject].
  		 cogMethod cmRefersToYoung: false].
  	cogMethod cmType = CMOpenPIC ifTrue:
  		[self removeFromOpenPICList: cogMethod.
  		 cogMethod cmRefersToYoung: false].
  	cogMethod cmType: CMFree.
  	methodBytesFreedSinceLastCompaction := methodBytesFreedSinceLastCompaction
  												+ cogMethod blockSize!

Item was changed:
  ----- Method: CogMethodZone>>manageFrom:to: (in category 'initialization') -----
  manageFrom: theStartAddress to: theLimitAddress
  	<returnTypeC: #void>
  	mzFreeStart := baseAddress := theStartAddress.
  	youngReferrers := limitAddress := theLimitAddress.
  	openPICList := nil.
+ 	self cppIf: NewspeakVM ifTrue: [unpairedMethodList := nil].
  	methodBytesFreedSinceLastCompaction := 0.
  	methodCount := 0!

Item was added:
+ ----- Method: CogMethodZone>>removeFromUnpairedMethodList: (in category 'accessing') -----
+ removeFromUnpairedMethodList: aCogMethod
+ 	<var: #aCogMethod type: #'CogMethod *'>
+ 	| prevMethod |
+ 	<var: #prevMethod type: #'CogMethod *'>
+ 	self assert: aCogMethod cmType = CMMethod.
+ 	aCogMethod = unpairedMethodList ifTrue:
+ 		[unpairedMethodList := aCogMethod nextMethod.
+ 		 ^nil].
+ 	prevMethod := unpairedMethodList.
+ 	[self assert: (prevMethod ~~ nil
+ 				and: [prevMethod cmType = CMMethod]).
+ 	 prevMethod nextMethod = aCogMethod ifTrue:
+ 		[prevMethod nextMethod: aCogMethod nextMethod.
+ 		 ^nil].
+ 	  prevMethod := aCogMethod nextMethod.
+ 	  true] whileTrue!

Item was changed:
  ----- Method: Cogit class>>additionalHeadersDo: (in category 'translation') -----
  additionalHeadersDo: aBinaryBlock
  	"Evaluate aBinaryBlock with the names and contents of
  	 any additional header files that need to be generated."
  	aBinaryBlock
  		value: 'cogmethod.h'
+ 		value: (NewspeakVM
+ 					ifTrue: [NewspeakCogMethod]
+ 					ifFalse: [CogMethod]) cogMethodHeader!
- 		value: CogMethod cogMethodHeader!

Item was changed:
  ----- Method: Cogit class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  	ProcessorClass ifNil: [thisContext methodClass theNonMetaClass initialize].
  	^{	CogMethodZone.
  		CogAbstractInstruction.
  		ProcessorClass basicNew abstractInstructionCompilerClass.
  		CogBlockStart.
  		CogBytecodeDescriptor.
  		CogBytecodeFixup.
  		CogInstructionAnnotation.
  		CogPrimitiveDescriptor.
  		CogBlockMethod.
+ 		CogMethod },
+ 	((options at: #NewspeakVM ifAbsent: [false])
+ 		ifTrue: [{NewspeakCogMethod}]
+ 		ifFalse: [#()])!
- 		CogMethod
- 	  }!

Item was changed:
  ----- Method: Cogit class>>shouldGenerateTypedefFor: (in category 'translation') -----
  shouldGenerateTypedefFor: aStructClass
  	"Hack to work-around mutliple definitions.  Sometimes a type has been defined in an include."
+ 	^({ CogBlockMethod. CogMethod. SistaCogMethod. NewspeakCogMethod } includes: aStructClass) not!
- 	^({ CogBlockMethod. CogMethod. SistaCogMethod } includes: aStructClass) not!

Item was changed:
  ----- Method: Cogit>>compileEntry (in category 'compile abstract instructions') -----
  compileEntry
  	"The entry code to a method checks that the class of the current receiver matches
  	 that in the inline cache.  Other non-obvious elements are that its alignment must be
  	 different from the alignment of the noCheckEntry so that the method map machinery
  	 can distinguish normal and super sends (super sends bind to the noCheckEntry).
  	 In Newspeak we also need to distinguish dynSuperSends from normal and super
  	 and so bind a the preceeding nop (on x86 there happens to be one anyway)."
  	self cppIf: NewspeakVM
+ 		ifTrue: "1st nop differentiates dynSuperEntry from no-check entry if using nextMethod"
+ 			[self Nop. 
+ 			dynSuperEntry := self Nop].
- 		ifTrue: [dynSuperEntry := self Nop].
  	self AlignmentNops: (BytesPerWord max: 8).
  	entry := self Label.
  	objectRepresentation getInlineCacheClassTagFrom: ReceiverResultReg into: TempReg.
  	self CmpR: ClassReg R: TempReg.
  	self JumpNonZero: sendMissCall.
  	noCheckEntry := self Label.
  	self recordSendTrace ifTrue:
  		[self CallRT: ceTraceLinkedSendTrampoline]!

Item was changed:
  ----- Method: Cogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
  	<returnTypeC: #'CogMethod *'>
  	<var: #method type: #'CogMethod *'>
  	<var: #originalMethod type: #'CogMethod *'>
  	| methodHeader originalMethod |
  	method cmType: CMMethod.
  	method objectHeader: objectMemory nullHeaderForMachineCodeMethod.
  	method blockSize: size.
  	method methodObject: methodObj.
  	methodHeader := coInterpreter rawHeaderOf: methodObj.
  	"If the method has already been cogged (e.g. Newspeak accessors) then
  	 leave the original method attached to its cog method, but get the right header."
  	(coInterpreter isCogMethodReference: methodHeader)
  		ifTrue:
  			[originalMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  			self assert: originalMethod blockSize = size.
+ 			methodHeader := originalMethod methodHeader.
+ 			self cppIf: NewspeakVM ifTrue: [methodZone addToUnpairedMethodList: method]]
- 			methodHeader := originalMethod methodHeader]
  		ifFalse:
  			[coInterpreter rawHeaderOf: methodObj put: method asInteger].
  	method methodHeader: methodHeader.
  	method selector: selector.
  	method cmNumArgs: (coInterpreter argumentCountOfMethodHeader: methodHeader).
  	(method cmRefersToYoung: hasYoungReferent) ifTrue:
  		[methodZone addToYoungReferrers: method].
  	method cmUsageCount: self initialMethodUsageCount.
  	method cpicHasMNUCase: false.
  	method cmUsesPenultimateLit: maxLitIndex >= ((coInterpreter literalCountOfHeader: methodHeader) - 2).
  	method blockEntryOffset: (blockEntryLabel notNil
  								ifTrue: [blockEntryLabel address - method asInteger]
  								ifFalse: [0]).
  	"This can be an error check since a large stackCheckOffset is caused by compiling
  	 a machine-code primitive, and hence depends on the Cogit, not the input method."
  	needsFrame ifTrue:
  		[stackCheckLabel address - method asInteger <= MaxStackCheckOffset ifFalse:
  			[self error: 'too much code for stack check offset']].
  	method stackCheckOffset: (needsFrame
  								ifTrue: [stackCheckLabel address - method asInteger]
  								ifFalse: [0]).
  	self assert: (backEnd callTargetFromReturnAddress: method asInteger + missOffset)
  				= (self methodAbortTrampolineFor: method cmNumArgs).
  	self assert: size = (methodZone roundUpLength: size).
  	^method!

Item was changed:
  ----- Method: Cogit>>initialize (in category 'initialization') -----
  initialize
+ 	cogMethodSurrogateClass := NewspeakVM
+ 									ifTrue:
+ 										[BytesPerWord = 4
+ 											ifTrue: [NewspeakCogMethodSurrogate32]
+ 											ifFalse: [NewspeakCogMethodSurrogate64]]
+ 									ifFalse:
+ 										[BytesPerWord = 4
- 	cogMethodSurrogateClass := BytesPerWord = 4
  											ifTrue: [CogMethodSurrogate32]
+ 											ifFalse: [CogMethodSurrogate64]].
- 											ifFalse: [CogMethodSurrogate64].
  	cogBlockMethodSurrogateClass := BytesPerWord = 4
  											ifTrue: [CogBlockMethodSurrogate32]
  											ifFalse: [CogBlockMethodSurrogate64]!

Item was added:
+ CogMethod subclass: #NewspeakCogMethod
+ 	instanceVariableNames: 'nextMethod'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: NewspeakCogMethod class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"self initialize"
+ 	(Smalltalk classNamed: #NewspeakCogMethodSurrogate32) ifNotNil:
+ 		[:cms32|
+ 		self checkGenerateSurrogate: cms32 bytesPerWord: 4].
+ 	(Smalltalk classNamed: #NewspeakCogMethodSurrogate64) ifNotNil:
+ 		[:cms64|
+ 		self checkGenerateSurrogate: cms64 bytesPerWord: 8]!

Item was added:
+ ----- Method: NewspeakCogMethod class>>structTypeName (in category 'translation') -----
+ structTypeName
+ 	^#CogMethod!

Item was added:
+ ----- Method: NewspeakCogMethod>>nextMethod (in category 'accessing') -----
+ nextMethod
+ 	"Answer the value of nextMethod"
+ 
+ 	^ nextMethod!

Item was added:
+ ----- Method: NewspeakCogMethod>>nextMethod: (in category 'accessing') -----
+ nextMethod: anObject
+ 	"Set the value of nextMethod"
+ 
+ 	^nextMethod := anObject!

Item was added:
+ CogMethodSurrogate32 subclass: #NewspeakCogMethodSurrogate32
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JITSimulation'!

Item was added:
+ ----- Method: NewspeakCogMethodSurrogate32 class>>alignedByteSize (in category 'accessing') -----
+ alignedByteSize
+ 	^28!

Item was added:
+ ----- Method: NewspeakCogMethodSurrogate32>>nextMethod (in category 'accessing') -----
+ nextMethod
+ 	| v |
+ 	^(v := memory unsignedLongAt: address + 25) ~= 0 ifTrue:
+ 		[cogit cCoerceSimple: v to: #'CogMethod *']!

Item was added:
+ ----- Method: NewspeakCogMethodSurrogate32>>nextMethod: (in category 'accessing') -----
+ nextMethod: aValue
+ 	^memory
+ 		unsignedLongAt: address + 25
+ 		put: ((aValue ifNotNil: [aValue asUnsignedInteger] ifNil: [0]))!

Item was added:
+ CogMethodSurrogate64 subclass: #NewspeakCogMethodSurrogate64
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JITSimulation'!

Item was added:
+ ----- Method: NewspeakCogMethodSurrogate64 class>>alignedByteSize (in category 'accessing') -----
+ alignedByteSize
+ 	^48!

Item was added:
+ ----- Method: NewspeakCogMethodSurrogate64>>nextMethod (in category 'accessing') -----
+ nextMethod
+ 	| v |
+ 	^(v := memory unsignedLongLongAt: address + 41) ~= 0 ifTrue:
+ 		[cogit cCoerceSimple: v to: #'CogMethod *']!

Item was added:
+ ----- Method: NewspeakCogMethodSurrogate64>>nextMethod: (in category 'accessing') -----
+ nextMethod: aValue
+ 	^memory
+ 		unsignedLongLongAt: address + 41
+ 		put: ((aValue ifNotNil: [aValue asUnsignedInteger] ifNil: [0]))!

Item was changed:
  ----- Method: StackInterpreter>>explicitOuterReceiver:withObject:withMixin: (in category 'newspeak bytecode support') -----
  explicitOuterReceiver: n withObject: anObject withMixin: mixin 
  	"This is used to implement the innards of the pushExplicitOuterReceiverBytecode,
  	 used for explicit outer sends in NS2/NS3.  "
  	| explicitReceiver mixinApplication  targetMixin  count |
  	
  	explicitReceiver := anObject.
  	targetMixin := mixin.
  	count := 0.
  	[count < n] whileTrue:
  		[count := count + 1.
  		(targetMixin = objectMemory nilObject or:[explicitReceiver = objectMemory nilObject]) ifTrue:
  			[^objectMemory nilObject].
  		mixinApplication := self
  								findApplicationOfTargetMixin: targetMixin
+ 								startingAtNonMetaClass: (objectMemory fetchClassOf: explicitReceiver).
- 								startingAtNonMetaClass: (self fetchClassOf: explicitReceiver).
  		mixinApplication = objectMemory nilObject ifTrue:
  			[^objectMemory nilObject]. "should never happen!!"
  		explicitReceiver := objectMemory fetchPointer: EnclosingObjectIndex ofObject: mixinApplication.	
  		targetMixin := objectMemory fetchPointer: EnclosingMixinIndex ofObject: targetMixin].
  	
  	^explicitReceiver!

Item was added:
+ ----- Method: VMClass class>>cogMethodClass: (in category 'translation') -----
+ cogMethodClass: options
+ 	^(options at: #NewspeakVM ifAbsent: [false])
+ 		ifTrue: [NewspeakCogMethod]
+ 		ifFalse: [CogMethod]!

Item was changed:
  ----- Method: VMStructType class>>checkGenerateFieldAccessors:bitPosition:in: (in category 'code generation') -----
  checkGenerateFieldAccessors: fieldSpecs bitPosition: firstBitPosition in: surrogateClass
  	| bitPosition alignedByteSize |
  	bitPosition := firstBitPosition.
  	fieldSpecs do:
  		[:spec| | code |
  		"If the accessor is already defined in a superclass don't redefine it in the subclass.
  		 We assume it is correctly defined in the superclass."
  		(spec first ~= #unused
  		 and: [(surrogateClass whichClassIncludesSelector: spec first asSymbol)
  				ifNil: [true]
  				ifNotNil: [:implementingClass|
  						self assert: (implementingClass inheritsFrom: Object).
  						implementingClass == surrogateClass]]) ifTrue:
  			[code := self getter: spec first
  						 bitPosition: bitPosition
  						 bitWidth: spec second
+ 						 type: (spec at: 3 ifAbsent: []).
- 						 bool: (spec at: 3 ifAbsent: []) = #Boolean.
  			 code ~= (surrogateClass sourceCodeAt: spec first asSymbol ifAbsent: ['']) asString ifTrue:
  				[surrogateClass compile: code classified: #accessing].
  			 code := self setter: spec first
  						 bitPosition: bitPosition
  						 bitWidth: spec second
+ 						 type: (spec at: 3 ifAbsent: []).
- 						 bool: (spec at: 3 ifAbsent: []) = #Boolean.
  			 code ~= (surrogateClass sourceCodeAt: (spec first, ':') asSymbol ifAbsent: ['']) asString ifTrue:
  				[surrogateClass compile: code classified: #accessing]].
  		bitPosition := bitPosition + spec second].
  	alignedByteSize := bitPosition / 8.
  	self assert: alignedByteSize isInteger.
  	alignedByteSize ~= surrogateClass alignedByteSize ifTrue:
  		[surrogateClass class
  			compile: 'alignedByteSize'
  					, (String with: Character cr with: Character tab with: $^)
  					, alignedByteSize printString
  			classified: #accessing]!

Item was changed:
  ----- Method: VMStructType class>>fieldAccessorsForBytesPerWord: (in category 'code generation') -----
  fieldAccessorsForBytesPerWord: bytesPerWord
  	| fieldSpecs |
  	fieldSpecs := OrderedCollection new.
  	self instVarNamesAndTypesForTranslationDo:
  		[:ivn :typeTuple| | index replacement |
  		(index := typeTuple indexOf: #BytesPerWord ifAbsent: 0) > 0
  			ifTrue:
  				[(typeTuple at: index + 1) = bytesPerWord ifTrue:
  					[replacement := typeTuple copyReplaceFrom: index to: index + 1 with: #().
  					 replacement size = 1 ifTrue:
  						[replacement := replacement first].
  					fieldSpecs add: { ivn. replacement }]]
  			ifFalse:
  				[fieldSpecs add: { ivn. typeTuple }]].
  	^fieldSpecs collect:
  		[:tuple|
  			[:ivn :typeTuple|
  			{ ('*unused*' match: ivn) ifTrue: [#unused] ifFalse: [ivn].
  			  (typeTuple isArray and: ['unsigned' = typeTuple first])
  				ifTrue:
  					[Integer readFrom: (typeTuple last readStream skipTo: $:; skipSeparators)]
  				ifFalse:
+ 					[typeTuple
+ 						caseOf: {
- 					[typeTuple caseOf: {
  								['unsigned char']	->	[8].
  								['unsigned short']	->	[16].
+ 								['unsigned int']		->	[32] }
+ 						otherwise: [bytesPerWord * 8]].
+ 			typeTuple isArray
+ 				ifTrue:
+ 					[(typeTuple size >= 3 and: [typeTuple second = #Boolean]) ifTrue:
+ 						[#Boolean]]
+ 				ifFalse:
+ 					[typeTuple last = $* ifTrue:
+ 						[(typeTuple beginsWith: 'struct _') "remove struct tag if any"
+ 							ifTrue: [(typeTuple allButFirst: 8) asSymbol]
+ 							ifFalse: [typeTuple]]] }] valueWithArguments: tuple]
- 								['unsigned int']		->	[32].
- 								['unsigned long']	->	[bytesPerWord * 8].
- 								['sqInt']				->	[bytesPerWord * 8].
- 								['usqInt']			->	[bytesPerWord * 8] }].
- 			(typeTuple isArray and: [typeTuple size >= 3 and: [typeTuple second = #Boolean]]) ifTrue:
- 				[#Boolean] }] valueWithArguments: tuple]
  
  	"#(4 8) collect: [:bpw| (CogBlockMethod fieldAccessorsForBytesPerWord: bpw) asArray]"
  	"#(4 8) collect: [:bpw| (CogMethod fieldAccessorsForBytesPerWord: bpw) asArray]"!

Item was removed:
- ----- Method: VMStructType class>>getter:bitPosition:bitWidth:bool: (in category 'code generation') -----
- getter: getter bitPosition: bitPosition bitWidth: bitWidth bool: isBool
- 	^String streamContents:
- 		[:s| | startByte endByte alignedPowerOf2 shift bool |
- 		startByte := bitPosition // 8.
- 		endByte := bitPosition + bitWidth - 1 // 8.
- 		shift := bitPosition \\ 8.
- 		alignedPowerOf2 := (#(8 16 32 64) includes: bitWidth) and: [shift = 0].
- 		s nextPutAll: getter; crtab: 1; nextPut: $^.
- 		isBool ifTrue:
- 			[s nextPut: $(].
- 		alignedPowerOf2 ifFalse:
- 			[s nextPut: $(].
- 		shift ~= 0 ifTrue:
- 			[s nextPut: $(].
- 		s nextPutAll: 'memory unsigned';
- 		   nextPutAll: (#('Byte' 'Short' 'Long' 'Long')
- 							at: endByte - startByte + 1
- 							ifAbsent: ['LongLong']);
- 		  nextPutAll: 'At: address + '; print: startByte + 1.
- 		shift ~= 0 ifTrue:
- 			[s nextPutAll: ') bitShift: -'; print: shift].
- 		alignedPowerOf2 ifFalse:
- 			[s nextPutAll: ') bitAnd: '; nextPutAll: ((1 << bitWidth) - 1) hex].
- 		isBool ifTrue:
- 			[s nextPutAll: ') ~= 0']]!

Item was added:
+ ----- Method: VMStructType class>>getter:bitPosition:bitWidth:type: (in category 'code generation') -----
+ getter: getter bitPosition: bitPosition bitWidth: bitWidth type: typeOrNil
+ 	^String streamContents:
+ 		[:s| | startByte endByte alignedPowerOf2 shift bool |
+ 		startByte := bitPosition // 8.
+ 		endByte := bitPosition + bitWidth - 1 // 8.
+ 		shift := bitPosition \\ 8.
+ 		alignedPowerOf2 := (#(8 16 32 64) includes: bitWidth) and: [shift = 0].
+ 		s nextPutAll: getter; crtab: 1.
+ 		(typeOrNil notNil and: [typeOrNil last = $*]) ifTrue:
+ 			[s nextPutAll: '| v |'; crtab: 1].
+ 		s nextPut: $^.
+ 		typeOrNil ifNotNil:
+ 			[s nextPut: $(.
+ 			 typeOrNil last = $* ifTrue:
+ 				[s nextPutAll: 'v := ']].
+ 		alignedPowerOf2 ifFalse:
+ 			[s nextPut: $(].
+ 		shift ~= 0 ifTrue:
+ 			[s nextPut: $(].
+ 		s nextPutAll: 'memory unsigned';
+ 		   nextPutAll: (#('Byte' 'Short' 'Long' 'Long')
+ 							at: endByte - startByte + 1
+ 							ifAbsent: ['LongLong']);
+ 		  nextPutAll: 'At: address + '; print: startByte + 1.
+ 		shift ~= 0 ifTrue:
+ 			[s nextPutAll: ') bitShift: -'; print: shift].
+ 		alignedPowerOf2 ifFalse:
+ 			[s nextPutAll: ') bitAnd: '; nextPutAll: ((1 << bitWidth) - 1) hex].
+ 		typeOrNil ifNotNil:
+ 			[s nextPutAll: ') ~= 0'.
+ 			typeOrNil last = $* ifTrue:
+ 				[s nextPutAll: ' ifTrue:';
+ 					crtab: 2;
+ 					nextPutAll: '[cogit cCoerceSimple: v to: ';
+ 					store: typeOrNil;
+ 					nextPut: $]]]]!

Item was removed:
- ----- Method: VMStructType class>>setter:bitPosition:bitWidth:bool: (in category 'code generation') -----
- setter: getter bitPosition: bitPosition bitWidth: bitWidth bool: isBool
- 	^String streamContents:
- 		[:s| | startByte endByte shift alignedPowerOf2 accessor mask expr |
- 		startByte := bitPosition // 8.
- 		endByte := bitPosition + bitWidth - 1 // 8.
- 		shift := bitPosition \\ 8.
- 		alignedPowerOf2 := (#(8 16 32 64) includes: bitWidth) and: [shift = 0].
- 		accessor := 'unsigned'
- 					, (#('Byte' 'Short' 'Long' 'Long')
- 							at: endByte - startByte + 1
- 							ifAbsent: ['LongLong'])
- 					, 'At: address + '.
- 		mask := #(16rFF 16rFFFF 16rFFFFFFFF 16rFFFFFFFF)
- 						at: endByte - startByte + 1
- 						ifAbsent: [(2 raisedTo: 64) - 1].
- 		s nextPutAll: getter; nextPutAll: ': aValue'.
- 		(isBool or: [alignedPowerOf2]) ifFalse:
- 			[s crtab: 1; nextPutAll: 'self assert: (aValue between: 0 and: '; nextPutAll:  ((1 << bitWidth) - 1) hex; nextPutAll: ').'].
- 		s crtab: 1.
- 		alignedPowerOf2 ifTrue:
- 			[s nextPut: $^].
- 		s nextPutAll: 'memory';
- 		  crtab: 2; nextPutAll: accessor; print: startByte + 1;
- 		  crtab: 2; nextPutAll: 'put: '.
- 		isBool ifTrue:
- 			[s nextPut: $(].
- 		alignedPowerOf2 ifFalse:
- 			[s nextPutAll: '((memory '; nextPutAll: accessor; print: startByte + 1;
- 			    nextPutAll: ') bitAnd: '; nextPutAll: (mask - ((1 << bitWidth - 1) << shift)) hex;
- 			    nextPutAll: ') + '].
- 		expr := isBool ifTrue: ['(aValue ifTrue: [1] ifFalse: [0])'] ifFalse: ['aValue'].
- 		shift = 0
- 			ifTrue:
- 				[s nextPutAll: expr]
- 			ifFalse:
- 				[s nextPut: $(; nextPutAll: expr; nextPutAll: ' bitShift: '; print: shift; nextPut: $)].
- 		isBool ifTrue:
- 			[s nextPut: $)].
- 		alignedPowerOf2 ifFalse:
- 			[s nextPut: $.; crtab: 1; nextPutAll: '^aValue']]!

Item was added:
+ ----- Method: VMStructType class>>setter:bitPosition:bitWidth:type: (in category 'code generation') -----
+ setter: getter bitPosition: bitPosition bitWidth: bitWidth type: typeOrNil
+ 	^String streamContents:
+ 		[:s| | startByte endByte shift alignedPowerOf2 accessor mask expr |
+ 		startByte := bitPosition // 8.
+ 		endByte := bitPosition + bitWidth - 1 // 8.
+ 		shift := bitPosition \\ 8.
+ 		alignedPowerOf2 := (#(8 16 32 64) includes: bitWidth) and: [shift = 0].
+ 		accessor := 'unsigned'
+ 					, (#('Byte' 'Short' 'Long' 'Long')
+ 							at: endByte - startByte + 1
+ 							ifAbsent: ['LongLong'])
+ 					, 'At: address + '.
+ 		mask := #(16rFF 16rFFFF 16rFFFFFFFF 16rFFFFFFFF)
+ 						at: endByte - startByte + 1
+ 						ifAbsent: [(2 raisedTo: 64) - 1].
+ 		s nextPutAll: getter; nextPutAll: ': aValue'.
+ 		(typeOrNil notNil or: [alignedPowerOf2]) ifFalse:
+ 			[s crtab: 1; nextPutAll: 'self assert: (aValue between: 0 and: '; nextPutAll:  ((1 << bitWidth) - 1) hex; nextPutAll: ').'].
+ 		s crtab: 1.
+ 		alignedPowerOf2 ifTrue:
+ 			[s nextPut: $^].
+ 		s nextPutAll: 'memory';
+ 		  crtab: 2; nextPutAll: accessor; print: startByte + 1;
+ 		  crtab: 2; nextPutAll: 'put: '.
+ 		typeOrNil ifNotNil:
+ 			[s nextPut: $(].
+ 		alignedPowerOf2 ifFalse:
+ 			[s nextPutAll: '((memory '; nextPutAll: accessor; print: startByte + 1;
+ 			    nextPutAll: ') bitAnd: '; nextPutAll: (mask - ((1 << bitWidth - 1) << shift)) hex;
+ 			    nextPutAll: ') + '].
+ 		expr := typeOrNil caseOf: {
+ 						[nil] -> ['aValue'].
+ 						[#Boolean] -> ['(aValue ifTrue: [1] ifFalse: [0])'] }
+ 					otherwise: ['(aValue ifNotNil: [aValue asUnsignedInteger] ifNil: [0])'].
+ 		shift = 0
+ 			ifTrue:
+ 				[s nextPutAll: expr]
+ 			ifFalse:
+ 				[s nextPut: $(; nextPutAll: expr; nextPutAll: ' bitShift: '; print: shift; nextPut: $)].
+ 		typeOrNil notNil ifTrue:
+ 			[s nextPut: $)].
+ 		alignedPowerOf2 ifFalse:
+ 			[s nextPut: $.; crtab: 1; nextPutAll: '^aValue']]!



More information about the Vm-dev mailing list