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

commits at source.squeak.org commits at source.squeak.org
Sat Aug 17 21:33:22 UTC 2013


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

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

Name: VMMaker.oscog-eem.327
Author: eem
Time: 17 August 2013, 2:30:43.831 pm
UUID: 29b87ba8-cc32-406e-9698-6c022ab7abbd
Ancestors: VMMaker.oscog-eem.326

Fix StackToRegisterMappingCogit>>genPrimitiveClass for case where
numArgs > 0 (must use other than ReceiverResultReg, e.g. objectClass:).

Improve register usage in genSpecialSelectorClass.

Save & restore methodOrBlockNumTemps in compileBlockBodies for symmetry
with needsFrame & methodOrBlockNumArgs.

Fix disassembly of methods with blocks (avoid printing block dispatch twice).

Delete CoInterpreter class>>initialize; it breaks the simulator.

Fix disassembly of e.g. Character literals when using in-image compilation.

Slang: fix formatting of WhileForeverBreakIf loops.

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

Item was changed:
  ----- Method: CCodeGenerator>>generateWhileForeverBreakIf:loop:on:indent: (in category 'C translation') -----
  generateWhileForeverBreakIf: breakBoolean loop: msgNode on: aStream indent: level
  	"Generate either of
  		while(1) {stmtListA; if(cond) break; stmtListB}
  		while(1) {stmtListA; if(!!(cond)) break; stmtListB}."
  
  	| testStmt receiverWithoutTest |
+ 	aStream peekLast ~~ Character tab ifTrue:
+ 		[aStream tab: level - 1].
+ 	aStream nextPutAll: 'while (1) {'; cr.
- 	aStream tab: level - 1; nextPutAll: 'while (1) {'; cr.
  	testStmt := msgNode receiver statements last.
  	receiverWithoutTest := TStmtListNode new setStatements: msgNode receiver statements allButLast.
  	receiverWithoutTest emitCCodeOn: aStream level: level + 1 generator: self.
  	aStream tab: level + 1; nextPutAll: 'if ('.
  	breakBoolean ifFalse: [aStream nextPut: $!!; nextPut: $(].
  	testStmt emitCCodeOn: aStream level: 0 generator: self.
  	breakBoolean ifFalse: [aStream nextPut: $)].
  	aStream nextPutAll: ') break;'; cr.
  	msgNode args first emitCCodeOn: aStream level: level + 1 generator: self.
  	aStream tab: level; nextPut: $}!

Item was removed:
- ----- Method: CoInterpreter class>>initialize (in category 'class initialization') -----
- initialize
- 	"This is for Monticello package loading"
- 	self initializeWithOptions: Dictionary new!

