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

commits at source.squeak.org commits at source.squeak.org
Sat Nov 23 02:36:11 UTC 2013


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

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

Name: VMMaker.oscog-eem.518
Author: eem
Time: 22 November 2013, 6:32:05.641 pm
UUID: 47baf85e-eb07-401d-b604-8eeb30c62952
Ancestors: VMMaker.oscog-eem.517

Make sure dead code is not removed from plugin sources (if they're
shared they can't be prematurely optimized).

Fix compilation of Cog Spur VM.

Remove extraneous type decl from threadSchedulingLoop:.

Do a better job at generatign integer literals for flags.

Simple solution for endless ergeneration of exampleSqNamedPrims.h.

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

Item was changed:
  ----- Method: CCodeGenerator>>cLiteralFor: (in category 'C code generator') -----
  cLiteralFor: anObject
  	"Return a string representing the C literal value for the given object."
  	anObject isNumber
  		ifTrue:
  			[anObject isInteger ifTrue:
  				[| printString |
  				 printString := (anObject > 0
  								and: [(anObject >> anObject lowBit + 1) isPowerOfTwo
+ 								and: [(anObject highBit = anObject lowBit and: [anObject > 65536])
+ 									  or: [anObject highBit - anObject lowBit >= 4]]])
- 								and: [anObject highBit - anObject lowBit >= 4]])
  									ifTrue: ['0x', (anObject printStringBase: 16)]
  									ifFalse: [anObject printString].
  				^anObject > 16rFFFFFFFF
  						ifTrue: [printString, ObjectMemory unsignedLongLongSuffix]
  						ifFalse: [anObject < 16r7FFFFFFF
  							ifTrue: [printString]
  							ifFalse: [printString, ObjectMemory unsignedIntegerSuffix]]].
  			anObject isFloat ifTrue:
  				[^anObject printString]]
  		ifFalse:
  			[anObject isSymbol ifTrue:
  				[^self cFunctionNameFor: anObject].
  			anObject isString ifTrue:
  				[^'"', (anObject copyReplaceAll: (String with: Character cr) with: '\n') , '"'].
  			anObject == nil ifTrue: [^ 'null' ].
  			anObject == true ifTrue: [^ '1' ].
  			anObject == false ifTrue: [^ '0' ].
  			anObject isCharacter ifTrue:
  				[^anObject == $'
  					ifTrue: ['''\'''''] "i.e. '\''"
  					ifFalse: [anObject asString printString]]].
  	self error: 'Warning: A Smalltalk literal could not be translated into a C constant: ', anObject printString.
  	^'"XXX UNTRANSLATABLE CONSTANT XXX"'!

Item was changed:
  ----- Method: CoInterpreterMT>>threadSchedulingLoop: (in category 'vm scheduling') -----
  threadSchedulingLoop: vmThread
  	"Enter a loop attempting to run the VM with the highest priority process and
  	 blocking on the thread's OS semaphore when unable to run that process.
  	 We will return to this via threadSwitchIfNecessary:from: which is called in the
  	 middle of transferTo:from: once the active process has been stored in the scheduler."
  	<var: #vmThread type: #'CogVMThread *'>
  	| attemptToRun |
- 	<var: #dvmt type: #'CogVMThread *'>
  	<inline: false>
  	[self assert: vmThread state = CTMAssignableOrInVM.
  	 attemptToRun := false.
  	 (cogThreadManager getVMOwner = vmThread index)
  		ifTrue: [attemptToRun := true]
  		ifFalse:
  			[(cogThreadManager tryLockVMToIndex: vmThread index) ifTrue:
  				["If relinquishing is true, then primitiveRelinquishProcessor has disowned the
  				  VM and only a returning call or callback should take ownership in that case."
  				 relinquishing
  					ifTrue: [cogThreadManager releaseVM]
  					ifFalse: [attemptToRun := true]]].
  	 attemptToRun ifTrue:
  		[self tryToExecuteSmalltalk: vmThread].
  	 (cogThreadManager testVMOwnerIs: vmThread index) ifFalse:
  		[cogThreadManager waitForWork: vmThread].
  	 true] whileTrue!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreSourceReg:slotIndex:destReg:scratchReg: (in category 'compile abstract instructions') -----
  genStoreSourceReg: sourceReg slotIndex: index destReg: destReg scratchReg: scratchReg
  	| jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRemembered mask rememberedBitByteOffset |
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jmpDestYoung type: #'AbstractInstruction *'>
  	<var: #jmpSourceOld type: #'AbstractInstruction *'>
  	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
  	"do the store"
  	cogit MoveR: sourceReg
  		   Mw: index * objectMemory wordSize + objectMemory baseHeaderSize
  		   r: destReg.
  	"now the check.  Is value stored an integer?  If so we're done"
  	cogit MoveR: sourceReg R: scratchReg.
  	cogit AndCq: objectMemory tagMask R: scratchReg.
  	jmpImmediate := cogit JumpNonZero: 0.
  	"Get the old/new boundary in scratchReg"
+ 	cogit MoveCw: objectMemory storeCheckBoundary R: scratchReg.
- 	cogit MoveCw: objectMemory newSpaceLimit R: scratchReg.
  	"Is target young?  If so we're done"
  	cogit CmpR: scratchReg R: destReg. "N.B. FLAGS := destReg - scratchReg"
  	jmpDestYoung := cogit JumpBelow: 0.
  	"Is value stored old?  If so we're done."
  	cogit CmpR: scratchReg R: sourceReg. "N.B. FLAGS := sourceReg - scratchReg"
  	jmpSourceOld := cogit JumpAboveOrEqual: 0.
  	"value is young and target is old.
  	 Need to remember this only if the remembered bit is not already set.
  	 Test the remembered bit.  Only need to fetch the byte containing it,
  	 which reduces the size of the mask constant."
  	rememberedBitByteOffset := jmpSourceOld isBigEndian
  									ifTrue: [objectMemory baseHeaderSize - 1 - (objectMemory rememberedBitShift // 8)]
  									ifFalse:[objectMemory rememberedBitShift // 8].
  	mask := 1 << (objectMemory rememberedBitShift \\ 8).
  	"N.B. MoveMb:r:R: does not zero other bits"
  	cogit MoveMb: rememberedBitByteOffset r: destReg R: scratchReg.
  	cogit AndCq: mask R: scratchReg.
  	jmpAlreadyRemembered := cogit JumpNonZero: 0.
  	"Remembered bit is not set.  Call store check to insert dest into remembered table."
  	self assert: destReg == ReceiverResultReg.
  	cogit CallRT: ceStoreCheckTrampoline.
  	jmpImmediate jmpTarget:
  	(jmpDestYoung jmpTarget:
  	(jmpSourceOld jmpTarget:
  	(jmpAlreadyRemembered jmpTarget:
  		cogit Label))).
  	^0!

Item was added:
+ ----- Method: InterpreterPlugin class>>shouldGenerateDeadCode (in category 'translation') -----
+ shouldGenerateDeadCode
+ 	"Answer if the code generator should generate dead code, e.g. in false ifTrue: [dead] ifFalse: [live].
+ 	 Since plugin source is shared between different VM builds it is unsafe to assume any code is dead."
+ 
+ 	^true!

Item was changed:
  ----- Method: SpurMemoryManager>>newSpaceLimit (in category 'accessing') -----
  newSpaceLimit
+ 	<cmacro: '() GIV(newSpaceLimit)'>
- 	<api>
  	^newSpaceLimit!

Item was changed:
  ----- Method: SpurMemoryManager>>oldSpaceStart (in category 'accessing') -----
  oldSpaceStart
+ 	<cmacro: '() GIV(oldSpaceStart)'>
  	^oldSpaceStart!

Item was added:
+ ----- Method: SpurMemoryManager>>storeCheckBoundary (in category 'accessing') -----
+ storeCheckBoundary
+ 	"A renaming for the Cogit, which couldn't make sense of GIV(newSpaceLimit)"
+ 	<api>
+ 	^newSpaceLimit!

Item was changed:
  ----- Method: VMMaker>>generateExportsFile (in category 'exports') -----
  generateExportsFile
  	"Store the exports on the given file"
  	| cg contents filePath fileStream |
+ 	filePath := self interpreterExportsFilePath.
+ 	"don't bother endlessly regenerating the example file."
+ 	(internalPlugins isEmpty
+ 	 and: [(filePath includesSubString: 'example')
+ 	 and: [FileDirectory default fileExists: filePath]]) ifTrue:
+ 		[^self].
  	cg := self createCodeGenerator.
  	cg vmClass: self interpreterClass.
  	contents := String streamContents:
  		[:s|
  		s
  			nextPutAll:'/* This is an automatically generated table of all builtin modules in the VM';
  			cr;
  			next: 3 put: Character space;
  			nextPutAll: (cg shortMonticelloDescriptionForClass: cg vmClass);
  			cr;
  			nextPutAll:' */';
  			cr.
  		s cr; nextPutAll:'extern sqExport vm_exports[];'.
  		s cr; nextPutAll: 'extern sqExport os_exports[];'.
  		self internalPluginsDo:[:cls|
  			s cr; nextPutAll: 'extern sqExport '; nextPutAll: cls moduleName; nextPutAll:'_exports[];'.
  		].
  		s cr.
  
  		s cr; nextPutAll:'sqExport *pluginExports[] = {'.
  		s crtab; nextPutAll:'vm_exports,'.
  		s crtab; nextPutAll: 'os_exports,'.
  		self internalPluginsDo:[:cls|
  			s crtab; nextPutAll: cls moduleName; nextPutAll:'_exports,'
  		].
  		s crtab; nextPutAll:'NULL'.
  		s cr; nextPutAll:'};'; cr].
- 	filePath := self interpreterExportsFilePath.
  	(cg needToGenerateHeader: (FileDirectory baseNameFor: filePath) file: filePath contents: contents) ifTrue:
  		[[fileStream := VMMaker forceNewFileNamed: filePath] 
  			on: FileDoesNotExistException 
  			do:[^self couldNotOpenFile: filePath].
  		 fileStream nextPutAll: contents; close]!



More information about the Vm-dev mailing list