Merge remote-tracking branch 'origin/stable-2.0'
[bpt/guile.git] / module / ice-9 / eval.scm
1 ;;; -*- mode: scheme; coding: utf-8; -*-
2
3 ;;;; Copyright (C) 2009, 2010, 2011, 2012, 2013 Free Software Foundation, Inc.
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
20 \f
21
22 ;;; Commentary:
23
24 ;;; Scheme eval, written in Scheme.
25 ;;;
26 ;;; Expressions are first expanded, by the syntax expander (i.e.
27 ;;; psyntax), then memoized into internal forms. The evaluator itself
28 ;;; only operates on the internal forms ("memoized expressions").
29 ;;;
30 ;;; Environments are represented as linked lists of the form (VAL ... .
31 ;;; MOD). If MOD is #f, it means the environment was captured before
32 ;;; modules were booted. If MOD is the literal value '(), we are
33 ;;; evaluating at the top level, and so should track changes to the
34 ;;; current module.
35 ;;;
36 ;;; Evaluate this in Emacs to make code indentation work right:
37 ;;;
38 ;;; (put 'memoized-expression-case 'scheme-indent-function 1)
39 ;;;
40
41 ;;; Code:
42
43 \f
44
45 (eval-when (compile)
46 (define-syntax capture-env
47 (syntax-rules ()
48 ((_ (exp ...))
49 (let ((env (exp ...)))
50 (capture-env env)))
51 ((_ env)
52 (if (null? env)
53 (current-module)
54 (if (not env)
55 ;; the and current-module checks that modules are booted,
56 ;; and thus the-root-module is defined
57 (and (current-module) the-root-module)
58 env)))))
59
60 ;; Fast case for procedures with fixed arities.
61 (define-syntax make-fixed-closure
62 (lambda (x)
63 (define *max-static-argument-count* 8)
64 (define (make-formals n)
65 (map (lambda (i)
66 (datum->syntax
67 x
68 (string->symbol
69 (string (integer->char (+ (char->integer #\a) i))))))
70 (iota n)))
71 (syntax-case x ()
72 ((_ eval nreq body env) (not (identifier? #'env))
73 #'(let ((e env))
74 (make-fixed-closure eval nreq body e)))
75 ((_ eval nreq body env)
76 #`(case nreq
77 #,@(map (lambda (nreq)
78 (let ((formals (make-formals nreq)))
79 #`((#,nreq)
80 (lambda (#,@formals)
81 (eval body
82 (cons* #,@(reverse formals) env))))))
83 (iota *max-static-argument-count*))
84 (else
85 #,(let ((formals (make-formals *max-static-argument-count*)))
86 #`(lambda (#,@formals . more)
87 (let lp ((new-env (cons* #,@(reverse formals) env))
88 (nreq (- nreq #,*max-static-argument-count*))
89 (args more))
90 (if (zero? nreq)
91 (eval body
92 (if (null? args)
93 new-env
94 (scm-error 'wrong-number-of-args
95 "eval" "Wrong number of arguments"
96 '() #f)))
97 (if (null? args)
98 (scm-error 'wrong-number-of-args
99 "eval" "Wrong number of arguments"
100 '() #f)
101 (lp (cons (car args) new-env)
102 (1- nreq)
103 (cdr args)))))))))))))
104
105 (define-syntax call
106 (lambda (x)
107 (define *max-static-call-count* 4)
108 (syntax-case x ()
109 ((_ eval proc nargs args env) (identifier? #'env)
110 #`(case nargs
111 #,@(map (lambda (nargs)
112 #`((#,nargs)
113 (proc
114 #,@(map
115 (lambda (n)
116 (let lp ((n n) (args #'args))
117 (if (zero? n)
118 #`(eval (car #,args) env)
119 (lp (1- n) #`(cdr #,args)))))
120 (iota nargs)))))
121 (iota *max-static-call-count*))
122 (else
123 (apply proc
124 #,@(map
125 (lambda (n)
126 (let lp ((n n) (args #'args))
127 (if (zero? n)
128 #`(eval (car #,args) env)
129 (lp (1- n) #`(cdr #,args)))))
130 (iota *max-static-call-count*))
131 (let lp ((exps #,(let lp ((n *max-static-call-count*)
132 (args #'args))
133 (if (zero? n)
134 args
135 (lp (1- n) #`(cdr #,args)))))
136 (args '()))
137 (if (null? exps)
138 (reverse args)
139 (lp (cdr exps)
140 (cons (eval (car exps) env) args)))))))))))
141
142 ;; This macro could be more straightforward if the compiler had better
143 ;; copy propagation. As it is we do some copy propagation by hand.
144 (define-syntax mx-bind
145 (lambda (x)
146 (syntax-case x ()
147 ((_ data () body)
148 #'body)
149 ((_ data (a . b) body) (and (identifier? #'a) (identifier? #'b))
150 #'(let ((a (car data))
151 (b (cdr data)))
152 body))
153 ((_ data (a . b) body) (identifier? #'a)
154 #'(let ((a (car data))
155 (xb (cdr data)))
156 (mx-bind xb b body)))
157 ((_ data (a . b) body)
158 #'(let ((xa (car data))
159 (xb (cdr data)))
160 (mx-bind xa a (mx-bind xb b body))))
161 ((_ data v body) (identifier? #'v)
162 #'(let ((v data))
163 body)))))
164
165 ;; The resulting nested if statements will be an O(n) dispatch. Once
166 ;; we compile `case' effectively, this situation will improve.
167 (define-syntax mx-match
168 (lambda (x)
169 (syntax-case x (quote)
170 ((_ mx data tag)
171 #'(error "what" mx))
172 ((_ mx data tag (('type pat) body) c* ...)
173 #`(if (eqv? tag #,(or (memoized-typecode (syntax->datum #'type))
174 (error "not a typecode" #'type)))
175 (mx-bind data pat body)
176 (mx-match mx data tag c* ...))))))
177
178 (define-syntax memoized-expression-case
179 (lambda (x)
180 (syntax-case x ()
181 ((_ mx c ...)
182 #'(let ((tag (memoized-expression-typecode mx))
183 (data (memoized-expression-data mx)))
184 (mx-match mx data tag c ...)))))))
185
186
187 ;;;
188 ;;; On 18 Feb 2010, I did a profile of how often the various memoized expression
189 ;;; types occur when getting to a prompt on a fresh build. Here are the numbers
190 ;;; I got:
191 ;;;
192 ;;; lexical-ref: 32933054
193 ;;; call: 20281547
194 ;;; toplevel-ref: 13228724
195 ;;; if: 9156156
196 ;;; quote: 6610137
197 ;;; let: 2619707
198 ;;; lambda: 1010921
199 ;;; begin: 948945
200 ;;; lexical-set: 509862
201 ;;; call-with-values: 139668
202 ;;; apply: 49402
203 ;;; module-ref: 14468
204 ;;; define: 1259
205 ;;; toplevel-set: 328
206 ;;; dynwind: 162
207 ;;; with-fluids: 0
208 ;;; call/cc: 0
209 ;;; module-set: 0
210 ;;;
211 ;;; So until we compile `case' into a computed goto, we'll order the clauses in
212 ;;; `eval' in this order, to put the most frequent cases first.
213 ;;;
214
215 (define primitive-eval
216 (let ()
217 ;; We pre-generate procedures with fixed arities, up to some number of
218 ;; arguments; see make-fixed-closure above.
219
220 ;; A unique marker for unbound keywords.
221 (define unbound-arg (list 'unbound-arg))
222
223 ;; Procedures with rest, optional, or keyword arguments, potentially with
224 ;; multiple arities, as with case-lambda.
225 (define (make-general-closure env body nreq rest? nopt kw inits alt)
226 (define alt-proc
227 (and alt ; (body docstring nreq ...)
228 (let* ((body (car alt))
229 (spec (cddr alt))
230 (nreq (car spec))
231 (rest (if (null? (cdr spec)) #f (cadr spec)))
232 (tail (and (pair? (cdr spec)) (pair? (cddr spec)) (cddr spec)))
233 (nopt (if tail (car tail) 0))
234 (kw (and tail (cadr tail)))
235 (inits (if tail (caddr tail) '()))
236 (alt (and tail (cadddr tail))))
237 (make-general-closure env body nreq rest nopt kw inits alt))))
238 (define (set-procedure-arity! proc)
239 (let lp ((alt alt) (nreq nreq) (nopt nopt) (rest? rest?))
240 (if (not alt)
241 (begin
242 (set-procedure-property! proc 'arglist
243 (list nreq
244 nopt
245 (if kw (cdr kw) '())
246 (and kw (car kw))
247 (and rest? '_)))
248 (set-procedure-minimum-arity! proc nreq nopt rest?))
249 (let* ((spec (cddr alt))
250 (nreq* (car spec))
251 (rest?* (if (null? (cdr spec)) #f (cadr spec)))
252 (tail (and (pair? (cdr spec)) (pair? (cddr spec)) (cddr spec)))
253 (nopt* (if tail (car tail) 0))
254 (alt* (and tail (cadddr tail))))
255 (if (or (< nreq* nreq)
256 (and (= nreq* nreq)
257 (if rest?
258 (and rest?* (> nopt* nopt))
259 (or rest?* (> nopt* nopt)))))
260 (lp alt* nreq* nopt* rest?*)
261 (lp alt* nreq nopt rest?)))))
262 proc)
263 (set-procedure-arity!
264 (lambda %args
265 (let lp ((env env)
266 (nreq* nreq)
267 (args %args))
268 (if (> nreq* 0)
269 ;; First, bind required arguments.
270 (if (null? args)
271 (if alt
272 (apply alt-proc %args)
273 (scm-error 'wrong-number-of-args
274 "eval" "Wrong number of arguments"
275 '() #f))
276 (lp (cons (car args) env)
277 (1- nreq*)
278 (cdr args)))
279 ;; Move on to optional arguments.
280 (if (not kw)
281 ;; Without keywords, bind optionals from arguments.
282 (let lp ((env env)
283 (nopt nopt)
284 (args args)
285 (inits inits))
286 (if (zero? nopt)
287 (if rest?
288 (eval body (cons args env))
289 (if (null? args)
290 (eval body env)
291 (if alt
292 (apply alt-proc %args)
293 (scm-error 'wrong-number-of-args
294 "eval" "Wrong number of arguments"
295 '() #f))))
296 (if (null? args)
297 (lp (cons (eval (car inits) env) env)
298 (1- nopt) args (cdr inits))
299 (lp (cons (car args) env)
300 (1- nopt) (cdr args) (cdr inits)))))
301 (let lp ((env env)
302 (nopt* nopt)
303 (args args)
304 (inits inits))
305 (cond
306 ;; With keywords, we stop binding optionals at the
307 ;; first keyword.
308 ((> nopt* 0)
309 (if (or (null? args) (keyword? (car args)))
310 (lp (cons (eval (car inits) env) env)
311 (1- nopt*) args (cdr inits))
312 (lp (cons (car args) env)
313 (1- nopt*) (cdr args) (cdr inits))))
314 ;; Finished with optionals.
315 ((and alt (pair? args) (not (keyword? (car args)))
316 (not rest?))
317 ;; Too many positional args, no #:rest arg,
318 ;; and we have an alternate.
319 (apply alt-proc %args))
320 (else
321 (let* ((aok (car kw))
322 (kw (cdr kw))
323 (kw-base (+ nopt nreq (if rest? 1 0)))
324 (imax (let lp ((imax (1- kw-base)) (kw kw))
325 (if (null? kw)
326 imax
327 (lp (max (cdar kw) imax)
328 (cdr kw)))))
329 ;; Fill in kwargs with "undefined" vals.
330 (env (let lp ((i kw-base)
331 ;; Also, here we bind the rest
332 ;; arg, if any.
333 (env (if rest?
334 (cons args env)
335 env)))
336 (if (<= i imax)
337 (lp (1+ i) (cons unbound-arg env))
338 env))))
339 ;; Now scan args for keywords.
340 (let lp ((args args))
341 (if (and (pair? args) (pair? (cdr args))
342 (keyword? (car args)))
343 (let ((kw-pair (assq (car args) kw))
344 (v (cadr args)))
345 (if kw-pair
346 ;; Found a known keyword; set its value.
347 (list-set! env
348 (- imax (cdr kw-pair)) v)
349 ;; Unknown keyword.
350 (if (not aok)
351 (scm-error
352 'keyword-argument-error
353 "eval" "Unrecognized keyword"
354 '() #f)))
355 (lp (cddr args)))
356 (if (pair? args)
357 (if rest?
358 ;; Be lenient parsing rest args.
359 (lp (cdr args))
360 (scm-error 'keyword-argument-error
361 "eval" "Invalid keyword"
362 '() #f))
363 ;; Finished parsing keywords. Fill in
364 ;; uninitialized kwargs by evalling init
365 ;; expressions in their appropriate
366 ;; environment.
367 (let lp ((i (- imax kw-base))
368 (inits inits))
369 (if (pair? inits)
370 (let ((tail (list-tail env i)))
371 (if (eq? (car tail) unbound-arg)
372 (set-car! tail
373 (eval (car inits)
374 (cdr tail))))
375 (lp (1- i) (cdr inits)))
376 ;; Finally, eval the body.
377 (eval body env))))))))))))))))
378
379 ;; The "engine". EXP is a memoized expression.
380 (define (eval exp env)
381 (memoized-expression-case exp
382 (('lexical-ref n)
383 (list-ref env n))
384
385 (('call (f nargs . args))
386 (let ((proc (eval f env)))
387 (call eval proc nargs args env)))
388
389 (('toplevel-ref var-or-sym)
390 (variable-ref
391 (if (variable? var-or-sym)
392 var-or-sym
393 (memoize-variable-access! exp
394 (capture-env (if (pair? env)
395 (cdr (last-pair env))
396 env))))))
397
398 (('if (test consequent . alternate))
399 (if (eval test env)
400 (eval consequent env)
401 (eval alternate env)))
402
403 (('quote x)
404 x)
405
406 (('let (inits . body))
407 (let lp ((inits inits) (new-env (capture-env env)))
408 (if (null? inits)
409 (eval body new-env)
410 (lp (cdr inits)
411 (cons (eval (car inits) env) new-env)))))
412
413 (('lambda (body docstring nreq . tail))
414 (let ((proc
415 (if (null? tail)
416 (make-fixed-closure eval nreq body (capture-env env))
417 (if (null? (cdr tail))
418 (make-general-closure (capture-env env) body
419 nreq (car tail)
420 0 #f '() #f)
421 (apply make-general-closure (capture-env env)
422 body nreq tail)))))
423 (when docstring
424 (set-procedure-property! proc 'documentation docstring))
425 proc))
426
427 (('seq (head . tail))
428 (begin
429 (eval head env)
430 (eval tail env)))
431
432 (('lexical-set! (n . x))
433 (let ((val (eval x env)))
434 (list-set! env n val)))
435
436 (('call-with-values (producer . consumer))
437 (call-with-values (eval producer env)
438 (eval consumer env)))
439
440 (('apply (f args))
441 (apply (eval f env) (eval args env)))
442
443 (('module-ref var-or-spec)
444 (variable-ref
445 (if (variable? var-or-spec)
446 var-or-spec
447 (memoize-variable-access! exp #f))))
448
449 (('define (name . x))
450 (let ((x (eval x env)))
451 (if (and (procedure? x) (not (procedure-property x 'name)))
452 (set-procedure-property! x 'name name))
453 (define! name x)
454 (if #f #f)))
455
456 (('toplevel-set! (var-or-sym . x))
457 (variable-set!
458 (if (variable? var-or-sym)
459 var-or-sym
460 (memoize-variable-access! exp
461 (capture-env (if (pair? env)
462 (cdr (last-pair env))
463 env))))
464 (eval x env)))
465
466 (('dynwind (in exp . out))
467 (dynamic-wind (eval in env)
468 (lambda () (eval exp env))
469 (eval out env)))
470
471 (('with-fluids (fluids vals . exp))
472 (let* ((fluids (map (lambda (x) (eval x env)) fluids))
473 (vals (map (lambda (x) (eval x env)) vals)))
474 (let lp ((fluids fluids) (vals vals))
475 (if (null? fluids)
476 (eval exp env)
477 (with-fluids (((car fluids) (car vals)))
478 (lp (cdr fluids) (cdr vals)))))))
479
480 (('prompt (tag exp . handler))
481 (@prompt (eval tag env)
482 (eval exp env)
483 (eval handler env)))
484
485 (('call/cc proc)
486 (call/cc (eval proc env)))
487
488 (('module-set! (x . var-or-spec))
489 (variable-set!
490 (if (variable? var-or-spec)
491 var-or-spec
492 (memoize-variable-access! exp #f))
493 (eval x env)))))
494
495 ;; primitive-eval
496 (lambda (exp)
497 "Evaluate @var{exp} in the current module."
498 (eval
499 (memoize-expression
500 (if (macroexpanded? exp)
501 exp
502 ((module-transformer (current-module)) exp)))
503 '()))))