Item was changed:
  ----- Method: Cogit>>codeRangesFor: (in category 'disassembly') -----
  codeRangesFor: cogMethod
  	"Answer a sequence of ranges of code for the main method and all of the blocks in a CogMethod.
  	 N.B.  These are in order of block dispatch, _not_ necessarily address order in the method."
  	<doNotGenerate>
  	| pc end blockEntry starts |
  	cogMethod cmType = CMClosedPIC ifTrue:
  		[end := (self addressOfEndOfCase: cogMethod cPICNumCases - 1 inCPIC: cogMethod) + cPICEndSize.
  		 ^{ CogCodeRange
  				from: cogMethod asInteger + (self sizeof: CogMethod)
  				to: end
  				cogMethod: cogMethod
  				startpc: nil }].
  	end := (self mapEndFor: cogMethod) - 1.
  	cogMethod blockEntryOffset = 0 ifTrue:
  		[^{ CogCodeRange
  				from: cogMethod asInteger + (self sizeof: CogMethod)
  				to: end
  				cogMethod: cogMethod
  				startpc: (coInterpreter startPCOfMethodHeader: cogMethod methodHeader) }].
  	pc := blockEntry := cogMethod blockEntryOffset + cogMethod asInteger.
  	starts := OrderedCollection with: cogMethod.
  	[pc < end] whileTrue:
  		[| targetpc |
  		 targetpc := blockEntry.
  		 (backEnd isJumpAt: pc) ifTrue:
  			[targetpc := backEnd jumpTargetPCAt: pc.
  			 targetpc < blockEntry ifTrue:
  				[starts add: (self cCoerceSimple: targetpc - (self sizeof: CogBlockMethod) to: #'CogBlockMethod *')]].
  		 pc := pc + (backEnd instructionSizeAt: pc)].
  	starts := starts asSortedCollection.
  	^(1 to: starts size + 1) collect:
  		[:i| | cogSubMethod nextpc |
  		i <= starts size
  			ifTrue:
  				[cogSubMethod := starts at: i.
+ 				 nextpc := i < starts size ifTrue: [(starts at: i + 1) address] ifFalse: [blockEntry].
- 				 nextpc := i < starts size ifTrue: [(starts at: i + 1) address] ifFalse: [end].
  				 CogCodeRange
  					from: cogSubMethod address + (self sizeof: cogSubMethod)
  					to: nextpc - 1
  					cogMethod: cogSubMethod
  					startpc: (i = 1
  								ifTrue: [coInterpreter startPCOfMethodHeader: cogMethod methodHeader]
  								ifFalse: [cogSubMethod startpc])]
  			ifFalse:
  				[CogCodeRange
  					from: blockEntry
  					to: end]]!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>lookupAddress: (in category 'labels') -----
  lookupAddress: address
+ 	| thing |
+ 	thing := objectMap
- 	^(objectMap
- 		keyAtValue: address
- 		ifAbsent:
- 			[variables
  				keyAtValue: address
+ 				ifAbsent:
+ 					[variables
+ 						keyAtValue: address
+ 						ifAbsent: [^nil]].
+ 	^thing isLiteral
+ 		ifTrue: [thing storeString]
+ 		ifFalse: [thing asString]!
- 				ifAbsent: [^nil]]) asString!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>compileBlockBodies (in category 'compile abstract instructions') -----
  compileBlockBodies
  	"override to maintain counterIndex when recompiling blocks; sigh."
  	<inline: false>
+ 	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs savedNumTemps
- 	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs
  	  initialStackPtr initialOpcodeIndex initialAnnotationIndex initialCounterIndex |
  	<var: #blockStart type: #'BlockStart *'>
  	self assert: blockCount > 0.
  	"scanBlock: in compileBlockEntry: sets both of these appropriately for each block."
  	savedNeedsFrame := needsFrame.
  	savedNumArgs := methodOrBlockNumArgs.
+ 	savedNumTemps := methodOrBlockNumTemps.
  	inBlock := true.
  	compiledBlocksCount := 0.
  	[compiledBlocksCount < blockCount] whileTrue:
  		[blockStart := self blockStartAt: compiledBlocksCount.
  		 self scanBlock: blockStart.
  		 initialOpcodeIndex := opcodeIndex.
  		 initialAnnotationIndex := annotationIndex.
  		 initialCounterIndex := counterIndex.
  		 [self compileBlockEntry: blockStart.
  		  initialStackPtr := simStackPtr.
  		  (result := self compileAbstractInstructionsFrom: blockStart startpc + ((self pushNilSize: methodObj) * blockStart numInitialNils)
  						through: blockStart startpc + blockStart span - 1) < 0 ifTrue:
  			[^result].
  		  "If the final simStackPtr is less than the initial simStackPtr then scanBlock: over-
  		   estimated the number of initial nils (because it assumed one or more pushNils to
  		   produce an operand were pushNils to initialize temps.  This is very rare, so
  		   compensate by checking, adjusting numInitialNils and recompiling the block body."
  		  initialStackPtr = simStackPtr]
  			whileFalse:
  				[self assert: initialStackPtr > simStackPtr.
  				 blockStart numInitialNils: blockStart numInitialNils + simStackPtr - initialStackPtr.
  				 blockStart fakeHeader dependent: nil.
  				 self reinitializeFixupsFrom: blockStart startpc + blockStart numInitialNils
  					through: blockStart startpc + blockStart span - 1.
  				 self reinitializeCountersFrom: initialCounterIndex to: counterIndex - 1.
  				 self cCode: 'bzero(abstractOpcodes + initialOpcodeIndex,
  									(opcodeIndex - initialOpcodeIndex) * sizeof(AbstractInstruction))'
  					inSmalltalk: [initialOpcodeIndex to: opcodeIndex - 1 do:
  									[:i|
  									abstractOpcodes
  										at: i
  										put: (processor abstractInstructionCompilerClass for: self)]].
  				 opcodeIndex := initialOpcodeIndex.
  				 annotationIndex := initialAnnotationIndex.
  				 counterIndex := initialCounterIndex].
  		compiledBlocksCount := compiledBlocksCount + 1].
  	needsFrame := savedNeedsFrame.
  	methodOrBlockNumArgs := savedNumArgs.
+ 	methodOrBlockNumTemps := savedNumTemps.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>compileBlockBodies (in category 'compile abstract instructions') -----
  compileBlockBodies
  	<inline: false>
+ 	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs savedNumTemps
+ 	  initialStackPtr initialOpcodeIndex initialAnnotationIndex |
- 	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs initialStackPtr initialOpcodeIndex initialAnnotationIndex |
  	<var: #blockStart type: #'BlockStart *'>
  	self assert: blockCount > 0.
  	"scanBlock: in compileBlockEntry: sets both of these appropriately for each block."
  	savedNeedsFrame := needsFrame.
  	savedNumArgs := methodOrBlockNumArgs.
+ 	savedNumTemps := methodOrBlockNumTemps.
  	inBlock := true.
  	compiledBlocksCount := 0.
  	[compiledBlocksCount < blockCount] whileTrue:
  		[blockStart := self blockStartAt: compiledBlocksCount.
  		 self scanBlock: blockStart.
  		 initialOpcodeIndex := opcodeIndex.
  		 initialAnnotationIndex := annotationIndex.
  		 [self compileBlockEntry: blockStart.
  		  initialStackPtr := simStackPtr.
  		  (result := self compileAbstractInstructionsFrom: blockStart startpc + ((self pushNilSize: methodObj) * blockStart numInitialNils)
  						through: blockStart startpc + blockStart span - 1) < 0 ifTrue:
  			[^result].
  		  "If the final simStackPtr is less than the initial simStackPtr then scanBlock: over-
  		   estimated the number of initial nils (because it assumed one or more pushNils to
  		   produce an operand were pushNils to initialize temps.  This is very rare, so
  		   compensate by checking, adjusting numInitialNils and recompiling the block body."
  		  initialStackPtr = simStackPtr]
  			whileFalse:
  				[self assert: initialStackPtr > simStackPtr.
  				 blockStart numInitialNils: blockStart numInitialNils + simStackPtr - initialStackPtr.
  				 blockStart fakeHeader dependent: nil.
  				 self reinitializeFixupsFrom: blockStart startpc + blockStart numInitialNils
  					through: blockStart startpc + blockStart span - 1.
  				 self cCode: 'bzero(abstractOpcodes + initialOpcodeIndex,
  									(opcodeIndex - initialOpcodeIndex) * sizeof(AbstractInstruction))'
  					inSmalltalk: [initialOpcodeIndex to: opcodeIndex - 1 do:
  									[:i|
  									abstractOpcodes
  										at: i
  										put: (processor abstractInstructionCompilerClass for: self)]].
  				 opcodeIndex := initialOpcodeIndex.
  				 annotationIndex := initialAnnotationIndex].
  		compiledBlocksCount := compiledBlocksCount + 1].
  	needsFrame := savedNeedsFrame.
  	methodOrBlockNumArgs := savedNumArgs.
+ 	methodOrBlockNumTemps := savedNumTemps.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveClass (in category 'primitive generators') -----
  genPrimitiveClass
+ 	"Depending on argument count the argument is either
+ 		0 args: ReceiverResultReg
+ 		1 args: Arg0Reg
+ 		N args: top of stack (assuming 1 reg arg for now)"
+ 	| reg |
+ 	methodOrBlockNumArgs = 1
+ 		ifTrue:
+ 			[reg := Arg0Reg]
+ 		ifFalse:
+ 			[methodOrBlockNumArgs > 0 ifTrue:
+ 				[self MoveMw: BytesPerWord r: SPReg R: ReceiverResultReg].
+ 			reg := ReceiverResultReg].
  	objectRepresentation
+ 		genGetClassObjectOf: reg
- 		genGetClassObjectOf: ReceiverResultReg
  		into: ReceiverResultReg
  		scratchReg: TempReg.
  	self RetN: 0.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorClass (in category 'bytecode generators') -----
  genSpecialSelectorClass
+ 	| topReg |
+ 	topReg := self ssTop registerOrNil.
  	self ssPop: 1.
+ 	(topReg isNil or: [topReg = ClassReg])
+ 		ifTrue: [self ssAllocateRequiredReg: (topReg := SendNumArgsReg) and: ClassReg]
+ 		ifFalse: [self ssAllocateRequiredReg: ClassReg].
- 	self ssAllocateRequiredReg: SendNumArgsReg and: ClassReg.
  	self ssPush: 1.
+ 	self ssTop popToReg: topReg.
+ 	objectRepresentation genGetClassObjectOf: topReg into: ClassReg scratchReg: TempReg.
- 	self ssTop popToReg: SendNumArgsReg.
- 	objectRepresentation genGetClassObjectOf: SendNumArgsReg into: ClassReg scratchReg: TempReg.
  	^self ssPop: 1; ssPushRegister: ClassReg!

Item was added:
+ ----- Method: VMMaker class>>generateNewSqueakCogVM (in category 'configurations') -----
+ generateNewSqueakCogVM
+ 	"self generateNewSqueakCogVM"
+ 	^VMMaker
+ 		generate: (Smalltalk at: ([:choices| choices at: (UIManager default chooseFrom: choices) ifAbsent: [^self]]
+ 									value: #(CoInterpreter CoInterpreterMT)))
+ 		and: StackToRegisterMappingCogit
+ 		with: #(	MULTIPLEBYTECODESETS false
+ 				NewspeakVM false
+ 				bytecodeTableInitializer newInitializeBytecodeTableForSqueakV3PlusClosures)
+ 		to: (FileDirectory default pathFromURI: 'oscogvm/src')
+ 		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
+ 		including:#(	ADPCMCodecPlugin AsynchFilePlugin BalloonEnginePlugin B3DAcceleratorPlugin
+ 					BMPReadWriterPlugin BitBltSimulation BochsIA32Plugin CroquetPlugin DSAPlugin
+ 					DeflatePlugin DropPlugin FT2Plugin FFTPlugin FileCopyPlugin FilePlugin FloatArrayPlugin
+ 					FloatMathPlugin GeniePlugin HostWindowPlugin IA32ABIPlugin InternetConfigPlugin
+ 					JPEGReadWriter2Plugin JPEGReaderPlugin JoystickTabletPlugin KlattSynthesizerPlugin
+ 					LargeIntegersPlugin LocalePlugin MIDIPlugin MacMenubarPlugin Matrix2x3Plugin
+ 					MiscPrimitivePlugin Mpeg3Plugin QuicktimePlugin RePlugin SecurityPlugin SerialPlugin
+ 					SocketPlugin SoundCodecPlugin SoundGenerationPlugin SoundPlugin SqueakSSLPlugin StarSqueakPlugin
+ 					ThreadedIA32FFIPlugin UnixAioPlugin UUIDPlugin UnixOSProcessPlugin
+ 					Win32OSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin)!



More information about the Vm-dev mailing list