[Vm-dev] VM Maker: VMMaker.oscog-EstebanLorenzano.1326.mcz

commits at source.squeak.org commits at source.squeak.org
Tue May 26 13:31:09 UTC 2015


Esteban Lorenzano uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-EstebanLorenzano.1326.mcz

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

Name: VMMaker.oscog-EstebanLorenzano.1326
Author: EstebanLorenzano
Time: 26 May 2015, 3:29:25.646752 pm
UUID: 8979417d-cdd7-4f86-9439-d474c595e021
Ancestors: VMMaker.oscog-eem.1325

StackInterpreterSimulator>>#veryDeepCopyWith: just work if working inside a Spur image, and Pharo is still not ready to do that.
Added a check to ensure it works. 

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

Item was changed:
+ SystemOrganization addCategory: #VMMaker!
+ SystemOrganization addCategory: 'VMMaker-Building'!
+ SystemOrganization addCategory: 'VMMaker-Interpreter'!
+ SystemOrganization addCategory: 'VMMaker-InterpreterSimulation'!
+ SystemOrganization addCategory: 'VMMaker-InterpreterSimulation-Morphic'!
+ SystemOrganization addCategory: 'VMMaker-JIT'!
+ SystemOrganization addCategory: 'VMMaker-JITSimulation'!
+ SystemOrganization addCategory: 'VMMaker-Multithreading'!
+ SystemOrganization addCategory: 'VMMaker-Plugins'!
+ SystemOrganization addCategory: 'VMMaker-Plugins-Alien'!
+ SystemOrganization addCategory: 'VMMaker-Plugins-IOS'!
+ SystemOrganization addCategory: 'VMMaker-PostProcessing'!
+ SystemOrganization addCategory: 'VMMaker-SmartSyntaxPlugins'!
+ SystemOrganization addCategory: 'VMMaker-SpurMemoryManager'!
+ SystemOrganization addCategory: 'VMMaker-SpurMemoryManagerSimulation'!
+ SystemOrganization addCategory: 'VMMaker-Support'!
+ SystemOrganization addCategory: 'VMMaker-Tests'!
+ SystemOrganization addCategory: 'VMMaker-Translation to C'!
- SystemOrganization addCategory: #'VMMaker-Building'!
- SystemOrganization addCategory: #'VMMaker-Interpreter'!
- SystemOrganization addCategory: #'VMMaker-InterpreterSimulation'!
- SystemOrganization addCategory: #'VMMaker-InterpreterSimulation-Morphic'!
- SystemOrganization addCategory: #'VMMaker-JIT'!
- SystemOrganization addCategory: #'VMMaker-JITSimulation'!
- SystemOrganization addCategory: #'VMMaker-Multithreading'!
- SystemOrganization addCategory: #'VMMaker-Plugins'!
- SystemOrganization addCategory: #'VMMaker-Plugins-Alien'!
- SystemOrganization addCategory: #'VMMaker-Plugins-IOS'!
- SystemOrganization addCategory: #'VMMaker-PostProcessing'!
- SystemOrganization addCategory: #'VMMaker-SmartSyntaxPlugins'!
- SystemOrganization addCategory: #'VMMaker-SpurMemoryManager'!
- SystemOrganization addCategory: #'VMMaker-SpurMemoryManagerSimulation'!
- SystemOrganization addCategory: #'VMMaker-Support'!
- SystemOrganization addCategory: #'VMMaker-Tests'!
- SystemOrganization addCategory: #'VMMaker-Translation to C'!

Item was changed:
  ----- Method: CCodeGenerator>>storeAPIExportHeader:OnFile: (in category 'public') -----
  storeAPIExportHeader: headerName OnFile: fullHeaderPath
  	"Store C header code on the given file. Evaluate
  	 aBlock with the stream to generate its contents."
  
  	| header |
  	header := String streamContents:
  				[:s|
  				 s nextPutAll: (self fileHeaderVersionStampForSourceClass: nil); cr.
  				 self emitCAPIExportHeaderOn: s].
  	(self needToGenerateHeader: headerName file: fullHeaderPath contents: header) ifTrue:
  		[self storeHeaderOnFile: fullHeaderPath contents: header]!

Item was changed:
  ----- Method: CCodeGenerator>>storeHeaderOnFile:contents: (in category 'public') -----
  storeHeaderOnFile: fileName contents: contents
  	"Store C header code on the given file. Evaluate
  	 aBlock with the stream to generate its contents."
  
  	| aStream |
  	aStream := VMMaker forceNewFileNamed: fileName.
  	aStream ifNil: [Error signal: 'Could not open C header file: ', fileName].
  	[(contents beginsWith: '/* Automatic') ifFalse:
  		[aStream nextPutAll: (self fileHeaderVersionStampForSourceClass: nil); cr].
  	 aStream nextPutAll: contents]
  		ensure: [aStream close]!

