[Vm-dev] VM Maker: VMMaker.oscog-cb.1922.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Aug 30 11:52:22 UTC 2016


ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.1922.mcz

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

Name: VMMaker.oscog-cb.1922
Author: cb
Time: 30 August 2016, 1:48:41.283379 pm
UUID: 7c2ac8b2-b5ad-49ec-a845-9044ff84b144
Ancestors: VMMaker.oscog-cb.1921

Added support from error code while scanning block bodies.

=============== Diff against VMMaker.oscog-cb.1921 ===============

Item was changed:
  ----- Method: Cogit>>scanBlock: (in category 'compile abstract instructions') -----
  scanBlock: blockStart
  	"Scan the block to determine if the block needs a frame or not"
  	| descriptor pc end framelessStackDelta nExts |
  	<var: #blockStart type: #'BlockStart *'>
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	needsFrame := false.
  	methodOrBlockNumArgs := blockStart numArgs.
  	inBlock := true.
  	pc := blockStart startpc.
  	end := blockStart startpc + blockStart span.
  	framelessStackDelta := nExts := extA := extB := 0.
  	[pc < end] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 descriptor isExtension ifTrue:
  			[self loadSubsequentBytesForDescriptor: descriptor at: pc.
  			 self perform: descriptor generator].
  		 needsFrame ifFalse:
  			[(descriptor needsFrameFunction isNil
  			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  				ifTrue: [needsFrame := true]
  				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  		 objectRepresentation maybeNoteDescriptor: descriptor blockStart: blockStart.
  		 pc := self nextBytecodePCFor: descriptor at: pc exts: nExts in: methodObj.
  		 descriptor isExtension
  			ifTrue: [nExts := nExts + 1]
  			ifFalse: [nExts := extA := extB := 0]].
  	needsFrame ifFalse:
  		[framelessStackDelta < 0 ifTrue:
  			[self error: 'negative stack delta in block; block contains bogus code or internal error'].
  		 [framelessStackDelta > 0] whileTrue:
  			[descriptor := self generatorAt: (objectMemory fetchByte: blockStart startpc ofObject: methodObj) + bytecodeSetOffset.
  			 descriptor generator ~~ #genPushConstantNilBytecode ifTrue:
  				[self error: 'frameless block doesn''t start with enough pushNils'].
  			 blockStart
  				startpc: blockStart startpc + descriptor numBytes;
  				span: blockStart span - descriptor numBytes.
+ 			 framelessStackDelta := framelessStackDelta - 1]].
+ 	^0!
- 			 framelessStackDelta := framelessStackDelta - 1]]!

Item was changed:
  ----- Method: SistaCogit>>compileBlockBodies (in category 'compile abstract instructions') -----
  compileBlockBodies
  	"override to maintain counterIndex when recompiling blocks; sigh."
  	<inline: false>
  	| result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs savedNumTemps
  	  initialStackPtr initialOpcodeIndex initialCounterIndex initialIndexOfIRC |
  	<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.
+ 		 (result := self scanBlock: blockStart) < 0 ifTrue: [^result].
- 		 self scanBlock: blockStart.
  		 initialOpcodeIndex := opcodeIndex.
  		 initialCounterIndex := counterIndex.
  		 NewspeakVM ifTrue:
  			[initialIndexOfIRC := indexOfIRC].
  		 [self compileBlockEntry: blockStart.
  		  initialStackPtr := simStackPtr.
  		  (result := self compileAbstractInstructionsFrom: blockStart startpc + (self pushNilSize: methodObj numInitialNils: 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.
  		   N.B.  No need to reinitialize the literalsManager because it answers existing literals."
  		  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: (CogCompilerClass for: self)]].
  				 opcodeIndex := initialOpcodeIndex.
  				 counterIndex := initialCounterIndex.
  				 NewspeakVM ifTrue:
  					[indexOfIRC := initialIndexOfIRC]].
  		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 initialIndexOfIRC |
  	<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.
