123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460 |
- ;;; -*- mode: scheme; coding: utf-8; -*-
- ;;;; Copyright (C) 2009, 2010
- ;;;; Free Software Foundation, Inc.
- ;;;;
- ;;;; This library is free software; you can redistribute it and/or
- ;;;; modify it under the terms of the GNU Lesser General Public
- ;;;; License as published by the Free Software Foundation; either
- ;;;; version 3 of the License, or (at your option) any later version.
- ;;;;
- ;;;; This library is distributed in the hope that it will be useful,
- ;;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
- ;;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
- ;;;; Lesser General Public License for more details.
- ;;;;
- ;;;; You should have received a copy of the GNU Lesser General Public
- ;;;; License along with this library; if not, write to the Free Software
- ;;;; Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
- ;;;;
- ;;; Commentary:
- ;;; Scheme eval, written in Scheme.
- ;;;
- ;;; Expressions are first expanded, by the syntax expander (i.e.
- ;;; psyntax), then memoized into internal forms. The evaluator itself
- ;;; only operates on the internal forms ("memoized expressions").
- ;;;
- ;;; Environments are represented as linked lists of the form (VAL ... .
- ;;; MOD). If MOD is #f, it means the environment was captured before
- ;;; modules were booted. If MOD is the literal value '(), we are
- ;;; evaluating at the top level, and so should track changes to the
- ;;; current module.
- ;;;
- ;;; Evaluate this in Emacs to make code indentation work right:
- ;;;
- ;;; (put 'memoized-expression-case 'scheme-indent-function 1)
- ;;;
- ;;; Code:
- (eval-when (compile)
- (define-syntax capture-env
- (syntax-rules ()
- ((_ (exp ...))
- (let ((env (exp ...)))
- (capture-env env)))
- ((_ env)
- (if (null? env)
- (current-module)
- (if (not env)
- ;; the and current-module checks that modules are booted,
- ;; and thus the-root-module is defined
- (and (current-module) the-root-module)
- env)))))
- ;; Fast case for procedures with fixed arities.
- (define-syntax make-fixed-closure
- (lambda (x)
- (define *max-static-argument-count* 8)
- (define (make-formals n)
- (map (lambda (i)
- (datum->syntax
- x
- (string->symbol
- (string (integer->char (+ (char->integer #\a) i))))))
- (iota n)))
- (syntax-case x ()
- ((_ eval nreq body env) (not (identifier? #'env))
- #'(let ((e env))
- (make-fixed-closure eval nreq body e)))
- ((_ eval nreq body env)
- #`(case nreq
- #,@(map (lambda (nreq)
- (let ((formals (make-formals nreq)))
- #`((#,nreq)
- (lambda (#,@formals)
- (eval body
- (cons* #,@(reverse formals) env))))))
- (iota *max-static-argument-count*))
- (else
- #,(let ((formals (make-formals *max-static-argument-count*)))
- #`(lambda (#,@formals . more)
- (let lp ((new-env (cons* #,@(reverse formals) env))
- (nreq (- nreq #,*max-static-argument-count*))
- (args more))
- (if (zero? nreq)
- (eval body
- (if (null? args)
- new-env
- (scm-error 'wrong-number-of-args
- "eval" "Wrong number of arguments"
- '() #f)))
- (if (null? args)
- (scm-error 'wrong-number-of-args
- "eval" "Wrong number of arguments"
- '() #f)
- (lp (cons (car args) new-env)
- (1- nreq)
- (cdr args)))))))))))))
- (define-syntax call
- (lambda (x)
- (define *max-static-call-count* 4)
- (syntax-case x ()
- ((_ eval proc nargs args env) (identifier? #'env)
- #`(case nargs
- #,@(map (lambda (nargs)
- #`((#,nargs)
- (proc
- #,@(map
- (lambda (n)
- (let lp ((n n) (args #'args))
- (if (zero? n)
- #`(eval (car #,args) env)
- (lp (1- n) #`(cdr #,args)))))
- (iota nargs)))))
- (iota *max-static-call-count*))
- (else
- (apply proc
- #,@(map
- (lambda (n)
- (let lp ((n n) (args #'args))
- (if (zero? n)
- #`(eval (car #,args) env)
- (lp (1- n) #`(cdr #,args)))))
- (iota *max-static-call-count*))
- (let lp ((exps #,(let lp ((n *max-static-call-count*)
- (args #'args))
- (if (zero? n)
- args
- (lp (1- n) #`(cdr #,args)))))
- (args '()))
- (if (null? exps)
- (reverse args)
- (lp (cdr exps)
- (cons (eval (car exps) env) args)))))))))))
- ;; This macro could be more straightforward if the compiler had better
- ;; copy propagation. As it is we do some copy propagation by hand.
- (define-syntax mx-bind
- (lambda (x)
- (syntax-case x ()
- ((_ data () body)
- #'body)
- ((_ data (a . b) body) (and (identifier? #'a) (identifier? #'b))
- #'(let ((a (car data))
- (b (cdr data)))
- body))
- ((_ data (a . b) body) (identifier? #'a)
- #'(let ((a (car data))
- (xb (cdr data)))
- (mx-bind xb b body)))
- ((_ data (a . b) body)
- #'(let ((xa (car data))
- (xb (cdr data)))
- (mx-bind xa a (mx-bind xb b body))))
- ((_ data v body) (identifier? #'v)
- #'(let ((v data))
- body)))))
-
- ;; The resulting nested if statements will be an O(n) dispatch. Once
- ;; we compile `case' effectively, this situation will improve.
- (define-syntax mx-match
- (lambda (x)
- (syntax-case x (quote)
- ((_ mx data tag)
- #'(error "what" mx))
- ((_ mx data tag (('type pat) body) c* ...)
- #`(if (eqv? tag #,(or (memoized-typecode (syntax->datum #'type))
- (error "not a typecode" #'type)))
- (mx-bind data pat body)
- (mx-match mx data tag c* ...))))))
- (define-syntax memoized-expression-case
- (lambda (x)
- (syntax-case x ()
- ((_ mx c ...)
- #'(let ((tag (memoized-expression-typecode mx))
- (data (memoized-expression-data mx)))
- (mx-match mx data tag c ...)))))))
- ;;;
- ;;; On 18 Feb 2010, I did a profile of how often the various memoized expression
- ;;; types occur when getting to a prompt on a fresh build. Here are the numbers
- ;;; I got:
- ;;;
- ;;; lexical-ref: 32933054
- ;;; call: 20281547
- ;;; toplevel-ref: 13228724
- ;;; if: 9156156
- ;;; quote: 6610137
- ;;; let: 2619707
- ;;; lambda: 1010921
- ;;; begin: 948945
- ;;; lexical-set: 509862
- ;;; call-with-values: 139668
- ;;; apply: 49402
- ;;; module-ref: 14468
- ;;; define: 1259
- ;;; toplevel-set: 328
- ;;; dynwind: 162
- ;;; with-fluids: 0
- ;;; call/cc: 0
- ;;; module-set: 0
- ;;;
- ;;; So until we compile `case' into a computed goto, we'll order the clauses in
- ;;; `eval' in this order, to put the most frequent cases first.
- ;;;
- (define primitive-eval
- (let ()
- ;; We pre-generate procedures with fixed arities, up to some number of
- ;; arguments; see make-fixed-closure above.
- ;; A unique marker for unbound keywords.
- (define unbound-arg (list 'unbound-arg))
- ;; Procedures with rest, optional, or keyword arguments, potentially with
- ;; multiple arities, as with case-lambda.
- (define (make-general-closure env body nreq rest? nopt kw inits alt)
- (define alt-proc
- (and alt
- (let* ((body (car alt))
- (nreq (cadr alt))
- (rest (if (null? (cddr alt)) #f (caddr alt)))
- (tail (and (pair? (cddr alt)) (pair? (cdddr alt)) (cdddr alt)))
- (nopt (if tail (car tail) 0))
- (kw (and tail (cadr tail)))
- (inits (if tail (caddr tail) '()))
- (alt (and tail (cadddr tail))))
- (make-general-closure env body nreq rest nopt kw inits alt))))
- (lambda %args
- (let lp ((env env)
- (nreq* nreq)
- (args %args))
- (if (> nreq* 0)
- ;; First, bind required arguments.
- (if (null? args)
- (if alt
- (apply alt-proc %args)
- (scm-error 'wrong-number-of-args
- "eval" "Wrong number of arguments"
- '() #f))
- (lp (cons (car args) env)
- (1- nreq*)
- (cdr args)))
- ;; Move on to optional arguments.
- (if (not kw)
- ;; Without keywords, bind optionals from arguments.
- (let lp ((env env)
- (nopt nopt)
- (args args)
- (inits inits))
- (if (zero? nopt)
- (if rest?
- (eval body (cons args env))
- (if (null? args)
- (eval body env)
- (if alt
- (apply alt-proc %args)
- (scm-error 'wrong-number-of-args
- "eval" "Wrong number of arguments"
- '() #f))))
- (if (null? args)
- (lp (cons (eval (car inits) env) env)
- (1- nopt) args (cdr inits))
- (lp (cons (car args) env)
- (1- nopt) (cdr args) (cdr inits)))))
- ;; With keywords, we stop binding optionals at the first
- ;; keyword.
- (let lp ((env env)
- (nopt* nopt)
- (args args)
- (inits inits))
- (if (> nopt* 0)
- (if (or (null? args) (keyword? (car args)))
- (lp (cons (eval (car inits) env) env)
- (1- nopt*) args (cdr inits))
- (lp (cons (car args) env)
- (1- nopt*) (cdr args) (cdr inits)))
- ;; Finished with optionals.
- (let* ((aok (car kw))
- (kw (cdr kw))
- (kw-base (+ nopt nreq (if rest? 1 0)))
- (imax (let lp ((imax (1- kw-base)) (kw kw))
- (if (null? kw)
- imax
- (lp (max (cdar kw) imax)
- (cdr kw)))))
- ;; Fill in kwargs with "undefined" vals.
- (env (let lp ((i kw-base)
- ;; Also, here we bind the rest
- ;; arg, if any.
- (env (if rest? (cons args env) env)))
- (if (<= i imax)
- (lp (1+ i) (cons unbound-arg env))
- env))))
- ;; Now scan args for keywords.
- (let lp ((args args))
- (if (and (pair? args) (pair? (cdr args))
- (keyword? (car args)))
- (let ((kw-pair (assq (car args) kw))
- (v (cadr args)))
- (if kw-pair
- ;; Found a known keyword; set its value.
- (list-set! env (- imax (cdr kw-pair)) v)
- ;; Unknown keyword.
- (if (not aok)
- (scm-error 'keyword-argument-error
- "eval" "Unrecognized keyword"
- '() #f)))
- (lp (cddr args)))
- (if (pair? args)
- (if rest?
- ;; Be lenient parsing rest args.
- (lp (cdr args))
- (scm-error 'keyword-argument-error
- "eval" "Invalid keyword"
- '() #f))
- ;; Finished parsing keywords. Fill in
- ;; uninitialized kwargs by evalling init
- ;; expressions in their appropriate
- ;; environment.
- (let lp ((i (- imax kw-base))
- (inits inits))
- (if (pair? inits)
- (let ((tail (list-tail env i)))
- (if (eq? (car tail) unbound-arg)
- (set-car! tail
- (eval (car inits)
- (cdr tail))))
- (lp (1- i) (cdr inits)))
- ;; Finally, eval the body.
- (eval body env))))))))))))))
- ;; The "engine". EXP is a memoized expression.
- (define (eval exp env)
- (memoized-expression-case exp
- (('lexical-ref n)
- (list-ref env n))
-
- (('call (f nargs . args))
- (let ((proc (eval f env)))
- (call eval proc nargs args env)))
-
- (('toplevel-ref var-or-sym)
- (variable-ref
- (if (variable? var-or-sym)
- var-or-sym
- (memoize-variable-access! exp
- (capture-env (if (pair? env)
- (cdr (last-pair env))
- env))))))
- (('if (test consequent . alternate))
- (if (eval test env)
- (eval consequent env)
- (eval alternate env)))
-
- (('quote x)
- x)
- (('let (inits . body))
- (let lp ((inits inits) (new-env (capture-env env)))
- (if (null? inits)
- (eval body new-env)
- (lp (cdr inits)
- (cons (eval (car inits) env) new-env)))))
-
- (('lambda (body nreq . tail))
- (if (null? tail)
- (make-fixed-closure eval nreq body (capture-env env))
- (if (null? (cdr tail))
- (make-general-closure (capture-env env) body nreq (car tail)
- 0 #f '() #f)
- (apply make-general-closure (capture-env env) body nreq tail))))
- (('begin (first . rest))
- (let lp ((first first) (rest rest))
- (if (null? rest)
- (eval first env)
- (begin
- (eval first env)
- (lp (car rest) (cdr rest))))))
-
- (('lexical-set! (n . x))
- (let ((val (eval x env)))
- (list-set! env n val)))
-
- (('call-with-values (producer . consumer))
- (call-with-values (eval producer env)
- (eval consumer env)))
- (('apply (f args))
- (apply (eval f env) (eval args env)))
- (('module-ref var-or-spec)
- (variable-ref
- (if (variable? var-or-spec)
- var-or-spec
- (memoize-variable-access! exp #f))))
- (('define (name . x))
- (define! name (eval x env)))
-
- (('toplevel-set! (var-or-sym . x))
- (variable-set!
- (if (variable? var-or-sym)
- var-or-sym
- (memoize-variable-access! exp
- (capture-env (if (pair? env)
- (cdr (last-pair env))
- env))))
- (eval x env)))
-
- (('dynwind (in exp . out))
- (dynamic-wind (eval in env)
- (lambda () (eval exp env))
- (eval out env)))
-
- (('with-fluids (fluids vals . exp))
- (let* ((fluids (map (lambda (x) (eval x env)) fluids))
- (vals (map (lambda (x) (eval x env)) vals)))
- (let lp ((fluids fluids) (vals vals))
- (if (null? fluids)
- (eval exp env)
- (with-fluids (((car fluids) (car vals)))
- (lp (cdr fluids) (cdr vals)))))))
-
- (('prompt (tag exp . handler))
- (@prompt (eval tag env)
- (eval exp env)
- (eval handler env)))
-
- (('call/cc proc)
- (call/cc (eval proc env)))
- (('module-set! (x . var-or-spec))
- (variable-set!
- (if (variable? var-or-spec)
- var-or-spec
- (memoize-variable-access! exp #f))
- (eval x env)))))
-
- ;; primitive-eval
- (lambda (exp)
- "Evaluate @var{exp} in the current module."
- (eval
- (memoize-expression
- (if (macroexpanded? exp)
- exp
- ((module-transformer (current-module)) exp)))
- '()))))
|