;;; compiler.lisp ---
;; copyright (C) 2012, 2013 David Vazquez
;; Copyright (C) 2012 Raimon Grau
;; JSCL is free software: you can redistribute it and/or
;; modify it under the terms of the GNU General Public License as
;; published by the Free Software Foundation, either version 3 of the
;; License, or (at your option) any later version.
;;
;; JSCL 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
;; General Public License for more details.
;;
;; You should have received a copy of the GNU General Public License
;; along with JSCL. If not, see .
;;;; Compiler
;;; Translate the Lisp code to Javascript. It will compile the special
;;; forms. Some primitive functions are compiled as special forms
;;; too. The respective real functions are defined in the target (see
;;; the beginning of this file) as well as some primitive functions.
(defun code (&rest args)
(mapconcat (lambda (arg)
(cond
((null arg) "")
((integerp arg) (integer-to-string arg))
((floatp arg) (float-to-string arg))
((stringp arg) arg)
(t (error "Unknown argument `~S'." arg))))
args))
;;; Wrap X with a Javascript code to convert the result from
;;; Javascript generalized booleans to T or NIL.
(defun js!bool (x)
(code "(" x "?" (ls-compile t) ": " (ls-compile nil) ")"))
;;; Concatenate the arguments and wrap them with a self-calling
;;; Javascript anonymous function. It is used to make some Javascript
;;; statements valid expressions and provide a private scope as well.
;;; It could be defined as function, but we could do some
;;; preprocessing in the future.
(defmacro js!selfcall (&body body)
`(code "(function(){" *newline* (indent ,@body) "})()"))
;;; Like CODE, but prefix each line with four spaces. Two versions
;;; of this function are available, because the Ecmalisp version is
;;; very slow and bootstraping was annoying.
#+jscl
(defun indent (&rest string)
(let ((input (apply #'code string)))
(let ((output "")
(index 0)
(size (length input)))
(when (plusp (length input)) (concatf output " "))
(while (< index size)
(let ((str
(if (and (char= (char input index) #\newline)
(< index (1- size))
(not (char= (char input (1+ index)) #\newline)))
(concat (string #\newline) " ")
(string (char input index)))))
(concatf output str))
(incf index))
output)))
#+common-lisp
(defun indent (&rest string)
(with-output-to-string (*standard-output*)
(with-input-from-string (input (apply #'code string))
(loop
for line = (read-line input nil)
while line
do (write-string " ")
do (write-line line)))))
;;; A Form can return a multiple values object calling VALUES, like
;;; values(arg1, arg2, ...). It will work in any context, as well as
;;; returning an individual object. However, if the special variable
;;; `*multiple-value-p*' is NIL, is granted that only the primary
;;; value will be used, so we can optimize to avoid the VALUES
;;; function call.
(defvar *multiple-value-p* nil)
;; A very simple defstruct built on lists. It supports just slot with
;; an optional default initform, and it will create a constructor,
;; predicate and accessors for you.
(defmacro def!struct (name &rest slots)
(unless (symbolp name)
(error "It is not a full defstruct implementation."))
(let* ((name-string (symbol-name name))
(slot-descriptions
(mapcar (lambda (sd)
(cond
((symbolp sd)
(list sd))
((and (listp sd) (car sd) (cddr sd))
sd)
(t
(error "Bad slot description `~S'." sd))))
slots))
(predicate (intern (concat name-string "-P"))))
`(progn
;; Constructor
(defun ,(intern (concat "MAKE-" name-string)) (&key ,@slot-descriptions)
(list ',name ,@(mapcar #'car slot-descriptions)))
;; Predicate
(defun ,predicate (x)
(and (consp x) (eq (car x) ',name)))
;; Copier
(defun ,(intern (concat "COPY-" name-string)) (x)
(copy-list x))
;; Slot accessors
,@(with-collect
(let ((index 1))
(dolist (slot slot-descriptions)
(let* ((name (car slot))
(accessor-name (intern (concat name-string "-" (string name)))))
(collect
`(defun ,accessor-name (x)
(unless (,predicate x)
(error "The object `~S' is not of type `~S'" x ,name-string))
(nth ,index x)))
;; TODO: Implement this with a higher level
;; abstraction like defsetf or (defun (setf ..))
(collect
`(define-setf-expander ,accessor-name (x)
(let ((object (gensym))
(new-value (gensym)))
(values (list object)
(list x)
(list new-value)
`(progn
(rplaca (nthcdr ,',index ,object) ,new-value)
,new-value)
`(,',accessor-name ,object)))))
(incf index)))))
',name)))
;;; Environment
(def!struct binding
name
type
value
declarations)
(def!struct lexenv
variable
function
block
gotag)
(defun lookup-in-lexenv (name lexenv namespace)
(find name (ecase namespace
(variable (lexenv-variable lexenv))
(function (lexenv-function lexenv))
(block (lexenv-block lexenv))
(gotag (lexenv-gotag lexenv)))
:key #'binding-name))
(defun push-to-lexenv (binding lexenv namespace)
(ecase namespace
(variable (push binding (lexenv-variable lexenv)))
(function (push binding (lexenv-function lexenv)))
(block (push binding (lexenv-block lexenv)))
(gotag (push binding (lexenv-gotag lexenv)))))
(defun extend-lexenv (bindings lexenv namespace)
(let ((env (copy-lexenv lexenv)))
(dolist (binding (reverse bindings) env)
(push-to-lexenv binding env namespace))))
(defvar *environment* (make-lexenv))
(defvar *variable-counter* 0)
(defun gvarname (symbol)
(declare (ignore symbol))
(code "v" (incf *variable-counter*)))
(defun translate-variable (symbol)
(awhen (lookup-in-lexenv symbol *environment* 'variable)
(binding-value it)))
(defun extend-local-env (args)
(let ((new (copy-lexenv *environment*)))
(dolist (symbol args new)
(let ((b (make-binding :name symbol :type 'variable :value (gvarname symbol))))
(push-to-lexenv b new 'variable)))))
;;; Toplevel compilations
(defvar *toplevel-compilations* nil)
(defun toplevel-compilation (string)
(push string *toplevel-compilations*))
(defun null-or-empty-p (x)
(zerop (length x)))
(defun get-toplevel-compilations ()
(reverse (remove-if #'null-or-empty-p *toplevel-compilations*)))
(defun %compile-defmacro (name lambda)
(toplevel-compilation (ls-compile `',name))
(let ((binding (make-binding :name name :type 'macro :value lambda)))
(push-to-lexenv binding *environment* 'function))
name)
(defun global-binding (name type namespace)
(or (lookup-in-lexenv name *environment* namespace)
(let ((b (make-binding :name name :type type :value nil)))
(push-to-lexenv b *environment* namespace)
b)))
(defun claimp (symbol namespace claim)
(let ((b (lookup-in-lexenv symbol *environment* namespace)))
(and b (member claim (binding-declarations b)))))
(defun !proclaim (decl)
(case (car decl)
(special
(dolist (name (cdr decl))
(let ((b (global-binding name 'variable 'variable)))
(push 'special (binding-declarations b)))))
(notinline
(dolist (name (cdr decl))
(let ((b (global-binding name 'function 'function)))
(push 'notinline (binding-declarations b)))))
(constant
(dolist (name (cdr decl))
(let ((b (global-binding name 'variable 'variable)))
(push 'constant (binding-declarations b)))))))
#+jscl
(fset 'proclaim #'!proclaim)
(defun %define-symbol-macro (name expansion)
(let ((b (make-binding :name name :type 'macro :value expansion)))
(push-to-lexenv b *environment* 'variable)
name))
#+jscl
(defmacro define-symbol-macro (name expansion)
`(%define-symbol-macro ',name ',expansion))
;;; Special forms
(defvar *compilations* nil)
(defmacro define-compilation (name args &body body)
;; Creates a new primitive `name' with parameters args and
;; @body. The body can access to the local environment through the
;; variable *ENVIRONMENT*.
`(push (list ',name (lambda ,args (block ,name ,@body)))
*compilations*))
(define-compilation if (condition true false)
(code "(" (ls-compile condition) " !== " (ls-compile nil)
" ? " (ls-compile true *multiple-value-p*)
" : " (ls-compile false *multiple-value-p*)
")"))
(defvar *ll-keywords* '(&optional &rest &key))
(defun list-until-keyword (list)
(if (or (null list) (member (car list) *ll-keywords*))
nil
(cons (car list) (list-until-keyword (cdr list)))))
(defun ll-section (keyword ll)
(list-until-keyword (cdr (member keyword ll))))
(defun ll-required-arguments (ll)
(list-until-keyword ll))
(defun ll-optional-arguments-canonical (ll)
(mapcar #'ensure-list (ll-section '&optional ll)))
(defun ll-optional-arguments (ll)
(mapcar #'car (ll-optional-arguments-canonical ll)))
(defun ll-rest-argument (ll)
(let ((rest (ll-section '&rest ll)))
(when (cdr rest)
(error "Bad lambda-list `~S'." ll))
(car rest)))
(defun ll-keyword-arguments-canonical (ll)
(flet ((canonicalize (keyarg)
;; Build a canonical keyword argument descriptor, filling
;; the optional fields. The result is a list of the form
;; ((keyword-name var) init-form).
(let ((arg (ensure-list keyarg)))
(cons (if (listp (car arg))
(car arg)
(list (intern (symbol-name (car arg)) "KEYWORD") (car arg)))
(cdr arg)))))
(mapcar #'canonicalize (ll-section '&key ll))))
(defun ll-keyword-arguments (ll)
(mapcar (lambda (keyarg) (second (first keyarg)))
(ll-keyword-arguments-canonical ll)))
(defun ll-svars (lambda-list)
(let ((args
(append
(ll-keyword-arguments-canonical lambda-list)
(ll-optional-arguments-canonical lambda-list))))
(remove nil (mapcar #'third args))))
(defun lambda-name/docstring-wrapper (name docstring &rest strs)
(if (or name docstring)
(js!selfcall
"var func = " (join strs) ";" *newline*
(when name
(code "func.fname = '" (escape-string name) "';" *newline*))
(when docstring
(code "func.docstring = '" (escape-string docstring) "';" *newline*))
"return func;" *newline*)
(apply #'code strs)))
(defun lambda-check-argument-count
(n-required-arguments n-optional-arguments rest-p)
;; Note: Remember that we assume that the number of arguments of a
;; call is at least 1 (the values argument).
(let ((min n-required-arguments)
(max (if rest-p 'n/a (+ n-required-arguments n-optional-arguments))))
(block nil
;; Special case: a positive exact number of arguments.
(when (and (< 0 min) (eql min max))
(return (code "checkArgs(nargs, " min ");" *newline*)))
;; General case:
(code
(when (< 0 min)
(code "checkArgsAtLeast(nargs, " min ");" *newline*))
(when (numberp max)
(code "checkArgsAtMost(nargs, " max ");" *newline*))))))
(defun compile-lambda-optional (ll)
(let* ((optional-arguments (ll-optional-arguments-canonical ll))
(n-required-arguments (length (ll-required-arguments ll)))
(n-optional-arguments (length optional-arguments)))
(when optional-arguments
(code "switch(nargs){" *newline*
(let ((cases nil)
(idx 0))
(progn
(while (< idx n-optional-arguments)
(let ((arg (nth idx optional-arguments)))
(push (code "case " (+ idx n-required-arguments) ":" *newline*
(indent (translate-variable (car arg))
"="
(ls-compile (cadr arg)) ";" *newline*)
(when (third arg)
(indent (translate-variable (third arg))
"="
(ls-compile nil)
";" *newline*)))
cases)
(incf idx)))
(push (code "default: break;" *newline*) cases)
(join (reverse cases))))
"}" *newline*))))
(defun compile-lambda-rest (ll)
(let ((n-required-arguments (length (ll-required-arguments ll)))
(n-optional-arguments (length (ll-optional-arguments ll)))
(rest-argument (ll-rest-argument ll)))
(when rest-argument
(let ((js!rest (translate-variable rest-argument)))
(code "var " js!rest "= " (ls-compile nil) ";" *newline*
"for (var i = nargs-1; i>=" (+ n-required-arguments n-optional-arguments)
"; i--)" *newline*
(indent js!rest " = {car: arguments[i+2], cdr: " js!rest "};" *newline*))))))
(defun compile-lambda-parse-keywords (ll)
(let ((n-required-arguments
(length (ll-required-arguments ll)))
(n-optional-arguments
(length (ll-optional-arguments ll)))
(keyword-arguments
(ll-keyword-arguments-canonical ll)))
(code
;; Declare variables
(mapconcat (lambda (arg)
(let ((var (second (car arg))))
(code "var " (translate-variable var) "; " *newline*
(when (third arg)
(code "var " (translate-variable (third arg))
" = " (ls-compile nil)
";" *newline*)))))
keyword-arguments)
;; Parse keywords
(flet ((parse-keyword (keyarg)
;; ((keyword-name var) init-form)
(code "for (i=" (+ n-required-arguments n-optional-arguments)
"; i (LIST* a b c foo)
;;; provided a, b, c are not splicing frobs
;;; (APPEND (LIST* a b c) foo) => (LIST* a b (APPEND c foo))
;;; provided a, b, c are not splicing frobs
;;; (APPEND (QUOTE (x)) foo) => (LIST* (QUOTE x) foo)
;;; (APPEND (CLOBBERABLE x) foo) => (NCONC x foo)
(defun bq-simplify (x)
(if (atom x)
x
(let ((x (if (eq (car x) *bq-quote*)
x
(maptree #'bq-simplify x))))
(if (not (eq (car x) *bq-append*))
x
(bq-simplify-args x)))))
(defun bq-simplify-args (x)
(do ((args (reverse (cdr x)) (cdr args))
(result
nil
(cond ((atom (car args))
(bq-attach-append *bq-append* (car args) result))
((and (eq (caar args) *bq-list*)
(notany #'bq-splicing-frob (cdar args)))
(bq-attach-conses (cdar args) result))
((and (eq (caar args) *bq-list**)
(notany #'bq-splicing-frob (cdar args)))
(bq-attach-conses
(reverse (cdr (reverse (cdar args))))
(bq-attach-append *bq-append*
(car (last (car args)))
result)))
((and (eq (caar args) *bq-quote*)
(consp (cadar args))
(not (bq-frob (cadar args)))
(null (cddar args)))
(bq-attach-conses (list (list *bq-quote*
(caadar args)))
result))
((eq (caar args) *bq-clobberable*)
(bq-attach-append *bq-nconc* (cadar args) result))
(t (bq-attach-append *bq-append*
(car args)
result)))))
((null args) result)))
(defun null-or-quoted (x)
(or (null x) (and (consp x) (eq (car x) *bq-quote*))))
;;; When BQ-ATTACH-APPEND is called, the OP should be #:BQ-APPEND
;;; or #:BQ-NCONC. This produces a form (op item result) but
;;; some simplifications are done on the fly:
;;;
;;; (op '(a b c) '(d e f g)) => '(a b c d e f g)
;;; (op item 'nil) => item, provided item is not a splicable frob
;;; (op item 'nil) => (op item), if item is a splicable frob
;;; (op item (op a b c)) => (op item a b c)
(defun bq-attach-append (op item result)
(cond ((and (null-or-quoted item) (null-or-quoted result))
(list *bq-quote* (append (cadr item) (cadr result))))
((or (null result) (equal result *bq-quote-nil*))
(if (bq-splicing-frob item) (list op item) item))
((and (consp result) (eq (car result) op))
(list* (car result) item (cdr result)))
(t (list op item result))))
;;; The effect of BQ-ATTACH-CONSES is to produce a form as if by
;;; `(LIST* ,@items ,result) but some simplifications are done
;;; on the fly.
;;;
;;; (LIST* 'a 'b 'c 'd) => '(a b c . d)
;;; (LIST* a b c 'nil) => (LIST a b c)
;;; (LIST* a b c (LIST* d e f g)) => (LIST* a b c d e f g)
;;; (LIST* a b c (LIST d e f g)) => (LIST a b c d e f g)
(defun bq-attach-conses (items result)
(cond ((and (every #'null-or-quoted items)
(null-or-quoted result))
(list *bq-quote*
(append (mapcar #'cadr items) (cadr result))))
((or (null result) (equal result *bq-quote-nil*))
(cons *bq-list* items))
((and (consp result)
(or (eq (car result) *bq-list*)
(eq (car result) *bq-list**)))
(cons (car result) (append items (cdr result))))
(t (cons *bq-list** (append items (list result))))))
;;; Removes funny tokens and changes (#:BQ-LIST* a b) into
;;; (CONS a b) instead of (LIST* a b), purely for readability.
(defun bq-remove-tokens (x)
(cond ((eq x *bq-list*) 'list)
((eq x *bq-append*) 'append)
((eq x *bq-nconc*) 'nconc)
((eq x *bq-list**) 'list*)
((eq x *bq-quote*) 'quote)
((atom x) x)
((eq (car x) *bq-clobberable*)
(bq-remove-tokens (cadr x)))
((and (eq (car x) *bq-list**)
(consp (cddr x))
(null (cdddr x)))
(cons 'cons (maptree #'bq-remove-tokens (cdr x))))
(t (maptree #'bq-remove-tokens x))))
(define-transformation backquote (form)
(bq-completely-process form))
;;; Primitives
(defvar *builtins* nil)
(defmacro define-raw-builtin (name args &body body)
;; Creates a new primitive function `name' with parameters args and
;; @body. The body can access to the local environment through the
;; variable *ENVIRONMENT*.
`(push (list ',name (lambda ,args (block ,name ,@body)))
*builtins*))
(defmacro define-builtin (name args &body body)
`(define-raw-builtin ,name ,args
(let ,(mapcar (lambda (arg) `(,arg (ls-compile ,arg))) args)
,@body)))
;;; DECLS is a list of (JSVARNAME TYPE LISPFORM) declarations.
(defmacro type-check (decls &body body)
`(js!selfcall
,@(mapcar (lambda (decl)
`(code "var " ,(first decl) " = " ,(third decl) ";" *newline*))
decls)
,@(mapcar (lambda (decl)
`(code "if (typeof " ,(first decl) " != '" ,(second decl) "')" *newline*
(indent "throw 'The value ' + "
,(first decl)
" + ' is not a type "
,(second decl)
".';"
*newline*)))
decls)
(code "return " (progn ,@body) ";" *newline*)))
;;; VARIABLE-ARITY compiles variable arity operations. ARGS stands for
;;; a variable which holds a list of forms. It will compile them and
;;; store the result in some Javascript variables. BODY is evaluated
;;; with ARGS bound to the list of these variables to generate the
;;; code which performs the transformation on these variables.
(defun variable-arity-call (args function)
(unless (consp args)
(error "ARGS must be a non-empty list"))
(let ((counter 0)
(fargs '())
(prelude ""))
(dolist (x args)
(cond
((floatp x) (push (float-to-string x) fargs))
((numberp x) (push (integer-to-string x) fargs))
(t (let ((v (code "x" (incf counter))))
(push v fargs)
(concatf prelude
(code "var " v " = " (ls-compile x) ";" *newline*
"if (typeof " v " !== 'number') throw 'Not a number!';"
*newline*))))))
(js!selfcall prelude (funcall function (reverse fargs)))))
(defmacro variable-arity (args &body body)
(unless (symbolp args)
(error "`~S' is not a symbol." args))
`(variable-arity-call ,args
(lambda (,args)
(code "return " ,@body ";" *newline*))))
(defun num-op-num (x op y)
(type-check (("x" "number" x) ("y" "number" y))
(code "x" op "y")))
(define-raw-builtin + (&rest numbers)
(if (null numbers)
"0"
(variable-arity numbers
(join numbers "+"))))
(define-raw-builtin - (x &rest others)
(let ((args (cons x others)))
(variable-arity args
(if (null others)
(concat "-" (car args))
(join args "-")))))
(define-raw-builtin * (&rest numbers)
(if (null numbers)
"1"
(variable-arity numbers
(join numbers "*"))))
(define-raw-builtin / (x &rest others)
(let ((args (cons x others)))
(variable-arity args
(if (null others)
(concat "1 /" (car args))
(join args "/")))))
(define-builtin mod (x y) (num-op-num x "%" y))
(defun comparison-conjuntion (vars op)
(cond
((null (cdr vars))
"true")
((null (cddr vars))
(concat (car vars) op (cadr vars)))
(t
(concat (car vars) op (cadr vars)
" && "
(comparison-conjuntion (cdr vars) op)))))
(defmacro define-builtin-comparison (op sym)
`(define-raw-builtin ,op (x &rest args)
(let ((args (cons x args)))
(variable-arity args
(js!bool (comparison-conjuntion args ,sym))))))
(define-builtin-comparison > ">")
(define-builtin-comparison < "<")
(define-builtin-comparison >= ">=")
(define-builtin-comparison <= "<=")
(define-builtin-comparison = "==")
(define-builtin numberp (x)
(js!bool (code "(typeof (" x ") == \"number\")")))
(define-builtin floor (x)
(type-check (("x" "number" x))
"Math.floor(x)"))
(define-builtin expt (x y)
(type-check (("x" "number" x)
("y" "number" y))
"Math.pow(x, y)"))
(define-builtin float-to-string (x)
(type-check (("x" "number" x))
"x.toString()"))
(define-builtin cons (x y)
(code "({car: " x ", cdr: " y "})"))
(define-builtin consp (x)
(js!bool
(js!selfcall
"var tmp = " x ";" *newline*
"return (typeof tmp == 'object' && 'car' in tmp);" *newline*)))
(define-builtin car (x)
(js!selfcall
"var tmp = " x ";" *newline*
"return tmp === " (ls-compile nil)
"? " (ls-compile nil)
": tmp.car;" *newline*))
(define-builtin cdr (x)
(js!selfcall
"var tmp = " x ";" *newline*
"return tmp === " (ls-compile nil) "? "
(ls-compile nil)
": tmp.cdr;" *newline*))
(define-builtin rplaca (x new)
(type-check (("x" "object" x))
(code "(x.car = " new ", x)")))
(define-builtin rplacd (x new)
(type-check (("x" "object" x))
(code "(x.cdr = " new ", x)")))
(define-builtin symbolp (x)
(js!bool
(js!selfcall
"var tmp = " x ";" *newline*
"return (typeof tmp == 'object' && 'name' in tmp);" *newline*)))
(define-builtin make-symbol (name)
(type-check (("name" "string" name))
"({name: name})"))
(define-builtin symbol-name (x)
(code "(" x ").name"))
(define-builtin set (symbol value)
(code "(" symbol ").value = " value))
(define-builtin fset (symbol value)
(code "(" symbol ").fvalue = " value))
(define-builtin boundp (x)
(js!bool (code "(" x ".value !== undefined)")))
(define-builtin symbol-value (x)
(js!selfcall
"var symbol = " x ";" *newline*
"var value = symbol.value;" *newline*
"if (value === undefined) throw \"Variable `\" + symbol.name + \"' is unbound.\";" *newline*
"return value;" *newline*))
(define-builtin symbol-function (x)
(js!selfcall
"var symbol = " x ";" *newline*
"var func = symbol.fvalue;" *newline*
"if (func === undefined) throw \"Function `\" + symbol.name + \"' is undefined.\";" *newline*
"return func;" *newline*))
(define-builtin symbol-plist (x)
(code "((" x ").plist || " (ls-compile nil) ")"))
(define-builtin lambda-code (x)
(code "(" x ").toString()"))
(define-builtin eq (x y)
(js!bool (code "(" x " === " y ")")))
(define-builtin char-code (x)
(type-check (("x" "string" x))
"x.charCodeAt(0)"))
(define-builtin code-char (x)
(type-check (("x" "number" x))
"String.fromCharCode(x)"))
(define-builtin characterp (x)
(js!bool
(js!selfcall
"var x = " x ";" *newline*
"return (typeof(" x ") == \"string\") && x.length == 1;")))
(define-builtin char-to-string (x)
(type-check (("x" "string" x))
"(x)"))
(define-builtin stringp (x)
(js!bool (code "(typeof(" x ") == \"string\")")))
(define-builtin string-upcase (x)
(type-check (("x" "string" x))
"x.toUpperCase()"))
(define-builtin string-length (x)
(type-check (("x" "string" x))
"x.length"))
(define-raw-builtin slice (string a &optional b)
(js!selfcall
"var str = " (ls-compile string) ";" *newline*
"var a = " (ls-compile a) ";" *newline*
"var b;" *newline*
(when b (code "b = " (ls-compile b) ";" *newline*))
"return str.slice(a,b);" *newline*))
(define-builtin char (string index)
(type-check (("string" "string" string)
("index" "number" index))
"string.charAt(index)"))
(define-builtin concat-two (string1 string2)
(type-check (("string1" "string" string1)
("string2" "string" string2))
"string1.concat(string2)"))
(define-raw-builtin funcall (func &rest args)
(js!selfcall
"var f = " (ls-compile func) ";" *newline*
"return (typeof f === 'function'? f: f.fvalue)("
(join (list* (if *multiple-value-p* "values" "pv")
(integer-to-string (length args))
(mapcar #'ls-compile args))
", ")
")"))
(define-raw-builtin apply (func &rest args)
(if (null args)
(code "(" (ls-compile func) ")()")
(let ((args (butlast args))
(last (car (last args))))
(js!selfcall
"var f = " (ls-compile func) ";" *newline*
"var args = [" (join (list* (if *multiple-value-p* "values" "pv")
(integer-to-string (length args))
(mapcar #'ls-compile args))
", ")
"];" *newline*
"var tail = (" (ls-compile last) ");" *newline*
"while (tail != " (ls-compile nil) "){" *newline*
" args.push(tail.car);" *newline*
" args[1] += 1;" *newline*
" tail = tail.cdr;" *newline*
"}" *newline*
"return (typeof f === 'function'? f : f.fvalue).apply(this, args);" *newline*))))
(define-builtin js-eval (string)
(type-check (("string" "string" string))
(if *multiple-value-p*
(js!selfcall
"var v = globalEval(string);" *newline*
"return values.apply(this, forcemv(v));" *newline*)
"globalEval(string)")))
(define-builtin %throw (string)
(js!selfcall "throw " string ";" *newline*))
(define-builtin new () "{}")
(define-builtin objectp (x)
(js!bool (code "(typeof (" x ") === 'object')")))
(define-builtin oget (object key)
(js!selfcall
"var tmp = " "(" object ")[" key "];" *newline*
"return tmp == undefined? " (ls-compile nil) ": tmp ;" *newline*))
(define-builtin oset (object key value)
(code "((" object ")[" key "] = " value ")"))
(define-builtin in (key object)
(js!bool (code "((" key ") in (" object "))")))
(define-builtin functionp (x)
(js!bool (code "(typeof " x " == 'function')")))
(define-builtin write-string (x)
(type-check (("x" "string" x))
"lisp.write(x)"))
(define-builtin make-array (n)
(js!selfcall
"var r = [];" *newline*
"for (var i = 0; i < " n "; i++)" *newline*
(indent "r.push(" (ls-compile nil) ");" *newline*)
"return r;" *newline*))
(define-builtin arrayp (x)
(js!bool
(js!selfcall
"var x = " x ";" *newline*
"return typeof x === 'object' && 'length' in x;")))
(define-builtin aref (array n)
(js!selfcall
"var x = " "(" array ")[" n "];" *newline*
"if (x === undefined) throw 'Out of range';" *newline*
"return x;" *newline*))
(define-builtin aset (array n value)
(js!selfcall
"var x = " array ";" *newline*
"var i = " n ";" *newline*
"if (i < 0 || i >= x.length) throw 'Out of range';" *newline*
"return x[i] = " value ";" *newline*))
(define-builtin get-internal-real-time ()
"(new Date()).getTime()")
(define-builtin values-array (array)
(if *multiple-value-p*
(code "values.apply(this, " array ")")
(code "pv.apply(this, " array ")")))
(define-raw-builtin values (&rest args)
(if *multiple-value-p*
(code "values(" (join (mapcar #'ls-compile args) ", ") ")")
(code "pv(" (join (mapcar #'ls-compile args) ", ") ")")))
;; Receives the JS function as first argument as a literal string. The
;; second argument is compiled and should evaluate to a vector of
;; values to apply to the the function. The result returned.
(define-builtin %js-call (fun args)
(code fun ".apply(this, " args ")"))
#+common-lisp
(defvar *macroexpander-cache*
(make-hash-table :test #'eq))
(defun !macro-function (symbol)
(unless (symbolp symbol)
(error "`~S' is not a symbol." symbol))
(let ((b (lookup-in-lexenv symbol *environment* 'function)))
(if (and b (eq (binding-type b) 'macro))
(let ((expander (binding-value b)))
(cond
#+common-lisp
((gethash b *macroexpander-cache*)
(setq expander (gethash b *macroexpander-cache*)))
((listp expander)
(let ((compiled (eval expander)))
;; The list representation are useful while
;; bootstrapping, as we can dump the definition of the
;; macros easily, but they are slow because we have to
;; evaluate them and compile them now and again. So, let
;; us replace the list representation version of the
;; function with the compiled one.
;;
#+jscl (setf (binding-value b) compiled)
#+common-lisp (setf (gethash b *macroexpander-cache*) compiled)
(setq expander compiled))))
expander)
nil)))
(defun !macroexpand-1 (form)
(cond
((symbolp form)
(let ((b (lookup-in-lexenv form *environment* 'variable)))
(if (and b (eq (binding-type b) 'macro))
(values (binding-value b) t)
(values form nil))))
((consp form)
(let ((macrofun (!macro-function (car form))))
(if macrofun
(values (apply macrofun (cdr form)) t)
(values form nil))))
(t
(values form nil))))
(defun compile-funcall (function args)
(let* ((values-funcs (if *multiple-value-p* "values" "pv"))
(arglist (concat "(" (join (list* values-funcs
(integer-to-string (length args))
(mapcar #'ls-compile args)) ", ") ")")))
(unless (or (symbolp function)
(and (consp function)
(eq (car function) 'lambda)))
(error "Bad function designator `~S'" function))
(cond
((translate-function function)
(concat (translate-function function) arglist))
((and (symbolp function)
#+jscl (eq (symbol-package function) (find-package "COMMON-LISP"))
#+common-lisp t)
(code (ls-compile `',function) ".fvalue" arglist))
(t
(code (ls-compile `#',function) arglist)))))
(defun ls-compile-block (sexps &optional return-last-p)
(if return-last-p
(code (ls-compile-block (butlast sexps))
"return " (ls-compile (car (last sexps)) *multiple-value-p*) ";")
(join-trailing
(remove-if #'null-or-empty-p (mapcar #'ls-compile sexps))
(concat ";" *newline*))))
(defun ls-compile (sexp &optional multiple-value-p)
(multiple-value-bind (sexp expandedp) (!macroexpand-1 sexp)
(when expandedp
(return-from ls-compile (ls-compile sexp multiple-value-p)))
;; The expression has been macroexpanded. Now compile it!
(let ((*multiple-value-p* multiple-value-p))
(cond
((symbolp sexp)
(let ((b (lookup-in-lexenv sexp *environment* 'variable)))
(cond
((and b (not (member 'special (binding-declarations b))))
(binding-value b))
((or (keywordp sexp)
(and b (member 'constant (binding-declarations b))))
(code (ls-compile `',sexp) ".value"))
(t
(ls-compile `(symbol-value ',sexp))))))
((integerp sexp) (integer-to-string sexp))
((floatp sexp) (float-to-string sexp))
((characterp sexp) (code "\"" (escape-string (string sexp)) "\""))
((stringp sexp) (code "\"" (escape-string sexp) "\""))
((arrayp sexp) (literal sexp))
((listp sexp)
(let ((name (car sexp))
(args (cdr sexp)))
(cond
;; Special forms
((assoc name *compilations*)
(let ((comp (second (assoc name *compilations*))))
(apply comp args)))
;; Built-in functions
((and (assoc name *builtins*)
(not (claimp name 'function 'notinline)))
(let ((comp (second (assoc name *builtins*))))
(apply comp args)))
(t
(compile-funcall name args)))))
(t
(error "How should I compile `~S'?" sexp))))))
(defvar *compile-print-toplevels* nil)
(defun truncate-string (string &optional (width 60))
(let ((n (or (position #\newline string)
(min width (length string)))))
(subseq string 0 n)))
(defun ls-compile-toplevel (sexp &optional multiple-value-p)
(let ((*toplevel-compilations* nil))
(cond
((and (consp sexp) (eq (car sexp) 'progn))
(let ((subs (mapcar (lambda (s)
(ls-compile-toplevel s t))
(cdr sexp))))
(join (remove-if #'null-or-empty-p subs))))
(t
(when *compile-print-toplevels*
(let ((form-string (prin1-to-string sexp)))
(write-string "Compiling ")
(write-string (truncate-string form-string))
(write-line "...")))
(let ((code (ls-compile sexp multiple-value-p)))
(code (join-trailing (get-toplevel-compilations)
(code ";" *newline*))
(when code
(code code ";" *newline*))))))))