IRDecompiler.st
changeset 45 04a50b0d540a
parent 43 c8afb8e4c3cc
equal deleted inserted replaced
44:840c68a91cdd 45:04a50b0d540a
    47 					^self]].
    47 					^self]].
    48 			scope tempVarAt: i]) markArg]
    48 			scope tempVarAt: i]) markArg]
    49 !
    49 !
    50 
    50 
    51 decompileIR: ir 
    51 decompileIR: ir 
    52 	| sequenceNode temps args goto seq value method |
    52 "/        | sequenceNode temps args goto seq value method |
    53 	scope isBlockScope 
    53 "/        scope isBlockScope 
    54 		ifTrue:[(scope addTemp: 'parent env') markArg]
    54 "/                ifTrue:[(scope addTemp: 'parent env') markArg]
    55 		ifFalse:[(scope addTemp: 'self') markArg].
    55 "/                ifFalse:[(scope addTemp: 'self') markArg].
    56 	ir tempKeys do: [:temp | scope tempVarAt: temp].
    56 "/        ir tempKeys do: [:temp | scope tempVarAt: temp].
    57 	0 to: ir numRargs - 1 do: [:i | (scope tempVarAt: i) markArg].
    57 "/        0 to: ir numRargs - 1 do: [:i | (scope tempVarAt: i) markArg].
    58 	self interpret: ir.
    58 "/        self interpret: ir.
    59 	
    59 "/        
    60 	self addTempToScope: ir.
    60 "/        self addTempToScope: ir.
    61 	self label: #return.
    61 "/        self label: #return.
    62 	self Label: #return.
    62 "/        self Label: #return.
    63 	(self endCase: #lastReturn) ifFalse:[self Label: #return.].
    63 "/        (self endCase: #lastReturn) ifFalse:[self Label: #return.].
    64 	goto := self Goto.
    64 "/        goto := self Goto.
    65 	value := self ValueOrNone.
    65 "/        value := self ValueOrNone.
    66 	seq := self Sequence.
    66 "/        seq := self Sequence.
    67 	self removeClosureCreation: seq.
    67 "/        self removeClosureCreation: seq.
    68 	sp = 1 ifFalse: [stack explore. self error: 'error'].
    68 "/        sp = 1 ifFalse: [stack explore. self error: 'error'].
    69 	value ifNotNil: [seq addNode: value].
    69 "/        value ifNotNil: [seq addNode: value].
    70 	sequenceNode := (self newBlock: seq return: goto) body.
    70 "/        sequenceNode := (self newBlock: seq return: goto) body.
    71 	temps := scope compactIndexTemps asArray.
    71 "/        temps := scope compactIndexTemps asArray.
    72 	ir tempKeys: temps.
    72 "/        ir tempKeys: temps.
    73 	args := (temps first: ir numRargs) allButFirst.
    73 "/        args := (temps first: ir numRargs) allButFirst.
    74 	args := args collect: [:var | self newVar: var].
    74 "/        args := args collect: [:var | self newVar: var].
    75 	temps := temps allButFirst: ir numRargs.
    75 "/        temps := temps allButFirst: ir numRargs.
    76 	sequenceNode temporaries: (temps collect: [:var | self newVar: var]), 
    76 "/        sequenceNode temporaries: (temps collect: [:var | self newVar: var]), 
    77 		((scope capturedVars select:[:var | var name ~= 'self' and: [var sourceTemp == nil]]) 
    77 "/                ((scope capturedVars select:[:var | var name ~= 'self' and: [var sourceTemp == nil]]) 
    78 			collect:[:var | self newVar: var]).
    78 "/                        collect:[:var | self newVar: var]).
    79 	method := (RBMethodNode new)
    79 "/        method := (RBMethodNode new)
    80 				selectorParts: (self 
    80 "/                                selectorParts: (self 
    81 							newSelectorParts: (self class dummySelector: args size));
    81 "/                                                        newSelectorParts: (self class dummySelector: args size));
    82 				arguments: args;
    82 "/                                arguments: args;
    83 				body: sequenceNode;
    83 "/                                body: sequenceNode;
    84 				primitiveNode: ir primitiveNode;
    84 "/                                primitiveNode: ir primitiveNode;
    85 				scope: scope.
    85 "/                                scope: scope.
    86 	sequenceNode parent: method.
    86 "/        sequenceNode parent: method.
    87 	Preferences compileBlocksAsClosures 
    87 "/        Preferences compileBlocksAsClosures 
    88 		ifFalse: [ASTFixDecompileBlockScope new visitNode: method].
    88 "/                ifFalse: [ASTFixDecompileBlockScope new visitNode: method].
    89 	^ method
    89 "/        ^ method
       
    90 
       
    91     "Modified: / 30-10-2014 / 22:36:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    90 !
    92 !
    91 
    93 
    92 removeClosureCreation: seq 
    94 removeClosureCreation: seq 
    93 	(Preferences compileBlocksAsClosures 
    95         ("Preferences compileBlocksAsClosures"true
    94 		and: [seq statements size > 0]
    96                 and: [seq statements size > 0]
    95 		and: [seq statements first isClosureEnvironmentCreation]) ifTrue: [
    97                 and: [seq statements first isClosureEnvironmentCreation]) ifTrue: [
    96 			seq statements removeFirst.
    98                         seq statements removeFirst.
    97 			(seq statements size > 0
    99                         (seq statements size > 0
    98 				and: [seq statements first isClosureEnvironmentRegistration])
   100                                 and: [seq statements first isClosureEnvironmentRegistration])
    99 				ifTrue: [seq statements removeFirst]].
   101                                 ifTrue: [seq statements removeFirst]].
   100 			
   102                         
   101 	[Preferences compileBlocksAsClosures
   103         ["Preferences compileBlocksAsClosures"true
   102 		and: [seq statements size > 0]
   104                 and: [seq statements size > 0]
   103 		and: [seq statements first isClosureRegistrationAndCreation
   105                 and: [seq statements first isClosureRegistrationAndCreation
   104 			or: [seq statements first isSelfClosureRegistration]
   106                         or: [seq statements first isSelfClosureRegistration]
   105 			or: [seq statements first isTempClosureRegistration]]]
   107                         or: [seq statements first isTempClosureRegistration]]]
   106 					whileTrue: [seq statements removeFirst]
   108                                         whileTrue: [seq statements removeFirst]
       
   109 
       
   110     "Modified: / 30-10-2014 / 22:37:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   107 !
   111 !
   108 
   112 
   109 scope: aLexicalScope
   113 scope: aLexicalScope
   110 
   114 
   111 	scope := aLexicalScope
   115 	scope := aLexicalScope
   233         ] on: Abort do: [
   237         ] on: Abort do: [
   234                 [self stackPush: (RBPseudoSendNode new selector: selector).
   238                 [self stackPush: (RBPseudoSendNode new selector: selector).
   235                 ^self cascade] on: Abort do:[^false]
   239                 ^self cascade] on: Abort do:[^false]
   236         ].
   240         ].
   237 
   241 
   238         Preferences compileBlocksAsClosures 
   242         "Preferences compileBlocksAsClosures"true
   239                         ifTrue: [ (rcvr isLiteral and: [selector = #createBlock:]) ifTrue: [
   243                         ifTrue: [ (rcvr isLiteral and: [selector = #createBlock:]) ifTrue: [
   240                                          ^ self block: rcvr value env: args first]]
   244                                          ^ self block: rcvr value env: args first]]
   241                         ifFalse: [ (selector = #blockCopy:) ifTrue: [
   245                         ifFalse: [ (selector = #blockCopy:) ifTrue: [
   242                                          ^ self stackPush: (RBPseudoSendNode new selector: selector; arguments: args)]].
   246                                          ^ self stackPush: (RBPseudoSendNode new selector: selector; arguments: args)]].
   243 
   247 
   245                 receiver: rcvr
   249                 receiver: rcvr
   246                 selectorParts: (self newSelectorParts: selector)
   250                 selectorParts: (self newSelectorParts: selector)
   247                 arguments: args)).
   251                 arguments: args)).
   248 
   252 
   249     "Created: / 01-12-2008 / 19:40:52 / Jan Vrany <vranyj1@fel.cvut.cz>"
   253     "Created: / 01-12-2008 / 19:40:52 / Jan Vrany <vranyj1@fel.cvut.cz>"
       
   254     "Modified: / 30-10-2014 / 22:38:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   250 !
   255 !
   251 
   256 
   252 send: selector numArgs: numArgs toSuperOf: behavior
   257 send: selector numArgs: numArgs toSuperOf: behavior
   253 
   258 
   254         | args rcvr |
   259         | args rcvr |
   381 ! !
   386 ! !
   382 
   387 
   383 !IRDecompiler methodsFor:'priv instructions'!
   388 !IRDecompiler methodsFor:'priv instructions'!
   384 
   389 
   385 addReturn: statements from: goto
   390 addReturn: statements from: goto
   386 
   391 "/    |  |
   387 		| ret |
   392 
   388 		statements last isReturn ifTrue:[^self].
   393     self error: 'IRDecompiler is an unfinished code'.    
   389 		ret := RBReturnNode value: statements last.
   394 "/    statements last isReturn ifTrue:[^self].
   390 		Preferences compileBlocksAsClosures ifTrue:[
   395 "/    ret := RBReturnNode value: statements last.
   391 			scope isHome ifFalse: [ret homeBinding: scope outerEnvScope thisEnvVar]].
   396 "/    Preferences compileBlocksAsClosures ifTrue:[
   392 		goto mapInstr sourceNode: ret.
   397 "/            scope isHome ifFalse: [ret homeBinding: scope outerEnvScope thisEnvVar]].
   393 		statements atLast: 1 put: ret.
   398 "/    goto mapInstr sourceNode: ret.
       
   399 "/    statements atLast: 1 put: ret.
       
   400 
       
   401     "Modified: / 30-10-2014 / 22:35:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   394 !
   402 !
   395 
   403 
   396 block: method env: envRefNode
   404 block: method env: envRefNode
   397 
   405 
   398 	self stackPush: (IRDecompiler new
   406 	self stackPush: (IRDecompiler new
   777 	^ true
   785 	^ true
   778 !
   786 !
   779 
   787 
   780 endToDo: seqNum
   788 endToDo: seqNum
   781 
   789 
   782 	| start limit incr iter step loopBlock o if test limitExpr init |
   790         | start limit incr iter step loopBlock o if test limitExpr init |
   783 	[
   791         [
   784 		start := self Goto destination.
   792                 start := self Goto destination.
   785 		limit := self Value.
   793                 limit := self Value.
   786 		incr := self Assignment.
   794                 incr := self Assignment.
   787 		iter := incr variable.
   795                 iter := incr variable.
   788 		(incr value isMessage and:
   796                 (incr value isMessage and:
   789 		 [incr value selector == #+ and:
   797                  [incr value selector == #+ and:
   790 		  [incr value receiver isVariable and: 
   798                   [incr value receiver isVariable and: 
   791 		   [incr value receiver binding == iter binding]]]
   799                    [incr value receiver binding == iter binding]]]
   792 		) ifFalse: [self abort].
   800                 ) ifFalse: [self abort].
   793 		step := incr value arguments first.
   801                 step := incr value arguments first.
   794 		loopBlock := self Sequence.
   802                 loopBlock := self Sequence.
   795 		o := self Label destination.
   803                 o := self Label destination.
   796 		if := self IfGoto: seqNum otherwise: o.
   804                 if := self IfGoto: seqNum otherwise: o.
   797 		test := self Value.
   805                 test := self Value.
   798 		(test isMessage and:
   806                 (test isMessage and:
   799 		 [(test selector == #<= or: [test selector == #>=]) and:
   807                  [(test selector == #<= or: [test selector == #>=]) and:
   800 		  [(valueLabelMap at: test arguments first ifAbsent: [self abort]) destination = start]]
   808                   [(valueLabelMap at: test arguments first ifAbsent: [self abort]) destination = start]]
   801 		) ifFalse: [self abort].
   809                 ) ifFalse: [self abort].
   802 		limitExpr := test arguments first.
   810                 limitExpr := test arguments first.
   803 		limitExpr isAssignment ifTrue: [
   811                 limitExpr isAssignment ifTrue: [
   804 			(limitExpr variable binding index == limit binding index 
   812                         (limitExpr variable binding index == limit binding index 
   805 				and:[limitExpr variable binding scope == limit binding scope]) ifFalse: [self abort].
   813                                 and:[limitExpr variable binding scope == limit binding scope]) ifFalse: [self abort].
   806 			limitExpr := limitExpr value.
   814                         limitExpr := limitExpr value.
   807 		].
   815                 ].
   808 		init := test receiver.
   816                 init := test receiver.
   809 		(init isAssignment and: [init variable binding == iter binding])
   817                 (init isAssignment and: [init variable binding == iter binding])
   810 			ifFalse: [self abort].
   818                         ifFalse: [self abort].
   811 	] on: Abort do: [^ false].
   819         ] on: Abort do: [^ false].
   812 	limit isVariable 
   820         limit isVariable 
   813 		ifTrue:[scope 
   821                 ifTrue:[scope 
   814 			removeTemp: limit binding 
   822                         removeTemp: limit binding 
   815 			ifAbsent:[Preferences compileBlocksAsClosures 
   823                         ifAbsent:["Preferences compileBlocksAsClosures"true
   816 				ifFalse:[scope removeTempFromOldBlock: limit]]].
   824                                 ifFalse:[scope removeTempFromOldBlock: limit]]].
   817 	loopBlock := self newBlock: loopBlock.
   825         loopBlock := self newBlock: loopBlock.
   818 	loopBlock arguments: {iter}.
   826         loopBlock arguments: {iter}.
   819 	self stackPush: ((step isLiteral: [:c | c = 1])
   827         self stackPush: ((step isLiteral: [:c | c = 1])
   820 		ifTrue: [RBMessageNode
   828                 ifTrue: [RBMessageNode
   821 				receiver: init value
   829                                 receiver: init value
   822 				selector: #to:do:
   830                                 selector: #to:do:
   823 				arguments: {limitExpr. loopBlock}]
   831                                 arguments: {limitExpr. loopBlock}]
   824 		ifFalse: [RBMessageNode
   832                 ifFalse: [RBMessageNode
   825 				receiver: init value
   833                                 receiver: init value
   826 				selector: #to:by:do:
   834                                 selector: #to:by:do:
   827 				arguments: {limitExpr. step. loopBlock}]).
   835                                 arguments: {limitExpr. step. loopBlock}]).
   828 	self popTop.
   836         self popTop.
   829 	self goto: seqNum.
   837         self goto: seqNum.
   830 	^ true
   838         ^ true
       
   839 
       
   840     "Modified: / 30-10-2014 / 22:37:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   831 !
   841 !
   832 
   842 
   833 endWhile2: seqNum
   843 endWhile2: seqNum
   834 
   844 
   835 	| start loopBlock if test sequence o goto previousStack |
   845 	| start loopBlock if test sequence o goto previousStack |
   921 	mapEmptyStatement := IdentityDictionary new
   931 	mapEmptyStatement := IdentityDictionary new
   922 !
   932 !
   923 
   933 
   924 isExplicitReturn: goto
   934 isExplicitReturn: goto
   925 
   935 
   926 	Preferences compileBlocksAsClosures 
   936         "Preferences compileBlocksAsClosures"true
   927 		ifTrue:[^ goto isRet 
   937                 ifTrue:[^ goto isRet 
   928 			and: [goto mapInstr notNil] 
   938                         and: [goto mapInstr notNil] 
   929 			and: [goto mapInstr isRemote or: [scope isBlockScope not]]]
   939                         and: [goto mapInstr isRemote or: [scope isBlockScope not]]]
   930 		ifFalse: [^goto isRet and: [goto mapInstr isBlockReturnTop not]]
   940                 ifFalse: [^goto isRet and: [goto mapInstr isBlockReturnTop not]]
       
   941 
       
   942     "Modified: / 30-10-2014 / 22:37:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   931 !
   943 !
   932 
   944 
   933 mapNode: node
   945 mapNode: node
   934 
   946 
   935 	currentInstr ifNil: [^ self].
   947 	currentInstr ifNil: [^ self].
   943 	^ self newBlock: sequence return: nil
   955 	^ self newBlock: sequence return: nil
   944 !
   956 !
   945 
   957 
   946 newBlock: sequence return: goto
   958 newBlock: sequence return: goto
   947 
   959 
   948 	| statements block |
   960         | statements block |
   949 	statements := sequence statements.
   961         statements := sequence statements.
   950 	(goto notNil and: [self isExplicitReturn: goto]) ifTrue: [
   962         (goto notNil and: [self isExplicitReturn: goto]) ifTrue: [
   951 		self addReturn: statements from: goto
   963                 self addReturn: statements from: goto
   952 	].
   964         ].
   953 	sequence statements: statements.
   965         sequence statements: statements.
   954 	block := RBBlockNode body: sequence.
   966         block := RBBlockNode body: sequence.
   955 	sequence parent: block.
   967         sequence parent: block.
   956 	Preferences compileBlocksAsClosures ifFalse: [block scope: scope].
   968         "Preferences compileBlocksAsClosures"true ifFalse: [block scope: scope].
   957 	^block
   969         ^block
       
   970 
       
   971     "Modified: / 30-10-2014 / 22:37:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   958 !
   972 !
   959 
   973 
   960 newLiteral: literal
   974 newLiteral: literal
   961 
   975 
   962 	^ RBLiteralNode value: literal
   976 	^ RBLiteralNode value: literal