IRDecompiler.st
changeset 37 be8c2dd09dff
child 41 f3898a3b378d
equal deleted inserted replaced
36:1bfd09c6b3d8 37:be8c2dd09dff
       
     1 "{ Package: 'cvut:stx/goodies/newcompiler' }"
       
     2 
       
     3 IRInterpreter subclass:#IRDecompiler
       
     4 	instanceVariableNames:'stack sp scope currentInstr valueLabelMap mapEmptyStatement'
       
     5 	classVariableNames:''
       
     6 	poolDictionaries:''
       
     7 	category:'NewCompiler-IR'
       
     8 !
       
     9 
       
    10 IRDecompiler comment:'I interpret IRMethod instructions and generate a Smalltalk abstract syntax tree rooted at a RBMethodNode.
       
    11 This is implemented like a shift-reduce parser.  Each instruction either causes a node to be pushed on the stack (shift), or causes one or more nodes to be popped and combined into a single node which is push back on the stack (reduce).  Most reduction is done at the "label: labelNum" instruction where it tries to reduce jump structures into control messages like #ifTrue:, whileFalse:, etc.
       
    12 Several pseudo nodes (RBPseudoNode and subclasses) are used to represent basic instructions that have not been reduced to real AST nodes yet.
       
    13 '
       
    14 !
       
    15 
       
    16 
       
    17 !IRDecompiler class methodsFor:'as yet unclassified'!
       
    18 
       
    19 dummySelector: numArgs
       
    20 	"Answer a dummy selector with number of args"
       
    21 
       
    22 	| sel |
       
    23 	sel _ 'unknown'.
       
    24 	1 to: numArgs do: [:i |
       
    25 		sel _ sel, 'with:'].
       
    26 	^ sel asSymbol
       
    27 ! !
       
    28 
       
    29 !IRDecompiler methodsFor:'accessing'!
       
    30 
       
    31 scope
       
    32 
       
    33 	^scope
       
    34 ! !
       
    35 
       
    36 !IRDecompiler methodsFor:'init'!
       
    37 
       
    38 addTempToScope: ir 
       
    39 
       
    40 	"Temp may be created only if they are not used in the method"
       
    41 	0 to: ir numRargs - 1 do: [:i | (scope 
       
    42 		rawVarAt: i 
       
    43 		ifNone: [
       
    44 			scope capturedVars do: [:each | 
       
    45 				each index = i ifTrue:[
       
    46 					scope tempVarAt: scope capturedVars size + scope tempVars size.
       
    47 					^self]].
       
    48 			scope tempVarAt: i]) markArg]
       
    49 !
       
    50 
       
    51 decompileIR: ir 
       
    52 	| sequenceNode temps args goto seq value method |
       
    53 	scope isBlockScope 
       
    54 		ifTrue:[(scope addTemp: 'parent env') markArg]
       
    55 		ifFalse:[(scope addTemp: 'self') markArg].
       
    56 	ir tempKeys do: [:temp | scope tempVarAt: temp].
       
    57 	0 to: ir numRargs - 1 do: [:i | (scope tempVarAt: i) markArg].
       
    58 	self interpret: ir.
       
    59 	
       
    60 	self addTempToScope: ir.
       
    61 	self label: #return.
       
    62 	self Label: #return.
       
    63 	(self endCase: #lastReturn) ifFalse:[self Label: #return.].
       
    64 	goto := self Goto.
       
    65 	value := self ValueOrNone.
       
    66 	seq := self Sequence.
       
    67 	self removeClosureCreation: seq.
       
    68 	sp = 1 ifFalse: [stack explore. self error: 'error'].
       
    69 	value ifNotNil: [seq addNode: value].
       
    70 	sequenceNode := (self newBlock: seq return: goto) body.
       
    71 	temps := scope compactIndexTemps asArray.
       
    72 	ir tempKeys: temps.
       
    73 	args := (temps first: ir numRargs) allButFirst.
       
    74 	args := args collect: [:var | self newVar: var].
       
    75 	temps := temps allButFirst: ir numRargs.
       
    76 	sequenceNode temporaries: (temps collect: [:var | self newVar: var]), 
       
    77 		((scope capturedVars select:[:var | var name ~= 'self' and: [var sourceTemp == nil]]) 
       
    78 			collect:[:var | self newVar: var]).
       
    79 	method := (RBMethodNode new)
       
    80 				selectorParts: (self 
       
    81 							newSelectorParts: (self class dummySelector: args size));
       
    82 				arguments: args;
       
    83 				body: sequenceNode;
       
    84 				primitiveNode: ir primitiveNode;
       
    85 				scope: scope.
       
    86 	sequenceNode parent: method.
       
    87 	Preferences compileBlocksAsClosures 
       
    88 		ifFalse: [ASTFixDecompileBlockScope new visitNode: method].
       
    89 	^ method
       
    90 !
       
    91 
       
    92 removeClosureCreation: seq 
       
    93 	(Preferences compileBlocksAsClosures 
       
    94 		and: [seq statements size > 0]
       
    95 		and: [seq statements first isClosureEnvironmentCreation]) ifTrue: [
       
    96 			seq statements removeFirst.
       
    97 			(seq statements size > 0
       
    98 				and: [seq statements first isClosureEnvironmentRegistration])
       
    99 				ifTrue: [seq statements removeFirst]].
       
   100 			
       
   101 	[Preferences compileBlocksAsClosures
       
   102 		and: [seq statements size > 0]
       
   103 		and: [seq statements first isClosureRegistrationAndCreation
       
   104 			or: [seq statements first isSelfClosureRegistration]
       
   105 			or: [seq statements first isTempClosureRegistration]]]
       
   106 					whileTrue: [seq statements removeFirst]
       
   107 !
       
   108 
       
   109 scope: aLexicalScope
       
   110 
       
   111 	scope := aLexicalScope
       
   112 ! !
       
   113 
       
   114 !IRDecompiler methodsFor:'instructions'!
       
   115 
       
   116 goto: seqNum
       
   117 
       
   118 	self stackPush: (RBPseudoGotoNode new destination: seqNum).
       
   119 !
       
   120 
       
   121 if: bool goto: seqNum1 otherwise: seqNum2
       
   122 
       
   123 	self stackPush: (RBPseudoIfNode new
       
   124 		boolean: bool;
       
   125 		destination: seqNum1;
       
   126 		otherwise: seqNum2)
       
   127 !
       
   128 
       
   129 label: seqNum
       
   130 
       
   131 	stack isEmpty ifTrue: [  "start"
       
   132 		^ stack addLast: (RBPseudoLabelNode new destination: seqNum)].
       
   133 
       
   134 	self captureEmptyStatement.
       
   135 	"Reduce jump structures to one of the following if possible"
       
   136 	[	(self endBlock: seqNum) or: [
       
   137 		 (self endAndOr: seqNum) or: [
       
   138 		  (self endAndOr2: seqNum) or: [
       
   139 		   (self endIfThen: seqNum) or: [
       
   140 		    (self endIfThen2: seqNum) or:[
       
   141 		      (self endIfThenElse: seqNum) or: [
       
   142 		       (self endCase: seqNum) or: [
       
   143 		        (self endToDo: seqNum) or: [
       
   144 		         (self endWhile: seqNum) or: [
       
   145 			     (self endWhile2: seqNum) or: [
       
   146 			      (self endIfNil: seqNum)]]]]]]]]]]
       
   147 	] whileTrue.
       
   148 
       
   149 	stack addLast: (RBPseudoLabelNode new destination: seqNum).
       
   150 !
       
   151 
       
   152 popTop
       
   153 
       
   154 	| value |
       
   155 	stack last ifNil: [^ stack removeLast].  "pop no-op from #simplifyTempAssign:"
       
   156 	[stack last isLabel 
       
   157 		and: [(stack atLast:2) isGoto] 
       
   158 		and: [stack last destination = (stack atLast: 2) destination]]
       
   159 			whileTrue: [
       
   160 				stack removeLast.
       
   161 				stack removeLast].
       
   162 	stack last isValue ifTrue: [
       
   163 		(stack atLast: 2) isSequence ifTrue: [
       
   164 			value := stack removeLast.
       
   165 			^ stack last addNode: value.
       
   166 		] ifFalse: [(stack atLast: 2) isPseudo ifTrue: [
       
   167 			value := stack removeLast.
       
   168 			^ stack addLast: (RBSequenceNode statements: {value}).
       
   169 		]].
       
   170 	].
       
   171 	stack addLast: RBPseudoPopNode new
       
   172 !
       
   173 
       
   174 pushBlock: irMethod
       
   175 
       
   176 	self block: irMethod env: nil
       
   177 !
       
   178 
       
   179 pushBlockMethod: irMethod
       
   180 
       
   181 	"block will recognized when send: #createBlock:"
       
   182 	self pushLiteral: irMethod
       
   183 !
       
   184 
       
   185 pushDup
       
   186 
       
   187 	stack addLast: RBPseudoDupNode new
       
   188 !
       
   189 
       
   190 pushInstVar: index
       
   191 	
       
   192 	self stackPush: (self newVar: (scope instanceScope instVar: index))
       
   193 !
       
   194 
       
   195 pushLiteral: object
       
   196 
       
   197 	self stackPush: (self newLiteral: object).
       
   198 !
       
   199 
       
   200 pushLiteralVariable: object
       
   201 
       
   202 	| var |
       
   203 	var := scope lookupVar: object key asString.
       
   204 	self stackPush: (self newVar: var)
       
   205 !
       
   206 
       
   207 pushTemp: tempIndex
       
   208 
       
   209 	| var |
       
   210 	var := scope basicTempVarAt: tempIndex.
       
   211 	var isTemp ifTrue: [var cantBeCapture].
       
   212 	self stackPush: (self newVar: var).
       
   213 !
       
   214 
       
   215 remoteReturn
       
   216 
       
   217 	stack removeLast.  "pop home context free var"
       
   218 	self goto: #return.
       
   219 !
       
   220 
       
   221 returnTop
       
   222 
       
   223 	self goto: #return.
       
   224 !
       
   225 
       
   226 send: selector numArgs: numArgs
       
   227 
       
   228         | args rcvr |
       
   229         selector = #caseError ifTrue:[^self stackPush: (RBPseudoSendNode new selector: selector)].
       
   230         args := OrderedCollection new.
       
   231         [       selector numArgs timesRepeat: [args addFirst: self Value].
       
   232                 rcvr := self Value.
       
   233         ] on: Abort do: [
       
   234                 [self stackPush: (RBPseudoSendNode new selector: selector).
       
   235                 ^self cascade] on: Abort do:[^false]
       
   236         ].
       
   237 
       
   238         Preferences compileBlocksAsClosures 
       
   239                         ifTrue: [ (rcvr isLiteral and: [selector = #createBlock:]) ifTrue: [
       
   240                                          ^ self block: rcvr value env: args first]]
       
   241                         ifFalse: [ (selector = #blockCopy:) ifTrue: [
       
   242                                          ^ self stackPush: (RBPseudoSendNode new selector: selector; arguments: args)]].
       
   243 
       
   244         self stackPush: (self simplify: (RBMessageNode new
       
   245                 receiver: rcvr
       
   246                 selectorParts: (self newSelectorParts: selector)
       
   247                 arguments: args)).
       
   248 
       
   249     "Created: / 01-12-2008 / 19:40:52 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
   250 !
       
   251 
       
   252 send: selector numArgs: numArgs toSuperOf: behavior
       
   253 
       
   254         | args rcvr |
       
   255         args := OrderedCollection new.
       
   256         selector numArgs timesRepeat: [args addFirst: self Value].
       
   257         rcvr := self Value.
       
   258         (rcvr isVariable and: [rcvr name = 'self']) ifFalse: [self patternError].
       
   259 
       
   260         rcvr identifierToken: (SqueakToken value: 'super' start: 0).
       
   261         self stackPush: (RBMessageNode new
       
   262                 receiver: rcvr
       
   263                 selectorParts: (self newSelectorParts: selector)
       
   264                 arguments: args).
       
   265 
       
   266     "Created: / 01-12-2008 / 19:45:52 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
   267 !
       
   268 
       
   269 storeIntoLiteralVariable: association
       
   270 
       
   271 	| var |
       
   272 	var := scope lookupVar: association key asString.
       
   273 	self stackPush: (self simplifyTempAssign:
       
   274 		(RBAssignmentNode variable: (self newVar: (var markWrite)) value: self Value))
       
   275 !
       
   276 
       
   277 storeTemp: tempIndex
       
   278 
       
   279 	| var |
       
   280 	var := scope basicTempVarAt: tempIndex.
       
   281 	var isCaptured ifFalse: [var cantBeCapture].
       
   282 	var isTemp ifTrue:[
       
   283 		var isArg: false].
       
   284 	self stackPush: (self simplifyTempAssign:
       
   285 		(RBAssignmentNode variable: (self newVar: (var markWrite)) value: self Value)).
       
   286 ! !
       
   287 
       
   288 !IRDecompiler methodsFor:'interpret'!
       
   289 
       
   290 interpretInstruction: irInstruction
       
   291 
       
   292 	currentInstr := irInstruction.
       
   293 	super interpretInstruction: irInstruction.
       
   294 !
       
   295 
       
   296 interpretSequence: instructionSequence
       
   297 
       
   298 	super interpretSequence: instructionSequence.
       
   299 	"currentInstr := nil."
       
   300 ! !
       
   301 
       
   302 !IRDecompiler methodsFor:'old blocks'!
       
   303 
       
   304 blockReturnTop
       
   305 
       
   306 	self goto: #return.
       
   307 !
       
   308 
       
   309 endBlock: seqNum
       
   310 
       
   311 	| blockSeq block goto startBlock |
       
   312 	[
       
   313 		goto := self GotoOrReturn: seqNum.
       
   314 		(goto isRet 
       
   315 			or:[goto mapInstr notNil 
       
   316 				and: [goto mapInstr isBlockReturnTop]]) ifFalse: [self abort].
       
   317 		sp = 0 ifTrue: [self abort].
       
   318 		blockSeq := self Sequence2.
       
   319 		startBlock := self Label.
       
   320 		block := self Block.
       
   321 		(goto isRet not
       
   322 			and:[goto mapInstr notNil] 
       
   323 			and: [goto mapInstr isBlockReturnTop]
       
   324 			and: [block successor ~= seqNum]) ifTrue:[
       
   325 				self stackPush: block.
       
   326 				self stackPush: startBlock.
       
   327 				self stackPush: blockSeq. 
       
   328 				self stackPush: goto.
       
   329 				self abort].
       
   330 		self Send.
       
   331 	] on: Abort do: [^ false].
       
   332 
       
   333 	self stackPush: (self newBlock: blockSeq return: goto).	
       
   334 	stack last arguments: block arguments.
       
   335 	"No extra scope is need if we don't use any temporaries and arguments.
       
   336 	so we remove them"
       
   337 	(stack last arguments isEmpty and: [stack last body temporaries isEmpty])
       
   338 		ifTrue:[ASTReplaceVariableScope replace: stack last scope: scope outerScope ].
       
   339 	scope := scope outerScope.
       
   340 	currentInstr := nil.
       
   341 	self goto: block successor.
       
   342 	^ true
       
   343 !
       
   344 
       
   345 jumpOverBlock: seqNum1  to: seqNum2
       
   346 	| numArgs args oldscope pseudoBlock |
       
   347 
       
   348 	oldscope := scope.
       
   349 	self scope: (scope newBlockScope).
       
   350 	oldscope tempVarAt: 0.
       
   351 	(scope addObjectTemp: (oldscope tempVarAt: 0)).
       
   352 	numArgs := stack last arguments first value.
       
   353 	self stackPush: (pseudoBlock := RBPseudoBlockNode new).
       
   354 	
       
   355 	args := OrderedCollection new.
       
   356 	numArgs timesRepeat: [ | var instr |
       
   357 		instr :=  currentInstr blockSequence removeFirst.
       
   358  		var := oldscope tempVarAt: instr number.
       
   359 		args add: (self newVar: var).
       
   360 		var isUnused ifTrue: [oldscope removeTempFromOldBlock: var].
       
   361 		scope addObjectTemp: var.
       
   362 		currentInstr blockSequence first isPop 
       
   363 			ifFalse: [
       
   364 				currentInstr blockSequence sequence addFirst: (IRInstruction pushTemp: var index)]
       
   365 			ifTrue:[currentInstr blockSequence removeFirst].
       
   366 		
       
   367 	].
       
   368 	args := args reverse.
       
   369 	pseudoBlock
       
   370 		block: seqNum1;
       
   371 		successor: seqNum2;
       
   372 		arguments: args
       
   373 	
       
   374 !
       
   375 
       
   376 storeInstVar: number
       
   377 
       
   378 	| var |
       
   379 	var := scope  instanceScope instVar: number.
       
   380 	self stackPush: (RBAssignmentNode variable: (self newVar: var)  value:  self Value)
       
   381 ! !
       
   382 
       
   383 !IRDecompiler methodsFor:'priv instructions'!
       
   384 
       
   385 addReturn: statements from: goto
       
   386 
       
   387 		| ret |
       
   388 		statements last isReturn ifTrue:[^self].
       
   389 		ret := RBReturnNode value: statements last.
       
   390 		Preferences compileBlocksAsClosures ifTrue:[
       
   391 			scope isHome ifFalse: [ret homeBinding: scope outerEnvScope thisEnvVar]].
       
   392 		goto mapInstr sourceNode: ret.
       
   393 		statements atLast: 1 put: ret.
       
   394 !
       
   395 
       
   396 block: method env: envRefNode
       
   397 
       
   398 	self stackPush: (IRDecompiler new
       
   399 		scope: (scope newBlockScope "capturedVars: vars");
       
   400 		decompileIR: method ir)
       
   401 		asBlock
       
   402 !
       
   403 
       
   404 cascade
       
   405 
       
   406 	| messages selector args rcvr |
       
   407 	messages := OrderedCollection new.
       
   408 	"last message"
       
   409 	selector _ self Send selector.
       
   410 	args := OrderedCollection new.
       
   411 	selector numArgs timesRepeat: [args addFirst: self Value].
       
   412 	messages addFirst: selector -> args.
       
   413 
       
   414 	"rest of messages"
       
   415 	[(rcvr := self ValueOrNone) isNil] whileTrue: [
       
   416 		self Pop.
       
   417 		selector := self Send selector.
       
   418 		args := OrderedCollection new.
       
   419 		selector numArgs timesRepeat: [args addFirst: self Value].
       
   420 		self Dup.
       
   421 		messages addFirst: selector -> args.
       
   422 	].
       
   423 
       
   424 	messages := messages collect: [:assoc |
       
   425 		RBMessageNode
       
   426 			receiver: rcvr
       
   427 			selector: assoc key
       
   428 			arguments: assoc value].
       
   429 	self stackPush: (RBCascadeNode messages: messages).
       
   430 !
       
   431 
       
   432 endAndOr2: seqNum
       
   433 
       
   434 	| goto seq p if2 test else o if1 seqValue elseTest otherwise |
       
   435 	[
       
   436 		goto _ self Goto.
       
   437 		seqValue _ self ValueOrNone.
       
   438 		seq _ self Sequence.
       
   439 		p _ self Label destination.
       
   440 		if2 _ self IfGoto: seqNum otherwise: p.
       
   441 		elseTest _ self Value.
       
   442 		else _ self SequenceBackTo: goto destination.
       
   443 		o _ self Label destination.
       
   444 		o = goto destination ifTrue: [self abort].
       
   445 		if1 _ self IfGoto: seqNum otherwise: o.
       
   446 		test _ self Value.
       
   447 	] on: Abort do: [^ false].
       
   448 
       
   449 	if1 boolean = if2 boolean 
       
   450 		ifFalse: [
       
   451 			otherwise := RBSequenceNode statements: #().
       
   452 			otherwise addNode: (self newLiteral: if2 boolean).
       
   453 			self stackPush: (RBMessageNode
       
   454 				receiver: test 
       
   455 				selector: (if2 boolean ifTrue: [#ifTrue:ifFalse:] ifFalse: [#ifFalse:ifTrue:]) 
       
   456 				arguments: {self newBlock: (else addNode: elseTest).
       
   457 					self newBlock: otherwise}).]
       
   458 		ifTrue:[self stackPush: (RBMessageNode
       
   459 			receiver: test
       
   460 			selector: (if2 boolean ifTrue: [#or:] ifFalse: [#and:])
       
   461 			arguments: {self newBlock: (else addNode: elseTest)})].
       
   462 	stack addLast: if2.
       
   463 	self label: p.
       
   464 	stack addLast: seq.
       
   465 	seqValue ifNotNil: [stack addLast: seqValue].
       
   466 	stack addLast: goto.
       
   467 	^ true
       
   468 !
       
   469 
       
   470 endAndOr: seqNum
       
   471 
       
   472 	| o test branches if body block sel1 sel2 if2 |
       
   473 	branches := OrderedCollection new.
       
   474 	[
       
   475 		(if2 := self If) otherwise = seqNum ifFalse: [self abort].
       
   476 		[	test := self Value.
       
   477 			body := self Sequence.
       
   478 			branches add: {body. test}.
       
   479 			o := self Label destination.
       
   480 			(if := self If) otherwise = o ifFalse: [self abort].
       
   481 			if destination = seqNum
       
   482 		] whileFalse: [
       
   483 			if boolean = if2 boolean ifFalse: [self abort].
       
   484 			if destination = if2 destination ifFalse: [self abort].
       
   485 		].
       
   486 		if boolean = if2 boolean ifTrue: [self abort].
       
   487 		test := self Value.
       
   488 	] on: Abort do: [^ false].
       
   489 
       
   490 	if boolean
       
   491 		ifTrue: [sel1 := #or:. sel2 := #and:]
       
   492 		ifFalse: [sel1 := #and:. sel2 := #or:].
       
   493 	block := self newBlock: (branches first first addNode: branches first second).
       
   494 	branches allButFirstDo: [:pair |
       
   495 		block := self newBlock: (pair first addNode: (RBMessageNode
       
   496 				receiver: pair second
       
   497 				selector: sel2
       
   498 				arguments: {block})).
       
   499 	].
       
   500 	self stackPush: (RBMessageNode
       
   501 		receiver: test
       
   502 		selector: sel1
       
   503 		arguments: {block}).
       
   504 	stack addLast: if2.
       
   505 	^ true
       
   506 !
       
   507 
       
   508 endCase: seqNum
       
   509 
       
   510 	| otherwiseGoto goto node otherwiseValue otherwiseSeq n branchValue branchSeq f caseValue caseSeq rcvr branches message seqEnd afterOterwise seq afterOterwiseValue |
       
   511 	branches := OrderedCollection new.
       
   512 	[	"otherwise"
       
   513 		otherwiseGoto := self Goto.
       
   514 		node := self stackDown.
       
   515 		node isSequence ifTrue: [(node statements size = 1 
       
   516 			and:[node statements first isSend] 
       
   517 			and: [
       
   518 				node := node statements first. 
       
   519 				node selector == #caseError]) ifFalse: [
       
   520 					otherwiseSeq := node] ].
       
   521 		(node isPop or: [node isSend and: [node selector == #caseError]]) ifTrue: [
       
   522 			node isPop ifTrue: [node := self Send].
       
   523 			node selector == #caseError ifFalse: [self abort].
       
   524 		] ifFalse: [
       
   525 			sp := sp + 1.  "stackUp"
       
   526 			
       
   527 			seqNum == #lastReturn 
       
   528 				ifFalse: [
       
   529 					otherwiseValue := self ValueOrNone.
       
   530 					otherwiseSeq := self Sequence]
       
   531 				ifTrue: [
       
   532 					afterOterwiseValue := self ValueOrNone.
       
   533 					otherwiseSeq := RBSequenceNode statements: #().
       
   534 					afterOterwise := self SequenceOtherwise].
       
   535 		].
       
   536 		n := self Label destination.
       
   537 		"last case branch"
       
   538 		seqNum == #lastReturn 
       
   539 			ifFalse: [goto := self GotoOrReturn: seqNum]
       
   540 			ifTrue: [
       
   541 				seqEnd := n.
       
   542 				goto := self GotoOrReturn: n.
       
   543 				otherwiseGoto := goto].
       
   544 		branchValue := self ValueOrNone.
       
   545 		branchSeq := self Sequence.
       
   546 		(stack at: sp) isPop ifTrue: [self stackDown].
       
   547 		f := self Label destination.
       
   548 		
       
   549 		"last case"
       
   550 		self IfGoto: n otherwise: f.
       
   551 		self Send selector == #= ifFalse: [self abort].
       
   552 		caseValue := self Value.
       
   553 		caseSeq := self Sequence.
       
   554 		otherwiseSeq ifNil: [self Dup].
       
   555 		branches addFirst: ({caseSeq. caseValue} -> {branchSeq. branchValue. goto}).
       
   556 
       
   557 		[(rcvr := self ValueOrNone) isNil] whileTrue: [
       
   558 			"case branch"
       
   559 			n := self Label destination.
       
   560 			seqNum == #lastReturn 
       
   561 				ifFalse: [goto := self GotoOrReturn: seqNum]
       
   562 				ifTrue: [goto := self GotoOrReturn: seqEnd].
       
   563 			branchValue := self ValueOrNone.
       
   564 			branchSeq := self Sequence.
       
   565 			self Pop.
       
   566 			f := self Label destination.
       
   567 			"case"
       
   568 			self IfGoto: n otherwise: f.
       
   569 			self Send selector == #= ifFalse: [self abort].
       
   570 			caseValue := self Value.
       
   571 			caseSeq := self Sequence.
       
   572 			self Dup.
       
   573 			branches addFirst: ({caseSeq. caseValue} -> {branchSeq. branchValue. goto}).
       
   574 		].
       
   575 	] on: Abort do: [^ false].
       
   576 
       
   577 	branches := branches collect: [:assoc |
       
   578 		assoc key second
       
   579 			ifNotNil: [assoc key first addNode: assoc key second].
       
   580 		assoc value second
       
   581 			ifNotNil: [assoc value first addNode: assoc value second].
       
   582 		RBMessageNode
       
   583 			receiver: (self newBlock: assoc key first return: nil)
       
   584 			selector: #->
       
   585 			arguments:
       
   586 				{self newBlock: assoc value first return: assoc value third}
       
   587 	].
       
   588 	message := otherwiseSeq
       
   589 		ifNil: [
       
   590 			RBMessageNode
       
   591 				receiver: rcvr
       
   592 				selector: #caseOf:
       
   593 				arguments: {RBArrayNode statements: branches}]
       
   594 		ifNotNil: [
       
   595 			otherwiseValue
       
   596 				ifNotNil: [otherwiseSeq addNode: otherwiseValue].
       
   597 			RBMessageNode
       
   598 				receiver: rcvr
       
   599 				selector: #caseOf:otherwise:
       
   600 				arguments: 
       
   601 					{RBArrayNode statements: branches.
       
   602 					self newBlock: otherwiseSeq return: otherwiseGoto}.
       
   603 		].
       
   604 	self stackPush: message.
       
   605 	seqNum == #lastReturn ifTrue: [
       
   606 		self popTop.
       
   607 		seq := self Sequence.
       
   608 		afterOterwise ifNotNil:[seq statements addAllLast: afterOterwise statements].
       
   609 		self stackPush: seq.
       
   610 		afterOterwiseValue ifNotNil:[self stackPush: afterOterwiseValue].
       
   611 		branchValue := 1].
       
   612 	branchValue ifNil: [self popTop].
       
   613 	self stackPush: otherwiseGoto.
       
   614 	^ true
       
   615 !
       
   616 
       
   617 endIfNil: seqNum
       
   618 
       
   619 	| goto branch o if rcvr value |
       
   620 	[
       
   621 		goto := self Goto.
       
   622 		value := self Value.
       
   623 		branch := self Sequence.
       
   624 		self Pop.
       
   625 		o := self Label destination.
       
   626 		if := self IfGoto: seqNum otherwise: o.
       
   627 		self Send selector == #== ifFalse: [self abort].
       
   628 		(self Value isLiteral: [:v | v isNil]) ifFalse: [self abort].
       
   629 		self Dup.
       
   630 		rcvr := self Value.
       
   631 	] on: Abort do: [^ false].
       
   632 
       
   633 	branch addNode: value.
       
   634 	self stackPush: (RBMessageNode
       
   635 		receiver: rcvr
       
   636 		selector: (if boolean ifTrue: [#ifNotNil:] ifFalse: [#ifNil:])
       
   637 		arguments: {self newBlock: branch return: goto}).
       
   638 	self goto: seqNum.
       
   639 	^ true
       
   640 !
       
   641 
       
   642 endIfThen2: seqNum
       
   643 
       
   644 	| goto branch o if test value gotoNum branch2 |
       
   645 	[
       
   646 		goto := self Goto.
       
   647 		(goto mapInstr ~= nil 
       
   648 			and: [goto mapInstr isJump]
       
   649 			and: [goto mapInstr destination size = 1]  
       
   650 			and: [goto mapInstr destination last isJump]) 
       
   651 				ifTrue: [gotoNum := goto 
       
   652 					mapInstr destination last destination orderNumber]
       
   653 				ifFalse:[self abort].
       
   654 		(currentInstr ~= nil 
       
   655 			and: [currentInstr isJump] 
       
   656 			and: [currentInstr destination orderNumber = goto destination])
       
   657 				ifFalse: [self abort].
       
   658 		value := self Value.
       
   659 		branch := self Sequence.
       
   660 		o := self Label destination.
       
   661 		seqNum = gotoNum 
       
   662 			ifFalse:[if := self IfGoto: gotoNum otherwise: o]
       
   663 			ifTrue:[self abort].
       
   664 		test := self Value.
       
   665 	] on: Abort do: [^ false].
       
   666 	
       
   667 	value ifNotNil: [branch addNode: value].
       
   668 	branch2 := RBSequenceNode statements: #().
       
   669 	branch2 addNode: (self newLiteral: if boolean).
       
   670 	self stackPush: (self simplify: (RBMessageNode
       
   671 		receiver: test
       
   672 		selector: (if boolean ifTrue: [#ifFalse:ifTrue:] ifFalse: [#ifTrue:ifFalse:])
       
   673 		arguments: {self newBlock: branch return: goto.
       
   674 			self newBlock: branch2})).
       
   675 	self goto: goto destination.
       
   676 	^true
       
   677 !
       
   678 
       
   679 endIfThen3: seqNum
       
   680 
       
   681 	| goto branch o if test value |
       
   682 	[
       
   683 		goto := self Goto.
       
   684 		(goto destination == seqNum or: [self isExplicitReturn: goto])
       
   685 			ifFalse: [self abort].
       
   686 		goto isRet ifTrue: [value := self Value].
       
   687 		branch := self Sequence.
       
   688 		o := self Label destination.
       
   689 		if := self If.
       
   690 		((if destination = seqNum 
       
   691 			or: [if destination = (mapEmptyStatement at: seqNum ifAbsent:[seqNum])])
       
   692 				and: [if otherwise = o])
       
   693 			ifFalse:[self abort].
       
   694 		test := self Value.
       
   695 	] on: Abort do: [^ false].
       
   696 	
       
   697 
       
   698 	value ifNotNil: [branch addNode: value].
       
   699 	self stackPush: (self simplify: (RBMessageNode
       
   700 		receiver: test
       
   701 		selector: (if boolean ifTrue: [#ifFalse:] ifFalse: [#ifTrue:])
       
   702 		arguments: {self newBlock: branch return: goto})).
       
   703 	self popTop.
       
   704 	self goto: seqNum.
       
   705 	^ true
       
   706 !
       
   707 
       
   708 endIfThen: seqNum
       
   709 
       
   710 	| goto branch o if test value |
       
   711 	[
       
   712 		goto := self Goto.
       
   713 		(goto destination == seqNum or: [self isExplicitReturn: goto])
       
   714 			ifFalse: [self abort].
       
   715 		goto isRet ifTrue: [value := self Value].
       
   716 		branch := self Sequence.
       
   717 		o := self Label destination.
       
   718 		if := self IfGoto: seqNum otherwise: o.
       
   719 		test := self Value.
       
   720 	] on: Abort do: [^ false].
       
   721 	
       
   722 
       
   723 	value ifNotNil: [branch addNode: value].
       
   724 	self stackPush: (self simplify: (RBMessageNode
       
   725 		receiver: test
       
   726 		selector: (if boolean ifTrue: [#ifFalse:] ifFalse: [#ifTrue:])
       
   727 		arguments: {self newBlock: branch return: goto})).
       
   728 	self popTop.
       
   729 	self goto: seqNum.
       
   730 	^ true
       
   731 !
       
   732 
       
   733 endIfThenElse: seqNum
       
   734 
       
   735 	| goto2 else d goto1 then o if test value2 value1 |
       
   736 	[
       
   737 		goto2 := self Goto.
       
   738 		value2 := self ValueOrNone.
       
   739 		else := self Sequence.
       
   740 		d := self Label destination.
       
   741 		goto1 := self Goto.
       
   742 		((self isExplicitReturn: goto2) or: [goto2 destination == goto1 destination]) ifFalse: [self abort].
       
   743 		value1 := self ValueOrNone.
       
   744 		then := self Sequence.
       
   745 		o := self Label destination.
       
   746 		if := self IfGoto: d otherwise: o.
       
   747 		test := self Value.
       
   748 	] on: Abort do: [^ false].
       
   749 
       
   750 	value2 ifNotNil: [else addNode: value2].
       
   751 	value1 ifNotNil: [then addNode: value1].
       
   752 	(self isExplicitReturn: goto1) ifTrue:[self addReturn: then statements from: goto1].
       
   753 	(self isExplicitReturn: goto2) ifTrue:[self addReturn: else statements from: goto2].
       
   754 	self stackPush: (self simplify: (else isEmpty
       
   755 		ifTrue: [RBMessageNode
       
   756 			receiver: test
       
   757 			selector: (if boolean ifTrue: [#ifFalse:] ifFalse: [#ifTrue:])
       
   758 			arguments: {self newBlock: then return: goto1}]
       
   759 		ifFalse: [RBMessageNode
       
   760 			receiver: test
       
   761 			selector: (if boolean
       
   762 				ifTrue: [#ifFalse:ifTrue:]
       
   763 				ifFalse: [#ifTrue:ifFalse:])
       
   764 			arguments: {
       
   765 				self newBlock: then return: goto1.
       
   766 				self newBlock: else return: goto2}])).
       
   767 	value1 ifNil: [self popTop].
       
   768 	currentInstr := goto1 mapInstr.
       
   769 	self stackPush: goto1.
       
   770 	(else statements isEmpty and:
       
   771 	 [stack anySatisfy: [:n | n isIf and: [n destination = d]]]
       
   772 	) ifTrue: [
       
   773 		self label: d.
       
   774 		currentInstr := goto2 mapInstr.
       
   775 		self stackPush: goto2.
       
   776 	].
       
   777 	^ true
       
   778 !
       
   779 
       
   780 endToDo: seqNum
       
   781 
       
   782 	| start limit incr iter step loopBlock o if test limitExpr init |
       
   783 	[
       
   784 		start := self Goto destination.
       
   785 		limit := self Value.
       
   786 		incr := self Assignment.
       
   787 		iter := incr variable.
       
   788 		(incr value isMessage and:
       
   789 		 [incr value selector == #+ and:
       
   790 		  [incr value receiver isVariable and: 
       
   791 		   [incr value receiver binding == iter binding]]]
       
   792 		) ifFalse: [self abort].
       
   793 		step := incr value arguments first.
       
   794 		loopBlock := self Sequence.
       
   795 		o := self Label destination.
       
   796 		if := self IfGoto: seqNum otherwise: o.
       
   797 		test := self Value.
       
   798 		(test isMessage and:
       
   799 		 [(test selector == #<= or: [test selector == #>=]) and:
       
   800 		  [(valueLabelMap at: test arguments first ifAbsent: [self abort]) destination = start]]
       
   801 		) ifFalse: [self abort].
       
   802 		limitExpr := test arguments first.
       
   803 		limitExpr isAssignment ifTrue: [
       
   804 			(limitExpr variable binding index == limit binding index 
       
   805 				and:[limitExpr variable binding scope == limit binding scope]) ifFalse: [self abort].
       
   806 			limitExpr := limitExpr value.
       
   807 		].
       
   808 		init := test receiver.
       
   809 		(init isAssignment and: [init variable binding == iter binding])
       
   810 			ifFalse: [self abort].
       
   811 	] on: Abort do: [^ false].
       
   812 	limit isVariable 
       
   813 		ifTrue:[scope 
       
   814 			removeTemp: limit binding 
       
   815 			ifAbsent:[Preferences compileBlocksAsClosures 
       
   816 				ifFalse:[scope removeTempFromOldBlock: limit]]].
       
   817 	loopBlock := self newBlock: loopBlock.
       
   818 	loopBlock arguments: {iter}.
       
   819 	self stackPush: ((step isLiteral: [:c | c = 1])
       
   820 		ifTrue: [RBMessageNode
       
   821 				receiver: init value
       
   822 				selector: #to:do:
       
   823 				arguments: {limitExpr. loopBlock}]
       
   824 		ifFalse: [RBMessageNode
       
   825 				receiver: init value
       
   826 				selector: #to:by:do:
       
   827 				arguments: {limitExpr. step. loopBlock}]).
       
   828 	self popTop.
       
   829 	self goto: seqNum.
       
   830 	^ true
       
   831 !
       
   832 
       
   833 endWhile2: seqNum
       
   834 
       
   835 	| start loopBlock if test sequence o goto previousStack |
       
   836 	[
       
   837 		stack := (previousStack := stack) copy.
       
   838 		start := (goto := self Goto) destination.
       
   839 		self stackPush: goto.
       
   840 		[self endIfThen3: start] whileTrue.
       
   841 		start :=  self Goto destination.
       
   842 		loopBlock _ self Sequence.
       
   843 		o _ self Label destination.
       
   844 		if _ self IfGoto: seqNum otherwise: o.
       
   845 		test _ self Value.
       
   846 		sequence _ self SequenceBackTo: start.
       
   847 		self Label: start.
       
   848 		sp _ sp + 1.  "stackUp"
       
   849 	] on: Abort do: [stack := previousStack. ^ false].
       
   850 	loopBlock isEmpty
       
   851 		ifTrue:[self stackPush: (self simplify: (RBMessageNode
       
   852 			receiver: (self newBlock: (sequence addNode: test))
       
   853 			selector: (if boolean ifTrue: [#whileFalse] ifFalse: [#whileTrue])
       
   854 			arguments: #()))]
       
   855 		ifFalse:[self stackPush: (self simplify: (RBMessageNode
       
   856 			receiver: (self newBlock: (sequence addNode: test))
       
   857 			selector: (if boolean ifTrue: [#whileFalse:] ifFalse: [#whileTrue:])
       
   858 			arguments: {self newBlock: loopBlock}))].
       
   859 	self popTop.
       
   860 	self goto: seqNum.
       
   861 	^ true
       
   862 !
       
   863 
       
   864 endWhile: seqNum
       
   865 
       
   866 	| start loopBlock if test sequence o |
       
   867 	[
       
   868 		start _ self Goto destination.
       
   869 		loopBlock _ self Sequence.
       
   870 		o _ self Label destination.
       
   871 		if _ self IfGoto: seqNum otherwise: o.
       
   872 		test _ self Value.
       
   873 		sequence _ self SequenceBackTo: start.
       
   874 		self Label: start.
       
   875 		sp _ sp + 1.  "stackUp"
       
   876 	] on: Abort do: [^ false].
       
   877 	loopBlock isEmpty
       
   878 		ifTrue:[self stackPush: (self simplify: (RBMessageNode
       
   879 			receiver: (self newBlock: (sequence addNode: test))
       
   880 			selector: (if boolean ifTrue: [#whileFalse] ifFalse: [#whileTrue])
       
   881 			arguments: #()))]
       
   882 		ifFalse:[self stackPush: (self simplify: (RBMessageNode
       
   883 			receiver: (self newBlock: (sequence addNode: test))
       
   884 			selector: (if boolean ifTrue: [#whileFalse:] ifFalse: [#whileTrue:])
       
   885 			arguments: {self newBlock: loopBlock}))].
       
   886 	self popTop.
       
   887 	self goto: seqNum.
       
   888 	^ true
       
   889 ! !
       
   890 
       
   891 !IRDecompiler methodsFor:'private'!
       
   892 
       
   893 captureEmptyStatement
       
   894 	| by replace node |
       
   895 	
       
   896 	[by := self Goto destination.
       
   897 	replace := self Label destination.
       
   898 	replace = 0 ifTrue: [self abort]] 
       
   899 			on: Abort
       
   900 			do: [^ false].
       
   901 	mapEmptyStatement at: by put: replace.
       
   902 	sp := nil.
       
   903 	^ true
       
   904 !
       
   905 
       
   906 fixInnerFreeVar: aRcvrTemp
       
   907 
       
   908 	| scopeInnerFreeVar |
       
   909 	scopeInnerFreeVar := scope outerScope.
       
   910 	[aRcvrTemp scope = scopeInnerFreeVar] whileFalse:[
       
   911 		scopeInnerFreeVar hasInnerFreeVars: true.
       
   912 		scopeInnerFreeVar := scopeInnerFreeVar outerScope].
       
   913 	aRcvrTemp scope hasInnerFreeVars: true
       
   914 !
       
   915 
       
   916 initialize
       
   917 
       
   918 	stack := OrderedCollection new.
       
   919 	scope := nil parseScope newMethodScope.  "in case never set"
       
   920 	valueLabelMap := IdentityDictionary new.
       
   921 	mapEmptyStatement := IdentityDictionary new
       
   922 !
       
   923 
       
   924 isExplicitReturn: goto
       
   925 
       
   926 	Preferences compileBlocksAsClosures 
       
   927 		ifTrue:[^ goto isRet 
       
   928 			and: [goto mapInstr notNil] 
       
   929 			and: [goto mapInstr isRemote or: [scope isBlockScope not]]]
       
   930 		ifFalse: [^goto isRet and: [goto mapInstr isBlockReturnTop not]]
       
   931 !
       
   932 
       
   933 mapNode: node
       
   934 
       
   935 	currentInstr ifNil: [^ self].
       
   936 	node isPseudo
       
   937 		ifTrue: [node mapInstr: currentInstr]
       
   938 		ifFalse: [currentInstr sourceNode: node]
       
   939 !
       
   940 
       
   941 newBlock: sequence
       
   942 
       
   943 	^ self newBlock: sequence return: nil
       
   944 !
       
   945 
       
   946 newBlock: sequence return: goto
       
   947 
       
   948 	| statements block |
       
   949 	statements := sequence statements.
       
   950 	(goto notNil and: [self isExplicitReturn: goto]) ifTrue: [
       
   951 		self addReturn: statements from: goto
       
   952 	].
       
   953 	sequence statements: statements.
       
   954 	block := RBBlockNode body: sequence.
       
   955 	sequence parent: block.
       
   956 	Preferences compileBlocksAsClosures ifFalse: [block scope: scope].
       
   957 	^block
       
   958 !
       
   959 
       
   960 newLiteral: literal
       
   961 
       
   962 	^ RBLiteralNode value: literal
       
   963 !
       
   964 
       
   965 newSelectorParts: selector
       
   966 
       
   967 	^ selector keywords collect: [:word |
       
   968 		RBLiteralToken value: word]
       
   969 !
       
   970 
       
   971 newVar: semVar
       
   972 
       
   973 	^ RBVariableNode new
       
   974 		identifierToken: (RBIdentifierToken value: semVar name start: 0);
       
   975 		binding: semVar
       
   976 !
       
   977 
       
   978 simplify: mess
       
   979 	"mess is a messageNode.  If it is a message created by the compiler convert it back to its normal form"
       
   980 
       
   981 	| rcvr var |
       
   982 "	(mess selector == #value and: [mess receiver isLiteral]) ifTrue: [
       
   983 		^ self newVar: (GlobalVar new assoc: mess receiver value; scope: scope)
       
   984 	]."
       
   985 
       
   986 	(mess selector = #privSetInHolder: and: [mess arguments first isLiteral]) ifTrue: [
       
   987 		^ RBAssignmentNode
       
   988 			variable: (self newVar: (GlobalVar new assoc: mess arguments first value; scope: scope) markWrite)
       
   989 			value: mess receiver
       
   990 	].
       
   991 
       
   992 	(mess selector = #privGetInstVar: and:
       
   993 	 [mess arguments first isLiteral and:
       
   994 	  [mess receiver isVariable]]) ifTrue: [
       
   995 		rcvr := mess receiver binding.
       
   996 		rcvr == scope receiverVar ifTrue: [
       
   997 			^ self newVar: (scope receiverVarAt: mess arguments first value)].
       
   998 		(rcvr isContextVar and: [mess arguments first value == 5]) ifTrue: [
       
   999 			var := scope tempVarAt: -1.
       
  1000 			^self newVar: var].
       
  1001 		(rcvr isCaptured and:[rcvr sourceTemp = rcvr scope receiverVar])
       
  1002 			ifTrue:[
       
  1003 				self fixInnerFreeVar: rcvr.
       
  1004 				^self newVar: (rcvr scope receiverVarAt: mess arguments first value)].
       
  1005 		rcvr isEnv ifTrue: [^self newVar: (rcvr scope captureVarAt: mess arguments first value)]].
       
  1006 
       
  1007 	(mess selector = #privStoreIn:instVar: and:
       
  1008 	 [mess arguments last isLiteral and:
       
  1009 	  [mess arguments first isVariable]]) ifTrue: [
       
  1010 		rcvr := mess arguments first binding.
       
  1011 		(mess receiver name = 'self' and: [rcvr isEnv]) 
       
  1012 			ifTrue:[scope captureSelf: mess arguments last value. 
       
  1013 				^mess].
       
  1014 		rcvr == scope  receiverVar ifTrue: [^ RBAssignmentNode
       
  1015 				variable: (self newVar: (scope receiverVarForAssignmentAt: mess arguments last value) markWrite) 
       
  1016 				value: mess receiver].
       
  1017 		(rcvr isCaptured and:[rcvr sourceTemp = rcvr scope receiverVar])
       
  1018 			ifTrue:[
       
  1019 				self fixInnerFreeVar: rcvr.
       
  1020 				^RBAssignmentNode
       
  1021 					variable: (self newVar: (rcvr scope receiverVarForAssignmentAt: mess arguments last value) markWrite) 
       
  1022 					value: mess receiver].
       
  1023 		mess isClosureEnvironmentRegistration
       
  1024 			ifTrue: [
       
  1025 				scope captureSelf: mess arguments last value.
       
  1026 				^mess].
       
  1027 		rcvr isEnv ifTrue:[
       
  1028 			mess receiver isTemp 
       
  1029 				ifTrue:[var := (scope 
       
  1030 					captureVarAt: mess arguments last value  
       
  1031 					sourceTemp: mess receiver binding) markWrite.]
       
  1032 				ifFalse:[var := (scope 
       
  1033 					captureVarAt: mess arguments last value sourceTemp: ((TempVar new)
       
  1034 								name: (scope captureVarName: mess arguments last value);
       
  1035 								index: mess arguments last value;
       
  1036 								scope: self;
       
  1037 								cantBeCapture)) markWrite
       
  1038 					].
       
  1039 			^ RBAssignmentNode
       
  1040 				variable: (self newVar: var)
       
  1041 				value: mess receiver]].
       
  1042 	^mess
       
  1043 !
       
  1044 
       
  1045 simplifyTempAssign: assignment
       
  1046 	"If it is a assignment created by the compiler convert it back to its normal form"
       
  1047 
       
  1048 	| mess |
       
  1049 	((mess := assignment value) isMessage and: 
       
  1050 	 [mess selector = #wrapInTempHolder and:
       
  1051 	  [mess receiver isLiteral: [:v | v isNil]]]
       
  1052 	) ifTrue: [
       
  1053 		^ nil  "no-op"
       
  1054 	].
       
  1055 
       
  1056 	^ assignment
       
  1057 ! !
       
  1058 
       
  1059 !IRDecompiler methodsFor:'stack'!
       
  1060 
       
  1061 Assignment
       
  1062 
       
  1063 	| node |
       
  1064 	(node := self stackDown) isAssignment ifTrue: [^ node].
       
  1065 	self abort
       
  1066 !
       
  1067 
       
  1068 Block
       
  1069 
       
  1070 	| node |
       
  1071 	(node := self stackDown) isBlock ifTrue: [^ node].
       
  1072 	self abort
       
  1073 !
       
  1074 
       
  1075 Dup
       
  1076 
       
  1077 	| node |
       
  1078 	(node := self stackDown) isDup ifTrue: [^ node].
       
  1079 	self abort
       
  1080 !
       
  1081 
       
  1082 Goto
       
  1083 
       
  1084 	| node |
       
  1085 	(node := self stackDown) isGoto ifTrue: [^ node].
       
  1086 	self abort
       
  1087 !
       
  1088 
       
  1089 Goto: seqNum
       
  1090 
       
  1091 	| goto |
       
  1092 	(goto := self Goto) destination = seqNum ifTrue: [^ goto].
       
  1093 	self abort
       
  1094 !
       
  1095 
       
  1096 GotoOrReturn: seqNum
       
  1097 
       
  1098 	| goto |
       
  1099 	goto := self Goto.
       
  1100 	(goto destination = seqNum or: [goto isRet]) ifTrue: [^ goto].
       
  1101 	self abort
       
  1102 !
       
  1103 
       
  1104 If
       
  1105 
       
  1106 	| node |
       
  1107 	(node := self stackDown) isIf ifTrue: [^ node].
       
  1108 	self abort
       
  1109 !
       
  1110 
       
  1111 IfGoto: seqNum otherwise: seqNum2
       
  1112 
       
  1113 	| if |
       
  1114 	((if := self If) destination = seqNum and: [if otherwise = seqNum2])
       
  1115 		ifTrue: [^ if].
       
  1116 	self abort
       
  1117 !
       
  1118 
       
  1119 Label
       
  1120 
       
  1121 	| node |
       
  1122 	(node := self stackDown) isLabel ifTrue: [^ node].
       
  1123 	self abort
       
  1124 !
       
  1125 
       
  1126 Label: seqNum
       
  1127 
       
  1128 	| label |
       
  1129 	(label := self Label) destination = seqNum ifTrue: [^ label].
       
  1130 	self abort
       
  1131 !
       
  1132 
       
  1133 Pop
       
  1134 
       
  1135 	| node |
       
  1136 	(node := self stackDown) isPop ifTrue: [^ node].
       
  1137 	self abort
       
  1138 !
       
  1139 
       
  1140 Send
       
  1141 
       
  1142 	| node |
       
  1143 	(node := self stackDown) isPseudoSend ifTrue: [^ node].
       
  1144 	self abort
       
  1145 !
       
  1146 
       
  1147 Sequence
       
  1148 	| node seq i goto |
       
  1149 	seq := RBSequenceNode statements: #().
       
  1150 	i := self spIndex.
       
  1151 	[node := stack at: i.
       
  1152 	node isSequence 
       
  1153 		ifTrue: 
       
  1154 			[seq addNodesFirst: node statements.
       
  1155 			node := stack at: (i := i - 1)].
       
  1156 	(node isLabel and: [i > 1]) 
       
  1157 		ifFalse: 
       
  1158 			[sp := i.
       
  1159 			^ seq].
       
  1160 	goto := stack at: (i := i - 1).
       
  1161 	goto isGoto and: [goto destination = node destination]] 
       
  1162 			whileTrue: [i := i - 1].
       
  1163 	sp := i + 1.
       
  1164 	^ seq
       
  1165 !
       
  1166 
       
  1167 Sequence2
       
  1168 	| node seq i block temps label |
       
  1169 	seq := RBSequenceNode statements: #().
       
  1170 	i := self spIndex.
       
  1171 	node := stack at: i.
       
  1172 	[(node isLabel and: [(stack at: i - 1) isGoto] and:[node destination = (stack at: i - 1) destination])
       
  1173 		ifTrue:[
       
  1174 			i := i - 2.
       
  1175 			node := stack at: i].
       
  1176 	(node isLabel not and: [i > 1])] whileTrue: 
       
  1177 			[
       
  1178 			node isSequence 
       
  1179 				ifTrue: [seq addNodesFirst: node statements]
       
  1180 				ifFalse: [seq addNodeFirst: node].
       
  1181 			i := i - 1.
       
  1182 			node := stack at: i].
       
  1183 	sp := i.
       
  1184 	label := self Label.
       
  1185 	block := self Block.
       
  1186 	self stackPush: block.
       
  1187 	self stackPush: label.
       
  1188 	"Add the temporaries find"
       
  1189 	temps := scope tempVars asArray allButFirst.
       
  1190 	temps := temps select: [:each | ((block arguments 
       
  1191 							collect: [:var | var binding])  includes: each) not].
       
  1192 	seq temporaries: (temps collect: [:var | self newVar: var]).
       
  1193 	^ seq
       
  1194 !
       
  1195 
       
  1196 SequenceBackTo: labelNum 
       
  1197 	| node seq i goto |
       
  1198 	seq := RBSequenceNode statements: #().
       
  1199 	i := self spIndex.
       
  1200 	[node := stack at: i.
       
  1201 	node isSequence 
       
  1202 		ifTrue: 
       
  1203 			[seq addNodesFirst: node statements.
       
  1204 			node := stack at: (i := i - 1)].
       
  1205 	(node isLabel and: [i > 1]) 
       
  1206 		ifFalse: 
       
  1207 			[sp := i.
       
  1208 			^ seq].
       
  1209 	node destination = labelNum 
       
  1210 		ifTrue: 
       
  1211 			[sp := i.
       
  1212 			^ seq].
       
  1213 	goto := stack at: (i := i - 1).
       
  1214 	goto isGoto and: [goto destination = node destination]] 
       
  1215 			whileTrue: [i := i - 1].
       
  1216 	sp := i + 1.
       
  1217 	^ seq
       
  1218 !
       
  1219 
       
  1220 SequenceOtherwise
       
  1221 	| node seq i |
       
  1222 	seq := RBSequenceNode statements: #().
       
  1223 	i := self spIndex.
       
  1224 	node := stack at: i.
       
  1225 	node isSequence ifTrue: [
       
  1226 			seq addNodesFirst: node statements.
       
  1227 			self stackDown]
       
  1228 		ifFalse:[node isLabel ifFalse:[self abort]].
       
  1229 	^ seq
       
  1230 !
       
  1231 
       
  1232 Value
       
  1233 
       
  1234 	| node |
       
  1235 	node := self ValueOrNone.
       
  1236 	node ifNil: [self abort].
       
  1237 	^ node
       
  1238 !
       
  1239 
       
  1240 ValueOrNone
       
  1241 	| node i label |
       
  1242 	i := self spIndex.
       
  1243 	[node := stack at: i.
       
  1244 	node isValue 
       
  1245 		ifTrue: 
       
  1246 			[label ifNotNil: [valueLabelMap at: node put: label].
       
  1247 			sp := i - 1.
       
  1248 			^ node].
       
  1249 	(node isLabel and: [i > 1]) ifFalse: [^ nil].
       
  1250 	label := node.
       
  1251 	node := stack at: (i := i - 1).
       
  1252 	node isGoto and: [node destination = label destination]] 
       
  1253 			whileTrue: [i := i - 1].
       
  1254 	^ nil
       
  1255 !
       
  1256 
       
  1257 abort
       
  1258 
       
  1259 	| spWas |
       
  1260 	spWas := sp.
       
  1261 	sp := nil.
       
  1262 	Abort signal
       
  1263 !
       
  1264 
       
  1265 fixStack
       
  1266 
       
  1267 	sp ifNotNil: [stack removeLast: (stack size - sp)].
       
  1268 	sp := nil.
       
  1269 !
       
  1270 
       
  1271 spIndex
       
  1272 	^ sp ifNil: [sp := stack size]
       
  1273 !
       
  1274 
       
  1275 stackDown
       
  1276 
       
  1277 	| node |
       
  1278 	sp ifNil: [sp _ stack size].
       
  1279 	sp = 0 ifTrue: [self abort].
       
  1280 	node _ stack at: sp.
       
  1281 	sp _ sp - 1.
       
  1282 	^ node
       
  1283 !
       
  1284 
       
  1285 stackPush: node
       
  1286 
       
  1287 	self fixStack.
       
  1288 	stack addLast: node.
       
  1289 	node ifNil: [^ self].  "no op"
       
  1290 	self mapNode: node.
       
  1291 ! !
       
  1292 
       
  1293 !IRDecompiler class methodsFor:'documentation'!
       
  1294 
       
  1295 version
       
  1296     ^ '$Id$'
       
  1297 !
       
  1298 
       
  1299 version_CVS
       
  1300     ^ '§Header: /cvs/stx/cvut/stx/goodies/newcompiler/IRDecompiler.st,v 1.3 2009/10/08 12:04:20 fm Exp §'
       
  1301 !
       
  1302 
       
  1303 version_SVN
       
  1304     ^ '$Id::                                                                                                                        $'
       
  1305 ! !