+ 		  (result := self scanBlock: blockStart) < 0 ifTrue: [^result].
- 		 self scanBlock: blockStart.
  		 initialOpcodeIndex := opcodeIndex.
  		 literalsManager saveForBlockCompile.
  		 NewspeakVM ifTrue:
  			[initialIndexOfIRC := indexOfIRC].
  		 [self compileBlockEntry: blockStart.
  		  initialStackPtr := simStackPtr.
  		  (result := self compileAbstractInstructionsFrom: blockStart startpc + (self pushNilSize: methodObj numInitialNils: 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.
  		   N.B.  No need to reinitialize the literalsManager because it answers existing literals."
  		  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: (CogCompilerClass for: self)]].
  				 opcodeIndex := initialOpcodeIndex.
  				 literalsManager resetForBlockCompile.
  				 NewspeakVM ifTrue:
  					[indexOfIRC := initialIndexOfIRC]].
  		compiledBlocksCount := compiledBlocksCount + 1].
  	needsFrame := savedNeedsFrame.
  	methodOrBlockNumArgs := savedNumArgs.
  	methodOrBlockNumTemps := savedNumTemps.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>scanBlock: (in category 'compile abstract instructions') -----
  scanBlock: blockStart
  	"Scan the block to determine if the block needs a frame or not"
  	| descriptor pc end framelessStackDelta nExts pushingNils numPushNils |
  	<var: #blockStart type: #'BlockStart *'>
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	needsFrame := false.
  	prevBCDescriptor := nil.
  	methodOrBlockNumArgs := blockStart numArgs.
  	inBlock := true.
  	pc := blockStart startpc.
  	end := blockStart startpc + blockStart span.
  	framelessStackDelta := nExts := extA := extB := 0.
  	pushingNils := true.
  	[pc < end] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 descriptor isExtension ifTrue:
  			[self loadSubsequentBytesForDescriptor: descriptor at: pc.
  			 self perform: descriptor generator].
  		 needsFrame ifFalse:
  			[(descriptor needsFrameFunction isNil
  			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  				ifTrue: [needsFrame := true]
  				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  		 objectRepresentation maybeNoteDescriptor: descriptor blockStart: blockStart.
  		 (pushingNils
  		  and: [descriptor isExtension not]) ifTrue:
  			["Count the initial number of pushed nils acting as temp initializers.  We can't tell
  			  whether an initial pushNil is an operand reference or a temp initializer, except
  			  when the pushNil is a jump target (has a fixup), which never happens:
  					self systemNavigation browseAllSelect:
  						[:m| | ebc |
  						(ebc := m embeddedBlockClosures
  									select: [:ea| ea decompile statements first isMessage]
  									thenCollect: [:ea| ea decompile statements first selector]) notEmpty
  						and: [(#(whileTrue whileFalse whileTrue: whileFalse:) intersection: ebc) notEmpty]]
  			  or if the bytecode set has a push multiple nils bytecode.  We simply count initial nils.
  			  Rarely we may end up over-estimating.  We will correct by checking the stack depth
  			  at the end of the block in compileBlockBodies."
  			 (numPushNils := self numPushNils: descriptor pc: pc nExts: nExts method: methodObj) > 0
  				ifTrue:
  					[self assert: (descriptor numBytes = 1
  									or: [descriptor generator == #genPushClosureTempsBytecode]).
  					 blockStart numInitialNils: blockStart numInitialNils + numPushNils]
  				ifFalse:
  					[pushingNils := false]].
  		 pc := self nextBytecodePCFor: descriptor at: pc exts: nExts in: methodObj.
  		 descriptor isExtension
  			ifTrue: [nExts := nExts + 1]
  			ifFalse: [nExts := extA := extB := 0].
  		 prevBCDescriptor := descriptor].
  	"It would be nice of this wasn't necessary but alas we need to do the eager
  	 scan for frameless methods so that we don't end up popping too much off
  	 the simulated stack, e.g. for pushNil; returnTopFromBlock methods."
  	needsFrame ifFalse:
  		[self assert: (framelessStackDelta >= 0 and: [blockStart numInitialNils >= framelessStackDelta]).
+ 		 blockStart numInitialNils: blockStart numInitialNils - framelessStackDelta].
+ 	^0!
- 		 blockStart numInitialNils: blockStart numInitialNils - framelessStackDelta]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>sistaV1PushNilSize:numInitialNils: (in category 'span functions') -----
  sistaV1PushNilSize: aMethodObj numInitialNils: numInitialNils
  	"230		11100110	iiiiiiii		PushNClosureTemps iiiiiiii"
  	<inline: true>
+ 	^numInitialNils!
- 	^numInitialNils = 0 ifTrue: [0] ifFalse: [2]!

Item was changed:
  ----- Method: StackToRegisterMappingCogitChecker>>scanBlock: (in category 'compile abstract instructions') -----
  scanBlock: blockStart
+ 	| result |
+ 	 (result := super scanBlock: blockStart) < 0 ifTrue: [^result].
- 	super scanBlock: blockStart.
  	needsFrame ifTrue:
  		[| tempCount |
  		 tempCount := coInterpreter tempCountForBlockStartingAt: blockStart startpc + 1 in: methodObj.
  		 blockStart numInitialNils ~= tempCount ifTrue:
+ 			[blockStart numInitialNils: tempCount]].
+ 	^0!
- 			[blockStart numInitialNils: tempCount]]!



More information about the Vm-dev mailing list