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) (funcall #.
(maxima-nregex::regex-compile
"^(.*\\.[0-9]*[1-9])00*$") s
))
397 (defun trailing-zeros-regex-f-1 (s) (funcall #.
(maxima-nregex::regex-compile
"^(.*\\.0)00*$") s
))
398 (defun trailing-zeros-regex-e-0 (s) (funcall #.
(maxima-nregex::regex-compile
"^(.*\\.[0-9]*[1-9])00*([^0-9][+-][0-9]*)$") s
))
399 (defun trailing-zeros-regex-e-1 (s) (funcall #.
(maxima-nregex::regex-compile
"^(.*\\.0)00*([^0-9][+-][0-9]*)$") s
))
401 ;; Return S with trailing zero digits stripped off, or NIL if there are none.
403 (defun strip-float-zeros (s)
405 ((or (trailing-zeros-regex-f-0 s
) (trailing-zeros-regex-f-1 s
))
407 ((group1 (aref maxima-nregex
::*regex-groups
* 1)))
408 (subseq s
(first group1
) (second group1
))))
409 ((or (trailing-zeros-regex-e-0 s
) (trailing-zeros-regex-e-1 s
))
411 ((group1 (aref maxima-nregex
::*regex-groups
* 1))
412 (s1 (subseq s
(first group1
) (second group1
)))
413 (group2 (aref maxima-nregex
::*regex-groups
* 2))
414 (s2 (subseq s
(first group2
) (second group2
))))
415 (concatenate 'string s1 s2
)))
418 (defun explodec (symb) ;is called for symbols and numbers
419 (loop for v in
(coerce (print-invert-case symb
) 'list
)
420 collect
(intern (string v
))))
422 ;;; If the 'string is all the same case, invert the case. Otherwise,
425 (defun maybe-invert-string-case (string)
428 (length (length string
)))
430 (let ((ch (char string i
)))
431 (when (both-case-p ch
)
432 (if (upper-case-p ch
)
434 (setq all-upper nil
)))))
436 (string-downcase string
))
438 (string-upcase string
))
443 (defun maybe-invert-string-case (string)
444 (cond (#+scl
(eq ext
:*case-mode
* :lower
)
445 #+allegro
(eq excl
:*current-case-mode
* :case-sensitive-lower
)
450 (length (length string
)))
452 (let ((ch (aref string i
)))
453 (when (both-case-p ch
)
454 (if (upper-case-p ch
)
456 (setq all-upper nil
)))))
458 (string-downcase string
))
460 (string-upcase string
))
464 (defun intern-invert-case (string)
465 ;; Like read-from-string with readtable-case :invert
466 ;; Supply package argument in case this function is called
467 ;; from outside the :maxima package.
468 (intern (maybe-invert-string-case string
) :maxima
))
471 #-
(or gcl scl allegro
)
472 (let ((local-table (copy-readtable nil
)))
473 (setf (readtable-case local-table
) :invert
)
474 (defun print-invert-case (sym)
475 (let ((*readtable
* local-table
)
476 (*print-case
* :upcase
))
477 (princ-to-string sym
))))
480 (let ((local-table (copy-readtable nil
)))
481 (unless #+scl
(eq ext
:*case-mode
* :lower
)
482 #+allegro
(eq excl
:*current-case-mode
* :case-sensitive-lower
)
483 (setf (readtable-case local-table
) :invert
))
484 (defun print-invert-case (sym)
485 (cond (#+scl
(eq ext
:*case-mode
* :lower
)
486 #+allegro
(eq excl
:*current-case-mode
* :case-sensitive-lower
)
487 (let ((*readtable
* local-table
)
488 (*print-case
* :downcase
))
489 (princ-to-string sym
)))
491 (let ((*readtable
* local-table
)
492 (*print-case
* :upcase
))
493 (princ-to-string sym
))))))
496 (defun print-invert-case (sym)
498 (let* ((str (princ-to-string sym
))
502 (map 'string
(lambda (c)
503 (cond ((upper-case-p c
)
511 (if (and have-upper have-lower
)
514 (t (princ-to-string sym
))))
516 (defun implode (list)
517 (declare (optimize (speed 3)))
518 (intern-invert-case (map 'string
#'(lambda (v)
521 (symbol (char (symbol-name v
) 0))
522 (integer (code-char v
))))
525 ;; Note: symb can also be a number, not just a symbol.
526 (defun explode (symb)
527 (declare (optimize (speed 3)))
528 (map 'list
#'(lambda (v) (intern (string v
))) (format nil
"~s" symb
)))
530 ;;; return the first character of the name of a symbol or a string or char
531 (defun get-first-char (symb)
532 (declare (optimize (speed 3)))
533 (char (string symb
) 0))
535 (defun getchar (symb i
)
536 (let ((str (string symb
)))
537 (if (<= 1 i
(length str
))
538 (intern (string (char str
(1- i
))))
547 collecting
(char (symbol-name v
) 0) into tem
550 collecting v into tem
551 else do
(maxima-error "bad entry")
553 (return (make-symbol (maybe-invert-string-case (coerce tem
'string
))))))
555 ;;for those window labels etc. that are wrong type.
556 ;; is not only called for symbols, but also on numbers
558 (length (explodec sym
)))
560 (defun flatsize (sym &aux
(*print-circle
* t
))
561 (length (exploden sym
)))
563 (defmacro safe-zerop
(x)
565 `(and (numberp ,x
) (zerop ,x
))
567 (and (numberp .x.
) (zerop .x.
)))))
569 (defmacro signp
(sym x
)
578 (n `(not (zerop ,x
))))))
579 `(and (numberp ,x
) ,test
)))
583 (defvar *prompt-on-read-hang
* nil
)
584 (defvar *read-hang-prompt
* "")
586 (defun tyi-raw (&optional
(stream *standard-input
*) eof-option
)
587 ;; Adding this extra EOF test, because the testsuite generates
588 ;; unexpected end of input-stream with Windows XP and GCL 2.6.8.
590 (when (eql (peek-char nil stream nil eof-option
) eof-option
)
591 (return-from tyi-raw eof-option
))
593 (let ((ch (read-char-no-hang stream nil eof-option
)))
597 (when (and *prompt-on-read-hang
* *read-hang-prompt
*)
598 (princ *read-hang-prompt
*)
599 (finish-output *standard-output
*))
600 (read-char stream nil eof-option
)))))
602 (defun tyi (&optional
(stream *standard-input
*) eof-option
)
603 (let ((ch (tyi-raw stream eof-option
)))
604 (if (eql ch eof-option
)
606 (backslash-check ch stream eof-option
))))
608 ; The sequences of characters
609 ; <anything-except-backslash>
610 ; (<backslash> <newline> | <backslash> <return> | <backslash> <return> <newline>)+
612 ; are reduced to <anything-except-backslash> <anything> .
613 ; Note that this has no effect on <backslash> <anything-but-newline-or-return> .
615 (let ((previous-tyi #\a))
616 (defun backslash-check (ch stream eof-option
)
617 (if (eql previous-tyi
#\\ )
618 (progn (setq previous-tyi
#\a) ch
)
621 (let ((next-char (peek-char nil stream nil eof-option
)))
622 (if (or (eql next-char
#\newline
) (eql next-char
#\return
))
623 (eat-continuations ch stream eof-option
)
626 ; We have just read <backslash> and we know the next character is <newline> or <return>.
627 ; Eat line continuations until we come to something which doesn't match, or we reach eof.
628 (defun eat-continuations (ch stream eof-option
)
629 (setq ch
(tyi-raw stream eof-option
))
630 (do () ((not (or (eql ch
#\newline
) (eql ch
#\return
))))
631 (let ((next-char (peek-char nil stream nil eof-option
)))
632 (if (and (eql ch
#\return
) (eql next-char
#\newline
))
633 (tyi-raw stream eof-option
)))
634 (setq ch
(tyi-raw stream eof-option
))
635 (let ((next-char (peek-char nil stream nil eof-option
)))
636 (if (and (eql ch
#\\ ) (or (eql next-char
#\return
) (eql next-char
#\newline
)))
637 (setq ch
(tyi-raw stream eof-option
))
638 (return-from eat-continuations ch
))))
641 (defmfun $timedate
(&optional
(time (get-universal-time)) tz
)
643 ((and (consp tz
) (eq (caar tz
) 'rat
))
644 (setq tz
(/ (second tz
) (third tz
))))
646 (setq tz
(rationalize tz
))))
647 (if tz
(setq tz
(/ (round tz
1/60) 60)))
649 ((time-integer (mfuncall '$floor time
))
650 (time-fraction (sub time time-integer
))
651 (time-millis (mfuncall '$round
(mul 1000 time-fraction
))))
652 (when (= time-millis
1000)
653 (setq time-integer
(1+ time-integer
))
654 (setq time-millis
0))
656 (second minute hour date month year day-of-week dst-p tz
)
657 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
658 ;; so work around null TZ here.
659 (if tz
(decode-universal-time time-integer
(- tz
))
660 (decode-universal-time time-integer
))
661 (declare (ignore day-of-week
#+gcl dst-p
))
662 ;; DECODE-UNIVERSAL-TIME might return a timezone offset
663 ;; which is a multiple of 1/3600 but not 1/60.
664 ;; We need a multiple of 1/60 because our formatted
665 ;; timezone offset has only minutes and seconds.
666 (if (/= (mod tz
1/60) 0)
667 ($timedate time-integer
(/ (round (- tz
) 1/60) 60))
669 #-gcl
(if dst-p
(- 1 tz
) (- tz
))
670 #+gcl
(- tz
) ; bug in gcl https://savannah.gnu.org/bugs/?50570
673 (tz-hours tz-hour-fraction
)
676 ((tz-sign (if (<= 0 tz-offset
) #\
+ #\-
)))
677 (if (= time-millis
0)
678 (format nil
"~4,'0d-~2,'0d-~2,'0d ~2,'0d:~2,'0d:~2,'0d~a~2,'0d:~2,'0d"
679 year month date hour minute second tz-sign
(abs tz-hours
) (floor (* 60 (abs tz-hour-fraction
))))
680 (format nil
"~4,'0d-~2,'0d-~2,'0d ~2,'0d:~2,'0d:~2,'0d.~3,'0d~a~2,'0d:~2,'0d"
681 year month date hour minute second time-millis tz-sign
(abs tz-hours
) (floor (* 60 (abs tz-hour-fraction
))))))))))))
683 ;; Parse date/time strings in these formats (and only these):
685 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?([+-]hh:mm)?
686 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?([+-]hhmm)?
687 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?([+-]hh)?
688 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?[Z]?
690 ;; where (...)? indicates an optional group (occurs zero or one times)
691 ;; ...+ indicates one or more instances of ...,
692 ;; and [...] indicates literal character alternatives.
694 ;; Note that the nregex package doesn't handle optional groups or ...+.
695 ;; The notation above is only for describing the behavior of the parser.
697 ;; Trailing unparsed stuff causes the parser to fail (return NIL).
699 (defun match-date-yyyy-mm-dd (s) (funcall #.
(maxima-nregex::regex-compile
"^([0-9][0-9][0-9][0-9])-([0-9][0-9])-([0-9][0-9])") s
))
700 (defun match-time-hh-mm-ss (s) (funcall #.
(maxima-nregex::regex-compile
"^[ T]([0-9][0-9]):([0-9][0-9]):([0-9][0-9])") s
))
701 (defun match-fraction-nnn (s) (funcall #.
(maxima-nregex::regex-compile
"^[,.]([0-9][0-9]*)") s
))
702 (defun match-tz-hh-mm (s) (funcall #.
(maxima-nregex::regex-compile
"^([+-])([0-9][0-9]):([0-9][0-9])$") s
))
703 (defun match-tz-hhmm (s) (funcall #.
(maxima-nregex::regex-compile
"^([+-])([0-9][0-9])([0-9][0-9])$") s
))
704 (defun match-tz-hh (s) (funcall #.
(maxima-nregex::regex-compile
"^([+-])([0-9][0-9])$") s
))
705 (defun match-tz-Z (s) (funcall #.
(maxima-nregex::regex-compile
"^Z$") s
))
707 (defmfun $parse_timedate
(s)
708 (setq s
(string-trim '(#\Space
#\Tab
#\Newline
#\Return
) s
))
710 (hours 0) (minutes 0) (seconds 0)
711 (seconds-fraction 0) seconds-fraction-numerator tz
)
712 (if (match-date-yyyy-mm-dd s
)
714 (multiple-value-setq (year month day
) (extract-groups-integers s
))
715 (setq s
(subseq s
(second (aref maxima-nregex
::*regex-groups
* 0)))))
716 (return-from $parse_timedate nil
))
717 (when (match-time-hh-mm-ss s
)
718 (multiple-value-setq (hours minutes seconds
) (extract-groups-integers s
))
719 (setq s
(subseq s
(second (aref maxima-nregex
::*regex-groups
* 0)))))
720 (when (match-fraction-nnn s
)
721 (multiple-value-setq (seconds-fraction-numerator) (extract-groups-integers s
))
722 (let ((group1 (aref maxima-nregex
::*regex-groups
* 1)))
723 (setq seconds-fraction
(div seconds-fraction-numerator
(expt 10 (- (second group1
) (first group1
))))))
724 (setq s
(subseq s
(second (aref maxima-nregex
::*regex-groups
* 0)))))
727 (multiple-value-bind (tz-sign tz-hours tz-minutes
) (extract-groups-integers s
)
728 (setq tz
(* tz-sign
(+ tz-hours
(/ tz-minutes
60))))))
730 (multiple-value-bind (tz-sign tz-hours tz-minutes
) (extract-groups-integers s
)
731 (setq tz
(* tz-sign
(+ tz-hours
(/ tz-minutes
60))))))
733 (multiple-value-bind (tz-sign tz-hours
) (extract-groups-integers s
)
734 (setq tz
(* tz-sign tz-hours
))))
739 (return-from $parse_timedate nil
))))
741 (encode-time-with-all-parts year month day hours minutes seconds seconds-fraction
(if tz
(- tz
)))))
743 (defun extract-groups-integers (s)
744 (let ((groups (coerce (subseq maxima-nregex
::*regex-groups
* 1 maxima-nregex
::*regex-groupings
*) 'list
)))
745 (values-list (mapcar #'parse-integer-or-sign
746 (mapcar #'(lambda (ab) (subseq s
(first ab
) (second ab
)))
749 (defun parse-integer-or-sign (s)
753 (t (parse-integer s
))))
755 ; Clisp (2.49) / Windows does have a problem with dates before 1970-01-01,
756 ; therefore add 400 years in that case and subtract 12622780800
757 ; (= parse_timedate("2300-01-01Z") (Lisp starts with 1900-01-01) in timezone
759 ; see discussion on mailing list circa 2015-04-21: "parse_timedate error"
761 ; Nota bene that this approach is correct only if the daylight saving time flag
762 ; is the same for the given date and date + 400 years. That is true for
763 ; dates before 1970-01-01 and after 2038-01-18, for Clisp at least,
764 ; which ignores daylight saving time for all dates in those ranges,
765 ; effectively making them all standard time.
768 (defun encode-time-with-all-parts (year month day hours minutes seconds-integer seconds-fraction tz
)
769 ;; Experimenting with Clisp 2.49 for Windows seems to show that the bug
770 ;; is triggered when local time zone is east of UTC, for times before
771 ;; 1970-01-01 00:00:00 UTC + the number of hours of the time zone.
772 ;; So apply the bug workaround to all times < 1970-01-02.
773 (if (or (< year
1970) (and (= year
1970) (= day
1)))
774 (sub (encode-time-with-all-parts (add year
400) month day hours minutes seconds-integer seconds-fraction tz
) 12622780800)
775 (add seconds-fraction
776 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
777 ;; so work around null TZ here.
779 (encode-universal-time seconds-integer minutes hours day month year tz
)
780 (encode-universal-time seconds-integer minutes hours day month year
)))))
783 (defun encode-time-with-all-parts (year month day hours minutes seconds-integer seconds-fraction tz
)
784 (add seconds-fraction
785 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
786 ;; so work around null TZ here.
788 (encode-universal-time seconds-integer minutes hours day month year tz
)
789 (encode-universal-time seconds-integer minutes hours day month year
))))
791 (defmfun $encode_time
(year month day hours minutes seconds
&optional tz-offset
)
793 (setq tz-offset
(sub 0 tz-offset
))
795 ((and (consp tz-offset
) (eq (caar tz-offset
) 'rat
))
796 (setq tz-offset
(/ (second tz-offset
) (third tz-offset
))))
798 (setq tz-offset
(rationalize tz-offset
))))
799 (setq tz-offset
(/ (round tz-offset
1/3600) 3600)))
801 ((seconds-integer (mfuncall '$floor seconds
))
802 (seconds-fraction (sub seconds seconds-integer
)))
803 (encode-time-with-all-parts year month day hours minutes seconds-integer seconds-fraction tz-offset
)))
805 (defmfun $decode_time
(seconds &optional tz
)
807 ((and (consp tz
) (eq (caar tz
) 'rat
))
808 (setq tz
(/ (second tz
) (third tz
))))
810 (setq tz
(rationalize tz
))))
811 (if tz
(setq tz
(/ (round tz
1/3600) 3600)))
813 ((seconds-integer (mfuncall '$floor seconds
))
814 (seconds-fraction (sub seconds seconds-integer
)))
816 (seconds minutes hours day month year day-of-week dst-p tz
)
817 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
818 ;; so work around null TZ here.
819 (if tz
(decode-universal-time seconds-integer
(- tz
))
820 (decode-universal-time seconds-integer
))
821 (declare (ignore day-of-week
#+gcl dst-p
))
822 ;; HMM, CAN DECODE-UNIVERSAL-TIME RETURN TZ = NIL ??
824 #-gcl
(if dst-p
(- 1 tz
) (- tz
))
825 #+gcl
(- tz
) ; bug in gcl https://savannah.gnu.org/bugs/?50570
827 (list '(mlist) year month day hours minutes
(add seconds seconds-fraction
) ($ratsimp tz-offset
))))))
829 ;;Some systems make everything functionp including macros:
832 (and (not (macro-function x
))
836 ;; These symbols are shadowed because we use them also as special
838 (deff break
#'cl
:break
)
841 #+(and sbcl sb-package-locks
)
842 (defun makunbound (sym)
843 (sb-ext:without-package-locks
844 (cl:makunbound sym
)))