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