Add component slot to nodes
[jscl.git] / experimental / compiler.lisp
1 ;;; compiler.lisp ---
2
3 ;; Copyright (C) 2013 David Vazquez
4
5 ;; JSCL is free software: you can redistribute it and/or
6 ;; modify it under the terms of the GNU General Public License as
7 ;; published by the Free Software Foundation, either version 3 of the
8 ;; License, or (at your option) any later version.
9 ;;
10 ;; JSCL is distributed in the hope that it will be useful, but
11 ;; WITHOUT ANY WARRANTY; without even the implied warranty of
12 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
13 ;; General Public License for more details.
14 ;;
15 ;; You should have received a copy of the GNU General Public License
16 ;; along with JSCL.  If not, see <http://www.gnu.org/licenses/>.
17
18 (defpackage :jscl
19   (:use :cl))
20
21 (in-package :jscl)
22
23 ;;;; Utilities
24 ;;;;
25 ;;;; Random Common Lisp code useful to use here and there. 
26
27 (defmacro with-gensyms ((&rest vars) &body body)
28   `(let ,(mapcar (lambda (var) `(,var (gensym ,(concatenate 'string (string var) "-")))) vars)
29      ,@body))
30
31 (defun singlep (x)
32   (and (consp x) (null (cdr x))))
33
34 (defun unlist (x)
35   (assert (singlep x))
36   (first x))
37
38
39 ;;;; Intermediate representation structures
40 ;;;;
41 ;;;; This intermediate representation (IR) is a simplified version of
42 ;;;; the first intermediate representation what you will find if you
43 ;;;; have a look to the source code of SBCL. Some terminology is also
44 ;;;; used, but other is changed, so be careful if you assume you know
45 ;;;; what it is because you know the name.
46 ;;;;
47 ;;;; Computations are represented by `node'.  Nodes are grouped
48 ;;;; sequencially into `basic-block'. It is a plain representation
49 ;;;; rather than a nested one. Computations take data and produce a
50 ;;;; value. Both data transfer are represented by `lvar'.
51
52 (defstruct leaf)
53
54 ;;; A (lexical) variable. Special variables has not a special
55 ;;; representation in the IR. They are handled by the primitive
56 ;;; functions `%symbol-function' and `%symbol-value'.
57 (defstruct (var (:include leaf))
58   ;; The symbol which names this variable in the source code.
59   name)
60
61 ;;; A literal Lisp object. It usually comes from a quoted expression.
62 (defstruct (constant (:include leaf))
63   ;; The object itself.
64   value)
65
66 ;;; A lambda expression. Why do we name it `functional'? Well,
67 ;;; function is reserved by the ANSI, isn't it?
68 (defstruct (functional (:include leaf))
69   ;; The symbol which names this function in the source code or null
70   ;; if we do not know or it is an anonymous function.
71   name
72   arguments
73   return-lvar
74   entry-point)
75
76 ;;; An abstract place where the result of a computation is stored and
77 ;;; it can be referenced from other nodes, so lvars are responsible
78 ;;; for keeping the necessary information of the nested structure of
79 ;;; the code in this plain representation.
80 (defstruct lvar
81   (id (gensym "$")))
82
83 ;;; A base structure for every single computation. Most of the
84 ;;; computations are valued.
85 (defstruct node
86   ;; The next and the prev slots are the next nodes and the previous
87   ;; node in the basic block sequence respectively.
88   next prev
89   ;; Lvar which stands for the result of the computation of this node.
90   lvar)
91
92 ;;; Sentinel nodes in the basic block sequence of nodes.
93 (defstruct (block-entry (:include node)))
94 (defstruct (block-exit (:include node)))
95
96 ;;; A reference to a leaf (variable, constant and functions). The
97 ;;; meaning of this node is leaving the leaf into the lvar of the
98 ;;; node.
99 (defstruct (ref (:include node))
100   leaf)
101
102 ;;; An assignation of the LVAR VALUE into the var VARIABLE.
103 (defstruct (assignment (:include node))
104   variable
105   value)
106
107 ;;; A base node to function calls with a list of lvar as ARGUMENTS.
108 (defstruct (combination (:include node) (:constructor))
109   arguments)
110
111 ;;; A function call to the ordinary Lisp function in the lvar FUNCTION.
112 (defstruct (call (:include combination))
113   function)
114
115 ;;; A function call to the primitive FUNCTION.
116 (defstruct (primitive-call (:include combination))
117   function)
118
119
120 ;;; A conditional branch. If the LVAR is not NIL, then we will jump to
121 ;;; the basic block CONSEQUENT, jumping to ALTERNATIVE otherwise. By
122 ;;; definition, a conditional must appear at the end of a basic block.
123 (defstruct (conditional (:include node))
124   test
125   consequent
126   alternative)
127
128
129 ;;;; Components
130 ;;;;
131 ;;;; Components are connected pieces of the control flow graph of
132 ;;;; basic blocks with some additional information. Components have
133 ;;;; well-defined entry and exit nodes. It is the toplevel
134 ;;;; organizational entity in the compiler. The IR translation result
135 ;;;; is accumulated into components incrementally.
136 (defstruct (component)
137   entry
138   exit)
139
140 ;;; The current component. We accumulate the results of the IR
141 ;;; conversion in this component.
142 (defvar *component*)
143
144 ;;; Create a new component with an empty basic block, ready to start
145 ;;; conversion to IR. It returns the component and the basic block as
146 ;;; multiple values.
147 (defun make-empty-component ()
148   (let ((*component* (make-component)))
149     (let ((entry (make-component-entry))
150           (block (make-empty-block))
151           (exit (make-component-exit)))
152       (setf (block-succ entry) (list block)
153             (block-pred exit)  (list block)
154             (block-succ block) (list exit)
155             (block-pred block) (list entry)
156             (component-entry *component*) entry
157             (component-exit  *component*) exit)
158       (values *component* block))))
159
160 ;;; Prepare a new component with a current empty block ready to start
161 ;;; IR conversion bound in the current cursor. BODY is evaluated and
162 ;;; the value of the last form is returned.
163 (defmacro with-component-compilation (&body body)
164   (with-gensyms (block)
165     `(multiple-value-bind (*component* ,block)
166          (make-empty-component)
167        (let ((*cursor* (cursor :block ,block)))
168          ,@body))))
169
170 ;;; Return the list of blocks in COMPONENT, conveniently sorted.
171 (defun component-blocks (component)
172   (let ((seen nil)
173         (output nil))
174     (labels ((compute-rdfo-from (block)
175                (unless (or (component-exit-p block) (find block seen))
176                  (push block seen)
177                  (dolist (successor (block-succ block))
178                    (unless (component-exit-p block)
179                      (compute-rdfo-from successor)))
180                  (push block output))))
181       (compute-rdfo-from (unlist (block-succ (component-entry component))))
182       output)))
183
184 ;;; Iterate across different blocks in COMPONENT.
185 (defmacro do-blocks ((block component &optional result) &body body)
186   `(dolist (,block (component-blocks ,component) ,result)
187      ,@body))
188
189 (defmacro do-blocks-backward ((block component &optional result) &body body)
190   `(dolist (,block (reverse (component-blocks ,component)) ,result)
191      ,@body))
192
193 ;;; A few consistency checks in the IR useful for catching bugs.
194 (defun check-ir-consistency (component)
195   (with-simple-restart (continue "Continue execution")
196     (do-blocks (block component)
197       (dolist (succ (block-succ block))
198         (unless (find block (block-pred succ))
199           (error "The block `~S' does not belong to the predecessors list of the its successor `~S'"
200                  (block-id block)
201                  (block-id succ))))
202       (dolist (pred (block-pred block))
203         (unless (find block (block-succ pred))
204           (error "The block `~S' does not belong to the successors' list of its predecessor `~S'"
205                  (block-id block)
206                  (block-id pred)))))))
207
208
209 ;;; Blocks are `basic block`. Basic blocks are organized as a control
210 ;;; flow graph with some more information in omponents.
211 (defstruct (basic-block
212              (:conc-name "BLOCK-")
213              (:constructor make-block)
214              (:predicate block-p))
215   (id (gensym "L"))
216   ;; List of successors and predecessors of this basic block.
217   succ pred
218   ;; The sentinel nodes of the sequence.
219   entry exit
220   ;; The component where this block belongs
221   (component *component*))
222
223 ;;; Sentinel nodes in the control flow graph of basic blocks.
224 (defstruct (component-entry (:include basic-block)))
225 (defstruct (component-exit (:include basic-block)))
226
227 ;;; Return a fresh empty basic block.
228 (defun make-empty-block ()
229   (let ((entry (make-block-entry))
230         (exit (make-block-exit)))
231     (setf (node-next entry) exit
232           (node-prev exit) entry)
233     (make-block :entry entry :exit exit)))
234
235 ;;; Return T if B is an empty basic block and NIL otherwise.
236 (defun empty-block-p (b)
237   (block-exit-p (node-next (block-entry b))))
238
239 ;;; Iterate across the nodes in a basic block forward.
240 (defmacro do-nodes
241     ((node block &optional result &key include-sentinel-p) &body body)
242   `(do ((,node ,(if include-sentinel-p
243                     `(block-entry ,block)
244                     `(node-next (block-entry ,block))) 
245                (node-next ,node)))
246        (,(if include-sentinel-p
247              `(null ,node)
248              `(block-exit-p ,node))
249         ,result)
250      ,@body))
251
252 ;;; Iterate across the nodes in a basic block backward.
253 (defmacro do-nodes-backward
254     ((node block &optional result &key include-sentinel-p) &body body)
255   `(do ((,node ,(if include-sentinel-p
256                     `(block-exit ,block)
257                     `(node-prev (block-entry ,block))) 
258                (node-prev ,node)))
259        (,(if include-sentinel-p
260              `(null ,node)
261              `(block-entry-p ,node))
262         ,result)
263      ,@body))
264
265 ;;; Link FROM and TO nodes together. FROM and TO must belong to the
266 ;;; same basic block and appear in such order. The nodes between FROM
267 ;;; and TO are discarded.
268 (defun link-nodes (from to)
269   (setf (node-next from) to
270         (node-prev to) from)
271   (values))
272
273
274
275 ;;;; Cursors
276 ;;;;
277 ;;;; A cursor is a point between two nodes in some basic block in the
278 ;;;; IR representation where manipulations can take place, similarly
279 ;;;; to the cursors in text editing.
280 ;;;;
281 ;;;; Cursors cannot point to special component's entry and exit basic
282 ;;;; blocks or after a conditional node. Conveniently, the `cursor'
283 ;;;; function will signal an error if the cursor is not positioned
284 ;;;; correctly, so the rest of the code does not need to check once
285 ;;;; and again.
286
287 (defstruct cursor
288   block next)
289
290 ;;; The current cursor. It is the default cursor for many functions
291 ;;; which work on cursors.
292 (defvar *cursor*)
293
294 ;;; Return the current basic block. It is to say, the basic block
295 ;;; where the current cursor is pointint.
296 (defun current-block ()
297   (cursor-block *cursor*))
298
299 ;;; Create a cursor which points to the basic block BLOCK. If omitted,
300 ;;; then the current block is used.
301 ;;;
302 ;;; The keywords AFTER and BEFORE specify the cursor will point after (or
303 ;;; before) that node respectively. If none is specified, the cursor is
304 ;;; created before the exit node in BLOCK. An error is signaled if both
305 ;;; keywords are specified inconsistently, or if the nodes do not belong
306 ;;; to BLOCK.
307 ;;;
308 ;;; AFTER and BEFORE could also be the special values :ENTRY and :EXIT,
309 ;;; which stand for the entry and exit nodes of the block respectively.
310 (defun cursor (&key (block (current-block))
311                  (before nil before-p)
312                  (after nil after-p))
313   (when (or (component-entry-p block) (component-exit-p block))
314     (error "Invalid cursor on special entry/exit basic block."))
315   ;; Handle special values :ENTRY and :EXIT.
316   (flet ((node-designator (x)
317            (case x
318              (:entry (block-entry block))
319              (:exit  (block-exit block))
320              (t x))))
321     (setq before (node-designator before))
322     (setq after  (node-designator after)))
323   (let* ((next (or before (and after (node-next after)) (block-exit block)))
324          (cursor (make-cursor :block block :next next)))
325     (flet ((out-of-range-cursor ()
326              (error "Out of range cursor."))
327            (ambiguous-cursor ()
328              (error "Ambiguous cursor specified between two non-adjacent nodes.")))
329       (when (conditional-p (node-prev next))
330         (error "Invalid cursor after conditional node."))
331       (when (or (null next) (block-entry-p next))
332         (out-of-range-cursor))
333       (when (and before-p after-p (not (eq after before)))
334         (ambiguous-cursor))
335       (do-nodes-backward (node block (out-of-range-cursor) :include-sentinel-p t)
336         (when (eq next node) (return))))
337     cursor))
338
339 ;;; Accept a cursor specification just as described in `cursor'
340 ;;; describing a position in the IR and modify destructively the
341 ;;; current cursor to point there.
342 (defun set-cursor (&rest cursor-spec)
343   (let ((newcursor (apply #'cursor cursor-spec)))
344     (setf (cursor-block *cursor*) (cursor-block newcursor))
345     (setf (cursor-next *cursor*) (cursor-next newcursor))
346     *cursor*))
347
348 ;;; Insert NODE at cursor.
349 (defun insert-node (node &optional (cursor *cursor*))
350   ;; After if? wrong!
351   (link-nodes (node-prev (cursor-next cursor)) node)
352   (link-nodes node (cursor-next cursor))
353   t)
354
355 ;;; Split the block at CURSOR. The cursor will point to the end of the
356 ;;; first basic block. Return the three basic blocks as multiple
357 ;;; values.
358 (defun split-block (&optional (cursor *cursor*))
359   ;; <aaaaa|zzzzz>  ==>  <aaaaa|>--<zzzzz>
360   (let* ((block (cursor-block cursor))
361          (newexit (make-block-exit))
362          (newentry (make-block-entry))
363          (exit (block-exit block))
364          (newblock (make-block :entry newentry
365                                :exit exit
366                                :pred (list block)
367                                :succ (block-succ block))))
368     (insert-node newexit)
369     (insert-node newentry)
370     (setf (node-next newexit)  nil)
371     (setf (node-prev newentry) nil)
372     (setf (block-exit block) newexit)
373     (setf (block-succ block) (list newblock))
374     (dolist (succ (block-succ newblock))
375       (setf (block-pred succ) (substitute newblock block (block-pred succ))))
376     (set-cursor :block block :before newexit)
377     newblock))
378
379 ;;; Split the block at CURSOR if it is in the middle of it. The cursor
380 ;;; will point to the end of the first basic block. Return the three
381 ;;; basic blocks as multiple values.
382 (defun maybe-split-block (&optional (cursor *cursor*))
383   ;; If we are converting IR into the end of the basic block, it's
384   ;; fine, we don't need to do anything.
385   (unless (block-exit-p (cursor-next cursor))
386     (split-block cursor)))
387
388
389
390 ;;;; Lexical environment
391 ;;;;
392 ;;;; It keeps an association between names and the IR entities. It is
393 ;;;; used to guide the translation from the Lisp source code to the
394 ;;;; intermediate representation.
395
396 (defstruct binding
397   name namespace type value)
398
399 (defvar *lexenv* nil)
400
401 (defun find-binding (name namespace)
402   (find-if (lambda (b)
403              (and (eq (binding-name b) name)
404                   (eq (binding-namespace b) namespace)))
405            *lexenv*))
406
407 (defun push-binding (name namespace value &optional type)
408   (push (make-binding :name name
409                       :namespace namespace
410                       :type type
411                       :value value)
412         *lexenv*))
413
414
415 ;;;; IR Translation
416 ;;;;
417 ;;;; This code covers the translation from Lisp source code to the
418 ;;;; intermediate representation. The main entry point function to do
419 ;;;; that is the `ir-convert' function, which dispatches to IR
420 ;;;; translators. This function ss intended to do the initial
421 ;;;; conversion as well as insert new IR code during optimizations.
422 ;;;;
423 ;;;; The function `ir-complete' will coalesce basic blocks in a
424 ;;;; component to generate proper maximal basic blocks.
425
426 ;;; A alist of IR translator functions.
427 (defvar *ir-translator* nil)
428
429 ;;; Define a IR translator for NAME. LAMBDA-LIST is used to
430 ;;; destructure the arguments of the form. Calling the local function
431 ;;; `result-lvar' you can get the LVAR where the compilation of the
432 ;;; expression should store the result of the evaluation.
433 ;;;
434 ;;; The cursor is granted to be at the end of a basic block with a
435 ;;; unique successor, and so it should be when the translator returns.
436 (defmacro define-ir-translator (name lambda-list &body body)
437   (check-type name symbol)
438   (let ((fname (intern (format nil "IR-CONVERT-~a" (string name)))))
439     (with-gensyms (result form)
440       `(progn
441          (defun ,fname (,form ,result)
442            (flet ((result-lvar () ,result))
443              (declare (ignorable (function result-lvar)))
444              (destructuring-bind ,lambda-list ,form
445                ,@body)))
446          (push (cons ',name #',fname) *ir-translator*)))))
447
448 ;;; Return the unique successor of the current block. If it is not
449 ;;; unique signal an error.
450 (defun next-block ()
451   (unlist (block-succ (current-block))))
452
453 ;;; Set the next block of the current one.
454 (defun (setf next-block) (new-value)
455   (let ((block (current-block)))
456     (dolist (succ (block-succ block))
457       (setf (block-pred succ) (remove block (block-pred succ))))
458     (setf (block-succ block) (list new-value))
459     (push block (block-pred new-value))
460     new-value))
461
462 (defun ir-convert-constant (form result)
463   (let* ((leaf (make-constant :value form)))
464     (insert-node (make-ref :leaf leaf :lvar result))))
465
466 (define-ir-translator quote (form)
467   (ir-convert-constant form (result-lvar)))
468
469 (define-ir-translator setq (variable value)
470   (let ((var (make-var :name variable))
471         (value-lvar (make-lvar)))
472     (ir-convert value value-lvar)
473     (let ((assign (make-assignment :variable var :value value-lvar :lvar (result-lvar))))
474       (insert-node assign))))
475
476 (define-ir-translator progn (&body body)
477   (mapc #'ir-convert (butlast body))
478   (ir-convert (car (last body)) (result-lvar)))
479
480 (define-ir-translator if (test then &optional else)
481   ;; It is the schema of how the basic blocks will look like
482   ;;
483   ;;              / ..then.. \
484   ;;  <aaaaXX> --<            >-- <|> -- <zzzz>
485   ;;              \ ..else.. /
486   ;;
487   ;; Note that is important to leave the cursor in an empty basic
488   ;; block, as zzz could be the exit basic block of the component,
489   ;; which is an invalid position for a cursor.
490   (let ((test-lvar (make-lvar))
491         (then-block (make-empty-block))
492         (else-block (make-empty-block))
493         (join-block (make-empty-block)))
494     (ir-convert test test-lvar)
495     (insert-node (make-conditional :test test-lvar :consequent then-block :alternative else-block))
496     (let* ((block (current-block))
497            (tail-block (next-block)))
498       ;; Link together the different created basic blocks.
499       (setf (block-succ block)      (list else-block then-block)
500             (block-pred else-block) (list block)
501             (block-pred then-block) (list block)
502             (block-succ then-block) (list join-block)
503             (block-succ else-block) (list join-block)
504             (block-pred join-block) (list else-block then-block)
505             (block-succ join-block) (list tail-block)
506             (block-pred tail-block) (substitute join-block block (block-pred tail-block))))
507     ;; Convert he consequent and alternative forms and update cursor.
508     (ir-convert then (result-lvar) (cursor :block then-block))
509     (ir-convert else (result-lvar) (cursor :block else-block))
510     (set-cursor :block join-block)))
511
512 (define-ir-translator block (name &body body)
513   (let ((new (split-block)))
514     (push-binding name 'block (cons (next-block) (result-lvar)))
515     (ir-convert `(progn ,@body) (result-lvar))
516     (set-cursor :block new)))
517
518 (define-ir-translator return-from (name &optional value)
519   (let ((binding
520          (or (find-binding name 'block)
521              (error "Tried to return from unknown block `~S' name" name))))
522     (destructuring-bind (jump-block . lvar)
523         (binding-value binding)
524       (ir-convert value lvar)
525       (setf (next-block) jump-block)
526       ;; This block is really unreachable, even if the following code
527       ;; is labelled in a tagbody, as tagbody will create a new block
528       ;; for each label. However, we have to leave the cursor
529       ;; somewhere to convert new input.
530       (let ((dummy (make-empty-block)))
531         (set-cursor :block dummy)))))
532
533 (define-ir-translator tagbody (&rest statements)
534   (flet ((go-tag-p (x)
535            (or (integerp x) (symbolp x))))
536     (let* ((tags (remove-if-not #'go-tag-p statements))
537            (tag-blocks nil))
538       ;; Create a chain of basic blocks for the tags, recording each
539       ;; block in a alist in TAG-BLOCKS.
540       (let ((*cursor* *cursor*))
541         (dolist (tag tags)
542           (setq *cursor* (cursor :block (split-block)))
543           (push-binding tag 'tag (current-block))
544           (if (assoc tag tag-blocks)
545               (error "Duplicated tag `~S' in tagbody." tag)
546               (push (cons tag (current-block)) tag-blocks))))
547       ;; Convert the statements into the correct block.
548       (dolist (stmt statements)
549         (if (go-tag-p stmt)
550             (set-cursor :block (cdr (assoc stmt tag-blocks)))
551             (ir-convert stmt))))))
552
553 (define-ir-translator go (label)
554   (let ((tag-binding
555          (or (find-binding label 'tag)
556              (error "Unable to jump to the label `~S'" label))))
557     (setf (next-block) (binding-value tag-binding))
558     ;; Unreachable block.
559     (let ((dummy (make-empty-block)))
560       (set-cursor :block dummy))))
561
562
563 (defun ir-convert-functoid (result name arguments &rest body)
564   (let ((component)
565         (return-lvar (make-lvar)))
566     (with-component-compilation
567       (ir-convert `(progn ,@body) return-lvar)
568       (setq component *component*))
569     (let ((functional
570            (make-functional
571             :name name
572             :arguments arguments
573             :entry-point component
574             :return-lvar return-lvar)))
575       (insert-node (make-ref :leaf functional :lvar result)))))
576
577 (define-ir-translator function (name)
578   (if (atom name)
579       (ir-convert `(symbol-function ,name) (result-lvar))
580       (ecase (car name)
581         ((lambda named-lambda)
582          (let ((desc (cdr name)))
583            (when (eq 'lambda (car name))
584              (push nil desc))
585            (apply #'ir-convert-functoid (result-lvar) desc)))
586         (setf))))
587
588 (defun ir-convert-var (form result)
589   (let ((binds (find-binding form 'variable)))
590     (if binds
591         (insert-node (make-ref :leaf (binding-value binds) :lvar result))
592         (ir-convert `(symbol-value ',form) result))))
593
594 (defun ir-convert-call (form result)
595   (destructuring-bind (function &rest args) form
596     (let ((func-lvar (make-lvar))
597           (args-lvars nil))
598       ;; Argument list
599       (dolist (arg args)
600         (let ((arg-lvar (make-lvar)))
601           (push arg-lvar args-lvars)
602           (ir-convert arg arg-lvar)))
603       (setq args-lvars (reverse args-lvars))
604       ;; Funcall
605       (if (find-primitive function)
606           (insert-node (make-primitive-call
607                         :function (find-primitive function)
608                         :arguments args-lvars
609                         :lvar result))
610           (progn
611             (ir-convert `(symbol-function ,function) func-lvar)
612             (insert-node (make-call :function func-lvar
613                                     :arguments args-lvars
614                                     :lvar result)))))))
615
616 ;;; Convert the Lisp expression FORM, it may create new basic
617 ;;; blocks. RESULT is the lvar representing the result of the
618 ;;; computation or null if the value should be discarded. The IR is
619 ;;; inserted at *CURSOR*.
620 (defun ir-convert (form &optional result (*cursor* *cursor*))
621   ;; Rebinding the lexical environment here we make sure that the
622   ;; lexical information introduced by FORM is just available for
623   ;; subforms.
624   (let ((*lexenv* *lexenv*))
625     ;; Possibly create additional blocks in order to make sure the
626     ;; cursor is at end the end of a basic block.
627     (maybe-split-block)
628     (cond
629       ((atom form)
630        (cond
631          ((symbolp form)
632           (ir-convert-var form result))
633          (t
634           (ir-convert-constant form result))))
635       (t
636        (destructuring-bind (op &rest args) form
637          (let ((translator (cdr (assoc op *ir-translator*))))
638            (if translator
639                (funcall translator args result)
640                (ir-convert-call form result))))))
641     (values)))
642
643
644 ;;; Change all the predecessors of BLOCK to precede NEW-BLOCK instead.
645 (defun replace-block (block new-block)
646   (let ((predecessors (block-pred block)))
647     (setf (block-pred new-block) (union (block-pred new-block) predecessors))
648     (dolist (pred predecessors)
649       (setf (block-succ pred) (substitute new-block block (block-succ pred)))
650       (unless (component-entry-p pred)
651         (let ((last-node (node-prev (block-exit pred))))
652           (when (conditional-p last-node)
653             (macrolet ((replacef (place)
654                          `(setf ,place (if (eq block ,place) new-block ,place))))
655               (replacef (conditional-consequent last-node))
656               (replacef (conditional-alternative last-node)))))))))
657
658 (defun delete-empty-block (block)
659   (when (or (component-entry-p block) (component-exit-p block))
660     (error "Cannot delete entry or exit basic blocks."))
661   (unless (empty-block-p block)
662     (error "Block `~S' is not empty!" (block-id block)))
663   (replace-block block (unlist (block-succ block))))
664
665 ;;; Try to coalesce BLOCK with the successor if it is unique and block
666 ;;; is its unique predecessor.
667 (defun maybe-coalesce-block (block)
668   (when (singlep (block-succ block))
669     (let ((succ (first (block-succ block))))
670       (when (and (not (component-exit-p succ)) (singlep (block-pred succ)))
671         (link-nodes (node-prev (block-exit block))
672                     (node-next (block-entry succ)))
673         (setf (block-succ block) (block-succ succ))
674         (dolist (next (block-succ succ))
675           (setf (block-pred next) (substitute block succ (block-pred next))))
676         t))))
677
678 (defun ir-complete (&optional (component *component*))
679   (do-blocks-backward (block component)
680     (maybe-coalesce-block block)
681     (when (empty-block-p block)
682       (delete-empty-block block))))
683
684
685 ;;; IR Debugging
686
687 (defun print-node (node)
688   (when (node-lvar node)
689     (format t "~a = " (lvar-id (node-lvar node))))
690   (cond
691     ((ref-p node)
692      (let ((leaf (ref-leaf node)))
693        (cond
694          ((var-p leaf)
695           (format t "~a" (var-name leaf)))
696          ((constant-p leaf)
697           (format t "'~s" (constant-value leaf)))
698          ((functional-p leaf)
699           (format t "#<function ~a>" (functional-name leaf))))))
700     ((assignment-p node)
701      (format t "set ~a ~a"
702              (var-name (assignment-variable node))
703              (lvar-id (assignment-value node))))
704     ((primitive-call-p node)
705      (format t "primitive ~a" (primitive-name (primitive-call-function node)))
706      (dolist (arg (primitive-call-arguments node))
707        (format t " ~a" (lvar-id arg))))
708     ((call-p node)
709      (format t "call ~a" (lvar-id (call-function node)))
710      (dolist (arg (call-arguments node))
711        (format t " ~a" (lvar-id arg))))
712     ((conditional-p node)
713      (format t "if ~a ~a ~a"
714              (lvar-id (conditional-test node))
715              (block-id (conditional-consequent node))
716              (block-id (conditional-alternative node))))
717     (t
718      (error "`print-node' does not support printing ~S as a node." node)))
719   (terpri))
720
721 (defun print-block (block)
722   (flet ((block-name (block)
723            (cond
724              ((and (singlep (block-pred block))
725                    (component-entry-p (unlist (block-pred block))))
726               "ENTRY")
727              ((component-exit-p block)
728               "EXIT")
729              (t (string (block-id block))))))
730     (format t "BLOCK ~a:~%" (block-name block))
731     (do-nodes (node block)
732       (print-node node))
733     (when (singlep (block-succ block))
734       (format t "GO ~a~%" (block-name (first (block-succ block)))))
735     (terpri)))
736
737 (defun print-component (component &optional (stream *standard-output*))
738   (let ((*standard-output* stream))
739     (do-blocks (block component)
740       (print-block block))))
741
742 ;;; Translate FORM into IR and print a textual repreresentation of the
743 ;;; component.
744 (defun describe-ir (form &optional (complete t))
745   (with-component-compilation
746     (ir-convert form (make-lvar :id "$out"))
747     (when complete (ir-complete))
748     (check-ir-consistency *component*)
749     (print-component *component*)))
750
751
752
753 ;;;; Primitives
754 ;;;;
755 ;;;; Primitive functions are a set of functions provided by the
756 ;;;; compiler. They cannot usually be written in terms of other
757 ;;;; functions. When the compiler tries to compile a function call, it
758 ;;;; looks for a primitive function firstly, and if it is found and
759 ;;;; the declarations allow it, a primitive call is inserted in the
760 ;;;; IR. The back-end of the compiler knows how to compile primitive
761 ;;;; calls.
762 ;;;; 
763
764 (defvar *primitive-function-table* nil)
765
766 (defstruct primitive
767   name)
768
769 (defmacro define-primitive (name args &body body)
770   (declare (ignore args body))
771   `(push (make-primitive :name ',name)
772          *primitive-function-table*))
773
774 (defun find-primitive (name)
775   (find name *primitive-function-table* :key #'primitive-name))
776
777 (define-primitive symbol-function (symbol))
778 (define-primitive symbol-value (symbol))
779
780
781 ;;; compiler.lisp ends here