1"======================================================================
2|
3|   Smalltalk bytecode decompiler
4|
5|
6 ======================================================================"
7
8"======================================================================
9|
10| Copyright 1999, 2000, 2001, 2002, 2003, 2006 Free Software Foundation, Inc.
11| Written by Paolo Bonzini.
12|
13| This file is part of GNU Smalltalk.
14|
15| GNU Smalltalk is free software; you can redistribute it and/or modify it
16| under the terms of the GNU General Public License as published by the Free
17| Software Foundation; either version 2, or (at your option) any later version.
18|
19| GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
20| ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
21| FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
22| details.
23|
24| You should have received a copy of the GNU General Public License along with
25| GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
26| Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
27|
28 ======================================================================"
29
30
31
32RBValueToken subclass: STDecompiledValueToken [
33
34    <comment: nil>
35    <category: 'System-Compiler'>
36
37    length [
38	"Always answer 1 (the size of a bytecode)."
39
40	<category: 'overrides'>
41	^1
42    ]
43]
44
45
46
47Object subclass: STDecompilationContext [
48    | mclass outer method numTemps numArgs tmpNames current jumps instVarNames instVarNamesSet cfg basicBlocks |
49
50    <category: 'System-Compiler'>
51    <comment: 'This class holds the information about the current decompilation,
52including the CFG and the synthetic variable names.
53
54Most of this information is interesting to the decompilers for
55the blocks, which is why the sub-contexts hold a pointer to
56the outer context.'>
57
58    STDecompilationContext class >> on: aCompiledCodeObject class: aClass outer: outerContext [
59	<category: 'instance creation'>
60	^self new
61	    initialize: aCompiledCodeObject
62	    class: aClass
63	    outer: outerContext
64    ]
65
66    initialize: aCompiledCodeObject class: aClass outer: outerContext [
67	"Initialize the receiver's instance variables with information
68	 about decompiling the block or method aCompiledCodeObject, found in
69	 the aClass class.  If we are to decompile a block, the context
70	 for the outer method is found in outerContext."
71
72	<category: 'initialization'>
73	mclass := aClass.
74	outer := outerContext.
75	method := aCompiledCodeObject.
76	numTemps := outer isNil ifTrue: [0] ifFalse: [outer numTemps].
77	numArgs := outer isNil ifTrue: [0] ifFalse: [outer numArgs].
78	instVarNames := aClass allInstVarNames.
79	instVarNamesSet := instVarNames asSet.
80	tmpNames := IdentityDictionary new.
81	jumps := IdentityDictionary new.
82	0 to: self methodNumArgs - 1
83	    do: [:index | tmpNames at: index put: self newArgName].
84	aCompiledCodeObject dispatchTo: self with: nil.
85	self buildCFG
86    ]
87
88    buildCFG [
89	"Build the control-flow graph of the object to be decompiled."
90
91	<category: 'initialization'>
92	| basicBlockBoundaries n |
93	basicBlockBoundaries := jumps keys collect: [:each | each + 2].
94	basicBlockBoundaries addAll: (jumps values collect: [:each | each value]).
95	basicBlockBoundaries add: method size + 2.
96
97	"Build a map from bytecode numbers to basic block ids"
98	basicBlocks := OrderedCollection new.
99	cfg := OrderedCollection new.
100	n := 1.
101	basicBlockBoundaries asSortedCollection inject: 1
102	    into:
103		[:old :boundary |
104		boundary > old
105		    ifTrue:
106			[boundary - old timesRepeat: [basicBlocks add: n].
107			cfg addLast: (STControlFlowGraphNode id: n).
108			n := n + 1].
109		boundary].
110
111	"Now use it to build the CFG"
112	jumps keysAndValuesDo:
113		[:key :each |
114		(self cfgNodeAt: key)
115		    addSuccessor: each key -> (self cfgNodeAt: each value)].
116
117	"Add arcs for falling off the basic block."
118	cfg
119	    from: 1
120	    to: cfg size - 1
121	    do:
122		[:each |
123		each succ isNil
124		    ifTrue: [each addSuccessor: #jump -> (cfg at: each id + 1)].
125		(each succ at: 1) key = #jumpTrue
126		    ifTrue: [each addSuccessor: #jumpFalse -> (cfg at: each id + 1)].
127		(each succ at: 1) key = #jumpFalse
128		    ifTrue: [each addSuccessor: #jumpTrue -> (cfg at: each id + 1)]].
129
130	"Sort in depth-first order"
131	(cfg at: 1) computeDfnums: 1
132    ]
133
134    outer [
135	"Answer the outer decompilation context"
136
137	<category: 'accessing'>
138	^outer
139    ]
140
141    mclass [
142	"Answer the class in which the method we are decompiling lives"
143
144	<category: 'accessing'>
145	^mclass
146    ]
147
148    method [
149	"Answer the method we are decompiling"
150
151	<category: 'accessing'>
152	^method
153    ]
154
155    cfg [
156	"Answer an Array with all the nodes in the method's control-flow
157	 graph."
158
159	<category: 'accessing'>
160	^cfg
161    ]
162
163    cfgNodeAt: bytecode [
164	"Answer the node of the control-flow graph that contains information
165	 for the basic block of which the given bytecode index is part"
166
167	<category: 'accessing'>
168	^cfg at: (basicBlocks at: bytecode)
169    ]
170
171    outerTemporaryAt: anIndex scopes: scopes [
172	"Answer the name of the anIndex-th temporary in the scopes-th outer
173	 scope"
174
175	<category: 'accessing'>
176	^scopes > 0
177	    ifTrue: [self outer outerTemporaryAt: anIndex scopes: scopes - 1]
178	    ifFalse: [self temporaryAt: anIndex]
179    ]
180
181    instVarNameAt: anIndex [
182	"Answer the name of the anIndex-th instance variable of the class
183	 in which the decompiled method lives."
184
185	<category: 'accessing'>
186	^instVarNames at: anIndex + 1
187    ]
188
189    temporaryAt: anIndex [
190	"Answer the name of the anIndex-th temporary of the decompiled method."
191
192	<category: 'accessing'>
193	^tmpNames at: anIndex
194    ]
195
196    temporaryNames [
197	"Answer the name of all the temporaries of the decompiled method."
198
199	<category: 'accessing'>
200	^tmpNames values
201    ]
202
203    methodNumArgs [
204	"Answer the number of arguments that the decompiled method receives."
205
206	<category: 'accessing'>
207	^method numArgs
208    ]
209
210    numArgs [
211	"Answer the number of argXXX variables that have been defined so far."
212
213	<category: 'accessing'>
214	^numArgs
215    ]
216
217    numTemps [
218	"Answer the number of tXXX variables that have been defined so far."
219
220	<category: 'accessing'>
221	^numTemps
222    ]
223
224    newArgName [
225	"Answer a new argXXX variable"
226
227	<category: 'accessing'>
228	| candidate |
229
230	[candidate := 'arg' , (numArgs := numArgs + 1) printString.
231	instVarNamesSet includes: candidate]
232		whileTrue.
233	^candidate
234    ]
235
236    newTemporaryName [
237	"Answer a new tXXX variable"
238
239	<category: 'accessing'>
240	| candidate |
241
242	[candidate := 't' , (numTemps := numTemps + 1) printString.
243	instVarNamesSet includes: candidate]
244		whileTrue.
245	^candidate
246    ]
247
248    invalidOpcode: unused [
249	"Signal an error"
250
251	<category: 'analyzing'>
252	self error: 'invalid opcode'
253    ]
254
255    pushInstVar: anIndex with: unused [
256	<category: 'analyzing'>
257
258    ]
259
260    storeInstVar: anIndex with: unused [
261	<category: 'analyzing'>
262
263    ]
264
265    makeDirtyBlock: unused [
266	<category: 'analyzing'>
267
268    ]
269
270    pushTemporary: anIndex outer: scopes with: unused [
271	"Create the name of the given temporary"
272
273	<category: 'analyzing'>
274	scopes > 0
275	    ifTrue: [self pushTemporary: anIndex with: unused]
276	    ifFalse:
277		[outer
278		    pushTemporary: anIndex
279		    outer: scopes - 1
280		    with: unused]
281    ]
282
283    storeTemporary: anIndex outer: scopes with: unused [
284	"Create the name of the given temporary"
285
286	<category: 'analyzing'>
287	scopes > 0
288	    ifTrue: [self storeTemporary: anIndex with: unused]
289	    ifFalse:
290		[outer
291		    storeTemporary: anIndex
292		    outer: scopes - 1
293		    with: unused]
294    ]
295
296    pushTemporary: anIndex with: unused [
297	"Create the name of the given temporary"
298
299	<category: 'analyzing'>
300	tmpNames at: anIndex ifAbsentPut: [self newTemporaryName]
301    ]
302
303    storeTemporary: anIndex with: unused [
304	"Create the name of the given temporary"
305
306	<category: 'analyzing'>
307	tmpNames at: anIndex ifAbsentPut: [self newTemporaryName]
308    ]
309
310    popIntoArray: anIndex with: unused [
311	<category: 'analyzing'>
312
313    ]
314
315    pushLiteral: anObject with: unused [
316	<category: 'analyzing'>
317
318    ]
319
320    pushGlobal: anObject with: unused [
321	<category: 'analyzing'>
322
323    ]
324
325    storeGlobal: anObject with: unused [
326	<category: 'analyzing'>
327
328    ]
329
330    pushSelf: unused [
331	<category: 'analyzing'>
332
333    ]
334
335    popStackTop: unused [
336	<category: 'analyzing'>
337
338    ]
339
340    dupStackTop: unused [
341	<category: 'analyzing'>
342
343    ]
344
345    exitInterpreter: unused [
346	<category: 'analyzing'>
347
348    ]
349
350    returnFromContext: unused [
351	"Returns are treated as jumps to past the final bytecode"
352
353	<category: 'analyzing'>
354	self jumpTo: method size + 1 with: unused
355    ]
356
357    returnFromMethod: unused [
358	"Returns are treated as jumps to past the final bytecode"
359
360	<category: 'analyzing'>
361	self jumpTo: method size + 1 with: unused
362    ]
363
364    popJumpIfFalseTo: destination with: unused [
365	"Record the jump"
366
367	<category: 'analyzing'>
368	jumps at: current put: #jumpFalse -> destination
369    ]
370
371    popJumpIfTrueTo: destination with: unused [
372	"Record the jump"
373
374	<category: 'analyzing'>
375	jumps at: current put: #jumpTrue -> destination
376    ]
377
378    jumpTo: destination with: unused [
379	"Record the jump"
380
381	<category: 'analyzing'>
382	jumps at: current put: #jump -> destination
383    ]
384
385    lineNo: n with: unused [
386	<category: 'analyzing'>
387
388    ]
389
390    superSend: aSymbol numArgs: anInteger with: unused [
391	<category: 'analyzing'>
392
393    ]
394
395    send: aSymbol numArgs: anInteger with: unused [
396	<category: 'analyzing'>
397
398    ]
399
400    bytecodeIndex: byte with: unused [
401	<category: 'analyzing'>
402	current := byte
403    ]
404]
405
406
407
408Magnitude subclass: STControlFlowGraphNode [
409    | id dfnum pred succ fallThrough statements stack |
410
411    <category: 'System-Compiler'>
412    <comment: 'This class is a node in the CFG of a method.  It knows how
413to simplify itself to a single node that uses Smalltalk''s
414control-structures-as-messages.'>
415
416    STControlFlowGraphNode class >> id: id [
417	"Create a new instance of the receiver"
418
419	<category: 'instance creation'>
420	^self new id: id
421    ]
422
423    printOn: aStream [
424	"Print a textual representation of the receiver on aStream"
425
426	<category: 'printing'>
427	aStream
428	    print: self id;
429	    nextPutAll: ' df=';
430	    print: self dfnum.
431	self succ isNil
432	    ifFalse:
433		[aStream
434		    print: (self succ collect: [:each | each key -> each value id]) asArray].
435	statements isNil
436	    ifFalse:
437		[statements do:
438			[:each |
439			aStream
440			    nl;
441			    space: 4;
442			    print: each]].
443	aStream nl
444    ]
445
446    printTreeOn: aStream [
447	"Print a textual representation of the receiver and all of its
448	 successors on aStream"
449
450	<category: 'printing'>
451	(self withAllSuccessors asSortedCollection: [:a :b | a id < b id]) do:
452		[:node |
453		aStream
454		    print: node;
455		    nl]
456    ]
457
458    addPredecessor: node [
459	"Private - Add `node' to the set of predecessors of the receiver."
460
461	<category: 'private'>
462	pred := pred isNil ifTrue: [{node}] ifFalse: [pred copyWith: node]
463    ]
464
465    removeSuccessor: node [
466	"Private - Remove `node' from the set of successors of the receiver."
467
468	<category: 'private'>
469	succ isNil
470	    ifFalse:
471		[succ := succ reject: [:each | each value = node].
472		succ isEmpty ifTrue: [succ := nil]]
473    ]
474
475    removePredecessor: node [
476	"Private - Remove `node' from the set of predecessors of the receiver."
477
478	<category: 'private'>
479	pred isNil
480	    ifFalse:
481		[pred := pred copyWithout: node.
482		pred isEmpty ifTrue: [pred := nil]]
483    ]
484
485    addAllSuccessorsTo: aSet [
486	"Private - Add all the direct and indirect successors of the receiver
487	 to aSet."
488
489	<category: 'private'>
490	succ isNil ifTrue: [^aSet].
491	succ do:
492		[:each |
493		(aSet includes: each value)
494		    ifFalse:
495			[aSet add: each value.
496			each value addAllSuccessorsTo: aSet]].
497	^aSet
498    ]
499
500    computeDfnums: n [
501	"Private - Number the receiver and all of its direct and
502	 indirect successors in depth-first order, starting from n."
503
504	<category: 'private'>
505	| num |
506	self dfnum isNil ifFalse: [^n].
507	self dfnum: n.
508	num := n + 1.
509	self succ isNil
510	    ifFalse: [succ do: [:each | num := each value computeDfnums: num]].
511	^num
512    ]
513
514    < anObject [
515	"Sort in depth-first order"
516
517	<category: 'comparison'>
518	^self dfnum < anObject dfnum
519    ]
520
521    = anObject [
522	"Sort in depth-first order"
523
524	<category: 'comparison'>
525	^self class == anObject class and: [self dfnum = anObject dfnum]
526    ]
527
528    hash [
529	"Sort in depth-first order"
530
531	<category: 'comparison'>
532	^self dfnum
533    ]
534
535    allSuccessors [
536	"Answer the set of all direct and indirect successors of
537	 the receiver"
538
539	<category: 'accessing'>
540	^self addAllSuccessorsTo: Set new
541    ]
542
543    withAllSuccessors [
544	"Answer the set of all the nodes in the receiver's CFG, that
545	 is the node and all of its direct and indirect successors."
546
547	<category: 'accessing'>
548	^(self addAllSuccessorsTo: Set new)
549	    add: self;
550	    yourself
551    ]
552
553    dfnum [
554	"Answer the progressive number of the receiver in a depth-first
555	 visit of the graph."
556
557	<category: 'accessing'>
558	^dfnum
559    ]
560
561    dfnum: n [
562	"Set the progressive number of the receiver in a depth-first
563	 visit of the graph."
564
565	<category: 'accessing'>
566	dfnum := n
567    ]
568
569    id [
570	"Answer a numeric identifier for the receiver.  Consecutive indexes
571	 represent basic blocks that are adjacent in memory."
572
573	<category: 'accessing'>
574	^id
575    ]
576
577    id: n [
578	"Set the numeric identifier for the receiver.  Consecutive indexes
579	 represent basic blocks that are adjacent in memory."
580
581	<category: 'accessing'>
582	id := n
583    ]
584
585    pred [
586	"Answer the set of predecessors of the receiver."
587
588	<category: 'accessing'>
589	^pred
590    ]
591
592    succ [
593	"Answer the set of successors of the receiver."
594
595	<category: 'accessing'>
596	^succ
597    ]
598
599    succ: newSucc [
600	"Set the set of successors of the receiver to be newSucc.
601	 newSucc should hold associations that represent the kind
602	 of jump (#jump, #jumpTrue, #jumpFalse) in the key, and
603	 the destination basic block in the value."
604
605	<category: 'accessing'>
606	succ isNil
607	    ifFalse:
608		[succ do: [:each | each value removePredecessor: self].
609		succ := nil].
610	succ := newSucc.
611	succ isNil ifTrue: [^self].
612	succ do: [:assoc | assoc value addPredecessor: self]
613    ]
614
615    statements [
616	"Answer the set of statements executed by the receiver"
617
618	<category: 'accessing'>
619	^ statements ifNil: [ #() ]
620    ]
621
622    statements: aCollection [
623	"Set the set of statements executed by the receiver"
624
625	<category: 'accessing'>
626	statements := aCollection
627    ]
628
629    stack [
630	"Answer the state of the stack after the receiver completes
631	 its execution"
632
633	<category: 'accessing'>
634	stack isNil ifTrue: [stack := OrderedCollection new].
635	^stack
636    ]
637
638    stack: aCollection [
639	"Set the state of the stack after the receiver completes
640	 its execution"
641
642	<category: 'accessing'>
643	stack := aCollection
644    ]
645
646    fallThroughIfFalse [
647	"Answer whether the receiver ends with a `jump if true'
648	 bytecode"
649
650	<category: 'accessing'>
651	^fallThrough = #jumpFalse
652    ]
653
654    fallThroughIfTrue [
655	"Answer whether the receiver ends with a `jump if false'
656	 bytecode"
657
658	<category: 'accessing'>
659	^fallThrough = #jumpTrue
660    ]
661
662    addSuccessor: kindBlockAssociation [
663	"Add the successor represented by kindBlockAssociation,
664	 which should be an association that represents the kind
665	 of jump (#jump, #jumpTrue, #jumpFalse) in the key, and
666	 the destination basic block in the value."
667
668	<category: 'accessing'>
669	kindBlockAssociation value id = (self id + 1)
670	    ifTrue: [fallThrough := kindBlockAssociation key].
671	succ := succ isNil
672		    ifTrue: [{kindBlockAssociation}]
673		    ifFalse: [succ copyWith: kindBlockAssociation].
674	kindBlockAssociation value addPredecessor: self
675    ]
676
677    blkNode: statements arguments: args [
678	"Private - Answer an RBBlockNode with the given statements
679	 and arguments."
680
681	<category: 'simplification'>
682	^(RBBlockNode new)
683	    body: (self seqNode: statements);
684	    arguments: args
685    ]
686
687    blkNode: statements [
688	"Private - Answer an RBBlockNode with the given statements."
689
690	<category: 'simplification'>
691	^(RBBlockNode new)
692	    body: (self seqNode: statements);
693	    arguments: #()
694    ]
695
696    msgNode: arguments receiver: receiver selector: aSymbol [
697	"Private - Answer an RBMessageNode with the given arguments,
698	 receiver and selector."
699
700	<category: 'simplification'>
701	| selParts |
702	selParts := aSymbol keywords
703		    collect: [:each | RBValueToken new value: each].
704	^(RBMessageNode new)
705	    arguments: arguments;
706	    receiver: receiver;
707	    selectorParts: selParts
708    ]
709
710    seqNode: statements [
711	"Private - Answer an RBSequenceNode with the given statements."
712
713	<category: 'simplification'>
714	^(RBSequenceNode new)
715	    temporaries: #();
716	    statements: statements;
717	    periods: #()
718    ]
719
720    disconnect [
721	"Disconnect the receiver from the graph (removing
722	 all arcs that point to it or depart from it)."
723
724	<category: 'simplification'>
725	pred isNil
726	    ifFalse:
727		[pred do: [:each | each removeSuccessor: self].
728		pred := nil].
729	self succ: nil
730    ]
731
732    disconnectSuccessorsAndMerge: newSucc [
733	"Disconnect the receiver's successors from the graph (removing
734	 all arcs that point to them or depart from them),
735	 then try to merge the receiver with its predecessor
736	 (if there is only one after the disconnection) and
737	 possibly with the new successors, newSucc (if there
738	 is only one and it has no other predecessors than the
739	 receiver)."
740
741	<category: 'simplification'>
742	succ do: [:each | each value disconnect].
743	self merge: newSucc
744    ]
745
746    merge: succSet [
747	"Try to merge the receiver with its predecessor
748	 (if there is only one after the disconnection) and
749	 possibly with the new successors, succSet (if there
750	 is only one and it has no other predecessors than the
751	 receiver)."
752
753	<category: 'simplification'>
754	| newSelf newSucc theSucc |
755	newSucc := succSet.
756	newSelf := self.
757	self succ: newSucc.
758	newSelf pred size = 1
759	    ifTrue:
760		[newSelf := pred at: 1.
761		newSelf statements addAllLast: self statements.
762		self disconnect.
763		newSelf succ: newSucc].
764
765	[newSucc size = 1 ifFalse: [^self].
766	theSucc := (newSucc at: 1) value.
767	theSucc pred size = 1 ifFalse: [^self].
768	newSelf statements addAllLast: theSucc statements.
769	newSucc := theSucc succ.
770	theSucc disconnect]
771		repeat
772    ]
773
774    simplify [
775	"Recognize simple control structures in the receiver and
776	 reduce them to a single basic block that sends the appropriate
777	 Smalltalk messages."
778
779	<category: 'simplification'>
780	self
781	    simplifyRepeat;
782	    simplifyIf;
783	    simplifyLoop
784    ]
785
786    simplifyIf: cond then: arm2 else: arm1 ifTrueIfFalse: ifTrueIfFalse [
787	"Simplify a two-way conditional.  cond used to be the
788	 last statement of the receiver, arm1 and arm2 are the
789	 receiver's successor basic blocks."
790
791	<category: 'simplification'>
792	"'resolving if/then/else' displayNl."
793
794	| block1 block2 |
795	block2 := self blkNode: arm2 statements.
796	block1 := self blkNode: arm1 statements.
797	self statements addLast: (self
798		    msgNode:
799			{block1.
800			block2}
801		    receiver: cond
802		    selector: (ifTrueIfFalse
803			    ifTrue: [#ifTrue:ifFalse:]
804			    ifFalse: [#ifFalse:ifTrue:]))
805    ]
806
807    simplifyIf: cond then: arm ifTrue: ifTrue [
808	"Simplify a one-way conditional.  cond used to be the
809	 last statement of the receiver, arm is one of the
810	 receiver's successor basic blocks."
811
812	<category: 'simplification'>
813	"'resolving if/then' displayNl."
814
815	| seq block |
816	block := self blkNode: arm statements.
817	self statements addLast: (self
818		    msgNode: {block}
819		    receiver: cond
820		    selector: (ifTrue ifTrue: [#ifTrue:] ifFalse: [#ifFalse:]))
821    ]
822
823    simplifyIf [
824	"Recognize conditional control structures where the
825	 receiver is the header, and simplify them."
826
827	<category: 'simplification'>
828	| cond arm1 arm2 |
829	succ size < 2 ifTrue: [^false].
830	arm1 := (self succ at: 1) value.
831	arm2 := (self succ at: 2) value.
832	((arm1 succ at: 1) value = (arm2 succ at: 1) value
833	    and: [(arm1 succ at: 1) value ~= self and: [(arm2 succ at: 1) value ~= self]])
834		ifTrue:
835		    [self
836			simplifyIf: self statements removeLast
837			    then: arm1
838			    else: arm2
839			    ifTrueIfFalse: self fallThroughIfFalse;
840			disconnectSuccessorsAndMerge: arm1 succ.
841		    ^true].
842	((arm2 succ at: 1) value = arm1 and: [(arm2 succ at: 1) value ~= self])
843	    ifTrue:
844		[self
845		    simplifyIf: self statements removeLast
846			then: arm2
847			ifTrue: self fallThroughIfTrue;
848		    disconnectSuccessorsAndMerge: arm1 succ.
849		^true].
850	^false
851    ]
852
853    simplifyWhile: body whileTrue: whileTrue [
854	"Simplify a #whileTrue: or #whileFalse: control structure
855	 where the receiver will be the receiver block, and body
856	 the argument block."
857
858	<category: 'simplification'>
859	"'resolving while' displayNl."
860
861	| cond block |
862	cond := self blkNode: self statements.
863	block := self blkNode: body statements.
864	self
865	    statements: (OrderedCollection with: (self
866			    msgNode: {block}
867			    receiver: cond
868			    selector: (whileTrue ifTrue: [#whileTrue:] ifFalse: [#whileFalse:])))
869    ]
870
871    simplifyTimesRepeat: body newSucc: newSucc [
872	"Simplify a #timesRepeat: control structure."
873
874	<category: 'simplification'>
875	"'resolving timesRepeat' displayNl."
876
877	| to block |
878	(newSucc statements)
879	    removeFirst;
880	    removeFirst.
881	(self statements)
882	    removeLast;
883	    removeLast.
884	(body statements)
885	    removeLast;
886	    removeLast.
887	((self pred at: 2) statements)
888	    removeLast;
889	    removeLast.
890	to := self statements removeLast.
891	block := self blkNode: body statements.
892	self statements addLast: (self
893		    msgNode: {block}
894		    receiver: to
895		    selector: #timesRepeat:)
896    ]
897
898    simplifyToByDo: body newSucc: newSucc [
899	"Simplify a #to:do: or #to:by:do: control structure."
900
901	<category: 'simplification'>
902	| variable from to by block |
903	(self statements at: self statements size - 2) isAssignment
904	    ifFalse: [^self simplifyTimesRepeat: body newSucc: newSucc].
905
906	"'resolving to/by/do' displayNl."
907	(newSucc statements)
908	    removeFirst;
909	    removeFirst.
910	self statements removeLast.
911	to := self statements removeLast.
912	from := self statements last value.
913	variable := self statements removeLast variable.
914	by := body statements removeLast value arguments at: 1.
915	(body statements)
916	    removeLast;
917	    removeLast;
918	    removeLast.
919	((self pred at: 2) statements)
920	    removeLast;
921	    removeLast;
922	    removeLast;
923	    removeLast.
924	block := self blkNode: body statements arguments: {variable}.
925	self statements addLast: (self
926		    msgNode: (by = 1
927			    ifTrue:
928				[
929				{to.
930				block}]
931			    ifFalse:
932				[
933				{to.
934				by.
935				block}])
936		    receiver: from
937		    selector: (by = 1 ifFalse: [#to:by:do:] ifTrue: [#to:do:]))
938    ]
939
940    simplifyLoop [
941	"Recognize looping control structures where the
942	 receiver is the dominator, and simplify them."
943
944	<category: 'simplification'>
945	| middle bottom |
946	succ size < 2 ifTrue: [^false].
947	pred isNil ifTrue: [^false].
948	bottom := succ detect: [:each | pred includes: each value] ifNone: [^false].
949	middle := succ detect: [:each | each ~= bottom].
950	middle value statements size = 0
951	    ifFalse:
952		[self simplifyToByDo: bottom value newSucc: middle value.
953		self disconnectSuccessorsAndMerge: {middle}]
954	    ifTrue:
955		[self simplifyWhile: bottom value whileTrue: self fallThroughIfFalse.
956		self disconnectSuccessorsAndMerge: middle value succ].
957	^true
958    ]
959
960    simplifyRepeat [
961	"Recognize and simplify infinite loops (#repeat)."
962
963	<category: 'simplification'>
964	| block |
965	self succ isNil ifTrue: [^false].
966	(self succ at: 1) value = self ifFalse: [^false].
967
968	"'resolving repeat' displayNl."
969	block := self blkNode: self statements.
970	self statements:
971		{self
972		    msgNode: #()
973		    receiver: block
974		    selector: #repeat}.
975	self merge: nil.
976	^true
977    ]
978]
979
980
981
982Object subclass: STDecompiler [
983    | context stack statements isBlock current bbList bb |
984
985    <category: 'System-Compiler'>
986    <comment: 'This class converts bytecodes back to parse trees.'>
987
988    STDecompiler class >> decompile: aSelector in: aClass [
989	"Answer the source code for the selector aSelector of the
990	 given class"
991
992	<category: 'instance creation'>
993	| node |
994	node := self parseTreeForMethod: aClass >> aSelector in: aClass.
995	^RBFormatter new format: node
996    ]
997
998    STDecompiler class >> parseTreeForMethod: aMethod in: aClass [
999	"Answer the parse tree for the method aMethod of the
1000	 given class"
1001
1002	<category: 'instance creation'>
1003	^self new decompileMethod: (STDecompilationContext
1004		    on: aMethod
1005		    class: aClass
1006		    outer: nil)
1007    ]
1008
1009    STDecompiler class >> parseTreeForBlock: aBlock from: aDecompilerObject [
1010	"Answer the parse tree for the block aBlock, considering
1011	 the information already dug by aDecompilerObject"
1012
1013	<category: 'instance creation'>
1014	^self new decompileBlock: (STDecompilationContext
1015		    on: aBlock
1016		    class: aDecompilerObject context mclass
1017		    outer: aDecompilerObject context)
1018    ]
1019
1020    STDecompiler class >> testRepeat [
1021	"A meaningless method to test #repeat simplification"
1022
1023	<category: 'test'>
1024	| c |
1025	c := 'c'.
1026
1027	[c * 2.
1028	true ifTrue: [c * c].
1029	2 * c] repeat
1030    ]
1031
1032    STDecompiler class >> testIfTrue [
1033	"A meaningless method to test #ifTrue: simplification"
1034
1035	<category: 'test'>
1036	| a b c |
1037	a := 'a'.
1038	b := 'b'.
1039	c := 'c'.
1040	a = b ifTrue: [c * c]
1041    ]
1042
1043    STDecompiler class >> testWhile [
1044	"A meaningless method to test #whileTrue: simplification"
1045
1046	<category: 'test'>
1047	| a b c |
1048	a := 'a'.
1049	b := 'b'.
1050	c := 'c'.
1051
1052	[b = 1.
1053	1 = b] whileFalse:
1054		    [c * 1.
1055		    1 * c].
1056
1057	[b = 2.
1058	2 = b] whileTrue:
1059		    [c * 2.
1060		    2 * c]
1061    ]
1062
1063    STDecompiler class >> testToByDo [
1064	"A meaningless method to test #to:by:do: simplification"
1065
1066	<category: 'test'>
1067	| a b c |
1068	a := 'a'.
1069	b := 'b'.
1070	c := 'c'.
1071	a to: b
1072	    by: 3
1073	    do:
1074		[:i |
1075		a = b.
1076		c = i]
1077    ]
1078
1079    STDecompiler class >> test [
1080	"Do some tests"
1081
1082	<category: 'test'>
1083	(self decompile: #testToByDo in: STDecompiler class) displayNl.
1084	'' displayNl.
1085	(self decompile: #testWhile in: STDecompiler class) displayNl.
1086	'' displayNl.
1087	(self decompile: #testIfTrue in: STDecompiler class) displayNl.
1088	'' displayNl.
1089	(self decompile: #testRepeat in: STDecompiler class) displayNl.
1090	'' displayNl.
1091	(self decompile: #path in: VariableBinding) displayNl.
1092	'' displayNl.
1093	(self decompile: #bindWith: in: CharacterArray) displayNl.
1094	'' displayNl.
1095	(self decompile: #detect: in: Iterable) displayNl.
1096	'' displayNl.
1097	(self decompile: #key:value:environment: in: HomedAssociation class)
1098	    displayNl.
1099	'' displayNl.
1100	(self decompile: #storeOn: in: VariableBinding) displayNl.
1101	'' displayNl.
1102	(self decompile: #contents in: MappedCollection) displayNl.
1103	'' displayNl.
1104	(self decompile: #collect: in: MappedCollection) displayNl.
1105	'' displayNl.
1106	(self decompile: #repeat in: BlockClosure) displayNl.
1107	'' displayNl.
1108	(self decompile: #binaryRepresentationObject in: Object) displayNl.
1109	'' displayNl.
1110	(self decompile: #whileTrue: in: BlockClosure) displayNl.
1111	'' displayNl.
1112	(self decompile: #become: in: Object) displayNl.
1113	'' displayNl.
1114	(self decompile: #timesRepeat: in: Integer) displayNl
1115    ]
1116
1117    context [
1118	<category: 'auxiliary'>
1119	^context
1120    ]
1121
1122    source [
1123	"Answer a dummy source code object to be used to insert
1124	 primitive names in the decompiled code."
1125
1126	<category: 'auxiliary'>
1127	^context method primitive > 0
1128	    ifTrue:
1129		['<primitive: %1>' % {VMPrimitives keyAtValue: context method primitive}]
1130	    ifFalse: ['']
1131    ]
1132
1133    tags: source [
1134	<category: 'auxiliary'>
1135	^source isEmpty ifTrue: [#()] ifFalse: [{1 to: source size}]
1136    ]
1137
1138    argumentNames [
1139	<category: 'auxiliary'>
1140	^(0 to: context methodNumArgs - 1)
1141	    collect: [:each | context temporaryAt: each]
1142    ]
1143
1144    arguments [
1145	<category: 'auxiliary'>
1146	^self argumentNames collect: [:each | self varNode: each]
1147    ]
1148
1149    selectorParts: aSymbol [
1150	<category: 'auxiliary'>
1151	^aSymbol keywords
1152	    collect: [:each | RBValueToken value: each start: current]
1153    ]
1154
1155    temporaries [
1156	<category: 'auxiliary'>
1157	^self temporaryNames collect: [:each | self varNode: each]
1158    ]
1159
1160    temporaryNames [
1161	<category: 'auxiliary'>
1162	^(context temporaryNames asOrderedCollection)
1163	    removeAll: self argumentNames;
1164	    yourself
1165    ]
1166
1167    litNode: anObject [
1168	<category: 'auxiliary'>
1169	| tok |
1170	anObject class == BlockClosure
1171	    ifTrue: [^self class parseTreeForBlock: anObject block from: self].
1172	tok := anObject class == Association
1173		    ifFalse: [RBLiteralToken value: anObject start: current]
1174		    ifTrue: [RBBindingToken value: anObject path start: current].
1175	^RBLiteralNode new literalToken: tok
1176    ]
1177
1178    varNode: name [
1179	<category: 'auxiliary'>
1180	^RBVariableNode new
1181	    identifierToken: (STDecompiledValueToken value: name start: current)
1182    ]
1183
1184    assignment: name [
1185	<category: 'auxiliary'>
1186	^(RBAssignmentNode new)
1187	    value: stack removeLast;
1188	    variable: (self varNode: name)
1189    ]
1190
1191    decompileBlock: stDecompilationContext [
1192	<category: 'decompilation'>
1193	isBlock := true.
1194	^(RBBlockNode new)
1195	    body: (self decompileBody: stDecompilationContext);
1196	    arguments: self arguments;
1197	    yourself
1198    ]
1199
1200    decompileMethod: stDecompilationContext [
1201	<category: 'decompilation'>
1202	| parseNode |
1203	isBlock := false.
1204	^(parseNode := RBMethodNode new)
1205	    body: (self decompileBody: stDecompilationContext);
1206	    selectorParts: (self selectorParts: context method selector);
1207	    source: self source;
1208	    tags: (self tags: parseNode source);
1209	    arguments: self arguments;
1210	    yourself
1211    ]
1212
1213    decompileBody: stDecompilationContext [
1214	<category: 'decompilation'>
1215	| seq |
1216	context := stDecompilationContext.
1217	stack := OrderedCollection new.
1218	bbList := SortedCollection new.
1219	context method dispatchTo: self with: nil.
1220	self bytecodeIndex: context method size + 1 with: nil.
1221	self simplify.
1222	seq := (RBSequenceNode new)
1223		    temporaries: self temporaries;
1224		    statements: (context cfg at: 1) statements;
1225		    periods: #().
1226	^seq
1227    ]
1228
1229    doCascade: send [
1230	<category: 'decompilation'>
1231	(stack notEmpty and: [stack last isCascade])
1232	    ifFalse:
1233		[stack
1234		    addLast: (RBCascadeNode new messages: (OrderedCollection with: send))]
1235	    ifTrue:
1236		[send parent: stack last.
1237		stack last messages addLast: send]
1238    ]
1239
1240    endStatement [
1241	<category: 'decompilation'>
1242	statements addLast: stack removeLast
1243    ]
1244
1245    invalidOpcode: unused [
1246	<category: 'analyzing'>
1247	self error: 'invalid opcode'
1248    ]
1249
1250    makeDirtyBlock: unused [
1251	<category: 'analyzing'>
1252
1253    ]
1254
1255    pushInstVar: anIndex with: unused [
1256	<category: 'analyzing'>
1257	stack addLast: (self varNode: (context instVarNameAt: anIndex))
1258    ]
1259
1260    storeInstVar: anIndex with: unused [
1261	<category: 'analyzing'>
1262	stack addLast: (self assignment: (context instVarNameAt: anIndex))
1263    ]
1264
1265    pushTemporary: anIndex outer: scopes with: unused [
1266	<category: 'analyzing'>
1267	stack
1268	    addLast: (self varNode: (context outerTemporaryAt: anIndex scopes: scopes))
1269    ]
1270
1271    storeTemporary: anIndex outer: scopes with: unused [
1272	<category: 'analyzing'>
1273	stack addLast: (self
1274		    assignment: (context outerTemporaryAt: anIndex scopes: scopes))
1275    ]
1276
1277    pushTemporary: anIndex with: unused [
1278	<category: 'analyzing'>
1279	stack addLast: (self varNode: (context temporaryAt: anIndex))
1280    ]
1281
1282    storeTemporary: anIndex with: unused [
1283	<category: 'analyzing'>
1284	stack addLast: (self assignment: (context temporaryAt: anIndex))
1285    ]
1286
1287    popIntoArray: anIndex with: unused [
1288	<category: 'analyzing'>
1289	| value |
1290	value := stack removeLast.
1291	anIndex = 0
1292	    ifTrue:
1293		[stack removeLast.
1294		stack
1295		    addLast: (RBArrayConstructorNode new body: ((RBSequenceNode new)
1296				    temporaries: #();
1297				    statements: OrderedCollection new;
1298				    periods: #()))].
1299	stack last body addNode: value
1300    ]
1301
1302    pushLiteral: anObject with: unused [
1303	<category: 'analyzing'>
1304	stack addLast: (self litNode: anObject)
1305    ]
1306
1307    pushGlobal: anObject with: unused [
1308	<category: 'analyzing'>
1309	stack addLast: (self varNode: anObject path)
1310    ]
1311
1312    storeGlobal: anObject with: unused [
1313	<category: 'analyzing'>
1314	stack addLast: (self assignment: anObject path)
1315    ]
1316
1317    pushSelf: unused [
1318	<category: 'analyzing'>
1319	stack addLast: (self varNode: 'self')
1320    ]
1321
1322    isCascadeLast [
1323	<category: 'analyzing'>
1324	^stack size >= 2 and: [(stack at: stack size - 1) isCascade]
1325    ]
1326
1327    isCascade [
1328	<category: 'analyzing'>
1329	(stack size >= 3 and: [(stack at: stack size - 2) isCascade])
1330	    ifTrue: [^true].
1331	^stack size >= 2 and:
1332		[stack last isMessage
1333		    and: [(stack at: stack size - 1) == stack last receiver]]
1334    ]
1335
1336    popStackTop: unused [
1337	<category: 'analyzing'>
1338	| send receiver |
1339	self isCascade ifFalse: [^self endStatement].
1340
1341	"There are two possible cases:
1342
1343	 the receiver		-->	an RBCascadeNode
1344	 the new message send		the receiver
1345
1346	 the RBCascadeNode		augmented RBCascadeNode
1347	 the receiver		-->	the receiver
1348	 the new message send"
1349	send := stack removeLast.
1350	receiver := stack removeLast.
1351	self doCascade: send.
1352	stack addLast: receiver
1353    ]
1354
1355    dupStackTop: unused [
1356	<category: 'analyzing'>
1357	stack addLast: (stack at: stack size)
1358    ]
1359
1360    exitInterpreter: unused [
1361	<category: 'analyzing'>
1362
1363    ]
1364
1365    returnFromContext: unused [
1366	<category: 'analyzing'>
1367	isBlock
1368	    ifTrue: [self endStatement]
1369	    ifFalse: [self returnFromMethod: unused]
1370    ]
1371
1372    returnFromMethod: unused [
1373	<category: 'analyzing'>
1374	| retVal |
1375	retVal := stack removeLast.
1376	stack size timesRepeat: [statements addAllLast: stack removeFirst].
1377	statements addLast: (RBReturnNode value: retVal)
1378    ]
1379
1380    popJumpIfFalseTo: destination with: unused [
1381	<category: 'analyzing'>
1382
1383    ]
1384
1385    popJumpIfTrueTo: destination with: unused [
1386	<category: 'analyzing'>
1387
1388    ]
1389
1390    jumpTo: destination with: unused [
1391	<category: 'analyzing'>
1392
1393    ]
1394
1395    lineNo: n with: unused [
1396	<category: 'analyzing'>
1397
1398    ]
1399
1400    superSend: aSymbol numArgs: anInteger with: unused [
1401	"Pop the class at which we start the search."
1402
1403	<category: 'analyzing'>
1404	stack removeLast.
1405	stack at: stack size - anInteger put: (self varNode: 'super').
1406	^self
1407	    send: aSymbol
1408	    numArgs: anInteger
1409	    with: unused
1410    ]
1411
1412    send: aSymbol numArgs: anInteger with: unused [
1413	<category: 'analyzing'>
1414	"Not a very efficient check, but a rare one indeed (who
1415	 sends #thisContext?)"
1416
1417	| args collection msg |
1418	(aSymbol == #thisContext
1419	    and: [stack last = self varNode: ContextPart binding path])
1420		ifTrue:
1421		    [stack
1422			removeLast;
1423			addLast: (self varNode: 'thisContext').
1424		    ^self].
1425	args := Array new: anInteger.
1426	anInteger to: 1
1427	    by: -1
1428	    do: [:each | args at: each put: stack removeLast].
1429	stack addLast: ((RBMessageNode new)
1430		    arguments: args;
1431		    receiver: stack removeLast;
1432		    selectorParts: (self selectorParts: aSymbol)).
1433
1434	"If the receiver was over an RBCascadeNode, merge the send
1435	 with the cascade."
1436	self isCascadeLast ifTrue: [self doCascade: stack removeLast]
1437    ]
1438
1439    bytecodeIndex: byte with: unused [
1440	<category: 'analyzing'>
1441	| newBB |
1442	current := byte.
1443	newBB := context cfgNodeAt: byte.
1444	newBB == bb
1445	    ifFalse:
1446		[self newBasicBlock: newBB.
1447		statements := OrderedCollection new.
1448		bb := newBB]
1449    ]
1450
1451    newBasicBlock: newBB [
1452	<category: 'analyzing'>
1453	bb isNil ifTrue: [^self].
1454	bb dfnum isNil ifTrue: [^self].
1455	statements addAllLast: stack.
1456	bb statements: statements.
1457	bbList add: bb.
1458	bb succ do:
1459		[:each |
1460		each value stack: stack copy.
1461		each key = #jump ifFalse: [each value stack removeLast]].
1462	stack := newBB stack
1463    ]
1464
1465    simplify [
1466	<category: 'analyzing'>
1467	| oldSize goOn |
1468	bbList := bbList asArray.
1469
1470	[bbList := bbList select:
1471			[:each |
1472			each succ size >= 2
1473			    or: [each succ notNil and: [(each succ at: 1) value id <= each id]]].
1474	bbList isEmpty]
1475		whileFalse: [bbList do: [:each | each simplify]]
1476    ]
1477]
1478
1479