Implemented string<
[jscl.git] / src / boot.lisp
1 ;;; boot.lisp --- First forms to be cross compiled
2
3 ;; Copyright (C) 2012, 2013 David Vazquez
4 ;; Copyright (C) 2012 Raimon Grau
5
6 ;; JSCL is free software: you can redistribute it and/or
7 ;; modify it under the terms of the GNU General Public License as
8 ;; published by the Free Software Foundation, either version 3 of the
9 ;; License, or (at your option) any later version.
10 ;;
11 ;; JSCL is distributed in the hope that it will be useful, but
12 ;; WITHOUT ANY WARRANTY; without even the implied warranty of
13 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
14 ;; General Public License for more details.
15 ;;
16 ;; You should have received a copy of the GNU General Public License
17 ;; along with JSCL.  If not, see <http://www.gnu.org/licenses/>.
18
19 ;;; This code is executed when JSCL compiles this file itself. The
20 ;;; compiler provides compilation of some special forms, as well as
21 ;;; funcalls and macroexpansion, but no functions. So, we define the
22 ;;; Lisp world from scratch. This code has to define enough language
23 ;;; to the compiler to be able to run.
24
25 (eval-when-compile
26   (let ((defmacro-macroexpander
27          '#'(lambda (form)
28               (destructuring-bind (name args &body body)
29                   form
30                 (let ((whole (gensym)))
31                   `(eval-when-compile
32                      (%compile-defmacro ',name
33                                         '#'(lambda (,whole)
34                                              (destructuring-bind ,args ,whole
35                                                ,@body)))))))))
36     (%compile-defmacro 'defmacro defmacro-macroexpander)))
37
38 (defmacro declaim (&rest decls)
39   `(eval-when-compile
40      ,@(mapcar (lambda (decl) `(!proclaim ',decl)) decls)))
41
42 (defmacro defconstant (name value &optional docstring)
43   `(progn
44      (declaim (special ,name))
45      (declaim (constant ,name))
46      (setq ,name ,value)
47      ,@(when (stringp docstring) `((oset ',name "vardoc" ,docstring)))
48      ',name))
49
50 (defconstant t 't)
51 (defconstant nil 'nil)
52 (%js-vset "nil" nil)
53
54 (defmacro lambda (args &body body)
55   `(function (lambda ,args ,@body)))
56
57 (defmacro when (condition &body body)
58   `(if ,condition (progn ,@body) nil))
59
60 (defmacro unless (condition &body body)
61   `(if ,condition nil (progn ,@body)))
62
63 (defmacro defvar (name &optional (value nil value-p) docstring)
64   `(progn
65      (declaim (special ,name))
66      ,@(when value-p `((unless (boundp ',name) (setq ,name ,value))))
67      ,@(when (stringp docstring) `((oset ',name "vardoc" ,docstring)))
68      ',name))
69
70 (defmacro defparameter (name value &optional docstring)
71   `(progn
72      (setq ,name ,value)
73      ,@(when (stringp docstring) `((oset ',name "vardoc" ,docstring)))
74      ',name))
75
76 (defmacro defun (name args &rest body)
77   `(progn
78      (fset ',name #'(named-lambda ,name ,args ,@body))
79      ',name))
80
81 (defmacro return (&optional value)
82   `(return-from nil ,value))
83
84 (defmacro while (condition &body body)
85   `(block nil (%while ,condition ,@body)))
86
87 (defvar *gensym-counter* 0)
88 (defun gensym (&optional (prefix "G"))
89   (setq *gensym-counter* (+ *gensym-counter* 1))
90   (make-symbol (concat-two prefix (integer-to-string *gensym-counter*))))
91
92 (defun boundp (x)
93   (boundp x))
94
95 (defun fboundp (x)
96   (fboundp x))
97
98 ;; Basic functions
99 (defun = (x y) (= x y))
100 (defun * (x y) (* x y))
101 (defun / (x y) (/ x y))
102 (defun 1+ (x) (+ x 1))
103 (defun 1- (x) (- x 1))
104 (defun zerop (x) (= x 0))
105
106 (defun truncate (x &optional (y 1))
107   (floor (/ x y)))
108
109 (defun eql (x y) (eq x y))
110
111 (defun not (x) (if x nil t))
112
113 ;; Basic macros
114
115 (defmacro incf (place &optional (delta 1))
116   (multiple-value-bind (dummies vals newval setter getter)
117       (get-setf-expansion place)
118     (let ((d (gensym)))
119       `(let* (,@(mapcar #'list dummies vals)
120               (,d ,delta)
121                 (,(car newval) (+ ,getter ,d))
122                 ,@(cdr newval))
123          ,setter))))
124
125 (defmacro decf (place &optional (delta 1))
126   (multiple-value-bind (dummies vals newval setter getter)
127       (get-setf-expansion place)
128     (let ((d (gensym)))
129       `(let* (,@(mapcar #'list dummies vals)
130               (,d ,delta)
131               (,(car newval) (- ,getter ,d))
132               ,@(cdr newval))
133          ,setter))))
134
135 (defmacro push (x place)
136   (multiple-value-bind (dummies vals newval setter getter)
137       (get-setf-expansion place)
138     (let ((g (gensym)))
139       `(let* ((,g ,x)
140               ,@(mapcar #'list dummies vals)
141               (,(car newval) (cons ,g ,getter))
142               ,@(cdr newval))
143          ,setter))))
144
145 (defmacro dolist ((var list &optional result) &body body)
146   (let ((g!list (gensym)))
147     (unless (symbolp var) (error "`~S' is not a symbol." var))
148     `(block nil
149        (let ((,g!list ,list)
150              (,var nil))
151          (%while ,g!list
152                  (setq ,var (car ,g!list))
153                  (tagbody ,@body)
154                  (setq ,g!list (cdr ,g!list)))
155          ,result))))
156
157 (defmacro dotimes ((var count &optional result) &body body)
158   (let ((g!count (gensym)))
159     (unless (symbolp var) (error "`~S' is not a symbol." var))
160     `(block nil
161        (let ((,var 0)
162              (,g!count ,count))
163          (%while (< ,var ,g!count)
164                  (tagbody ,@body)
165                  (incf ,var))
166          ,result))))
167
168 (defmacro cond (&rest clausules)
169   (unless (null clausules)
170     (destructuring-bind (condition &body body)
171         (first clausules)
172       (cond
173         ((eq condition t)
174          `(progn ,@body))
175         ((null body)
176          (let ((test-symbol (gensym)))
177            `(let ((,test-symbol ,condition))
178               (if ,test-symbol
179                   ,test-symbol
180                   (cond ,@(rest clausules))))))
181         (t
182          `(if ,condition
183               (progn ,@body)
184               (cond ,@(rest clausules))))))))
185
186 (defmacro case (form &rest clausules)
187   (let ((!form (gensym)))
188     `(let ((,!form ,form))
189        (cond
190          ,@(mapcar (lambda (clausule)
191                      (destructuring-bind (keys &body body)
192                          clausule
193                        (if (or (eq keys 't) (eq keys 'otherwise))
194                            `(t nil ,@body)
195                            (let ((keys (if (listp keys) keys (list keys))))
196                              `((or ,@(mapcar (lambda (key) `(eql ,!form ',key)) keys))
197                                nil ,@body)))))
198                    clausules)))))
199
200 (defmacro ecase (form &rest clausules)
201   (let ((g!form (gensym)))
202     `(let ((,g!form ,form))
203        (case ,g!form
204          ,@(append
205             clausules
206             `((t
207                (error "ECASE expression failed for the object `~S'." ,g!form))))))))
208
209 (defmacro and (&rest forms)
210   (cond
211     ((null forms)
212      t)
213     ((null (cdr forms))
214      (car forms))
215     (t
216      `(if ,(car forms)
217           (and ,@(cdr forms))
218           nil))))
219
220 (defmacro or (&rest forms)
221   (cond
222     ((null forms)
223      nil)
224     ((null (cdr forms))
225      (car forms))
226     (t
227      (let ((g (gensym)))
228        `(let ((,g ,(car forms)))
229           (if ,g ,g (or ,@(cdr forms))))))))
230
231 (defmacro prog1 (form &body body)
232   (let ((value (gensym)))
233     `(let ((,value ,form))
234        ,@body
235        ,value)))
236
237 (defmacro prog2 (form1 result &body body)
238   `(prog1 (progn ,form1 ,result) ,@body))
239
240 (defmacro prog (inits &rest body )
241   (multiple-value-bind (forms decls docstring) (parse-body body)
242     `(block nil
243        (let ,inits
244          ,@decls
245          (tagbody ,@forms)))))
246
247
248 ;;; Go on growing the Lisp language in Ecmalisp, with more high level
249 ;;; utilities as well as correct versions of other constructions.
250
251 (defun + (&rest args)
252   (let ((r 0))
253     (dolist (x args r)
254       (incf r x))))
255
256 (defun - (x &rest others)
257   (if (null others)
258       (- x)
259       (let ((r x))
260         (dolist (y others r)
261           (decf r y)))))
262
263 (defun append-two (list1 list2)
264   (if (null list1)
265       list2
266       (cons (car list1)
267             (append (cdr list1) list2))))
268
269 (defun append (&rest lists)
270   (!reduce #'append-two lists nil))
271
272 (defun revappend (list1 list2)
273   (while list1
274     (push (car list1) list2)
275     (setq list1 (cdr list1)))
276   list2)
277
278 (defun reverse (list)
279   (revappend list '()))
280
281 (defmacro psetq (&rest pairs)
282   (let (;; For each pair, we store here a list of the form
283         ;; (VARIABLE GENSYM VALUE).
284         (assignments '()))
285     (while t
286       (cond
287         ((null pairs) (return))
288         ((null (cdr pairs))
289          (error "Odd paris in PSETQ"))
290         (t
291          (let ((variable (car pairs))
292                (value (cadr pairs)))
293            (push `(,variable ,(gensym) ,value)  assignments)
294            (setq pairs (cddr pairs))))))
295     (setq assignments (reverse assignments))
296     ;;
297     `(let ,(mapcar #'cdr assignments)
298        (setq ,@(!reduce #'append (mapcar #'butlast assignments) nil)))))
299
300 (defmacro do (varlist endlist &body body)
301   `(block nil
302      (let ,(mapcar (lambda (x) (list (first x) (second x))) varlist)
303        (while t
304          (when ,(car endlist)
305            (return (progn ,@(cdr endlist))))
306          (tagbody ,@body)
307          (psetq
308           ,@(apply #'append
309                    (mapcar (lambda (v)
310                              (and (consp (cddr v))
311                                   (list (first v) (third v))))
312                            varlist)))))))
313
314 (defmacro do* (varlist endlist &body body)
315   `(block nil
316      (let* ,(mapcar (lambda (x) (list (first x) (second x))) varlist)
317        (while t
318          (when ,(car endlist)
319            (return (progn ,@(cdr endlist))))
320          (tagbody ,@body)
321          (setq
322           ,@(apply #'append
323                    (mapcar (lambda (v)
324                              (and (consp (cddr v))
325                                   (list (first v) (third v))))
326                            varlist)))))))
327
328 (defun list-length (list)
329   (let ((l 0))
330     (while (not (null list))
331       (incf l)
332       (setq list (cdr list)))
333     l))
334
335 (defun length (seq)
336   (cond
337     ((stringp seq)
338      (string-length seq))
339     ((arrayp seq)
340      (oget seq "length"))
341     ((listp seq)
342      (list-length seq))))
343
344 (defun concat-two (s1 s2)
345   (concat-two s1 s2))
346
347 (defmacro with-collect (&body body)
348   (let ((head (gensym))
349         (tail (gensym)))
350     `(let* ((,head (cons 'sentinel nil))
351             (,tail ,head))
352        (flet ((collect (x)
353                 (rplacd ,tail (cons x nil))
354                 (setq ,tail (cdr ,tail))
355                 x))
356          ,@body)
357        (cdr ,head))))
358
359
360 (defmacro loop (&body body)
361   `(while t ,@body))
362
363 (defun identity (x) x)
364
365 (defun constantly (x)
366   (lambda (&rest args)
367     x))
368
369 (defun code-char (x)
370   (code-char x))
371
372 (defun char-code (x)
373   (char-code x))
374
375 (defun char= (x y)
376   (eql x y))
377
378 (defun char< (x y)
379   (< (char-code x) (char-code y)))
380
381 (defun integerp (x)
382   (and (numberp x) (= (floor x) x)))
383
384 (defun floatp (x)
385   (and (numberp x) (not (integerp x))))
386
387 (defun plusp (x) (< 0 x))
388 (defun minusp (x) (< x 0))
389
390 (defun atom (x)
391   (not (consp x)))
392
393 (defun alpha-char-p (x)
394   (or (<= (char-code #\a) (char-code x) (char-code #\z))
395       (<= (char-code #\A) (char-code x) (char-code #\Z))))
396
397 (defun digit-char-p (x)
398   (if (and (<= (char-code #\0) (char-code x) (char-code #\9)))
399       (- (char-code x) (char-code #\0))
400       nil))
401
402 (defun digit-char (weight)
403   (and (<= 0 weight 9)
404        (char "0123456789" weight)))
405
406 (defun equal (x y)
407   (cond
408     ((eql x y) t)
409     ((consp x)
410      (and (consp y)
411           (equal (car x) (car y))
412           (equal (cdr x) (cdr y))))
413     ((stringp x)
414      (and (stringp y) (string= x y)))
415     (t nil)))
416
417 (defun fdefinition (x)
418   (cond
419     ((functionp x)
420      x)
421     ((symbolp x)
422      (symbol-function x))
423     (t
424      (error "Invalid function `~S'." x))))
425
426 (defun disassemble (function)
427   (write-line (lambda-code (fdefinition function)))
428   nil)
429
430 (defun documentation (x type)
431   "Return the documentation of X. TYPE must be the symbol VARIABLE or FUNCTION."
432   (ecase type
433     (function
434      (let ((func (fdefinition x)))
435        (oget func "docstring")))
436     (variable
437      (unless (symbolp x)
438        (error "The type of documentation `~S' is not a symbol." type))
439      (oget x "vardoc"))))
440
441 (defmacro multiple-value-bind (variables value-from &body body)
442   `(multiple-value-call (lambda (&optional ,@variables &rest ,(gensym))
443                           ,@body)
444      ,value-from))
445
446 (defmacro multiple-value-list (value-from)
447   `(multiple-value-call #'list ,value-from))
448
449
450 ;;; Generalized references (SETF)
451
452 (defvar *setf-expanders* nil)
453
454 (defun get-setf-expansion (place)
455   (if (symbolp place)
456       (let ((value (gensym)))
457         (values nil
458                 nil
459                 `(,value)
460                 `(setq ,place ,value)
461                 place))
462       (let ((place (!macroexpand-1 place)))
463         (let* ((access-fn (car place))
464                (expander (cdr (assoc access-fn *setf-expanders*))))
465           (when (null expander)
466             (error "Unknown generalized reference."))
467           (apply expander (cdr place))))))
468
469 (defmacro define-setf-expander (access-fn lambda-list &body body)
470   (unless (symbolp access-fn)
471     (error "ACCESS-FN `~S' must be a symbol." access-fn))
472   `(progn (push (cons ',access-fn (lambda ,lambda-list ,@body))
473                 *setf-expanders*)
474           ',access-fn))
475
476 (defmacro setf (&rest pairs)
477   (cond
478     ((null pairs)
479      nil)
480     ((null (cdr pairs))
481      (error "Odd number of arguments to setf."))
482     ((null (cddr pairs))
483      (let ((place (!macroexpand-1 (first pairs)))
484            (value (second pairs)))
485        (multiple-value-bind (vars vals store-vars writer-form)
486            (get-setf-expansion place)
487          ;; TODO: Optimize the expansion a little bit to avoid let*
488          ;; or multiple-value-bind when unnecesary.
489          `(let* ,(mapcar #'list vars vals)
490             (multiple-value-bind ,store-vars
491                 ,value
492               ,writer-form)))))
493     (t
494      `(progn
495         ,@(do ((pairs pairs (cddr pairs))
496                (result '() (cons `(setf ,(car pairs) ,(cadr pairs)) result)))
497               ((null pairs)
498                (reverse result)))))))
499
500 ;; Incorrect typecase, but used in NCONC.
501 (defmacro typecase (x &rest clausules)
502   (let ((value (gensym)))
503     `(let ((,value ,x))
504        (cond
505          ,@(mapcar (lambda (c)
506                      (if (eq (car c) t)
507                          `((t ,@(rest c)))
508                          `((,(ecase (car c)
509                                     (integer 'integerp)
510                                     (cons 'consp)
511                                     (symbol 'symbolp)
512                                     (array 'arrayp)
513                                     (string 'stringp)
514                                     (atom 'atom)
515                                     (null 'null))
516                              ,value)
517                            ,@(or (rest c)
518                                  (list nil)))))
519                    clausules)))))
520
521 (defmacro etypecase (x &rest clausules)
522   (let ((g!x (gensym)))
523     `(let ((,g!x ,x))
524        (typecase ,g!x
525          ,@clausules
526          (t (error "~X fell through etypeacase expression." ,g!x))))))
527
528 (defun notany (fn seq)
529   (not (some fn seq)))
530
531 (defconstant internal-time-units-per-second 1000) 
532
533 (defun get-internal-real-time ()
534   (get-internal-real-time))
535
536 (defun get-unix-time ()
537   (truncate (/ (get-internal-real-time) 1000)))
538
539 (defun get-universal-time ()
540   (+ (get-unix-time) 2208988800))
541
542 (defun concat (&rest strs)
543   (!reduce #'concat-two strs ""))
544
545 (defun values-list (list)
546   (values-array (list-to-vector list)))
547
548 (defun values (&rest args)
549   (values-list args))
550
551 (defun error (fmt &rest args)
552   (%throw (apply #'format nil fmt args)))