Rename $ktrunc to $kreceive
[bpt/guile.git] / module / language / cps / dfg.scm
CommitLineData
6e8ad823
AW
1;;; Continuation-passing style (CPS) intermediate language (IL)
2
6eb02960 3;; Copyright (C) 2013, 2014 Free Software Foundation, Inc.
6e8ad823
AW
4
5;;;; This library is free software; you can redistribute it and/or
6;;;; modify it under the terms of the GNU Lesser General Public
7;;;; License as published by the Free Software Foundation; either
8;;;; version 3 of the License, or (at your option) any later version.
9;;;;
10;;;; This library is distributed in the hope that it will be useful,
11;;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
12;;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
13;;;; Lesser General Public License for more details.
14;;;;
15;;;; You should have received a copy of the GNU Lesser General Public
16;;;; License along with this library; if not, write to the Free Software
17;;;; Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
18
19;;; Commentary:
20;;;
21;;; Many passes rely on a local or global static analysis of a function.
22;;; This module implements a simple data-flow graph (DFG) analysis,
23;;; tracking the definitions and uses of variables and continuations.
f22979db 24;;; It also builds a table of continuations and scope links, to be able
6e8ad823
AW
25;;; to easily determine if one continuation is in the scope of another,
26;;; and to get to the expression inside a continuation.
27;;;
28;;; Note that the data-flow graph of continuation labels is a
29;;; control-flow graph.
30;;;
31;;; We currently don't expose details of the DFG type outside this
32;;; module, preferring to only expose accessors. That may change in the
33;;; future but it seems to work for now.
34;;;
35;;; Code:
36
37(define-module (language cps dfg)
38 #:use-module (ice-9 match)
39 #:use-module (srfi srfi-1)
40 #:use-module (srfi srfi-9)
41 #:use-module (srfi srfi-26)
42 #:use-module (language cps)
43 #:export (build-cont-table
44 build-local-cont-table
45 lookup-cont
46
47 compute-dfg
48 dfg-cont-table
49 lookup-def
50 lookup-uses
f22979db
AW
51 lookup-predecessors
52 lookup-successors
c8ad7426 53 lookup-block-scope
6e8ad823
AW
54 find-call
55 call-expression
56 find-expression
57 find-defining-expression
58 find-constant-value
f22979db 59 continuation-bound-in?
d51fb1e6 60 variable-free-in?
6e8ad823 61 constant-needs-allocation?
e636f424 62 control-point?
db11440d
AW
63 lookup-bound-syms
64
dda5fd94
AW
65 ;; Control flow analysis.
66 analyze-control-flow
67 cfa-k-idx cfa-k-count cfa-k-sym cfa-predecessors
68
db11440d
AW
69 ;; Data flow analysis.
70 compute-live-variables
71 dfa-k-idx dfa-k-sym dfa-k-count dfa-k-in dfa-k-out
72 dfa-var-idx dfa-var-name dfa-var-sym dfa-var-count
73 print-dfa))
6e8ad823
AW
74
75(define (build-cont-table fun)
6e422a35 76 (fold-conts (lambda (k cont table)
6e8ad823
AW
77 (hashq-set! table k cont)
78 table)
79 (make-hash-table)
80 fun))
81
82(define (build-local-cont-table cont)
6e422a35 83 (fold-local-conts (lambda (k cont table)
6e8ad823
AW
84 (hashq-set! table k cont)
85 table)
86 (make-hash-table)
87 cont))
88
89(define (lookup-cont sym conts)
90 (let ((res (hashq-ref conts sym)))
91 (unless res
92 (error "Unknown continuation!" sym (hash-fold acons '() conts)))
93 res))
94
95;; Data-flow graph for CPS: both for values and continuations.
96(define-record-type $dfg
f22979db 97 (make-dfg conts blocks use-maps)
6e8ad823 98 dfg?
f22979db 99 ;; hash table of sym -> $kif, $kargs, etc
6e8ad823 100 (conts dfg-cont-table)
f22979db
AW
101 ;; hash table of sym -> $block
102 (blocks dfg-blocks)
6e8ad823 103 ;; hash table of sym -> $use-map
f22979db 104 (use-maps dfg-use-maps))
6e8ad823
AW
105
106(define-record-type $use-map
fc95a944 107 (make-use-map name sym def uses)
6e8ad823 108 use-map?
fc95a944 109 (name use-map-name)
6e8ad823
AW
110 (sym use-map-sym)
111 (def use-map-def)
112 (uses use-map-uses set-use-map-uses!))
113
f22979db 114(define-record-type $block
334bd8e3 115 (%make-block scope scope-level preds succs)
f22979db
AW
116 block?
117 (scope block-scope set-block-scope!)
118 (scope-level block-scope-level set-block-scope-level!)
119 (preds block-preds set-block-preds!)
334bd8e3 120 (succs block-succs set-block-succs!))
f22979db
AW
121
122(define (make-block scope scope-level)
334bd8e3 123 (%make-block scope scope-level '() '()))
f22979db 124
5bff3125
AW
125;; Some analyses assume that the only relevant set of nodes is the set
126;; that is reachable from some start node. Others need to include nodes
127;; that are reachable from an end node as well, or all nodes in a
128;; function. In that case pass an appropriate implementation of
6eb02960
AW
129;; fold-all-conts, as analyze-control-flow does.
130(define (reverse-post-order k0 get-successors fold-all-conts)
3aee6cfd
AW
131 (let ((order '())
132 (visited? (make-hash-table)))
133 (let visit ((k k0))
134 (hashq-set! visited? k #t)
0e2446d4
AW
135 (for-each (lambda (k)
136 (unless (hashq-ref visited? k)
137 (visit k)))
334bd8e3 138 (get-successors k))
0e2446d4 139 (set! order (cons k order)))
5bff3125
AW
140 (list->vector (fold-all-conts
141 (lambda (k seed)
142 (if (hashq-ref visited? k)
143 seed
144 (begin
145 (hashq-set! visited? k #t)
146 (cons k seed))))
147 order))))
3aee6cfd 148
334bd8e3
AW
149(define (make-block-mapping order)
150 (let ((mapping (make-hash-table)))
366eb4d7
AW
151 (let lp ((n 0))
152 (when (< n (vector-length order))
153 (hashq-set! mapping (vector-ref order n) n)
154 (lp (1+ n))))
334bd8e3
AW
155 mapping))
156
157(define (convert-predecessors order get-predecessors)
158 (let ((preds-vec (make-vector (vector-length order) #f)))
366eb4d7
AW
159 (let lp ((n 0))
160 (when (< n (vector-length order))
334bd8e3
AW
161 (vector-set! preds-vec n (get-predecessors (vector-ref order n)))
162 (lp (1+ n))))
3aee6cfd
AW
163 preds-vec))
164
334bd8e3
AW
165;; Control-flow analysis.
166(define-record-type $cfa
dda5fd94 167 (make-cfa k-map order preds)
334bd8e3
AW
168 cfa?
169 ;; Hash table mapping k-sym -> k-idx
170 (k-map cfa-k-map)
171 ;; Vector of k-idx -> k-sym, in reverse post order
172 (order cfa-order)
173 ;; Vector of k-idx -> list of k-idx
dda5fd94
AW
174 (preds cfa-preds))
175
176(define* (cfa-k-idx cfa k
177 #:key (default (lambda (k)
178 (error "unknown k" k))))
179 (or (hashq-ref (cfa-k-map cfa) k)
180 (default k)))
181
182(define (cfa-k-count cfa)
183 (vector-length (cfa-order cfa)))
184
185(define (cfa-k-sym cfa n)
186 (vector-ref (cfa-order cfa) n))
187
188(define (cfa-predecessors cfa n)
189 (vector-ref (cfa-preds cfa) n))
190
9002277d
AW
191(define-inlinable (vector-push! vec idx val)
192 (let ((v vec) (i idx))
193 (vector-set! v i (cons val (vector-ref v i)))))
194
195(define (compute-reachable cfa dfg)
196 "Given the forward control-flow analysis in CFA, compute and return
197the continuations that may be reached if flow reaches a continuation N.
198Returns a vector of bitvectors. The given CFA should be a forward CFA,
199for quickest convergence."
200 (let* ((k-count (cfa-k-count cfa))
201 ;; Vector of bitvectors, indicating that continuation N can
202 ;; reach a set M...
203 (reachable (make-vector k-count #f))
204 ;; Vector of lists, indicating that continuation N can directly
205 ;; reach continuations M...
206 (succs (make-vector k-count '())))
207
208 ;; All continuations are reachable from themselves.
209 (let lp ((n 0))
210 (when (< n k-count)
211 (let ((bv (make-bitvector k-count #f)))
212 (bitvector-set! bv n #t)
213 (vector-set! reachable n bv)
214 (lp (1+ n)))))
215
216 ;; Initialize successor lists.
217 (let lp ((n 0))
218 (when (< n k-count)
219 (for-each (lambda (succ)
220 (vector-push! succs n (cfa-k-idx cfa succ)))
221 (block-succs (lookup-block (cfa-k-sym cfa n)
222 (dfg-blocks dfg))))
223 (lp (1+ n))))
224
225 ;; Iterate cfa backwards, to converge quickly.
226 (let ((tmp (make-bitvector k-count #f)))
227 (let lp ((n k-count) (changed? #f))
228 (cond
229 ((zero? n)
230 (if changed?
231 (lp 0 #f)
232 reachable))
233 (else
234 (let ((n (1- n)))
235 (bitvector-fill! tmp #f)
236 (for-each (lambda (succ)
237 (bit-set*! tmp (vector-ref reachable succ) #t))
238 (vector-ref succs n))
239 (bitvector-set! tmp n #t)
240 (bit-set*! tmp (vector-ref reachable n) #f)
241 (cond
242 ((bit-position #t tmp 0)
243 (bit-set*! (vector-ref reachable n) tmp #t)
244 (lp n #t))
245 (else
246 (lp n changed?))))))))))
247
248(define (find-prompts cfa dfg)
249 "Find the prompts in CFA, and return them as a list of PROMPT-INDEX,
250HANDLER-INDEX pairs."
251 (let lp ((n 0) (prompts '()))
252 (cond
253 ((= n (cfa-k-count cfa))
254 (reverse prompts))
255 (else
256 (match (lookup-cont (cfa-k-sym cfa n) (dfg-cont-table dfg))
257 (($ $kargs names syms body)
258 (match (find-expression body)
259 (($ $prompt escape? tag handler)
260 (lp (1+ n) (acons n (cfa-k-idx cfa handler) prompts)))
261 (_ (lp (1+ n) prompts))))
262 (_ (lp (1+ n) prompts)))))))
263
264(define (compute-interval cfa dfg reachable start end)
265 "Compute and return the set of continuations that may be reached from
266START, inclusive, but not reached by END, exclusive. Returns a
267bitvector."
268 (let ((body (make-bitvector (cfa-k-count cfa) #f)))
269 (bit-set*! body (vector-ref reachable start) #t)
270 (bit-set*! body (vector-ref reachable end) #f)
271 body))
272
273(define (find-prompt-bodies cfa dfg)
274 "Find all the prompts in CFA, and compute the set of continuations
275that is reachable from the prompt bodies but not from the corresponding
276handler. Returns a list of PROMPT, HANDLER, BODY lists, where the BODY
277is a bitvector."
278 (match (find-prompts cfa dfg)
279 (() '())
280 (((prompt . handler) ...)
281 (let ((reachable (compute-reachable cfa dfg)))
282 (map (lambda (prompt handler)
283 ;; FIXME: It isn't correct to use all continuations
284 ;; reachable from the prompt, because that includes
285 ;; continuations outside the prompt body. This point is
286 ;; moot if the handler's control flow joins with the the
287 ;; body, as is usually but not always the case.
288 ;;
289 ;; One counter-example is when the handler contifies an
290 ;; infinite loop; in that case we compute a too-large
291 ;; prompt body. This error is currently innocuous, but
292 ;; we should fix it at some point.
293 ;;
294 ;; The fix is to end the body at the corresponding "pop"
295 ;; primcall, if any.
296 (let ((body (compute-interval cfa dfg reachable prompt handler)))
297 (list prompt handler body)))
298 prompt handler)))))
299
300(define* (visit-prompt-control-flow cfa dfg f #:key complete?)
301 "For all prompts in CFA, invoke F with arguments PROMPT, HANDLER, and
302BODY for each body continuation in the prompt."
303 (for-each
304 (match-lambda
305 ((prompt handler body)
306 (define (out-or-back-edge? n)
307 ;; Most uses of visit-prompt-control-flow don't need every body
308 ;; continuation, and would be happy getting called only for
309 ;; continuations that postdominate the rest of the body. Unless
310 ;; you pass #:complete? #t, we only invoke F on continuations
311 ;; that can leave the body, or on back-edges in loops.
312 ;;
313 ;; You would think that looking for the final "pop" primcall
314 ;; would be sufficient, but that is incorrect; it's possible for
315 ;; a loop in the prompt body to be contified, and that loop need
316 ;; not continue to the pop if it never terminates. The pop could
317 ;; even be removed by DCE, in that case.
318 (or-map (lambda (succ)
319 (let ((succ (cfa-k-idx cfa succ)))
320 (or (not (bitvector-ref body succ))
321 (<= succ n))))
322 (block-succs (lookup-block (cfa-k-sym cfa n)
323 (dfg-blocks dfg)))))
324 (let lp ((n 0))
325 (let ((n (bit-position #t body n)))
326 (when n
327 (when (or complete? (out-or-back-edge? n))
328 (f prompt handler n))
329 (lp (1+ n)))))))
330 (find-prompt-bodies cfa dfg)))
331
332(define* (analyze-control-flow fun dfg #:key reverse? add-handler-preds?)
333 (define (build-cfa kentry block-succs block-preds forward-cfa)
dda5fd94
AW
334 (define (block-accessor accessor)
335 (lambda (k)
336 (accessor (lookup-block k (dfg-blocks dfg)))))
337 (define (reachable-preds mapping accessor)
338 ;; It's possible for a predecessor to not be in the mapping, if
339 ;; the predecessor is not reachable from the entry node.
340 (lambda (k)
341 (filter-map (cut hashq-ref mapping <>)
342 ((block-accessor accessor) k))))
9002277d
AW
343 (let* ((order (reverse-post-order
344 kentry
345 (block-accessor block-succs)
346 (if forward-cfa
347 (lambda (f seed)
348 (let lp ((n (cfa-k-count forward-cfa)) (seed seed))
349 (if (zero? n)
350 seed
351 (lp (1- n)
352 (f (cfa-k-sym forward-cfa (1- n)) seed)))))
353 (lambda (f seed) seed))))
dda5fd94
AW
354 (k-map (make-block-mapping order))
355 (preds (convert-predecessors order
9002277d
AW
356 (reachable-preds k-map block-preds)))
357 (cfa (make-cfa k-map order preds)))
358 (when add-handler-preds?
359 ;; Any expression in the prompt body could cause an abort to the
360 ;; handler. This code adds links from every block in the prompt
361 ;; body to the handler. This causes all values used by the
362 ;; handler to be seen as live in the prompt body, as indeed they
363 ;; are.
364 (let ((forward-cfa (or forward-cfa cfa)))
365 (visit-prompt-control-flow
366 forward-cfa dfg
367 (lambda (prompt handler body)
368 (define (renumber n)
369 (if (eq? forward-cfa cfa)
370 n
371 (cfa-k-idx cfa (cfa-k-sym forward-cfa n))))
372 (let ((handler (renumber handler))
373 (body (renumber body)))
374 (if reverse?
375 (vector-push! preds body handler)
376 (vector-push! preds handler body)))))))
377 cfa))
dda5fd94 378 (match fun
6e422a35
AW
379 (($ $fun src meta free
380 ($ $cont kentry
dda5fd94 381 (and entry
6e422a35 382 ($ $kentry self ($ $cont ktail tail) clauses))))
dda5fd94 383 (if reverse?
6eb02960 384 (build-cfa ktail block-preds block-succs
9002277d
AW
385 (analyze-control-flow fun dfg #:reverse? #f
386 #:add-handler-preds? #f))
387 (build-cfa kentry block-succs block-preds #f)))))
dda5fd94
AW
388
389;; Dominator analysis.
390(define-record-type $dominator-analysis
391 (make-dominator-analysis cfa idoms dom-levels loop-header irreducible)
392 dominator-analysis?
393 ;; The corresponding $cfa
394 (cfa dominator-analysis-cfa)
334bd8e3 395 ;; Vector of k-idx -> k-idx
dda5fd94 396 (idoms dominator-analysis-idoms)
334bd8e3 397 ;; Vector of k-idx -> dom-level
dda5fd94 398 (dom-levels dominator-analysis-dom-levels)
334bd8e3 399 ;; Vector of k-idx -> k-idx or -1
dda5fd94 400 (loop-header dominator-analysis-loop-header)
334bd8e3 401 ;; Vector of k-idx -> true or false value
dda5fd94 402 (irreducible dominator-analysis-irreducible))
334bd8e3 403
366eb4d7
AW
404(define (compute-dom-levels idoms)
405 (let ((dom-levels (make-vector (vector-length idoms) #f)))
3aee6cfd
AW
406 (define (compute-dom-level n)
407 (or (vector-ref dom-levels n)
408 (let ((dom-level (1+ (compute-dom-level (vector-ref idoms n)))))
409 (vector-set! dom-levels n dom-level)
410 dom-level)))
411 (vector-set! dom-levels 0 0)
412 (let lp ((n 0))
366eb4d7
AW
413 (when (< n (vector-length idoms))
414 (compute-dom-level n)
415 (lp (1+ n))))
416 dom-levels))
3aee6cfd 417
366eb4d7
AW
418(define (compute-idoms preds)
419 (let ((idoms (make-vector (vector-length preds) 0)))
3aee6cfd
AW
420 (define (common-idom d0 d1)
421 ;; We exploit the fact that a reverse post-order is a topological
422 ;; sort, and so the idom of a node is always numerically less than
423 ;; the node itself.
424 (cond
425 ((= d0 d1) d0)
426 ((< d0 d1) (common-idom d0 (vector-ref idoms d1)))
427 (else (common-idom (vector-ref idoms d0) d1))))
428 (define (compute-idom preds)
429 (match preds
430 (() 0)
431 ((pred . preds)
432 (let lp ((idom pred) (preds preds))
433 (match preds
434 (() idom)
435 ((pred . preds)
436 (lp (common-idom idom pred) preds)))))))
437 ;; This is the iterative O(n^2) fixpoint algorithm, originally from
438 ;; Allen and Cocke ("Graph-theoretic constructs for program flow
439 ;; analysis", 1972). See the discussion in Cooper, Harvey, and
440 ;; Kennedy's "A Simple, Fast Dominance Algorithm", 2001.
441 (let iterate ((n 0) (changed? #f))
442 (cond
443 ((< n (vector-length preds))
444 (let ((idom (vector-ref idoms n))
445 (idom* (compute-idom (vector-ref preds n))))
446 (cond
447 ((eqv? idom idom*)
448 (iterate (1+ n) changed?))
449 (else
450 (vector-set! idoms n idom*)
451 (iterate (1+ n) #t)))))
452 (changed?
453 (iterate 0 #f))
366eb4d7
AW
454 (else idoms)))))
455
96b8027c
AW
456;; Compute a vector containing, for each node, a list of the nodes that
457;; it immediately dominates. These are the "D" edges in the DJ tree.
458(define (compute-dom-edges idoms)
459 (let ((doms (make-vector (vector-length idoms) '())))
460 (let lp ((n 0))
461 (when (< n (vector-length idoms))
462 (let ((idom (vector-ref idoms n)))
463 (vector-push! doms idom n))
464 (lp (1+ n))))
465 doms))
466
467;; Compute a vector containing, for each node, a list of the successors
468;; of that node that are not dominated by that node. These are the "J"
469;; edges in the DJ tree.
470(define (compute-join-edges preds idoms)
471 (define (dominates? n1 n2)
472 (or (= n1 n2)
473 (and (< n1 n2)
474 (dominates? n1 (vector-ref idoms n2)))))
475 (let ((joins (make-vector (vector-length idoms) '())))
476 (let lp ((n 0))
477 (when (< n (vector-length preds))
478 (for-each (lambda (pred)
479 (unless (dominates? pred n)
480 (vector-push! joins pred n)))
481 (vector-ref preds n))
482 (lp (1+ n))))
483 joins))
484
485;; Compute a vector containing, for each node, a list of the back edges
486;; to that node. If a node is not the entry of a reducible loop, that
487;; list is empty.
488(define (compute-reducible-back-edges joins idoms)
489 (define (dominates? n1 n2)
490 (or (= n1 n2)
491 (and (< n1 n2)
492 (dominates? n1 (vector-ref idoms n2)))))
493 (let ((back-edges (make-vector (vector-length idoms) '())))
494 (let lp ((n 0))
495 (when (< n (vector-length joins))
496 (for-each (lambda (succ)
497 (when (dominates? succ n)
498 (vector-push! back-edges succ n)))
499 (vector-ref joins n))
500 (lp (1+ n))))
501 back-edges))
502
503;; Compute the levels in the dominator tree at which there are
504;; irreducible loops, as an integer. If a bit N is set in the integer,
505;; that indicates that at level N in the dominator tree, there is at
506;; least one irreducible loop.
507(define (compute-irreducible-dom-levels doms joins idoms dom-levels)
366eb4d7
AW
508 (define (dominates? n1 n2)
509 (or (= n1 n2)
510 (and (< n1 n2)
511 (dominates? n1 (vector-ref idoms n2)))))
96b8027c
AW
512 (let ((pre-order (make-vector (vector-length doms) #f))
513 (last-pre-order (make-vector (vector-length doms) #f))
514 (res 0)
515 (count 0))
516 ;; Is MAYBE-PARENT an ancestor of N on the depth-first spanning tree
517 ;; computed from the DJ graph? See Havlak 1997, "Nesting of
518 ;; Reducible and Irreducible Loops".
519 (define (ancestor? a b)
520 (let ((w (vector-ref pre-order a))
521 (v (vector-ref pre-order b)))
522 (and (<= w v)
523 (<= v (vector-ref last-pre-order w)))))
524 ;; Compute depth-first spanning tree of DJ graph.
525 (define (recurse n)
526 (unless (vector-ref pre-order n)
527 (visit n)))
528 (define (visit n)
529 ;; Pre-order visitation index.
530 (vector-set! pre-order n count)
531 (set! count (1+ count))
532 (for-each recurse (vector-ref doms n))
533 (for-each recurse (vector-ref joins n))
534 ;; Pre-order visitation index of last descendant.
535 (vector-set! last-pre-order (vector-ref pre-order n) (1- count)))
536
537 (visit 0)
538
539 (let lp ((n 0))
540 (when (< n (vector-length joins))
541 (for-each (lambda (succ)
542 ;; If this join edge is not a loop back edge but it
543 ;; does go to an ancestor on the DFST of the DJ
544 ;; graph, then we have an irreducible loop.
545 (when (and (not (dominates? succ n))
546 (ancestor? succ n))
547 (set! res (logior (ash 1 (vector-ref dom-levels succ))))))
548 (vector-ref joins n))
549 (lp (1+ n))))
550
551 res))
552
553(define (compute-nodes-by-level dom-levels)
554 (let* ((max-level (let lp ((n 0) (max-level 0))
555 (if (< n (vector-length dom-levels))
556 (lp (1+ n) (max (vector-ref dom-levels n) max-level))
557 max-level)))
558 (nodes-by-level (make-vector (1+ max-level) '())))
559 (let lp ((n (1- (vector-length dom-levels))))
560 (when (>= n 0)
561 (vector-push! nodes-by-level (vector-ref dom-levels n) n)
562 (lp (1- n))))
563 nodes-by-level))
564
565;; Collect all predecessors to the back-nodes that are strictly
566;; dominated by the loop header, and mark them as belonging to the loop.
567;; If they already have a loop header, that means they are either in a
568;; nested loop, or they have already been visited already.
569(define (mark-loop-body header back-nodes preds idoms loop-headers)
570 (define (strictly-dominates? n1 n2)
571 (and (< n1 n2)
572 (let ((idom (vector-ref idoms n2)))
573 (or (= n1 idom)
574 (strictly-dominates? n1 idom)))))
575 (define (visit node)
576 (when (strictly-dominates? header node)
577 (cond
578 ((vector-ref loop-headers node) => visit)
579 (else
580 (vector-set! loop-headers node header)
581 (for-each visit (vector-ref preds node))))))
582 (for-each visit back-nodes))
583
584(define (mark-irreducible-loops level idoms dom-levels loop-headers)
585 ;; FIXME: Identify strongly-connected components that are >= LEVEL in
586 ;; the dominator tree, and somehow mark them as irreducible.
587 (warn 'irreducible-loops-at-level level))
588
589;; "Identifying Loops Using DJ Graphs" by Sreedhar, Gao, and Lee, ACAPS
590;; Technical Memo 98, 1995.
591(define (identify-loops preds idoms dom-levels)
592 (let* ((doms (compute-dom-edges idoms))
593 (joins (compute-join-edges preds idoms))
594 (back-edges (compute-reducible-back-edges joins idoms))
595 (irreducible-levels
596 (compute-irreducible-dom-levels doms joins idoms dom-levels))
597 (loop-headers (make-vector (vector-length preds) #f))
598 (nodes-by-level (compute-nodes-by-level dom-levels)))
599 (let lp ((level (1- (vector-length nodes-by-level))))
600 (when (>= level 0)
601 (for-each (lambda (n)
602 (let ((edges (vector-ref back-edges n)))
603 (unless (null? edges)
604 (mark-loop-body n edges preds idoms loop-headers))))
605 (vector-ref nodes-by-level level))
606 (when (logbit? level irreducible-levels)
607 (mark-irreducible-loops level idoms dom-levels loop-headers))
608 (lp (1- level))))
609 loop-headers))
366eb4d7 610
dda5fd94
AW
611(define (analyze-dominators cfa)
612 (match cfa
613 (($ $cfa k-map order preds)
614 (let* ((idoms (compute-idoms preds))
615 (dom-levels (compute-dom-levels idoms))
616 (loop-headers (identify-loops preds idoms dom-levels)))
617 (make-dominator-analysis cfa idoms dom-levels loop-headers #f)))))
3aee6cfd 618
db11440d
AW
619
620;; Compute the maximum fixed point of the data-flow constraint problem.
621;;
622;; This always completes, as the graph is finite and the in and out sets
623;; are complete semi-lattices. If the graph is reducible and the blocks
624;; are sorted in reverse post-order, this completes in a maximum of LC +
625;; 2 iterations, where LC is the loop connectedness number. See Hecht
626;; and Ullman, "Analysis of a simple algorithm for global flow
627;; problems", POPL 1973, or the recent summary in "Notes on graph
628;; algorithms used in optimizing compilers", Offner 2013.
629(define (compute-maximum-fixed-point preds inv outv killv genv union?)
630 (define (bitvector-copy! dst src)
631 (bitvector-fill! dst #f)
632 (bit-set*! dst src #t))
633 (define (bitvector-meet! accum src)
634 (bit-set*! accum src union?))
635 (let lp ((n 0) (changed? #f))
636 (cond
637 ((< n (vector-length preds))
638 (let ((in (vector-ref inv n))
639 (out (vector-ref outv n))
640 (kill (vector-ref killv n))
641 (gen (vector-ref genv n)))
642 (let ((out-count (or changed? (bit-count #t out))))
643 (for-each
644 (lambda (pred)
645 (bitvector-meet! in (vector-ref outv pred)))
646 (vector-ref preds n))
647 (bitvector-copy! out in)
648 (for-each (cut bitvector-set! out <> #f) kill)
649 (for-each (cut bitvector-set! out <> #t) gen)
650 (lp (1+ n)
651 (or changed? (not (eqv? out-count (bit-count #t out))))))))
652 (changed?
653 (lp 0 #f)))))
654
655;; Data-flow analysis.
656(define-record-type $dfa
f235f926 657 (make-dfa cfa var-map names syms in out)
db11440d 658 dfa?
f235f926
AW
659 ;; CFA, for its reverse-post-order numbering
660 (cfa dfa-cfa)
334bd8e3
AW
661 ;; Hash table mapping var-sym -> var-idx
662 (var-map dfa-var-map)
db11440d
AW
663 ;; Vector of var-idx -> name
664 (names dfa-names)
665 ;; Vector of var-idx -> var-sym
666 (syms dfa-syms)
667 ;; Vector of k-idx -> bitvector
668 (in dfa-in)
669 ;; Vector of k-idx -> bitvector
670 (out dfa-out))
671
672(define (dfa-k-idx dfa k)
f235f926 673 (cfa-k-idx (dfa-cfa dfa) k))
db11440d
AW
674
675(define (dfa-k-sym dfa idx)
f235f926 676 (cfa-k-sym (dfa-cfa dfa) idx))
db11440d
AW
677
678(define (dfa-k-count dfa)
f235f926 679 (cfa-k-count (dfa-cfa dfa)))
db11440d
AW
680
681(define (dfa-var-idx dfa var)
334bd8e3
AW
682 (or (hashq-ref (dfa-var-map dfa) var)
683 (error "unknown var" var)))
db11440d
AW
684
685(define (dfa-var-name dfa idx)
686 (vector-ref (dfa-names dfa) idx))
687
688(define (dfa-var-sym dfa idx)
689 (vector-ref (dfa-syms dfa) idx))
690
691(define (dfa-var-count dfa)
692 (vector-length (dfa-syms dfa)))
693
694(define (dfa-k-in dfa idx)
695 (vector-ref (dfa-in dfa) idx))
696
697(define (dfa-k-out dfa idx)
698 (vector-ref (dfa-out dfa) idx))
699
5bff3125 700(define (compute-live-variables fun dfg)
334bd8e3 701 (define (make-variable-mapping use-maps)
db11440d
AW
702 (let ((mapping (make-hash-table))
703 (n 0))
704 (hash-for-each (lambda (sym use-map)
705 (hashq-set! mapping sym n)
706 (set! n (1+ n)))
707 use-maps)
334bd8e3 708 (values mapping n)))
f235f926
AW
709 (call-with-values (lambda () (make-variable-mapping (dfg-use-maps dfg)))
710 (lambda (var-map nvars)
146ce52d
AW
711 (let* ((cfa (analyze-control-flow fun dfg #:reverse? #t
712 #:add-handler-preds? #t))
f235f926
AW
713 (syms (make-vector nvars #f))
714 (names (make-vector nvars #f))
715 (usev (make-vector (cfa-k-count cfa) '()))
716 (defv (make-vector (cfa-k-count cfa) '()))
717 (live-in (make-vector (cfa-k-count cfa) #f))
718 (live-out (make-vector (cfa-k-count cfa) #f)))
719 ;; Initialize syms, names, defv, and usev.
720 (hash-for-each
721 (lambda (sym use-map)
722 (match use-map
723 (($ $use-map name sym def uses)
724 (let ((v (or (hashq-ref var-map sym)
725 (error "unknown var" sym))))
726 (vector-set! syms v sym)
727 (vector-set! names v name)
728 (for-each (lambda (def)
729 (vector-push! defv (cfa-k-idx cfa def) v))
730 (block-preds (lookup-block def (dfg-blocks dfg))))
731 (for-each (lambda (use)
732 (vector-push! usev (cfa-k-idx cfa use) v))
733 uses)))))
734 (dfg-use-maps dfg))
735
736 ;; Initialize live-in and live-out sets.
737 (let lp ((n 0))
738 (when (< n (vector-length live-out))
739 (vector-set! live-in n (make-bitvector nvars #f))
740 (vector-set! live-out n (make-bitvector nvars #f))
741 (lp (1+ n))))
742
743 ;; Liveness is a reverse data-flow problem, so we give
744 ;; compute-maximum-fixed-point a reversed graph, swapping in
745 ;; for out, and usev for defv. Note that since we are using
746 ;; a reverse CFA, cfa-preds are actually successors, and
747 ;; continuation 0 is ktail.
748 (compute-maximum-fixed-point (cfa-preds cfa)
749 live-out live-in defv usev #t)
750
751 (make-dfa cfa var-map names syms live-in live-out)))))
db11440d
AW
752
753(define (print-dfa dfa)
754 (match dfa
f235f926 755 (($ $dfa cfa var-map names syms in out)
db11440d
AW
756 (define (print-var-set bv)
757 (let lp ((n 0))
758 (let ((n (bit-position #t bv n)))
759 (when n
760 (format #t " ~A" (vector-ref syms n))
761 (lp (1+ n))))))
762 (let lp ((n 0))
f235f926
AW
763 (when (< n (cfa-k-count cfa))
764 (format #t "~A:\n" (cfa-k-sym cfa n))
db11440d
AW
765 (format #t " in:")
766 (print-var-set (vector-ref in n))
767 (newline)
768 (format #t " out:")
769 (print-var-set (vector-ref out n))
770 (newline)
771 (lp (1+ n)))))))
772
f22979db 773(define (visit-fun fun conts blocks use-maps global?)
fc95a944 774 (define (add-def! name sym def-k)
6e8ad823
AW
775 (unless def-k
776 (error "Term outside labelled continuation?"))
fc95a944 777 (hashq-set! use-maps sym (make-use-map name sym def-k '())))
6e8ad823
AW
778
779 (define (add-use! sym use-k)
780 (match (hashq-ref use-maps sym)
781 (#f (error "Symbol out of scope?" sym))
fc95a944 782 ((and use-map ($ $use-map name sym def uses))
6e8ad823
AW
783 (set-use-map-uses! use-map (cons use-k uses)))))
784
f22979db
AW
785 (define* (declare-block! label cont parent
786 #:optional (level
787 (1+ (lookup-scope-level parent blocks))))
788 (hashq-set! conts label cont)
789 (hashq-set! blocks label (make-block parent level)))
790
791 (define (link-blocks! pred succ)
792 (let ((pred-block (hashq-ref blocks pred))
793 (succ-block (hashq-ref blocks succ)))
794 (unless (and pred-block succ-block)
c8ad7426 795 (error "internal error" pred-block succ-block))
f22979db
AW
796 (set-block-succs! pred-block (cons succ (block-succs pred-block)))
797 (set-block-preds! succ-block (cons pred (block-preds succ-block)))))
6e8ad823
AW
798
799 (define (visit exp exp-k)
fc95a944
AW
800 (define (def! name sym)
801 (add-def! name sym exp-k))
6e8ad823
AW
802 (define (use! sym)
803 (add-use! sym exp-k))
3aee6cfd
AW
804 (define (use-k! k)
805 (link-blocks! exp-k k))
6e8ad823
AW
806 (define (recur exp)
807 (visit exp exp-k))
808 (match exp
6e422a35 809 (($ $letk (($ $cont k cont) ...) body)
6e8ad823
AW
810 ;; Set up recursive environment before visiting cont bodies.
811 (for-each (lambda (cont k)
f22979db 812 (declare-block! k cont exp-k))
6e8ad823
AW
813 cont k)
814 (for-each visit cont k)
815 (recur body))
816
817 (($ $kargs names syms body)
fc95a944 818 (for-each def! names syms)
6e8ad823
AW
819 (recur body))
820
821 (($ $kif kt kf)
f22979db
AW
822 (use-k! kt)
823 (use-k! kf))
6e8ad823 824
36527695 825 (($ $kreceive arity k)
f22979db 826 (use-k! k))
6e8ad823
AW
827
828 (($ $letrec names syms funs body)
829 (unless global?
830 (error "$letrec should not be present when building a local DFG"))
fc95a944 831 (for-each def! names syms)
f22979db 832 (for-each (cut visit-fun <> conts blocks use-maps global?) funs)
6e8ad823
AW
833 (visit body exp-k))
834
6e422a35 835 (($ $continue k src exp)
f22979db 836 (use-k! k)
6e8ad823 837 (match exp
6e8ad823
AW
838 (($ $call proc args)
839 (use! proc)
840 (for-each use! args))
841
842 (($ $primcall name args)
843 (for-each use! args))
844
845 (($ $values args)
846 (for-each use! args))
847
7ab76a83 848 (($ $prompt escape? tag handler)
6e8ad823 849 (use! tag)
146ce52d 850 (use-k! handler))
6e8ad823
AW
851
852 (($ $fun)
853 (when global?
f22979db 854 (visit-fun exp conts blocks use-maps global?)))
6e8ad823
AW
855
856 (_ #f)))))
857
858 (match fun
6e422a35
AW
859 (($ $fun src meta free
860 ($ $cont kentry
6e8ad823 861 (and entry
6e422a35 862 ($ $kentry self ($ $cont ktail tail) clauses))))
f22979db 863 (declare-block! kentry entry #f 0)
fc95a944 864 (add-def! #f self kentry)
6e8ad823 865
f22979db 866 (declare-block! ktail tail kentry)
6e8ad823
AW
867
868 (for-each
869 (match-lambda
6e422a35
AW
870 (($ $cont kclause
871 (and clause ($ $kclause arity ($ $cont kbody body))))
f22979db
AW
872 (declare-block! kclause clause kentry)
873 (link-blocks! kentry kclause)
6e8ad823 874
f22979db
AW
875 (declare-block! kbody body kclause)
876 (link-blocks! kclause kbody)
6e8ad823
AW
877
878 (visit body kbody)))
dda5fd94 879 clauses))))
6e8ad823
AW
880
881(define* (compute-dfg fun #:key (global? #t))
882 (let* ((conts (make-hash-table))
f22979db
AW
883 (blocks (make-hash-table))
884 (use-maps (make-hash-table)))
885 (visit-fun fun conts blocks use-maps global?)
886 (make-dfg conts blocks use-maps)))
6e8ad823 887
f22979db
AW
888(define (lookup-block k blocks)
889 (let ((res (hashq-ref blocks k)))
6e8ad823 890 (unless res
f22979db 891 (error "Unknown continuation!" k (hash-fold acons '() blocks)))
6e8ad823
AW
892 res))
893
f22979db
AW
894(define (lookup-scope-level k blocks)
895 (match (lookup-block k blocks)
896 (($ $block _ scope-level) scope-level)))
897
6e8ad823
AW
898(define (lookup-use-map sym use-maps)
899 (let ((res (hashq-ref use-maps sym)))
900 (unless res
901 (error "Unknown lexical!" sym (hash-fold acons '() use-maps)))
902 res))
903
904(define (lookup-def sym dfg)
905 (match dfg
f22979db 906 (($ $dfg conts blocks use-maps)
6e8ad823 907 (match (lookup-use-map sym use-maps)
fc95a944 908 (($ $use-map name sym def uses)
6e8ad823
AW
909 def)))))
910
911(define (lookup-uses sym dfg)
912 (match dfg
f22979db 913 (($ $dfg conts blocks use-maps)
6e8ad823 914 (match (lookup-use-map sym use-maps)
fc95a944 915 (($ $use-map name sym def uses)
6e8ad823
AW
916 uses)))))
917
c8ad7426
AW
918(define (lookup-block-scope k dfg)
919 (block-scope (lookup-block k (dfg-blocks dfg))))
920
f22979db
AW
921(define (lookup-predecessors k dfg)
922 (match (lookup-block k (dfg-blocks dfg))
923 (($ $block _ _ preds succs) preds)))
924
925(define (lookup-successors k dfg)
926 (match (lookup-block k (dfg-blocks dfg))
927 (($ $block _ _ preds succs) succs)))
928
6e8ad823 929(define (find-defining-term sym dfg)
f22979db 930 (match (lookup-predecessors (lookup-def sym dfg) dfg)
6e8ad823
AW
931 ((def-exp-k)
932 (lookup-cont def-exp-k (dfg-cont-table dfg)))
933 (else #f)))
934
935(define (find-call term)
936 (match term
937 (($ $kargs names syms body) (find-call body))
938 (($ $letk conts body) (find-call body))
939 (($ $letrec names syms funs body) (find-call body))
940 (($ $continue) term)))
941
942(define (call-expression call)
943 (match call
6e422a35 944 (($ $continue k src exp) exp)))
6e8ad823
AW
945
946(define (find-expression term)
947 (call-expression (find-call term)))
948
949(define (find-defining-expression sym dfg)
950 (match (find-defining-term sym dfg)
951 (#f #f)
36527695 952 (($ $kreceive) #f)
f22979db 953 (($ $kclause) #f)
6e8ad823
AW
954 (term (find-expression term))))
955
956(define (find-constant-value sym dfg)
957 (match (find-defining-expression sym dfg)
958 (($ $const val)
959 (values #t val))
6e422a35 960 (($ $continue k src ($ $void))
6e8ad823
AW
961 (values #t *unspecified*))
962 (else
963 (values #f #f))))
964
965(define (constant-needs-allocation? sym val dfg)
607fe5a6
AW
966 (define (immediate-u8? val)
967 (and (integer? val) (exact? val) (<= 0 val 255)))
968
6e8ad823
AW
969 (define (find-exp term)
970 (match term
971 (($ $kargs names syms body) (find-exp body))
972 (($ $letk conts body) (find-exp body))
973 (else term)))
974 (match dfg
f22979db 975 (($ $dfg conts blocks use-maps)
6e8ad823 976 (match (lookup-use-map sym use-maps)
fc95a944 977 (($ $use-map _ _ def uses)
6e8ad823
AW
978 (or-map
979 (lambda (use)
980 (match (find-expression (lookup-cont use conts))
981 (($ $call) #f)
58ef5f07 982 (($ $values) #f)
6e8ad823
AW
983 (($ $primcall 'free-ref (closure slot))
984 (not (eq? sym slot)))
985 (($ $primcall 'free-set! (closure slot value))
986 (not (eq? sym slot)))
987 (($ $primcall 'cache-current-module! (mod . _))
988 (eq? sym mod))
989 (($ $primcall 'cached-toplevel-box _)
990 #f)
991 (($ $primcall 'cached-module-box _)
992 #f)
993 (($ $primcall 'resolve (name bound?))
994 (eq? sym name))
4c906ad5
AW
995 (($ $primcall 'make-vector/immediate (len init))
996 (not (eq? sym len)))
997 (($ $primcall 'vector-ref/immediate (v i))
998 (not (eq? sym i)))
999 (($ $primcall 'vector-set!/immediate (v i x))
1000 (not (eq? sym i)))
1001 (($ $primcall 'allocate-struct/immediate (vtable nfields))
1002 (not (eq? sym nfields)))
1003 (($ $primcall 'struct-ref/immediate (s n))
1004 (not (eq? sym n)))
1005 (($ $primcall 'struct-set!/immediate (s n x))
1006 (not (eq? sym n)))
486013d6
AW
1007 (($ $primcall 'builtin-ref (idx))
1008 #f)
6e8ad823
AW
1009 (_ #t)))
1010 uses))))))
1011
f22979db
AW
1012(define (continuation-scope-contains? scope-k k blocks)
1013 (let ((scope-level (lookup-scope-level scope-k blocks)))
1014 (let lp ((k k))
1015 (or (eq? scope-k k)
1016 (match (lookup-block k blocks)
1017 (($ $block scope level)
1018 (and (< scope-level level)
1019 (lp scope))))))))
1020
f22979db 1021(define (continuation-bound-in? k use-k dfg)
d51fb1e6 1022 (match dfg
f22979db
AW
1023 (($ $dfg conts blocks use-maps)
1024 (match (lookup-block k blocks)
1025 (($ $block def-k)
1026 (continuation-scope-contains? def-k use-k blocks))))))
d51fb1e6
AW
1027
1028(define (variable-free-in? var k dfg)
6e8ad823 1029 (match dfg
f22979db 1030 (($ $dfg conts blocks use-maps)
6e8ad823 1031 (or-map (lambda (use)
f22979db 1032 (continuation-scope-contains? k use blocks))
6e8ad823 1033 (match (lookup-use-map var use-maps)
fc95a944 1034 (($ $use-map name sym def uses)
6e8ad823
AW
1035 uses))))))
1036
e636f424
AW
1037;; A continuation is a control point if it has multiple predecessors, or
1038;; if its single predecessor has multiple successors.
1039(define (control-point? k dfg)
1040 (match (lookup-predecessors k dfg)
1041 ((pred)
1042 (match (lookup-successors pred dfg)
1043 ((_) #f)
1044 (_ #t)))
1045 (_ #t)))
6e8ad823
AW
1046
1047(define (lookup-bound-syms k dfg)
1048 (match dfg
f22979db 1049 (($ $dfg conts blocks use-maps)
6e8ad823
AW
1050 (match (lookup-cont k conts)
1051 (($ $kargs names syms body)
1052 syms)))))