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 (defvar *prin1
* nil
) ;a function called instead of prin1.
17 ;; Should we give this a different name?
18 (defvar *fortran-print
* nil
19 "Tells EXPLODEN we are printing numbers for Fortran so include the exponent marker.")
21 (defun appears (tree var
)
22 (cond ((equal tree var
)
25 (t (appears (car tree
) var
)
26 (appears (cdr tree
) var
)))
29 (defun appears1 (tree var
)
34 (appears (car tree
) var
)
35 (appears (cdr tree
) var
)))
38 (defun appears-in (tree var
)
39 "Yields t if var appears in tree"
41 (if (or (symbolp var
) (fixnump var
))
45 ;; A more portable implementation of ml-typep. I (rtoy) think it
46 ;; would probably be better to replace uses of
47 ;; ml-typep with the corresponding Common Lisp typep or type-of or
48 ;; subtypep, as appropriate.
49 (defun ml-typep (x &optional type
)
51 (cl:let
((pred (get type
'ml-typep
)))
63 (cl:hash-table
'hash-table
)
67 (defprop :extended-number extended-number-p ml-typep
)
68 (defprop array arrayp ml-typep
)
69 (defprop atom atom ml-typep
)
72 (eval-when (:compile-toplevel
:load-toplevel
:execute
)
73 (shadow '(cl:compiled-function-p
) (find-package :maxima
))
76 (defun compiled-function-p (x)
77 (and (functionp x
) (not (symbolp x
))
78 (not (eval:interpreted-function-p x
))))
80 (defprop compiled-function compiled-function-p ml-typep
)
81 (defprop extended-number extended-number-p ml-typep
)
82 (defprop fixnum fixnump ml-typep
)
83 (defprop list consp ml-typep
)
84 (defprop number numberp ml-typep
)
85 (defprop string stringp ml-typep
)
86 (defprop symbol symbolp ml-typep
)
89 (defvar *maxima-arrays
* nil
90 "Trying to track down any functional arrays in maxima")
92 ;;only remaining calls are for maclisp-type = nil
93 (defun *array
(name maclisp-type
&rest dimlist
&aux aarray
)
94 (cond ((member maclisp-type
'(readtable obarray
) :test
#'eq
)
95 (error " bad type ~S" maclisp-type
)))
96 (pushnew name
*maxima-arrays
*) ;for tracking down old ones.
97 (setq aarray
(make-array dimlist
:initial-element
(case maclisp-type
101 (cond ((null name
) aarray
)
103 (setf (symbol-array name
) aarray
)
105 (t (error "~S is illegal first arg for *array" name
))))
107 ;;; Change maclisp array referencing.
108 ;;; Idea1: Make changes in the code which will allow the code to still run in maclisp,
109 ;;;yet will allow, with the appropriate macro definitions of array,arraycall, etc,
110 ;;;to put the array into the value-cell.
111 ;;; Idea2: Make changes in the array referencing of (a dim1 dim2..) to (arraycall nil (symbol-array a) dim1..)
112 ;;;which would then allow expansion into something which is common lisp compatible, for
113 ;;;the day when (a 2 3) no longer is equivalent to (aref (symbol-function a) 2 3).
114 ;;;I. change (array a typ dim1 dim2..) to expand to (defvar a (make-array (list dim1 dim2 ...) :type typ')
115 ;;;II. change (a dim1 dim2..) to (arraycall nil (symbol-array a) dim1 dim2 ..)
117 ;;(defmacro symbol-array (ar)
118 ;; `(symbol-function ,ar))
119 ;;(defmacro arraycall (ignore ar &rest dims)
120 ;; `(aref ,ar ,@ dims))
121 ;;;IV. change array setting to use (setf (arraycall nil ar dim1.. ) val)
122 ;;;which will generate the correct setting code on the lispm and will
123 ;;;still work in maclisp.
125 (defmacro maxima-error
(datum &rest args
)
126 `(cerror "without any special action" ,datum
,@args
))
128 (defmacro show
(&rest l
)
130 collecting
`(format t
"~%The value of ~A is ~A" ',v
,v
) into tem
131 finally
(return `(progn ,@ tem
))))
133 (defmacro defquote
(fn (aa . oth
) &body rest
&aux help ans
)
134 (setq help
(intern (format nil
"~a-~a" fn
'#:aux
)))
135 (cond ((eq aa
'&rest
)
138 `(defmacro ,fn
(&rest
,(car oth
))
139 `(,',help
',,(car oth
)))
140 `(defun ,help
(,(car oth
)) ,@rest
))))
141 (t (when (member '&rest oth
)
142 (error "at present &rest may only occur as first item in a defquote argument"))
145 `(defmacro ,fn
(,aa . other
)
146 (setq other
(loop for v in other collecting
(list 'quote v
)))
147 (check-arg other
(eql (length other
) ,(length oth
))
148 ,(format nil
"wrong number of args to ~a" fn
))
149 `(,',help
',,aa
,@ other
))
150 `(defun ,help
(,aa
,@ oth
) ,@rest
)))))
154 ;;the resulting function will translate to defvar and will behave
155 ;;correctly for the evaluator.
157 ;;(defun gg fexpr (ll)
159 ;;(defquote gg (&rest ll)
162 ;;(DEFQUOTE GG ( &rest C)
163 ;; (list (car c) (second c) ))
164 ;;the big advantage of using the following over defmspec is that it
165 ;;seems to translate more easily, since it is a fn.
166 ;;New functions which wanted quoted arguments should be defined using
170 (defun onep (x) (eql 1 x
))
172 (defun extended-number-p (x)
173 (member (type-of x
) '(bignum rational float
)))
175 (defvar *scan-string-buffer
* nil
)
177 (defun macsyma-read-string (a-string &aux answer
)
178 (cond ((not (or (search "$" a-string
:test
#'char-equal
)
179 (search ";" a-string
:test
#'char-equal
)))
180 (vector-push-extend #\$ a-string
)))
181 (with-input-from-string (stream a-string
)
182 (setq answer
(third (mread stream
)))
185 (defvar *sharp-read-buffer
*
186 (make-array 140 :element-type
' #.
(array-element-type "a") :fill-pointer
0 :adjustable t
))
188 (defun x$-cl-macro-read
(stream sub-char arg
)
189 (declare (ignore arg
))
190 ($-read-aux sub-char stream
))
192 (defun $-read-aux
(arg stream
&aux
(meval-flag t
) (*mread-prompt
* ""))
193 (declare (special *mread-prompt
*)
195 (setf (fill-pointer *sharp-read-buffer
*) 0)
196 (cond ((eql #\$
(peek-char t stream
))
198 (setq meval-flag nil
)))
199 (with-output-to-string (st *sharp-read-buffer
*)
201 (loop while
(not (eql char
#\$
))
203 (setq char
(tyi stream
))
204 (write-char char st
))))
206 (list 'meval
* (list 'quote
(macsyma-read-string *sharp-read-buffer
*)))
207 (list 'quote
(macsyma-read-string *sharp-read-buffer
*))))
209 (set-dispatch-macro-character #\
# #\$
#'x$-cl-macro-read
)
211 (defvar *macsyma-readtable
*)
213 (defun find-lisp-readtable-for-macsyma ()
214 (cond ((and (boundp '*macsyma-readtable
*)
215 (readtablep *macsyma-readtable
*))
217 (t (setq *macsyma-readtable
* (copy-readtable nil
))
218 (set-dispatch-macro-character #\
# #\$
'x$-cl-macro-read
*macsyma-readtable
*)
219 *macsyma-readtable
*)))
221 (defun set-readtable-for-macsyma ()
222 (setq *readtable
* (find-lisp-readtable-for-macsyma)))
224 (defvar *reset-var
* t
)
226 (defvar *variable-initial-values
* (make-hash-table)
227 "Hash table containing all Maxima defmvar variables and their initial
230 (defmacro defmvar
(var &rest val-and-doc
)
231 "If *reset-var* is true then loading or eval'ing will reset value, otherwise like defvar"
232 (cond ((> (length val-and-doc
) 2)
233 (setq val-and-doc
(list (car val-and-doc
) (second val-and-doc
)))))
235 (unless (gethash ',var
*variable-initial-values
*)
236 (setf (gethash ',var
*variable-initial-values
*)
237 ,(first val-and-doc
)))
238 (defvar ,var
,@val-and-doc
)))
240 (defun $mkey
(variable)
241 "($mkey '$demo)==>:demo"
242 (intern (string-left-trim "$" (string variable
)) 'keyword
))
245 `(narg1 ,x narg-rest-argument
))
247 (defun narg1 (x l
&aux tem
)
248 (cond ((null x
) (length l
))
249 (t (setq tem
(nthcdr (1- x
) l
))
250 (cond ((null tem
) (error "arg ~A beyond range ~A " x
(length l
)))
253 (defmacro listify
(x)
254 `(listify1 ,x narg-rest-argument
))
256 (defmacro setarg
(i val
)
257 `(setarg1 ,i
,val narg-rest-argument
))
259 (defun setarg1 (i val l
)
260 (setf (nth (1- i
) l
) val
)
263 (defun listify1 (n narg-rest-argument
)
264 (cond ((minusp n
) (copy-list (last narg-rest-argument
(- n
))) )
266 (t (subseq narg-rest-argument
0 n
))))
268 (defmacro defmfun
(function &body rest
&aux .n.
)
269 (cond ((and (car rest
) (symbolp (car rest
)))
270 ;;old maclisp narg syntax
271 (setq .n.
(car rest
))
273 `(&rest narg-rest-argument
&aux
(, .n.
(length narg-rest-argument
))))))
275 ;; I (rtoy) think we can consider all defmfun's as translated functions.
276 (defprop ,function t translated
)
277 (defun ,function .
,rest
)))
280 ;;(defmfun foo a (show a )(show (listify a)) (show (arg 3)))
282 (defun exploden (symb)
283 (let* (#+(and gcl
(not gmp
)) (big-chunk-size 120)
284 #+(and gcl
(not gmp
)) (tentochunksize (expt 10 big-chunk-size
))
286 (cond ((symbolp symb
)
287 (setq string
(print-invert-case symb
)))
289 (setq string
(exploden-format-float symb
)))
292 ;; When obase > 10, prepend leading zero to
293 ;; ensure that output is readable as a number.
294 (let ((leading-digit (if (> *print-base
* 10) #\
0)))
296 #+(and gcl
(not gmp
))
302 do
(multiple-value-setq (big rem
)
303 (floor big tentochunksize
))
305 while
(not (eql 0 big
)))))
306 (setq chunks
(nreverse chunks
))
307 (setq ans
(coerce (format nil
"~d" (car chunks
)) 'list
))
308 (if (and leading-digit
(not (digit-char-p (car ans
) 10.
)))
309 (setq ans
(cons leading-digit ans
)))
310 (loop for v in
(cdr chunks
)
311 do
(setq tem
(coerce (format nil
"~d" v
) 'list
))
312 (loop for i below
(- big-chunk-size
(length tem
))
313 do
(setq tem
(cons #\
0 tem
)))
314 (setq ans
(nconc ans tem
)))
315 (return-from exploden ans
)))
317 (setq string
(format nil
"~A" symb
))
318 (setq string
(coerce string
'list
))
319 (if (and leading-digit
(not (digit-char-p (car string
) 10.
)))
320 (setq string
(cons leading-digit string
)))
321 (return-from exploden string
)))))
323 (t (setq string
(format nil
"~A" symb
))))
324 (assert (stringp string
))
325 (coerce string
'list
)))
327 (defvar *exploden-strip-float-zeros
* t
) ;; NIL => allow trailing zeros
329 (defun exploden-format-float (symb)
330 (declare (special $maxfpprintprec
))
333 (effective-printprec (if (or (= $fpprintprec
0)
334 (> $fpprintprec $maxfpprintprec
))
337 ;; When printing out something for Fortran, we want to be
338 ;; sure to print the exponent marker so that Fortran
339 ;; knows what kind of number it is. It turns out that
340 ;; Fortran's exponent markers are the same as Lisp's so
341 ;; we just need to make sure the exponent marker is
345 ;; Strings for non-finite numbers as specified for input in Fortran 2003 spec;
346 ;; they apparently did not exist in earlier versions.
347 ((float-nan-p symb
) "NAN")
348 ((float-inf-p symb
) (if (< symb
0) "-INF" "INF"))
349 (t (format nil
"~e" symb
))))
350 (multiple-value-bind (form digits
)
354 ;; Work around for GCL bug #47404.
355 ;; Avoid numeric comparisons with NaN, which erroneously return T.
356 #+gcl
((or (float-inf-p symb
) (float-nan-p symb
))
357 (return-from exploden-format-float
(format nil
"~a" symb
)))
360 ((integer-log10 (floor (/ (log a
) #.
(log 10.0))))
361 (scale (1+ integer-log10
)))
362 (if (< scale effective-printprec
)
363 (values "~,vf" (- effective-printprec scale
))
364 (values "~,ve" (1- effective-printprec
)))))
365 #-gcl
((or (float-inf-p symb
) (float-nan-p symb
))
366 (return-from exploden-format-float
(format nil
"~a" symb
)))
368 (values "~,ve" (1- effective-printprec
))))
370 ;; Call FORMAT using format string chosen above.
371 (setq string
(format nil form digits a
))
373 ;; EXPLODEN is often called after NFORMAT, so it doesn't
374 ;; usually see a negative argument. I can't guarantee
375 ;; a non-negative argument, so handle negative here.
377 (setq string
(concatenate 'string
"-" string
)))))
379 (if *exploden-strip-float-zeros
*
380 (or (strip-float-zeros string
) string
)
383 (defun trailing-zeros-regex-f-0 (s) (funcall #.
(maxima-nregex::regex-compile
"^(.*\\.[0-9]*[1-9])00*$") s
))
384 (defun trailing-zeros-regex-f-1 (s) (funcall #.
(maxima-nregex::regex-compile
"^(.*\\.0)00*$") s
))
385 (defun trailing-zeros-regex-e-0 (s) (funcall #.
(maxima-nregex::regex-compile
"^(.*\\.[0-9]*[1-9])00*([^0-9][+-][0-9]*)$") s
))
386 (defun trailing-zeros-regex-e-1 (s) (funcall #.
(maxima-nregex::regex-compile
"^(.*\\.0)00*([^0-9][+-][0-9]*)$") s
))
388 ;; Return S with trailing zero digits stripped off, or NIL if there are none.
390 (defun strip-float-zeros (s)
392 ((or (trailing-zeros-regex-f-0 s
) (trailing-zeros-regex-f-1 s
))
394 ((group1 (aref maxima-nregex
::*regex-groups
* 1)))
395 (subseq s
(first group1
) (second group1
))))
396 ((or (trailing-zeros-regex-e-0 s
) (trailing-zeros-regex-e-1 s
))
398 ((group1 (aref maxima-nregex
::*regex-groups
* 1))
399 (s1 (subseq s
(first group1
) (second group1
)))
400 (group2 (aref maxima-nregex
::*regex-groups
* 2))
401 (s2 (subseq s
(first group2
) (second group2
))))
402 (concatenate 'string s1 s2
)))
405 (defun explodec (symb) ;is called for symbols and numbers
406 (loop for v in
(coerce (print-invert-case symb
) 'list
)
407 collect
(intern (string v
))))
409 ;;; If the 'string is all the same case, invert the case. Otherwise,
412 (defun maybe-invert-string-case (string)
415 (length (length string
)))
417 (let ((ch (char string i
)))
418 (when (both-case-p ch
)
419 (if (upper-case-p ch
)
421 (setq all-upper nil
)))))
423 (string-downcase string
))
425 (string-upcase string
))
430 (defun maybe-invert-string-case (string)
431 (cond (#+scl
(eq ext
:*case-mode
* :lower
)
432 #+allegro
(eq excl
:*current-case-mode
* :case-sensitive-lower
)
437 (length (length string
)))
439 (let ((ch (aref string i
)))
440 (when (both-case-p ch
)
441 (if (upper-case-p ch
)
443 (setq all-upper nil
)))))
445 (string-downcase string
))
447 (string-upcase string
))
451 (defun intern-invert-case (string)
452 ;; Like read-from-string with readtable-case :invert
453 ;; Supply package argument in case this function is called
454 ;; from outside the :maxima package.
455 (intern (maybe-invert-string-case string
) :maxima
))
458 #-
(or gcl scl allegro
)
459 (let ((local-table (copy-readtable nil
)))
460 (setf (readtable-case local-table
) :invert
)
461 (defun print-invert-case (sym)
462 (let ((*readtable
* local-table
)
463 (*print-case
* :upcase
))
464 (princ-to-string sym
))))
467 (let ((local-table (copy-readtable nil
)))
468 (unless #+scl
(eq ext
:*case-mode
* :lower
)
469 #+allegro
(eq excl
:*current-case-mode
* :case-sensitive-lower
)
470 (setf (readtable-case local-table
) :invert
))
471 (defun print-invert-case (sym)
472 (cond (#+scl
(eq ext
:*case-mode
* :lower
)
473 #+allegro
(eq excl
:*current-case-mode
* :case-sensitive-lower
)
474 (let ((*readtable
* local-table
)
475 (*print-case
* :downcase
))
476 (princ-to-string sym
)))
478 (let ((*readtable
* local-table
)
479 (*print-case
* :upcase
))
480 (princ-to-string sym
))))))
483 (defun print-invert-case (sym)
485 (let* ((str (princ-to-string sym
))
489 (map 'string
(lambda (c)
490 (cond ((upper-case-p c
)
498 (if (and have-upper have-lower
)
501 (t (princ-to-string sym
))))
503 (defun implode (list)
504 (declare (optimize (speed 3)))
505 (intern-invert-case (map 'string
#'(lambda (v)
508 (symbol (char (symbol-name v
) 0))
509 (integer (code-char v
))))
512 ;; Note: symb can also be a number, not just a symbol.
513 (defun explode (symb)
514 (declare (optimize (speed 3)))
515 (map 'list
#'(lambda (v) (intern (string v
))) (format nil
"~a" symb
)))
517 ;;; return the first character of the name of a symbol or a string or char
518 (defun get-first-char (symb)
519 (declare (optimize (speed 3)))
520 (char (string symb
) 0))
522 (defun getchar (symb i
)
523 (let ((str (string symb
)))
524 (if (<= 1 i
(length str
))
525 (intern (string (char str
(1- i
))))
534 collecting
(char (symbol-name v
) 0) into tem
537 collecting v into tem
538 else do
(maxima-error "bad entry")
540 (return (make-symbol (maybe-invert-string-case (coerce tem
'string
))))))
542 ;;for those window labels etc. that are wrong type.
543 ;; is not only called for symbols, but also on numbers
545 (length (explodec sym
)))
547 (defun flatsize (sym &aux
(*print-circle
* t
))
548 (length (exploden sym
)))
550 (defmacro safe-zerop
(x)
552 `(and (numberp ,x
) (zerop ,x
))
554 (and (numberp .x.
) (zerop .x.
)))))
556 (defmacro signp
(sym x
)
565 (n `(not (zerop ,x
))))))
566 `(and (numberp ,x
) ,test
)))
570 (defvar *prompt-on-read-hang
* nil
)
571 (defvar *read-hang-prompt
* "")
573 (defun tyi-raw (&optional
(stream *standard-input
*) eof-option
)
574 ;; Adding this extra EOF test, because the testsuite generates
575 ;; unexpected end of input-stream with Windows XP and GCL 2.6.8.
577 (when (eql (peek-char nil stream nil eof-option
) eof-option
)
578 (return-from tyi-raw eof-option
))
580 (let ((ch (read-char-no-hang stream nil eof-option
)))
584 (when (and *prompt-on-read-hang
* *read-hang-prompt
*)
585 (princ *read-hang-prompt
*)
586 (force-output *standard-output
*))
587 (read-char stream nil eof-option
)))))
589 (defun tyi (&optional
(stream *standard-input
*) eof-option
)
590 (let ((ch (tyi-raw stream eof-option
)))
591 (if (eql ch eof-option
)
593 (backslash-check ch stream eof-option
))))
595 ; The sequences of characters
596 ; <anything-except-backslash>
597 ; (<backslash> <newline> | <backslash> <return> | <backslash> <return> <newline>)+
599 ; are reduced to <anything-except-backslash> <anything> .
600 ; Note that this has no effect on <backslash> <anything-but-newline-or-return> .
602 (let ((previous-tyi #\a))
603 (defun backslash-check (ch stream eof-option
)
604 (if (eql previous-tyi
#\\ )
605 (progn (setq previous-tyi
#\a) ch
)
608 (let ((next-char (peek-char nil stream nil eof-option
)))
609 (if (or (eql next-char
#\newline
) (eql next-char
#\return
))
610 (eat-continuations ch stream eof-option
)
613 ; We have just read <backslash> and we know the next character is <newline> or <return>.
614 ; Eat line continuations until we come to something which doesn't match, or we reach eof.
615 (defun eat-continuations (ch stream eof-option
)
616 (setq ch
(tyi-raw stream eof-option
))
617 (do () ((not (or (eql ch
#\newline
) (eql ch
#\return
))))
618 (let ((next-char (peek-char nil stream nil eof-option
)))
619 (if (and (eql ch
#\return
) (eql next-char
#\newline
))
620 (tyi-raw stream eof-option
)))
621 (setq ch
(tyi-raw stream eof-option
))
622 (let ((next-char (peek-char nil stream nil eof-option
)))
623 (if (and (eql ch
#\\ ) (or (eql next-char
#\return
) (eql next-char
#\newline
)))
624 (setq ch
(tyi-raw stream eof-option
))
625 (return-from eat-continuations ch
))))
630 (defun $timedate
(&optional
(time (get-universal-time)) tz
)
632 ((and (consp tz
) (eq (caar tz
) 'rat
))
633 (setq tz
(/ (second tz
) (third tz
))))
635 (setq tz
(rationalize tz
))))
636 (if tz
(setq tz
(/ (round tz
1/60) 60)))
638 ((time-integer (mfuncall '$floor time
))
639 (time-fraction (sub time time-integer
))
640 (time-millis (mfuncall '$round
(mul 1000 time-fraction
))))
641 (when (= time-millis
1000)
642 (setq time-integer
(1+ time-integer
))
643 (setq time-millis
0))
645 (second minute hour date month year day-of-week dst-p tz
)
646 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
647 ;; so work around null TZ here.
648 (if tz
(decode-universal-time time-integer
(- tz
))
649 (decode-universal-time time-integer
))
650 (declare (ignore day-of-week
#+gcl dst-p
))
651 ;; DECODE-UNIVERSAL-TIME might return a timezone offset
652 ;; which is a multiple of 1/3600 but not 1/60.
653 ;; We need a multiple of 1/60 because our formatted
654 ;; timezone offset has only minutes and seconds.
655 (if (/= (mod tz
1/60) 0)
656 ($timedate time-integer
(/ (round (- tz
) 1/60) 60))
658 #-gcl
(if dst-p
(- 1 tz
) (- tz
))
659 #+gcl
(- tz
) ; bug in gcl https://savannah.gnu.org/bugs/?50570
662 (tz-hours tz-hour-fraction
)
665 ((tz-sign (if (<= 0 tz-offset
) #\
+ #\-
)))
666 (if (= time-millis
0)
667 (format nil
"~4,'0d-~2,'0d-~2,'0d ~2,'0d:~2,'0d:~2,'0d~a~2,'0d:~2,'0d"
668 year month date hour minute second tz-sign
(abs tz-hours
) (floor (* 60 (abs tz-hour-fraction
))))
669 (format nil
"~4,'0d-~2,'0d-~2,'0d ~2,'0d:~2,'0d:~2,'0d.~3,'0d~a~2,'0d:~2,'0d"
670 year month date hour minute second time-millis tz-sign
(abs tz-hours
) (floor (* 60 (abs tz-hour-fraction
))))))))))))
672 ;; Parse date/time strings in these formats (and only these):
674 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?([+-]hh:mm)?
675 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?([+-]hhmm)?
676 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?([+-]hh)?
677 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?[Z]?
679 ;; where (...)? indicates an optional group (occurs zero or one times)
680 ;; ...+ indicates one or more instances of ...,
681 ;; and [...] indicates literal character alternatives.
683 ;; Note that the nregex package doesn't handle optional groups or ...+.
684 ;; The notation above is only for describing the behavior of the parser.
686 ;; Trailing unparsed stuff causes the parser to fail (return NIL).
688 (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
))
689 (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
))
690 (defun match-fraction-nnn (s) (funcall #.
(maxima-nregex::regex-compile
"^[,.]([0-9][0-9]*)") s
))
691 (defun match-tz-hh-mm (s) (funcall #.
(maxima-nregex::regex-compile
"^([+-])([0-9][0-9]):([0-9][0-9])$") s
))
692 (defun match-tz-hhmm (s) (funcall #.
(maxima-nregex::regex-compile
"^([+-])([0-9][0-9])([0-9][0-9])$") s
))
693 (defun match-tz-hh (s) (funcall #.
(maxima-nregex::regex-compile
"^([+-])([0-9][0-9])$") s
))
694 (defun match-tz-Z (s) (funcall #.
(maxima-nregex::regex-compile
"^Z$") s
))
696 (defun $parse_timedate
(s)
697 (setq s
(string-trim '(#\Space
#\Tab
#\Newline
#\Return
) s
))
699 (hours 0) (minutes 0) (seconds 0)
700 (seconds-fraction 0) seconds-fraction-numerator tz
)
701 (if (match-date-yyyy-mm-dd s
)
703 (multiple-value-setq (year month day
) (extract-groups-integers s
))
704 (setq s
(subseq s
(second (aref maxima-nregex
::*regex-groups
* 0)))))
705 (return-from $parse_timedate nil
))
706 (when (match-time-hh-mm-ss s
)
707 (multiple-value-setq (hours minutes seconds
) (extract-groups-integers s
))
708 (setq s
(subseq s
(second (aref maxima-nregex
::*regex-groups
* 0)))))
709 (when (match-fraction-nnn s
)
710 (multiple-value-setq (seconds-fraction-numerator) (extract-groups-integers s
))
711 (let ((group1 (aref maxima-nregex
::*regex-groups
* 1)))
712 (setq seconds-fraction
(div seconds-fraction-numerator
(expt 10 (- (second group1
) (first group1
))))))
713 (setq s
(subseq s
(second (aref maxima-nregex
::*regex-groups
* 0)))))
716 (multiple-value-bind (tz-sign tz-hours tz-minutes
) (extract-groups-integers s
)
717 (setq tz
(* tz-sign
(+ tz-hours
(/ tz-minutes
60))))))
719 (multiple-value-bind (tz-sign tz-hours tz-minutes
) (extract-groups-integers s
)
720 (setq tz
(* tz-sign
(+ tz-hours
(/ tz-minutes
60))))))
722 (multiple-value-bind (tz-sign tz-hours
) (extract-groups-integers s
)
723 (setq tz
(* tz-sign tz-hours
))))
728 (return-from $parse_timedate nil
))))
730 (encode-time-with-all-parts year month day hours minutes seconds seconds-fraction
(if tz
(- tz
)))))
732 (defun extract-groups-integers (s)
733 (let ((groups (coerce (subseq maxima-nregex
::*regex-groups
* 1 maxima-nregex
::*regex-groupings
*) 'list
)))
734 (values-list (mapcar #'parse-integer-or-sign
735 (mapcar #'(lambda (ab) (subseq s
(first ab
) (second ab
)))
738 (defun parse-integer-or-sign (s)
742 (t (parse-integer s
))))
744 ; Clisp (2.49) / Windows does have a problem with dates before 1970-01-01,
745 ; therefore add 400 years in that case and subtract 12622780800
746 ; (= parse_timedate("2300-01-01Z") (Lisp starts with 1900-01-01) in timezone
748 ; see discussion on mailing list circa 2015-04-21: "parse_timedate error"
750 (if (and (string= (lisp-implementation-type) "CLISP") (string= *autoconf-windows
* "true"))
751 ; Clisp/Windows case:
752 (defun encode-time-with-all-parts (year month day hours minutes seconds-integer seconds-fraction tz
)
753 (add seconds-fraction
754 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
755 ;; so work around null TZ here.
759 (encode-universal-time seconds-integer minutes hours day month
(add year
400) tz
)
760 (encode-universal-time seconds-integer minutes hours day month
(add year
400)))))
761 (sub foo
12622780800))))
762 ; other Lisp / OS versions:
763 (defun encode-time-with-all-parts (year month day hours minutes seconds-integer seconds-fraction tz
)
764 (add seconds-fraction
765 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
766 ;; so work around null TZ here.
768 (encode-universal-time seconds-integer minutes hours day month year tz
)
769 (encode-universal-time seconds-integer minutes hours day month year
)))))
771 (defun $encode_time
(year month day hours minutes seconds
&optional tz-offset
)
773 (setq tz-offset
(sub 0 tz-offset
))
775 ((and (consp tz-offset
) (eq (caar tz-offset
) 'rat
))
776 (setq tz-offset
(/ (second tz-offset
) (third tz-offset
))))
778 (setq tz-offset
(rationalize tz-offset
))))
779 (setq tz-offset
(/ (round tz-offset
1/3600) 3600)))
781 ((seconds-integer (mfuncall '$floor seconds
))
782 (seconds-fraction (sub seconds seconds-integer
)))
783 (encode-time-with-all-parts year month day hours minutes seconds-integer seconds-fraction tz-offset
)))
785 (defun $decode_time
(seconds &optional tz
)
787 ((and (consp tz
) (eq (caar tz
) 'rat
))
788 (setq tz
(/ (second tz
) (third tz
))))
790 (setq tz
(rationalize tz
))))
791 (if tz
(setq tz
(/ (round tz
1/3600) 3600)))
793 ((seconds-integer (mfuncall '$floor seconds
))
794 (seconds-fraction (sub seconds seconds-integer
)))
796 (seconds minutes hours day month year day-of-week dst-p tz
)
797 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
798 ;; so work around null TZ here.
799 (if tz
(decode-universal-time seconds-integer
(- tz
))
800 (decode-universal-time seconds-integer
))
801 (declare (ignore day-of-week
#+gcl dst-p
))
802 ;; HMM, CAN DECODE-UNIVERSAL-TIME RETURN TZ = NIL ??
804 #-gcl
(if dst-p
(- 1 tz
) (- tz
))
805 #+gcl
(- tz
) ; bug in gcl https://savannah.gnu.org/bugs/?50570
807 (list '(mlist) year month day hours minutes
(add seconds seconds-fraction
) ($ratsimp tz-offset
))))))
809 ;;Some systems make everything functionp including macros:
812 (and (not (macro-function x
))
816 ;; These symbols are shadowed because we use them also as special
818 (deff break
#'cl
:break
)
821 #+(and sbcl sb-package-locks
)
822 (defun makunbound (sym)
823 (sb-ext:without-package-locks
824 (cl:makunbound sym
)))