Item was changed:
  ----- Method: CCodeGenerator>>structClassesForTranslationClasses: (in category 'utilities') -----
  structClassesForTranslationClasses: classes
  	"Answer in superclass order (any superclass precedes any subclass)
  	 the ancilliaryClasses that are struct classes for all the given classes."
  	| theStructClasses |
  	theStructClasses := OrderedCollection new.
  	classes do:
  		[:aTranslationClass|
  		([aTranslationClass ancilliaryClasses: self options]
  				on: MessageNotUnderstood
  				do: [:ex|
  					ex message selector == #ancilliaryClasses:
  						ifTrue: [#()]
  						ifFalse: [ex pass]]) do:
  			[:class|
  			(class isStructClass
  			 and: [(vmClass isNil or: [vmClass isAcceptableAncilliaryClass: class])
  			 and: [(theStructClasses includes: class) not]]) ifTrue:
  				[theStructClasses addLast: class]]].
  	^ChangeSet superclassOrder: theStructClasses!

Item was changed:
  ----- Method: CogARMCompiler>>sub:rn:imm:ror: (in category 'ARM convenience instructions') -----
  sub: destReg rn: srcReg imm: immediate ror: rot
  "	Remember the ROR is doubled by the cpu so use 30>>1 etc
  	SUB destReg, srcReg, #immediate ROR rot"
  
  	^self type: 1 op: SubOpcode set: 0 rn: srcReg rd: destReg shifterOperand: ((rot>>1) <<8 bitOr: immediate)!

Item was changed:
  ----- Method: CogMethodSurrogate32 class>>alignedByteSize (in category 'accessing') -----
  alignedByteSize
  	^20 + self baseHeaderSize!

Item was changed:
  ----- Method: CogMethodSurrogate64 class>>alignedByteSize (in category 'accessing') -----
  alignedByteSize
  	^32 + self baseHeaderSize!

Item was changed:
  ----- Method: Integer>>asUnsignedInteger (in category '*VMMaker-interpreter simulator') -----
  asUnsignedInteger
  	self assert: self >= 0.
  	^self!

Item was changed:
  ----- Method: InterpreterPlugin class>>shouldBeTranslated (in category 'translation') -----
  shouldBeTranslated
  "is this class intended to be translated as a plugin? Most subclasses should answer true, but some such as:-
  	TestInterpreterPlugin
  	FlippArrayPlugin2
  	InflatePlugin
  	should answer false for various reasons."
  	^true!

Item was changed:
  ----- Method: InterpreterPlugin class>>shouldBeTranslatedFor: (in category 'translation') -----
  shouldBeTranslatedFor: platformName
  	"Is this class intended to be translated as a plugin, perhaps specific to a platform?
  	 Most subclasses should answer true, but some such as simulation-only versions
  	 should answer false for various reasons."
  	^self shouldBeTranslated!

Item was changed:
  ----- Method: InterpreterProxy>>isImmediate: (in category 'testing') -----
  isImmediate: anObject
  	<option: #(atLeastVMProxyMajor:minor: 1 13)>
  	^StackInterpreter objectMemoryClass isImmediate: anObject!

Item was changed:
  ----- Method: SpurGenerationScavenger>>copyAndForward: (in category 'scavenger') -----
  copyAndForward: survivor
  	"copyAndForward: survivor copies a survivor object either to
  	 futureSurvivorSpace or, if it is to be promoted, to oldSpace.
  	 It leaves a forwarding pointer behind.  If the object is weak
  	 then corpse is threaded onto the weakList for later treatment."
  	<inline: false>
  	| bytesInObj format tenure newLocation |
  	self assert: ((manager isInEden: survivor) "cog methods should be excluded."
  				or: [manager isInPastSpace: survivor]).
  	bytesInObj := manager bytesInObject: survivor.
  	format := manager formatOf: survivor.
  	tenure := self shouldBeTenured: survivor. "Allow Slang to inline."
  	newLocation := (tenure or: [futureSurvivorStart + bytesInObj > futureSpace limit])
  						ifTrue: [self copyToOldSpace: survivor bytes: bytesInObj format: format]
  						ifFalse: [self copyToFutureSpace: survivor bytes: bytesInObj].
  	manager forwardSurvivor: survivor to: newLocation.
  	"if weak or ephemeron add to the relevant list for subsequent scanning."
  	(manager isWeakFormat: format) ifTrue:
  		[self addToWeakList: survivor].
  	((manager isEphemeronFormat: format)
  	 and: [(self isScavengeSurvivor: (manager keyOfEphemeron: newLocation)) not]) ifTrue:
  		[self addToEphemeronList: survivor].
  	^newLocation!

Item was changed:
  ----- Method: SpurMemoryManager>>isForwarded: (in category 'object testing') -----
  isForwarded: objOop
  	"Answer if objOop is that if a forwarder.  Take advantage of isForwardedObjectClassIndexPun
  	 being a power of two to generate a more efficient test than the straight-forward
  		(self classIndexOf: objOop) = self isForwardedObjectClassIndexPun
  	 at the cost of this being ambiguous with free chunks.  So either never apply this to free chunks
  	 or guard with (self isFreeObject: foo) not.  So far the idiom has been to guard with isFreeObject:"
  	<api>
  	<inline: true>
  	"self assert: (self isFreeObject: objOop) not."
  	^(self longAt: objOop) noMask: self classIndexMask - self isForwardedObjectClassIndexPun!

Item was changed:
  ----- Method: StackInterpreter>>codeGeneratorToComputeAccessorDepth (in category 'primitive support') -----
  codeGeneratorToComputeAccessorDepth
  	^VMMaker new
  		buildCodeGeneratorForInterpreter: self class primitivesClass
  		includeAPIMethods: false
  		initializeClasses: false!

Item was changed:
  ----- Method: StackInterpreter>>primitiveIndexOfMethod:header: (in category 'compiled methods') -----
  primitiveIndexOfMethod: theMethod header: methodHeader
  	"Note: With the Squeak V0 format we now have 10 bits of primitive index, but they are in
  	 two places for temporary backward compatibility.  The time to unpack is negligible,
  	 since the derived primitive function pointer is stored in the method cache.  With the new
  	 format we assume a 3-byte CallPrimitive with a little-endian 16-bit primitive index."
  	<api>
  	<inline: true>
  	| firstBytecode |
  	^objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[(self alternateHeaderHasPrimitiveFlag: methodHeader)
  				ifTrue:
  					[firstBytecode := self firstBytecodeOfAlternateHeader: methodHeader method: theMethod.
  					 (objectMemory byteAt: firstBytecode + 1) + ((objectMemory byteAt: firstBytecode + 2) << 8)]
  				ifFalse:
  					[0]]
  		ifFalse:
  			[MULTIPLEBYTECODESETS
  				ifTrue:
  					[(self headerIndicatesAlternateBytecodeSet: methodHeader)
  						ifTrue:
  							[(self alternateHeaderHasPrimitiveFlag: methodHeader)
  								ifTrue:
  									[firstBytecode := self firstBytecodeOfAlternateHeader: methodHeader method: theMethod.
  									 (objectMemory byteAt: firstBytecode + 1) + ((objectMemory byteAt: firstBytecode + 2) << 8)]
  								ifFalse:
  									[0]]
  						ifFalse:
  							[| primBits |
  							 primBits := objectMemory integerValueOf: methodHeader.
  							 (primBits bitAnd: 16r1FF) + (primBits >> 19 bitAnd: 16r200)]]
  				ifFalse:
  					[| primBits |
  					 primBits := objectMemory integerValueOf: methodHeader.
  					 (primBits bitAnd: 16r1FF) + (primBits >> 19 bitAnd: 16r200)]]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>runAtEachStep: (in category 'testing') -----
  runAtEachStep: aBlock
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[true] whileTrue:
  		[self assertValidExecutionPointers.
  		 aBlock value: currentBytecode.
  		 self dispatchOn: currentBytecode in: BytecodeTable.
  		 self incrementByteCount].
  	localIP := localIP - 1.
  	"undo the pre-increment of IP before returning"
  	self externalizeIPandSP!

Item was changed:
  ----- Method: StackInterpreterSimulator>>veryDeepCopyWith: (in category 'debug support') -----
  veryDeepCopyWith: deepCopier
  	"Override to short-circuit the copying of any VMPluginCodeGenerators referenced from mappedPluginEntries.
  	 These can in turn hold onto Monticello state, resulting in a huge ammount of unnecessary copying."
+ 	self objectMemory hasSpurMemoryManagerAPI ifTrue: 
+ 		[deepCopier references
+ 			at: mappedPluginEntries ifAbsentPut: [mappedPluginEntries].
+ 		mappedPluginEntries do:
+ 			[:tuple|
+ 			[:sim :sel :block :argCount|
+ 			deepCopier references at: block ifAbsentPut: [block]] valueWithArguments: tuple]].
- 	deepCopier references
- 		at: mappedPluginEntries ifAbsentPut: [mappedPluginEntries].
- 	mappedPluginEntries do:
- 		[:tuple|
- 		[:sim :sel :block :argCount|
- 		deepCopier references at: block ifAbsentPut: [block]] valueWithArguments: tuple].
  	^super veryDeepCopyWith: deepCopier!

Item was changed:
  ----- Method: TAssignmentNode>>emitCCodeAsExpressionOn:level:generator: (in category 'C code generation') -----
  emitCCodeAsExpressionOn: aStream level: level generator: aCodeGen
  	aStream nextPut: $(.
  	self emitCCodeOn: aStream level: level generator: aCodeGen.
  	aStream nextPut: $)!

Item was changed:
  ----- Method: TParseNode>>emitCCodeAsArgumentOn:level:generator: (in category 'C code generation') -----
  emitCCodeAsArgumentOn: aStream level: level generator: aCodeGen
  	^self emitCCodeOn: aStream level: level generator: aCodeGen!

Item was changed:
  ----- Method: TParseNode>>emitCCodeAsExpressionOn:level:generator: (in category 'C code generation') -----
  emitCCodeAsExpressionOn: aStream level: level generator: aCodeGen
  	^self emitCCodeOn: aStream level: level generator: aCodeGen!

Item was changed:
  ----- Method: TSendNode>>emitCCodeAsExpressionOn:level:generator: (in category 'C code generation') -----
  emitCCodeAsExpressionOn: aStream level: level generator: aCodeGen
  	^self emitCCodeAsArgumentOn: aStream level: level generator: aCodeGen!

Item was changed:
  ----- Method: VMClass class>>initializePrimitiveErrorCodes (in category 'initialization') -----
  initializePrimitiveErrorCodes
  	"Define the VM's primitive error codes.  N.B. these are
  	 replicated in platforms/Cross/vm/sqVirtualMachine.h."
  	"VMClass initializePrimitiveErrorCodes"
  	| pet |
  	PrimErrTableIndex := 51. "Zero-relative"
  	"See SmalltalkImage>>recreateSpecialObjectsArray for the table definition.
  	 If the table exists and is large enough the corresponding entry is returned as
  	 the primitive error, otherwise the error is answered numerically."
  	pet := Smalltalk specialObjectsArray at: PrimErrTableIndex + 1 ifAbsent: [#()].
  	pet isArray ifFalse: [pet := #()].
  	PrimNoErr := 0. "for helper methods that need to answer success or an error code."
  	PrimErrGenericFailure		:= pet indexOf: nil ifAbsent: 1.
  	PrimErrBadReceiver			:= pet indexOf: #'bad receiver' ifAbsent: 2.
  	PrimErrBadArgument		:= pet indexOf: #'bad argument' ifAbsent: 3.
  	PrimErrBadIndex			:= pet indexOf: #'bad index' ifAbsent: 4.
  	PrimErrBadNumArgs		:= pet indexOf: #'bad number of arguments' ifAbsent: 5.
  	PrimErrInappropriate		:= pet indexOf: #'inappropriate operation' ifAbsent: 6.
  	PrimErrUnsupported		:= pet indexOf: #'unsupported operation' ifAbsent: 7.
  	PrimErrNoModification		:= pet indexOf: #'no modification' ifAbsent: 8.
  	PrimErrNoMemory			:= pet indexOf: #'insufficient object memory' ifAbsent: 9.
  	PrimErrNoCMemory			:= pet indexOf: #'insufficient C memory' ifAbsent: 10.
  	PrimErrNotFound			:= pet indexOf: #'not found' ifAbsent: 11.
  	PrimErrBadMethod			:= pet indexOf: #'bad method' ifAbsent: 12.
  	PrimErrNamedInternal		:= pet indexOf: #'internal error in named primitive machinery' ifAbsent: 13.
  	PrimErrObjectMayMove		:= pet indexOf: #'object may move' ifAbsent: 14.
  	PrimErrLimitExceeded		:= pet indexOf: #'resource limit exceeded' ifAbsent: 15.
  	PrimErrObjectIsPinned		:= pet indexOf: #'object is pinned' ifAbsent: 16.
  	PrimErrWritePastObject	:= pet indexOf: #'primitive write beyond end of object' ifAbsent: 17!



More information about the Vm-dev mailing list