[squeak-dev] The Trunk: Compiler-mt.412.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Oct 9 07:47:40 UTC 2019


Marcel Taeumel uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-mt.412.mcz

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

Name: Compiler-mt.412
Author: mt
Time: 9 October 2019, 9:47:40.360433 am
UUID: e033a572-485d-41e4-9fcc-5cc55d49a893
Ancestors: Compiler-eem.411

Reformat the sources from my recent changes in the Compiler package in the style of rectangular blocks because it is the default style in that package.

Thanks to Eliot for the pointer.

=============== Diff against Compiler-eem.411 ===============

Item was changed:
  ----- Method: Decompiler>>jump:if: (in category 'instruction decoding') -----
  jump: dist if: condition
  
  	| savePc sign elsePc elseStart end cond ifExpr thenBlock elseBlock
  	  thenJump elseJump condHasValue isIfNil saveStack |
  	lastJumpIfPcStack addLast: lastPc.
  	stack last == CascadeFlag ifTrue: [^ [self case: dist] ensure: [lastJumpIfPcStack removeLast]].
  	elsePc := lastPc.
  	elseStart := pc + dist.
  	end := limit.
  	"Check for bfp-jmp to invert condition.
  	Don't be fooled by a loop with a null body."
  	sign := condition.
  	savePc := pc.
  	self interpretJump ifNotNil:
  		[:elseDist|
  		 (elseDist >= 0 and: [elseStart = pc]) ifTrue:
  			 [sign := sign not.  elseStart := pc + elseDist]].
  	pc := savePc.
  	ifExpr := stack removeLast.
  	(isIfNil := stack size > 0 and: [stack last == IfNilFlag]) ifTrue:
  		[stack removeLast].
  	saveStack := stack.
  	stack := OrderedCollection new.
  	thenBlock := self blockTo: elseStart.
  	condHasValue := hasValue or: [isIfNil].
  	"ensure jump is within block (in case thenExpr returns)"
  	thenJump := exit <= end ifTrue: [exit] ifFalse: [elseStart].
  	"if jump goes back, then it's a loop"
  	thenJump < elseStart
  		ifTrue:
  			[| blockBody blockArgs savedReadCounts blockBodyReadCounts selector |
  			 "Must be a while loop...
  			  thenJump will jump to the beginning of the while expr.  In the case of while's
  			  with a block in the condition, the while expr should include more than just
  			  the last expression: find all the statements needed by searching for the node
  			  with the relevant pc."
  			stack := saveStack.
  			savedReadCounts := tempReadCounts copy.
  			pc := thenJump.
  			blockBody := self statementsTo: elsePc.
  			blockBodyReadCounts := tempReadCounts.
  			savedReadCounts keysAndValuesDo:
  				[:temp :count|
  				 blockBodyReadCounts at: temp put: (blockBodyReadCounts at: temp) - count].
  			tempReadCounts := savedReadCounts.
  			"discard unwanted statements from block"
  			blockBody size - 1 timesRepeat: [statements removeLast].
  			blockArgs := thenBlock statements = constructor codeEmptyBlock statements
  							ifTrue: [#()]
  							ifFalse: [{ thenBlock }].
  			selector := blockArgs isEmpty
  							ifTrue: [sign ifTrue: [#whileFalse] ifFalse: [#whileTrue]]
  							ifFalse: [sign ifTrue: [#whileFalse:] ifFalse: [#whileTrue:]].
  			statements addLast:
  				(constructor
  					codeMessage: (constructor codeBlock: blockBody returns: false)
  					selector: (constructor codeSelector: selector code: #macro)
  					arguments: blockArgs).
  			pc := elseStart.
  			selector == #whileTrue: ifTrue:
  				[self convertToDoLoop: blockBodyReadCounts]]
  		ifFalse:
  			["Must be a conditional..."
  			elseBlock := self blockTo: thenJump.
  			elseJump := exit.
  			"if elseJump is backwards, it is not part of the elseExpr"
  			elseJump < elsePc ifTrue:
  				[pc := lastPc].
  			cond := isIfNil
  						ifTrue:
  							[constructor
  								codeMessage: ifExpr ifNilReceiver
  								selector: (constructor
  											codeSelector: (sign ifTrue: [#ifNotNil:] ifFalse: [#ifNil:])
  											code: #macro)
  								arguments: (Array with: thenBlock)]
  						ifFalse:
+ 							[(sign
+ 								ifTrue: [{elseBlock. thenBlock}]
+ 								ifFalse: [{thenBlock. elseBlock}]) in:
+ 									[:args |
+ 									(constructor
+ 										decodeIfNilWithReceiver: ifExpr
+ 										selector: #ifTrue:ifFalse:
+ 										arguments: args
+ 										tempReadCounts: tempReadCounts) ifNil:
+ 											[constructor
+ 												codeMessage: ifExpr
+ 												selector: (constructor codeSelector: #ifTrue:ifFalse: code: #macro)
+ 												arguments:	 args]]].
- 							[(sign ifTrue: [{elseBlock. thenBlock}] ifFalse: [{thenBlock. elseBlock}]) in: [:args |
- 								(constructor
- 									decodeIfNilWithReceiver: ifExpr
- 									selector: #ifTrue:ifFalse:
- 									arguments: args
- 									tempReadCounts: tempReadCounts) ifNil: [
- 										constructor
- 											codeMessage: ifExpr
- 											selector: (constructor codeSelector: #ifTrue:ifFalse: code: #macro)
- 											arguments:	 args]]].
  			stack := saveStack.
  			condHasValue
  				ifTrue: [stack addLast: cond]
  				ifFalse: [statements addLast: cond]].
  	lastJumpIfPcStack removeLast.!

Item was changed:
  ----- Method: DecompilerConstructor>>decodeIfNilWithReceiver:selector:arguments:tempReadCounts: (in category 'constructor') -----
  decodeIfNilWithReceiver: receiver selector: selector arguments: arguments tempReadCounts: tempReadCounts
  	
  	| node temp |
  	receiver ifNil: [ ^nil ].		"For instance, when cascading"
  	selector == #ifTrue:ifFalse:
  		ifFalse: [^ nil].
  				
  	(receiver isMessage: #==
  				receiver: nil
  				arguments: [:argNode | argNode == NodeNil])
  		ifFalse: [^ nil].
  		
  	"Like #to:(by:)do:, support only local temps."
  	(((temp := receiver ifNilTemporary) isNil or: [tempReadCounts includesKey: temp]) or: [
  		"What about 'object ifNotNil: [:o | ]', which as not read the blockArg? Just check that there is no remote vector pointing to it."
+ 		tempReadCounts keys noneSatisfy:
+ 			[:otherTemp |
+ 				otherTemp isIndirectTempVector
+ 					ifTrue: [otherTemp remoteTemps anySatisfy:
+ 						[:remoteTemp |
+ 						remoteTemp name = temp name]]
+ 					ifFalse: [otherTemp name = temp name]]
- 		tempReadCounts keys noneSatisfy: [:otherTemp |
- 			otherTemp isIndirectTempVector
- 				ifTrue: [otherTemp remoteTemps anySatisfy: [:remoteTemp | remoteTemp name = temp name]]
- 				ifFalse: [otherTemp name = temp name]]
  			])
  		ifFalse: [^ nil].
  		
  	node := (MessageNode new
  			receiver: receiver
  			selector: (SelectorNode new key: #ifTrue:ifFalse: code: #macro)
  			arguments: arguments
  			precedence: 3).
  
  	"Reconfigure the message node to #ifNil:ifNotNil:. Note that original* instance variables keep their optimized format. See MessageNode >> #printIfNilNotNil:indent:."	
  	node
  		noteSpecialSelector: #ifNil:ifNotNil:;
  		selector: (SelectorNode new key: #ifNil:ifNotNil:).
  	
  	temp ifNil: [^ node].
  	temp isTemp ifFalse: [^ node].
  	
+ 	(arguments second isJust: NodeNil) not ifTrue:
+ 		[temp beBlockArg.
+ 		node arguments: {
+ 			arguments first.
+ 			arguments second copy arguments: { temp }; yourself }].
- 	(arguments second isJust: NodeNil) not ifTrue: [
- 			temp beBlockArg.
- 			node arguments: {
- 				arguments first.
- 				arguments second copy arguments: { temp }; yourself } ].
  				
  	^ node!

Item was changed:
  ----- Method: MessageNode>>printIfNilNotNil:indent: (in category 'printing') -----
  printIfNilNotNil: aStream indent: level
  
+ 	(arguments first isJust: NodeNil) ifTrue:
+ 		[self printReceiver: receiver ifNilReceiver ifNilValue on: aStream indent: level.
+ 		^ self
+ 			printKeywords: #ifNotNil:
+ 			arguments: { arguments second }
+ 			on: aStream indent: level].
- 	(arguments first isJust: NodeNil) ifTrue: [
- 		self printReceiver: receiver ifNilReceiver ifNilValue on: aStream indent: level.
- 		^ self printKeywords: #ifNotNil:
- 				arguments: { arguments second }
- 				on: aStream indent: level].
  			
+ 	(arguments second isJust: NodeNil) ifTrue:
+ 		[self printReceiver: receiver ifNilReceiver on: aStream indent: level.
+ 		^ self
+ 			printKeywords: #ifNil:
+ 			arguments: { arguments first }
+ 			on: aStream indent: level].
- 	(arguments second isJust: NodeNil) ifTrue: [
- 		self printReceiver: receiver ifNilReceiver on: aStream indent: level.
- 		^ self printKeywords: #ifNil:
- 				arguments: { arguments first }
- 				on: aStream indent: level].
  	
  	self printReceiver: receiver ifNilReceiver ifNilValue on: aStream indent: level.
+ 	^ self
+ 		printKeywords: #ifNil:ifNotNil:
+ 		arguments: arguments
+ 		on: aStream indent: level!
- 	^ self printKeywords: #ifNil:ifNotNil:
- 			arguments: arguments
- 			on: aStream indent: level!

Item was changed:
  ----- Method: MessageNode>>printWithClosureAnalysisIfNilNotNil:indent: (in category 'printing') -----
  printWithClosureAnalysisIfNilNotNil: aStream indent: level
  
+ 	(arguments first isJust: NodeNil) ifTrue:
+ 		[self printWithClosureAnalysisReceiver: receiver ifNilReceiver ifNilValue on: aStream indent: level.
+ 		^ self
+ 			printWithClosureAnalysisKeywords: #ifNotNil:
+ 			arguments: { arguments second }
+ 			on: aStream indent: level].
- 	(arguments first isJust: NodeNil) ifTrue: [
- 		self printWithClosureAnalysisReceiver: receiver ifNilReceiver ifNilValue on: aStream indent: level.
- 		^ self printWithClosureAnalysisKeywords: #ifNotNil:
- 				arguments: { arguments second }
- 				on: aStream indent: level].
  			
+ 	(arguments second isJust: NodeNil) ifTrue:
+ 		[self printWithClosureAnalysisReceiver: receiver ifNilReceiver on: aStream indent: level.
+ 		^ self
+ 			printWithClosureAnalysisKeywords: #ifNil:
+ 			arguments: { arguments first }
+ 			on: aStream indent: level].
- 	(arguments second isJust: NodeNil) ifTrue: [
- 		self printWithClosureAnalysisReceiver: receiver ifNilReceiver on: aStream indent: level.
- 		^ self printWithClosureAnalysisKeywords: #ifNil:
- 				arguments: { arguments first }
- 				on: aStream indent: level].
  			
  	self printWithClosureAnalysisReceiver: receiver ifNilReceiver ifNilValue on: aStream indent: level.
+ 	^ self
+ 		printWithClosureAnalysisKeywords: #ifNil:ifNotNil:
+ 		arguments: arguments
+ 		on: aStream indent: level!
- 	^ self printWithClosureAnalysisKeywords: #ifNil:ifNotNil:
- 			arguments: arguments
- 			on: aStream indent: level!



More information about the Squeak-dev mailing list