1 ;; -*- Mode: Lisp; Package: Maxima; Syntax: Common-Lisp; Base: 10 -*- ;;;;
2 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
4 ;;; Copyright (c) 1984,1987 by William Schelter,University of Texas ;;;;;
5 ;;; All rights reserved ;;;;;
6 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
10 (defmacro defun-prop
(f arg
&body body
)
12 #+gcl
(eval-when (eval) (compiler::compiler-def-hook
(first f
) body
))
13 `(setf (get ',(first f
) ',(second f
)) #'(lambda ,arg
,@body
)))
15 ;; Should we give this a different name?
16 (defvar *fortran-print
* nil
17 "Tells EXPLODEN we are printing numbers for Fortran so include the exponent marker.")
19 (defun appears (tree var
)
20 (cond ((equal tree var
)
23 (t (appears (car tree
) var
)
24 (appears (cdr tree
) var
)))
27 (defun appears1 (tree var
)
32 (appears (car tree
) var
)
33 (appears (cdr tree
) var
)))
36 (defun appears-in (tree var
)
37 "Yields t if var appears in tree"
39 (if (or (symbolp var
) (fixnump var
))
43 ;; A more portable implementation of ml-typep. I (rtoy) think it
44 ;; would probably be better to replace uses of
45 ;; ml-typep with the corresponding Common Lisp typep or type-of or
46 ;; subtypep, as appropriate.
47 (defun ml-typep (x &optional type
)
49 (cl:let
((pred (get type
'ml-typep
)))
61 (cl:hash-table
'hash-table
)
65 (defprop :extended-number extended-number-p ml-typep
)
66 (defprop array arrayp ml-typep
)
67 (defprop atom atom ml-typep
)
70 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
71 (shadow '(cl:compiled-function-p
) (find-package :maxima
))
74 (defun compiled-function-p (x)
75 (and (functionp x
) (not (symbolp x
))
76 (not (eval:interpreted-function-p x
))))
78 (defprop compiled-function compiled-function-p ml-typep
)
79 (defprop extended-number extended-number-p ml-typep
)
80 (defprop fixnum fixnump ml-typep
)
81 (defprop list consp ml-typep
)
82 (defprop number numberp ml-typep
)
83 (defprop string stringp ml-typep
)
84 (defprop symbol symbolp ml-typep
)
87 (defvar *maxima-arrays
* nil
88 "Trying to track down any functional arrays in maxima")
90 (defun *array
(name maclisp-type
&rest dimlist
&aux aarray
)
91 (cond ((member maclisp-type
'(readtable obarray
) :test
#'eq
)
92 (error " bad type ~S" maclisp-type
)))
93 (pushnew name
*maxima-arrays
*) ;for tracking down old ones.
94 (setq aarray
(make-array dimlist
:initial-element
(case maclisp-type
98 (cond ((null name
) aarray
)
100 (setf (symbol-array name
) aarray
)
102 (t (error "~S is illegal first arg for *array" name
))))
104 ;;; Change maclisp array referencing.
105 ;;; Idea1: Make changes in the code which will allow the code to still run in maclisp,
106 ;;;yet will allow, with the appropriate macro definitions of array,arraycall, etc,
107 ;;;to put the array into the value-cell.
108 ;;; Idea2: Make changes in the array referencing of (a dim1 dim2..) to (arraycall nil (symbol-array a) dim1..)
109 ;;;which would then allow expansion into something which is common lisp compatible, for
110 ;;;the day when (a 2 3) no longer is equivalent to (aref (symbol-function a) 2 3).
111 ;;;I. change (array a typ dim1 dim2..) to expand to (defvar a (make-array (list dim1 dim2 ...) :type typ')
112 ;;;II. change (a dim1 dim2..) to (arraycall nil (symbol-array a) dim1 dim2 ..)
114 ;;(defmacro symbol-array (ar)
115 ;; `(symbol-function ,ar))
116 ;;(defmacro arraycall (ignore ar &rest dims)
117 ;; `(aref ,ar ,@ dims))
118 ;;;IV. change array setting to use (setf (arraycall nil ar dim1.. ) val)
119 ;;;which will generate the correct setting code on the lispm and will
120 ;;;still work in maclisp.
122 (defmacro maxima-error
(datum &rest args
)
123 `(cerror "without any special action" ,datum
,@args
))
125 (defmacro show
(&rest l
)
127 collecting
`(format t
"~%The value of ~A is ~A" ',v
,v
) into tem
128 finally
(return `(progn ,@ tem
))))
130 (defmacro defquote
(fn (aa . oth
) &body rest
&aux help ans
)
131 (setq help
(intern (format nil
"~a-~a" fn
'#:aux
)))
132 (cond ((eq aa
'&rest
)
135 `(defmacro ,fn
(&rest
,(car oth
))
136 `(,',help
',,(car oth
)))
137 `(defun ,help
(,(car oth
)) ,@rest
))))
138 (t (when (member '&rest oth
)
139 (error "at present &rest may only occur as first item in a defquote argument"))
142 `(defmacro ,fn
(,aa . other
)
143 (setq other
(loop for v in other collecting
(list 'quote v
)))
144 (check-arg other
(eql (length other
) ,(length oth
))
145 ,(format nil
"wrong number of args to ~a" fn
))
146 `(,',help
',,aa
,@ other
))
147 `(defun ,help
(,aa
,@ oth
) ,@rest
)))))
151 ;;the resulting function will translate to defvar and will behave
152 ;;correctly for the evaluator.
154 ;;(defun gg fexpr (ll)
156 ;;(defquote gg (&rest ll)
159 ;;(DEFQUOTE GG ( &rest C)
160 ;; (list (car c) (second c) ))
161 ;;the big advantage of using the following over defmspec is that it
162 ;;seems to translate more easily, since it is a fn.
163 ;;New functions which wanted quoted arguments should be defined using
167 (defun onep (x) (eql 1 x
))
169 (defun extended-number-p (x)
170 (member (type-of x
) '(bignum rational float
)))
172 (defvar *scan-string-buffer
* nil
)
174 (defun macsyma-read-string (a-string &aux answer
)
175 (cond ((not (or (search "$" a-string
:test
#'char-equal
)
176 (search ";" a-string
:test
#'char-equal
)))
177 (vector-push-extend #\$ a-string
)))
178 (with-input-from-string (stream a-string
)
179 (setq answer
(third (mread stream
)))
182 (defvar *sharp-read-buffer
*
183 (make-array 140 :element-type
' #.
(array-element-type "a") :fill-pointer
0 :adjustable t
))
185 (defmfun $-read-aux
(arg stream
&aux
(meval-flag t
) (*mread-prompt
* ""))
186 (declare (special *mread-prompt
*)
188 (setf (fill-pointer *sharp-read-buffer
*) 0)
189 (cond ((eql #\$
(peek-char t stream
))
191 (setq meval-flag nil
)))
192 (with-output-to-string (st *sharp-read-buffer
*)
194 (loop while
(not (eql char
#\$
))
196 (setq char
(tyi stream
))
197 (write-char char st
))))
199 (list 'meval
* (list 'quote
(macsyma-read-string *sharp-read-buffer
*)))
200 (list 'quote
(macsyma-read-string *sharp-read-buffer
*))))
202 (defun x$-cl-macro-read
(stream sub-char arg
)
203 (declare (ignore arg
))
204 ($-read-aux sub-char stream
))
206 (set-dispatch-macro-character #\
# #\$
#'x$-cl-macro-read
)
208 (defvar *macsyma-readtable
*)
210 (defun find-lisp-readtable-for-macsyma ()
211 (cond ((and (boundp '*macsyma-readtable
*)
212 (readtablep *macsyma-readtable
*))
214 (t (setq *macsyma-readtable
* (copy-readtable nil
))
215 (set-dispatch-macro-character #\
# #\$
'x$-cl-macro-read
*macsyma-readtable
*)
216 *macsyma-readtable
*)))
218 (defun set-readtable-for-macsyma ()
219 (setq *readtable
* (find-lisp-readtable-for-macsyma)))
221 (defvar *reset-var
* t
)
223 (defvar *variable-initial-values
* (make-hash-table)
224 "Hash table containing all Maxima defmvar variables and their initial
227 (defmacro defmvar
(var &rest val-and-doc
)
228 "If *reset-var* is true then loading or eval'ing will reset value, otherwise like defvar"
229 (cond ((> (length val-and-doc
) 2)
230 (setq val-and-doc
(list (car val-and-doc
) (second val-and-doc
)))))
232 (unless (gethash ',var
*variable-initial-values
*)
233 (setf (gethash ',var
*variable-initial-values
*)
234 ,(first val-and-doc
)))
235 (defvar ,var
,@val-and-doc
)))
237 (defmfun $mkey
(variable)
238 "($mkey '$demo)==>:demo"
239 (intern (string-left-trim "$" (string variable
)) 'keyword
))
242 `(narg1 ,x narg-rest-argument
))
244 (defun narg1 (x l
&aux tem
)
245 (cond ((null x
) (length l
))
246 (t (setq tem
(nthcdr (1- x
) l
))
247 (cond ((null tem
) (error "arg ~A beyond range ~A " x
(length l
)))
250 (defmacro listify
(x)
251 `(listify1 ,x narg-rest-argument
))
253 (defmacro setarg
(i val
)
254 `(setarg1 ,i
,val narg-rest-argument
))
256 (defun setarg1 (i val l
)
257 (setf (nth (1- i
) l
) val
)
260 (defun listify1 (n narg-rest-argument
)
261 (cond ((minusp n
) (copy-list (last narg-rest-argument
(- n
))) )
263 (t (subseq narg-rest-argument
0 n
))))
265 ;; This has been replaced by src/defmfun-check.lisp. I'm leaving this
266 ;; here for now until we finish up fixing everything like using defun
267 ;; for internal functions and updating user-exposed functions to use
268 ;; defmfun instead of defun.
270 (defmacro defmfun
(function &body rest
&aux .n.
)
271 (cond ((and (car rest
) (symbolp (car rest
)))
272 ;;old maclisp narg syntax
273 (setq .n.
(car rest
))
275 `(&rest narg-rest-argument
&aux
(, .n.
(length narg-rest-argument
))))))
277 ;; I (rtoy) think we can consider all defmfun's as translated functions.
278 (defprop ,function t translated
)
279 (defun ,function .
,rest
)))
282 ;;(defun foo a (show a )(show (listify a)) (show (arg 3)))
284 (defmacro defun-maclisp
(function &body rest
&aux .n.
)
285 (cond ((and (car rest
) (symbolp (car rest
)))
286 ;;old maclisp narg syntax
287 (setq .n.
(car rest
))
289 `(&rest narg-rest-argument
&aux
(, .n.
(length narg-rest-argument
))))))
291 ;; I (rtoy) think we can consider all defmfun's as translated functions.
292 (defprop ,function t translated
)
293 (defun ,function .
,rest
)))
295 (defun exploden (symb)
296 (let* (#+(and gcl
(not gmp
)) (big-chunk-size 120)
297 #+(and gcl
(not gmp
)) (tentochunksize (expt 10 big-chunk-size
))
299 (cond ((symbolp symb
)
300 (setq string
(print-invert-case symb
)))
302 (setq string
(exploden-format-float symb
)))
305 ;; When obase > 10, prepend leading zero to
306 ;; ensure that output is readable as a number.
307 (let ((leading-digit (if (> *print-base
* 10) #\
0)))
309 #+(and gcl
(not gmp
))
315 do
(multiple-value-setq (big rem
)
316 (floor big tentochunksize
))
318 while
(not (eql 0 big
)))))
319 (setq chunks
(nreverse chunks
))
320 (setq ans
(coerce (format nil
"~d" (car chunks
)) 'list
))
321 (if (and leading-digit
(not (digit-char-p (car ans
) 10.
)))
322 (setq ans
(cons leading-digit ans
)))
323 (loop for v in
(cdr chunks
)
324 do
(setq tem
(coerce (format nil
"~d" v
) 'list
))
325 (loop for i below
(- big-chunk-size
(length tem
))
326 do
(setq tem
(cons #\
0 tem
)))
327 (setq ans
(nconc ans tem
)))
328 (return-from exploden ans
)))
330 (setq string
(format nil
"~A" symb
))
331 (setq string
(coerce string
'list
))
332 (if (and leading-digit
(not (digit-char-p (car string
) 10.
)))
333 (setq string
(cons leading-digit string
)))
334 (return-from exploden string
)))))
336 (t (setq string
(format nil
"~A" symb
))))
337 (assert (stringp string
))
338 (coerce string
'list
)))
340 (defvar *exploden-strip-float-zeros
* t
) ;; NIL => allow trailing zeros
342 (defun exploden-format-float (symb)
343 (declare (special $maxfpprintprec
))
346 (effective-printprec (if (or (= $fpprintprec
0)
347 (> $fpprintprec $maxfpprintprec
))
350 ;; When printing out something for Fortran, we want to be
351 ;; sure to print the exponent marker so that Fortran
352 ;; knows what kind of number it is. It turns out that
353 ;; Fortran's exponent markers are the same as Lisp's so
354 ;; we just need to make sure the exponent marker is
358 ;; Strings for non-finite numbers as specified for input in Fortran 2003 spec;
359 ;; they apparently did not exist in earlier versions.
360 ((float-nan-p symb
) "NAN")
361 ((float-inf-p symb
) (if (< symb
0) "-INF" "INF"))
362 (t (format nil
"~e" symb
))))
363 (multiple-value-bind (form digits
)
367 ;; Work around for GCL bug #47404.
368 ;; Avoid numeric comparisons with NaN, which erroneously return T.
369 #+gcl
((or (float-inf-p symb
) (float-nan-p symb
))
370 (return-from exploden-format-float
(format nil
"~a" symb
)))
373 ((integer-log10 (floor (/ (log a
) #.
(log 10.0))))
374 (scale (1+ integer-log10
)))
375 (if (< scale effective-printprec
)
376 (values "~,vf" (- effective-printprec scale
))
377 (values "~,ve" (1- effective-printprec
)))))
378 #-gcl
((or (float-inf-p symb
) (float-nan-p symb
))
379 (return-from exploden-format-float
(format nil
"~a" symb
)))
381 (values "~,ve" (1- effective-printprec
))))
383 ;; Call FORMAT using format string chosen above.
384 (setq string
(format nil form digits a
))
386 ;; EXPLODEN is often called after NFORMAT, so it doesn't
387 ;; usually see a negative argument. I can't guarantee
388 ;; a non-negative argument, so handle negative here.
390 (setq string
(concatenate 'string
"-" string
)))))
392 (if *exploden-strip-float-zeros
*
393 (or (strip-float-zeros string
) string
)
396 (defun trailing-zeros-regex-f-0 (s)
397 (pregexp:pregexp-match-positions
'#.
(pregexp:pregexp
"^(.*\\.[0-9]*[1-9])00*$")
399 (defun trailing-zeros-regex-f-1 (s)
400 (pregexp:pregexp-match-positions
'#.
(pregexp::pregexp
"^(.*\\.0)00*$")
402 (defun trailing-zeros-regex-e-0 (s)
403 (pregexp:pregexp-match-positions
'#.
(pregexp:pregexp
"^(.*\\.[0-9]*[1-9])00*([^0-9][+-][0-9]*)$")
405 (defun trailing-zeros-regex-e-1 (s)
406 (pregexp:pregexp-match-positions
'#.
(pregexp:pregexp
"^(.*\\.0)00*([^0-9][+-][0-9]*)$")
409 ;; Return S with trailing zero digits stripped off, or NIL if there are none.
410 (defun strip-float-zeros (s)
413 ((setq matches
(or (trailing-zeros-regex-f-0 s
) (trailing-zeros-regex-f-1 s
)))
415 ((group1 (elt matches
1)))
416 (subseq s
(car group1
) (cdr group1
))))
417 ((setq matches
(or (trailing-zeros-regex-e-0 s
) (trailing-zeros-regex-e-1 s
)))
419 ((group1 (elt matches
1))
420 (s1 (subseq s
(car group1
) (cdr group1
)))
421 (group2 (elt matches
2))
422 (s2 (subseq s
(car group2
) (cdr group2
))))
423 (concatenate 'string s1 s2
)))
426 (defun explodec (symb) ;is called for symbols and numbers
427 (loop for v in
(coerce (print-invert-case symb
) 'list
)
428 collect
(intern (string v
))))
430 ;;; If the 'string is all the same case, invert the case. Otherwise,
433 (defun maybe-invert-string-case (string)
436 (length (length string
)))
438 (let ((ch (char string i
)))
439 (when (both-case-p ch
)
440 (if (upper-case-p ch
)
442 (setq all-upper nil
)))))
444 (string-downcase string
))
446 (string-upcase string
))
451 (defun maybe-invert-string-case (string)
452 (cond (#+scl
(eq ext
:*case-mode
* :lower
)
453 #+allegro
(eq excl
:*current-case-mode
* :case-sensitive-lower
)
458 (length (length string
)))
460 (let ((ch (aref string i
)))
461 (when (both-case-p ch
)
462 (if (upper-case-p ch
)
464 (setq all-upper nil
)))))
466 (string-downcase string
))
468 (string-upcase string
))
472 (defun intern-invert-case (string)
473 ;; Like read-from-string with readtable-case :invert
474 ;; Supply package argument in case this function is called
475 ;; from outside the :maxima package.
476 (intern (maybe-invert-string-case string
) :maxima
))
479 #-
(or gcl scl allegro
)
480 (let ((local-table (copy-readtable nil
)))
481 (setf (readtable-case local-table
) :invert
)
482 (defun print-invert-case (sym)
483 (let ((*readtable
* local-table
)
484 (*print-case
* :upcase
))
485 (princ-to-string sym
))))
488 (let ((local-table (copy-readtable nil
)))
489 (unless #+scl
(eq ext
:*case-mode
* :lower
)
490 #+allegro
(eq excl
:*current-case-mode
* :case-sensitive-lower
)
491 (setf (readtable-case local-table
) :invert
))
492 (defun print-invert-case (sym)
493 (cond (#+scl
(eq ext
:*case-mode
* :lower
)
494 #+allegro
(eq excl
:*current-case-mode
* :case-sensitive-lower
)
495 (let ((*readtable
* local-table
)
496 (*print-case
* :downcase
))
497 (princ-to-string sym
)))
499 (let ((*readtable
* local-table
)
500 (*print-case
* :upcase
))
501 (princ-to-string sym
))))))
504 (defun print-invert-case (sym)
506 (let* ((str (princ-to-string sym
))
510 (map 'string
(lambda (c)
511 (cond ((upper-case-p c
)
519 (if (and have-upper have-lower
)
522 (t (princ-to-string sym
))))
524 (defun implode (list)
525 (declare (optimize (speed 3)))
526 (intern-invert-case (map 'string
#'(lambda (v)
529 (symbol (char (symbol-name v
) 0))
530 (integer (code-char v
))))
533 ;; Note: symb can also be a number, not just a symbol.
534 (defun explode (symb)
535 (declare (optimize (speed 3)))
536 (map 'list
#'(lambda (v) (intern (string v
))) (format nil
"~s" symb
)))
538 ;;; return the first character of the name of a symbol or a string or char
539 (defun get-first-char (symb)
540 (declare (optimize (speed 3)))
541 (char (string symb
) 0))
543 (defun getchar (symb i
)
544 (let ((str (string symb
)))
545 (if (<= 1 i
(length str
))
546 (intern (string (char str
(1- i
))))
555 collecting
(char (symbol-name v
) 0) into tem
558 collecting v into tem
559 else do
(maxima-error "bad entry")
561 (return (make-symbol (maybe-invert-string-case (coerce tem
'string
))))))
563 ;;for those window labels etc. that are wrong type.
564 ;; is not only called for symbols, but also on numbers
566 (length (explodec sym
)))
568 (defun flatsize (sym &aux
(*print-circle
* t
))
569 (length (exploden sym
)))
571 (defmacro safe-zerop
(x)
573 `(and (numberp ,x
) (zerop ,x
))
575 (and (numberp .x.
) (zerop .x.
)))))
577 (defmacro signp
(sym x
)
586 (n `(not (zerop ,x
))))))
587 `(and (numberp ,x
) ,test
)))
591 (defvar *prompt-on-read-hang
* nil
)
592 (defvar *read-hang-prompt
* "")
594 (defun tyi-raw (&optional
(stream *standard-input
*) eof-option
)
595 ;; Adding this extra EOF test, because the testsuite generates
596 ;; unexpected end of input-stream with Windows XP and GCL 2.6.8.
598 (when (eql (peek-char nil stream nil eof-option
) eof-option
)
599 (return-from tyi-raw eof-option
))
601 (let ((ch (read-char-no-hang stream nil eof-option
)))
605 (when (and *prompt-on-read-hang
* *read-hang-prompt
*)
606 (princ *read-hang-prompt
*)
607 (finish-output *standard-output
*))
608 (read-char stream nil eof-option
)))))
610 (defun tyi (&optional
(stream *standard-input
*) eof-option
)
611 (let ((ch (tyi-raw stream eof-option
)))
612 (if (eql ch eof-option
)
614 (backslash-check ch stream eof-option
))))
616 ; The sequences of characters
617 ; <anything-except-backslash>
618 ; (<backslash> <newline> | <backslash> <return> | <backslash> <return> <newline>)+
620 ; are reduced to <anything-except-backslash> <anything> .
621 ; Note that this has no effect on <backslash> <anything-but-newline-or-return> .
623 (let ((previous-tyi #\a))
624 (defun backslash-check (ch stream eof-option
)
625 (if (eql previous-tyi
#\\ )
626 (progn (setq previous-tyi
#\a) ch
)
629 (let ((next-char (peek-char nil stream nil eof-option
)))
630 (if (or (eql next-char
#\newline
) (eql next-char
#\return
))
631 (eat-continuations ch stream eof-option
)
634 ; We have just read <backslash> and we know the next character is <newline> or <return>.
635 ; Eat line continuations until we come to something which doesn't match, or we reach eof.
636 (defun eat-continuations (ch stream eof-option
)
637 (setq ch
(tyi-raw stream eof-option
))
638 (do () ((not (or (eql ch
#\newline
) (eql ch
#\return
))))
639 (let ((next-char (peek-char nil stream nil eof-option
)))
640 (if (and (eql ch
#\return
) (eql next-char
#\newline
))
641 (tyi-raw stream eof-option
)))
642 (setq ch
(tyi-raw stream eof-option
))
643 (let ((next-char (peek-char nil stream nil eof-option
)))
644 (if (and (eql ch
#\\ ) (or (eql next-char
#\return
) (eql next-char
#\newline
)))
645 (setq ch
(tyi-raw stream eof-option
))
646 (return-from eat-continuations ch
))))
649 (defmfun $timedate
(&optional
(time (get-universal-time)) tz
)
651 ((and (consp tz
) (eq (caar tz
) 'rat
))
652 (setq tz
(/ (second tz
) (third tz
))))
654 (setq tz
(rationalize tz
))))
655 (if tz
(setq tz
(/ (round tz
1/60) 60)))
657 ((time-integer (mfuncall '$floor time
))
658 (time-fraction (sub time time-integer
))
659 (time-millis (mfuncall '$round
(mul 1000 time-fraction
))))
660 (when (= time-millis
1000)
661 (setq time-integer
(1+ time-integer
))
662 (setq time-millis
0))
664 (second minute hour date month year day-of-week dst-p tz
)
665 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
666 ;; so work around null TZ here.
667 (if tz
(decode-universal-time time-integer
(- tz
))
668 (decode-universal-time time-integer
))
669 (declare (ignore day-of-week
#+gcl dst-p
))
670 ;; DECODE-UNIVERSAL-TIME might return a timezone offset
671 ;; which is a multiple of 1/3600 but not 1/60.
672 ;; We need a multiple of 1/60 because our formatted
673 ;; timezone offset has only minutes and seconds.
674 (if (/= (mod tz
1/60) 0)
675 ($timedate time-integer
(/ (round (- tz
) 1/60) 60))
677 #-gcl
(if dst-p
(- 1 tz
) (- tz
))
678 #+gcl
(- tz
) ; bug in gcl https://savannah.gnu.org/bugs/?50570
681 (tz-hours tz-hour-fraction
)
684 ((tz-sign (if (<= 0 tz-offset
) #\
+ #\-
)))
685 (if (= time-millis
0)
686 (format nil
"~4,'0d-~2,'0d-~2,'0d ~2,'0d:~2,'0d:~2,'0d~a~2,'0d:~2,'0d"
687 year month date hour minute second tz-sign
(abs tz-hours
) (floor (* 60 (abs tz-hour-fraction
))))
688 (format nil
"~4,'0d-~2,'0d-~2,'0d ~2,'0d:~2,'0d:~2,'0d.~3,'0d~a~2,'0d:~2,'0d"
689 year month date hour minute second time-millis tz-sign
(abs tz-hours
) (floor (* 60 (abs tz-hour-fraction
))))))))))))
691 ;; Parse date/time strings in these formats (and only these):
693 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?([+-]hh:mm)?
694 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?([+-]hhmm)?
695 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?([+-]hh)?
696 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?[Z]?
698 ;; where (...)? indicates an optional group (occurs zero or one times)
699 ;; ...+ indicates one or more instances of ...,
700 ;; and [...] indicates literal character alternatives.
702 ;; Trailing unparsed stuff causes the parser to fail (return NIL).
704 ;; Originally, these functions all looked like
706 ;; (defun match-date-yyyy-mm-dd (s)
707 ;; (pregexp:pregexp-match-positions
708 ;; '#.(pregexp:pregexp "^([0-9][0-9][0-9][0-9])-([0-9][0-9])-([0-9][0-9])")
711 ;; However, sbcl produces incorrect results for this. For example,
713 ;; (match-date-yyyy-mm-dd "1900-01-01 16:00:00-08:00")
715 ;; returns ((0 . 10) (0 . 4) (8 . 10) NIL). But the correct answer is
716 ;; ((0 . 10) (0 . 4) (5 . 7) (8 . 10)).
718 ;; But if you replace the '#.(pregexp:pregexp ...) with
719 ;; (pregexp:pregexp ...), sbcl works. But then we end up compiling
720 ;; the the regexp on every call. So we use a closure so the regexp is
721 ;; compiled only once.
722 (let ((pat (pregexp:pregexp
"^([0-9][0-9][0-9][0-9])-([0-9][0-9])-([0-9][0-9])")))
723 (defun match-date-yyyy-mm-dd (s)
724 (pregexp:pregexp-match-positions
728 (let ((pat (pregexp:pregexp
"^[ T]([0-9][0-9]):([0-9][0-9]):([0-9][0-9])")))
729 (defun match-time-hh-mm-ss (s)
730 (pregexp:pregexp-match-positions
734 (let ((pat (pregexp:pregexp
"^[,.]([0-9][0-9]*)")))
735 (defun match-fraction-nnn (s)
736 (pregexp:pregexp-match-positions
741 (let ((pat (pregexp:pregexp
"^([+-])([0-9][0-9]):([0-9][0-9])$")))
742 (defun match-tz-hh-mm (s)
743 (pregexp:pregexp-match-positions
747 (let ((pat (pregexp:pregexp
"^([+-])([0-9][0-9])([0-9][0-9])$")))
748 (defun match-tz-hhmm (s)
749 (pregexp:pregexp-match-positions
753 (let ((pat (pregexp:pregexp
"^([+-])([0-9][0-9])$")))
754 (defun match-tz-hh (s)
755 (pregexp:pregexp-match-positions
759 (let ((pat (pregexp:pregexp
"^Z$")))
760 (defun match-tz-Z (s)
761 (pregexp:pregexp-match-positions
765 (defmfun $parse_timedate
(s)
766 (setq s
(string-trim '(#\Space
#\Tab
#\Newline
#\Return
) s
))
769 (hours 0) (minutes 0) (seconds 0)
770 (seconds-fraction 0) seconds-fraction-numerator tz
)
771 (if (setq matches
(match-date-yyyy-mm-dd s
))
773 (multiple-value-setq (year month day
)
774 (pregexp-extract-groups-integers matches s
))
775 (setq s
(subseq s
(cdr (elt matches
0)))))
776 (return-from $parse_timedate nil
))
777 (when (setq matches
(match-time-hh-mm-ss s
))
778 (multiple-value-setq (hours minutes seconds
)
779 (pregexp-extract-groups-integers matches s
))
780 (setq s
(subseq s
(cdr (elt matches
0)))))
781 (when (setq matches
(match-fraction-nnn s
))
782 (multiple-value-setq (seconds-fraction-numerator)
783 (pregexp-extract-groups-integers matches s
))
784 (let ((group1 (elt matches
1)))
785 (setq seconds-fraction
(div seconds-fraction-numerator
(expt 10 (- (cdr group1
) (car group1
))))))
786 (setq s
(subseq s
(cdr (elt matches
0)))))
788 ((setq matches
(match-tz-hh-mm s
))
789 (multiple-value-bind (tz-sign tz-hours tz-minutes
)
790 (pregexp-extract-groups-integers matches s
)
791 (setq tz
(* tz-sign
(+ tz-hours
(/ tz-minutes
60))))))
792 ((setq matches
(match-tz-hhmm s
))
793 (multiple-value-bind (tz-sign tz-hours tz-minutes
)
794 (pregexp-extract-groups-integers matches s
)
795 (setq tz
(* tz-sign
(+ tz-hours
(/ tz-minutes
60))))))
796 ((setq matches
(match-tz-hh s
))
797 (multiple-value-bind (tz-sign tz-hours
)
798 (pregexp-extract-groups-integers matches s
)
799 (setq tz
(* tz-sign tz-hours
))))
800 ((setq matches
(match-tz-Z s
))
804 (return-from $parse_timedate nil
))))
806 (encode-time-with-all-parts year month day hours minutes seconds seconds-fraction
(if tz
(- tz
)))))
808 (defun pregexp-extract-groups-integers (matches s
)
809 (values-list (mapcar #'parse-integer-or-sign
810 (mapcar #'(lambda (ab)
811 (subseq s
(car ab
) (cdr ab
)))
814 (defun parse-integer-or-sign (s)
818 (t (parse-integer s
))))
820 ; Clisp (2.49) / Windows does have a problem with dates before 1970-01-01,
821 ; therefore add 400 years in that case and subtract 12622780800
822 ; (= parse_timedate("2300-01-01Z") (Lisp starts with 1900-01-01) in timezone
824 ; see discussion on mailing list circa 2015-04-21: "parse_timedate error"
826 ; Nota bene that this approach is correct only if the daylight saving time flag
827 ; is the same for the given date and date + 400 years. That is true for
828 ; dates before 1970-01-01 and after 2038-01-18, for Clisp at least,
829 ; which ignores daylight saving time for all dates in those ranges,
830 ; effectively making them all standard time.
833 (defun encode-time-with-all-parts (year month day hours minutes seconds-integer seconds-fraction tz
)
834 ;; Experimenting with Clisp 2.49 for Windows seems to show that the bug
835 ;; is triggered when local time zone is east of UTC, for times before
836 ;; 1970-01-01 00:00:00 UTC + the number of hours of the time zone.
837 ;; So apply the bug workaround to all times < 1970-01-02.
838 (if (or (< year
1970) (and (= year
1970) (= day
1)))
839 (sub (encode-time-with-all-parts (add year
400) month day hours minutes seconds-integer seconds-fraction tz
) 12622780800)
840 (add seconds-fraction
841 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
842 ;; so work around null TZ here.
844 (encode-universal-time seconds-integer minutes hours day month year tz
)
845 (encode-universal-time seconds-integer minutes hours day month year
)))))
848 (defun encode-time-with-all-parts (year month day hours minutes seconds-integer seconds-fraction tz
)
849 (add seconds-fraction
850 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
851 ;; so work around null TZ here.
853 (encode-universal-time seconds-integer minutes hours day month year tz
)
854 (encode-universal-time seconds-integer minutes hours day month year
))))
856 (defmfun $encode_time
(year month day hours minutes seconds
&optional tz-offset
)
858 (setq tz-offset
(sub 0 tz-offset
))
860 ((and (consp tz-offset
) (eq (caar tz-offset
) 'rat
))
861 (setq tz-offset
(/ (second tz-offset
) (third tz-offset
))))
863 (setq tz-offset
(rationalize tz-offset
))))
864 (setq tz-offset
(/ (round tz-offset
1/3600) 3600)))
866 ((seconds-integer (mfuncall '$floor seconds
))
867 (seconds-fraction (sub seconds seconds-integer
)))
868 (encode-time-with-all-parts year month day hours minutes seconds-integer seconds-fraction tz-offset
)))
870 (defmfun $decode_time
(seconds &optional tz
)
872 ((and (consp tz
) (eq (caar tz
) 'rat
))
873 (setq tz
(/ (second tz
) (third tz
))))
875 (setq tz
(rationalize tz
))))
876 (if tz
(setq tz
(/ (round tz
1/3600) 3600)))
878 ((seconds-integer (mfuncall '$floor seconds
))
879 (seconds-fraction (sub seconds seconds-integer
)))
881 (seconds minutes hours day month year day-of-week dst-p tz
)
882 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
883 ;; so work around null TZ here.
884 (if tz
(decode-universal-time seconds-integer
(- tz
))
885 (decode-universal-time seconds-integer
))
886 (declare (ignore day-of-week
#+gcl dst-p
))
887 ;; HMM, CAN DECODE-UNIVERSAL-TIME RETURN TZ = NIL ??
889 #-gcl
(if dst-p
(- 1 tz
) (- tz
))
890 #+gcl
(- tz
) ; bug in gcl https://savannah.gnu.org/bugs/?50570
892 (list '(mlist) year month day hours minutes
(add seconds seconds-fraction
) ($ratsimp tz-offset
))))))
894 ;;Some systems make everything functionp including macros:
897 (and (not (macro-function x
))
901 ;; These symbols are shadowed because we use them also as special
903 (deff break
#'cl
:break
)
906 #+(and sbcl sb-package-locks
)
907 (defun makunbound (sym)
908 (sb-ext:without-package-locks
909 (cl:makunbound sym
)))