For loop
[jscl.git] / src / compiler-codegen.lisp
1 ;;; compiler-codege.lisp --- Naive Javascript unparser
2
3 ;; copyright (C) 2013 David Vazquez
4
5 ;; JSCL is free software: you can redistribute it and/or
6 ;; modify it under the terms of the GNU General Public License as
7 ;; published by the Free Software Foundation, either version 3 of the
8 ;; License, or (at your option) any later version.
9 ;;
10 ;; JSCL is distributed in the hope that it will be useful, but
11 ;; WITHOUT ANY WARRANTY; without even the implied warranty of
12 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
13 ;; General Public License for more details.
14 ;;
15 ;; You should have received a copy of the GNU General Public License
16 ;; along with JSCL.  If not, see <http://www.gnu.org/licenses/>.
17
18 ;;; This code generator takes as input a S-expression representation
19 ;;; of the Javascript AST and generates Javascript code without
20 ;;; redundant syntax constructions like extra parenthesis.
21 ;;;
22 ;;; It is intended to be used with the new compiler. However, it is
23 ;;; quite independent so it has been integrated early in JSCL.
24
25 (/debug "loading compiler-codegen.lisp!")
26
27 (defvar *js-output* t)
28
29 ;;; Two seperate functions are needed for escaping strings:
30 ;;;  One for producing JavaScript string literals (which are singly or
31 ;;;   doubly quoted)
32 ;;;  And one for producing Lisp strings (which are only doubly quoted)
33 ;;;
34 ;;; The same function would suffice for both, but for javascript string
35 ;;; literals it is neater to use either depending on the context, e.g:
36 ;;;  foo's => "foo's"
37 ;;;  "foo" => '"foo"'
38 ;;; which avoids having to escape quotes where possible
39 (defun js-escape-string (string)
40   (let ((index 0)
41         (size (length string))
42         (seen-single-quote nil)
43         (seen-double-quote nil))
44     (flet ((%js-escape-string (string escape-single-quote-p)
45              (let ((output "")
46                    (index 0))
47                (while (< index size)
48                  (let ((ch (char string index)))
49                    (when (char= ch #\\)
50                      (setq output (concat output "\\")))
51                    (when (and escape-single-quote-p (char= ch #\'))
52                      (setq output (concat output "\\")))
53                    (when (char= ch #\newline)
54                      (setq output (concat output "\\"))
55                      (setq ch #\n))
56                    (setq output (concat output (string ch))))
57                  (incf index))
58                output)))
59       ;; First, scan the string for single/double quotes
60       (while (< index size)
61         (let ((ch (char string index)))
62           (when (char= ch #\')
63             (setq seen-single-quote t))
64           (when (char= ch #\")
65             (setq seen-double-quote t)))
66         (incf index))
67       ;; Then pick the appropriate way to escape the quotes
68       (cond
69         ((not seen-single-quote)
70          (concat "'"   (%js-escape-string string nil) "'"))
71         ((not seen-double-quote)
72          (concat "\""  (%js-escape-string string nil) "\""))
73         (t (concat "'" (%js-escape-string string t)   "'"))))))
74
75
76 (defun js-format (fmt &rest args)
77   (apply #'format *js-output* fmt args))
78
79 (defun valid-js-identifier (string-designator)
80   (let ((string (typecase string-designator
81                   (symbol (symbol-name string-designator))
82                   (string string-designator)
83                   (t
84                    (return-from valid-js-identifier (values nil nil))))))
85     (flet ((constitutentp (ch)
86              (or (alphanumericp ch) (member ch '(#\$ #\_)))))
87       (if (and (every #'constitutentp string)
88                (if (plusp (length string))
89                    (not (digit-char-p (char string 0)))
90                    t))
91           (values (format nil "~a" string) t)
92           (values nil nil)))))
93
94 (defun js-identifier (string-designator)
95   (multiple-value-bind (string valid)
96       (valid-js-identifier string-designator)
97     (unless valid
98       (error "~S is not a valid Javascript identifier." string))
99     (js-format "~a" string)))
100
101 (defun js-primary-expr (form)
102   (cond
103     ((numberp form)
104      (if (<= 0 form)
105          (js-format "~a" form)
106          (js-expr `(- ,(abs form)))))
107     ((stringp form)
108      (js-format "~a" (js-escape-string form)))
109     ((symbolp form)
110      (case form
111        (true      (js-format "true"))
112        (false     (js-format "false"))
113        (null      (js-format "null"))
114        (this      (js-format "this"))
115        (undefined (js-format "undefined"))
116        (otherwise
117         (js-identifier form))))
118     (t
119      (error "Unknown Javascript syntax ~S." form))))
120
121 (defun js-vector-initializer (vector)
122   (let ((size (length vector)))
123     (js-format "[")
124     (dotimes (i (1- size))
125       (let ((elt (aref vector i)))
126         (unless (eq elt 'null)
127           (js-expr elt))
128         (js-format ",")))
129     (when (plusp size)
130       (js-expr (aref vector (1- size))))
131     (js-format "]")))
132
133 (defun js-object-initializer (plist)
134   (js-format "{")
135   (do* ((tail plist (cddr tail)))
136        ((null tail))
137     (let ((key (car tail))
138           (value (cadr tail)))
139       (multiple-value-bind (identifier identifier-p) (valid-js-identifier key)
140         (declare (ignore identifier))
141         (if identifier-p
142             (js-identifier key)
143             (js-expr (string key))))
144       (js-format ": ")
145       (js-expr value)
146       (unless (null (cddr tail))
147         (js-format ","))))
148   (js-format "}"))
149
150 (defun js-function (arguments &rest body)
151   (js-format "function(")
152   (when arguments
153     (js-identifier (car arguments))
154     (dolist (arg (cdr arguments))
155       (js-format ",")
156       (js-identifier arg)))
157   (js-format ")")
158   (js-stmt `(group ,@body) t))
159
160 (defun check-lvalue (x)
161   (unless (or (symbolp x)
162               (nth-value 1 (valid-js-identifier x))
163               (and (consp x)
164                    (member (car x) '(get = property))))
165     (error "Bad Javascript lvalue ~S" x)))
166
167 ;;; Process the Javascript AST to reduce some syntax sugar.
168 (defun js-expand-expr (form)
169   (if (consp form)
170       (case (car form)
171         (+
172          (case (length (cdr form))
173            (1 `(unary+ ,(cadr form)))
174            (t (reduce (lambda (x y) `(+ ,x ,y)) (cdr form)))))
175         (-
176          (case (length (cdr form))
177            (1 `(unary- ,(cadr form)))
178            (t (reduce (lambda (x y) `(- ,x ,y)) (cdr form)))))
179         ((progn comma)
180          (reduce (lambda (x y) `(comma ,x ,y)) (cdr form) :from-end t))
181         (t form))
182       form))
183
184 ;; Initialized to any value larger than any operator precedence
185 (defvar *js-operator-precedence* 1000)
186 (defvar *js-operator-associativity* 'left)
187 (defvar *js-operand-order* 'left)
188
189 ;; Format an expression optionally wrapped with parenthesis if the
190 ;; precedence rules require it.
191 (defmacro with-operator ((precedence associativity) &body body)
192   (let ((g!parens (gensym))
193         (g!precedence (gensym)))
194     `(let* ((,g!precedence ,precedence)
195             (,g!parens
196              (cond
197                ((> ,g!precedence *js-operator-precedence*))
198                ((< ,g!precedence *js-operator-precedence*) nil)
199                ;; Same precedence. Let us consider associativity.
200                (t
201                 (not (eq *js-operand-order* *js-operator-associativity*)))))
202             (*js-operator-precedence* ,g!precedence)
203             (*js-operator-associativity* ,associativity)
204             (*js-operand-order* 'left))
205        (when ,g!parens (js-format "("))
206        (progn ,@body)
207        (when ,g!parens (js-format ")")))))
208
209 (defun js-operator (string)
210   (js-format "~a" string)
211   (setq *js-operand-order* 'right))
212
213 (defun js-operator-expression (op args)
214   (let ((op1 (car args))
215         (op2 (cadr args)))
216     (case op
217       ;; Transactional compatible operator
218       (code
219        (js-format "~a" (apply #'code args)))
220       ;; Function call
221       (call
222        (js-expr (car args))
223        (js-format "(")
224        (when (cdr args)
225          (with-operator (12 'left)
226            (js-expr (cadr args))
227            (dolist (operand (cddr args))
228              (let ((*js-output* t))
229                (js-format ",")
230                (js-expr operand)))))
231        (js-format ")"))
232       ;; Accessors
233       (property
234        (js-expr (car args))
235        (js-format "[")
236        (js-expr (cadr args))
237        (js-format "]"))
238       (get
239        (multiple-value-bind (identifier identifierp)
240            (valid-js-identifier (car args))
241          (multiple-value-bind (accessor accessorp)
242              (valid-js-identifier (cadr args))
243            (cond
244              ((and identifierp accessorp)
245               (js-identifier identifier)
246               (js-format ".")
247               (js-identifier accessor))
248              (t
249               (js-expr (car args))
250               (js-format "[")
251               (js-expr (cadr args))
252               (js-format "]"))))))
253       ;; Object syntax
254       (object
255        (js-object-initializer args))
256       ;; Function expressions
257       (function
258        (js-format "(")
259        (apply #'js-function args)
260        (js-format ")"))
261       (t
262        (flet ((%unary-op (operator string precedence associativity post lvalue)
263                 (when (eq op operator)
264                   (with-operator (precedence associativity)
265                     (when lvalue (check-lvalue op1))
266                     (cond
267                       (post
268                        (js-expr op1)
269                        (js-operator string))
270                       (t
271                        (js-operator string)
272                        (js-expr op1))))
273                   (return-from js-operator-expression)))
274               (%binary-op (operator string precedence associativity lvalue)
275                 (when (eq op operator)
276                   (when lvalue (check-lvalue op1))
277                   (with-operator (precedence associativity)
278                     (js-expr op1)
279                     (js-operator string)
280                     (js-expr op2))
281                   (return-from js-operator-expression))))
282
283          (macrolet ((unary-op (operator string precedence associativity &key post lvalue)
284                       `(%unary-op ',operator ',string ',precedence ',associativity ',post ',lvalue))
285                     (binary-op (operator string precedence associativity &key lvalue)
286                       `(%binary-op ',operator ',string ',precedence ',associativity ',lvalue)))
287
288            (unary-op pre++       "++"            1    right :lvalue t)
289            (unary-op pre--       "--"            1    right :lvalue t)
290            (unary-op post++      "++"            1    right :lvalue t :post t)
291            (unary-op post--      "--"            1    right :lvalue t :post t)
292            (unary-op not         "!"             1    right)
293            (unary-op bit-not     "~"             1    right)
294            ;; Note that the leading space is necessary because it
295            ;; could break with post++, for example. TODO: Avoid
296            ;; leading space when it's possible.
297            (unary-op unary+      " +"            1    right)
298            (unary-op unary-      " -"            1    right)
299            (unary-op delete      "delete "       1    right)
300            (unary-op void        "void "         1    right)
301            (unary-op typeof      "typeof "       1    right)
302            (unary-op new         "new "          1    right)
303
304            (binary-op *          "*"             2    left)
305            (binary-op /          "/"             2    left)
306            (binary-op mod        "%"             2    left)
307            (binary-op %          "%"             2    left)
308            (binary-op +          "+"             3    left)
309            (binary-op -          "-"             3    left)
310            (binary-op <<         "<<"            4    left)
311            (binary-op >>         "<<"            4    left)
312            (binary-op >>>        ">>>"           4    left)
313            (binary-op <=         "<="            5    left)
314            (binary-op <          "<"             5    left)
315            (binary-op >          ">"             5    left)
316            (binary-op >=         ">="            5    left)
317            (binary-op instanceof " instanceof "  5    left)
318            (binary-op in         " in "          5    left)
319            (binary-op ==         "=="            6    left)
320            (binary-op !=         "!="            6    left)
321            (binary-op ===        "==="           6    left)
322            (binary-op !==        "!=="           6    left)
323            (binary-op bit-and    "&"             7    left)
324            (binary-op bit-xor    "^"             8    left)
325            (binary-op bit-or     "|"             9    left)
326            (binary-op and        "&&"           10    left)
327            (binary-op or         "||"           11    left)
328            (binary-op =          "="            13    right :lvalue t)
329            (binary-op +=         "+="           13    right :lvalue t)
330            (binary-op incf       "+="           13    right :lvalue t)
331            (binary-op -=         "-="           13    right :lvalue t)
332            (binary-op decf       "-="           13    right :lvalue t)
333            (binary-op *=         "*="           13    right :lvalue t)
334            (binary-op /=         "*="           13    right :lvalue t)
335            (binary-op bit-xor=   "^="           13    right :lvalue t)
336            (binary-op bit-and=   "&="           13    right :lvalue t)
337            (binary-op bit-or=    "|="           13    right :lvalue t)
338            (binary-op <<=        "<<="          13    right :lvalue t)
339            (binary-op >>=        ">>="          13    right :lvalue t)
340            (binary-op >>>=       ">>>="         13    right :lvalue t)
341
342            (binary-op comma      ","            13    right)
343            (binary-op progn      ","            13    right)
344
345            (when (member op '(? if))
346              (with-operator (12 'right)
347                (js-expr (first args))
348                (js-operator "?")
349                (js-expr (second args))
350                (js-format ":")
351                (js-expr (third args)))
352              (return-from js-operator-expression))
353
354            (error "Unknown operator `~S'" op)))))))
355
356 (defun js-expr (form)
357   (let ((form (js-expand-expr form)))
358     (cond
359       ((or (symbolp form) (numberp form) (stringp form))
360        (js-primary-expr form))
361       ((vectorp form)
362        (js-vector-initializer form))
363       (t
364        (js-operator-expression (car form) (cdr form))))))
365
366 (defun js-expand-stmt (form)
367   (cond
368     ((and (consp form) (eq (car form) 'progn))
369      (destructuring-bind (&body body) (cdr form)
370        (cond
371          ((null body)
372           nil)
373          ((null (cdr body))
374           (js-expand-stmt (car body)))
375          (t
376           `(group ,@(cdr form))))))
377     (t
378      form)))
379
380 (defun js-stmt (form &optional parent)
381   (let ((form (js-expand-stmt form)))
382     (flet ((js-stmt (x) (js-stmt x form)))
383       (cond
384         ((null form)
385          (unless (or (and (consp parent) (eq (car parent) 'group))
386                      (null parent))
387            (js-format ";")))
388         ((atom form)
389          (progn
390            (js-expr form)
391            (js-format ";")))
392         (t
393          (case (car form)
394            (code
395             (js-format "~a" (apply #'code (cdr form))))
396            (label
397             (destructuring-bind (label &body body) (cdr form)
398               (js-identifier label)
399               (js-format ":")
400               (js-stmt `(progn ,@body))))
401            (break
402             (destructuring-bind (label) (cdr form)
403               (js-format "break ")
404               (js-identifier label)
405               (js-format ";")))
406            (return
407              (destructuring-bind (value) (cdr form)
408                (js-format "return ")
409                (js-expr value)
410                (js-format ";")))
411            (var
412             (flet ((js-var (spec)
413                      (destructuring-bind (variable &optional initial)
414                          (ensure-list spec)
415                        (js-identifier variable)
416                        (when initial
417                          (js-format "=")
418                          (js-expr initial)))))
419               (destructuring-bind (var &rest vars) (cdr form)
420                 (let ((*js-operator-precedence* 12))
421                   (js-format "var ")
422                   (js-var var)
423                   (dolist (var vars)
424                     (js-format ",")
425                     (js-var var))
426                   (js-format ";")))))
427            (if
428             (destructuring-bind (condition true &optional false) (cdr form)
429               (js-format "if (")
430               (js-expr condition)
431               (js-format ") ")
432               (js-stmt true)
433               (when false
434                 (js-format " else ")
435                 (js-stmt false))))
436            (group
437             (let ((in-group-p
438                    (or (null parent)
439                        (and (consp parent) (eq (car parent) 'group)))))
440               (unless  in-group-p (js-format "{"))
441               (mapc #'js-stmt (cdr form))
442               (unless in-group-p (js-format "}"))))
443            (while
444                (destructuring-bind (condition &body body) (cdr form)
445                  (js-format "while (")
446                  (js-expr condition)
447                  (js-format ")")
448                  (js-stmt `(progn ,@body))))
449            (for
450             (destructuring-bind ((start condition step) &body body) (cdr form)
451               (js-format "for (")
452               (js-expr start)
453               (js-format ";")
454               (js-expr condition)
455               (js-format ";")
456               (js-expr step)
457               (js-format ")")
458               (js-stmt `(progn ,@body))))
459            (try
460             (destructuring-bind (&rest body) (cdr form)
461               (js-format "try")
462               (js-stmt `(group ,@body))))
463            (catch
464                (destructuring-bind ((var) &rest body) (cdr form)
465                  (js-format "catch (")
466                  (js-identifier var)
467                  (js-format ")")
468                  (js-stmt `(group ,@body))))
469            (finally
470             (destructuring-bind (&rest body) (cdr form)
471               (js-format "finally")
472               (js-stmt `(group ,@body))))
473            (throw
474                (destructuring-bind (object) (cdr form)
475                  (js-format "throw ")
476                  (js-expr object)
477                  (js-format ";")))
478            (t
479             (js-expr form)
480             (js-format ";"))))))))
481
482 (defun js (&rest stmts)
483   (mapc #'js-stmt stmts)
484   nil)