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 (defun $-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 (defmfun $mkey
(variable)
222 "($mkey '$demo)==>:demo"
223 (intern (string-left-trim "$" (string variable
)) 'keyword
))
226 `(narg1 ,x narg-rest-argument
))
228 (defun narg1 (x l
&aux tem
)
229 (cond ((null x
) (length l
))
230 (t (setq tem
(nthcdr (1- x
) l
))
231 (cond ((null tem
) (error "arg ~A beyond range ~A " x
(length l
)))
234 (defmacro listify
(x)
235 `(listify1 ,x narg-rest-argument
))
237 (defmacro setarg
(i val
)
238 `(setarg1 ,i
,val narg-rest-argument
))
240 (defun setarg1 (i val l
)
241 (setf (nth (1- i
) l
) val
)
244 (defun listify1 (n narg-rest-argument
)
245 (cond ((minusp n
) (copy-list (last narg-rest-argument
(- n
))) )
247 (t (subseq narg-rest-argument
0 n
))))
249 ;; This has been replaced by src/defmfun-check.lisp. I'm leaving this
250 ;; here for now until we finish up fixing everything like using defun
251 ;; for internal functions and updating user-exposed functions to use
252 ;; defmfun instead of defun.
254 (defmacro defmfun
(function &body rest
&aux .n.
)
255 (cond ((and (car rest
) (symbolp (car rest
)))
256 ;;old maclisp narg syntax
257 (setq .n.
(car rest
))
259 `(&rest narg-rest-argument
&aux
(, .n.
(length narg-rest-argument
))))))
261 ;; I (rtoy) think we can consider all defmfun's as translated functions.
262 (defprop ,function t translated
)
263 (defun ,function .
,rest
)))
266 ;;(defun foo a (show a )(show (listify a)) (show (arg 3)))
268 (defmacro defun-maclisp
(function &body body
&aux .n.
)
269 (when (typep body
'(cons symbol
))
270 ;;old maclisp narg syntax
271 (setq .n.
(car body
))
273 (cons `(&rest narg-rest-argument
&aux
(, .n.
(length narg-rest-argument
)))
276 ;; I (rtoy) think we can consider all defmfun's as translated functions.
277 (defprop ,function t translated
)
278 (defun ,function .
,body
)))
280 (defun exploden (symb)
282 (cond ((symbolp symb
)
283 (setq string
(print-invert-case symb
)))
285 (setq string
(exploden-format-float symb
)))
287 ;; When obase > 10, prepend leading zero to
288 ;; ensure that output is readable as a number.
289 (let ((leading-digit (if (> *print-base
* 10) #\
0)))
290 (setq string
(format nil
"~A" symb
))
291 (setq string
(coerce string
'list
))
292 (if (and leading-digit
(not (digit-char-p (car string
) 10.
)))
293 (setq string
(cons leading-digit string
)))
294 (return-from exploden string
)))
295 (t (setq string
(format nil
"~A" symb
))))
296 (assert (stringp string
))
297 (coerce string
'list
)))
299 (defvar *exploden-strip-float-zeros
* t
) ;; NIL => allow trailing zeros
301 (defun exploden-format-float (symb)
302 (if (or (= $fpprintprec
0) (> $fpprintprec
16.
))
303 (exploden-format-float-readably-except-special-values symb
)
304 (exploden-format-float-pretty symb
)))
306 ;; Return a readable string, EXCEPT for not-a-number and infinity, if present;
307 ;; for those, return a probably-nonreadable string.
308 ;; This avoids an error from SBCL about trying to readably print those values.
310 (defun exploden-format-float-readably-except-special-values (x)
311 (if (or (float-inf-p x
) (float-nan-p x
))
313 (let ((*print-readably
* t
))
314 (let ((s (prin1-to-string x
)))
315 ;; Skip the fix up unless we know it's needed for the Lisp implementation.
316 #+(or clisp abcl
) (fix-up-exponent-in-place s
)
317 #+ecl
(insert-zero-before-exponent s
)
318 #-
(or clisp abcl ecl
) s
))))
320 ;; (1) If string looks like "n.nnnD0" or "n.nnnd0", return just "n.nnn".
321 ;; (2) Otherwise, replace #\D or #\d (if present) with #\E or #\e, respectively.
322 ;; (3) Otherwise, return S unchanged.
324 (defun fix-up-exponent-in-place (s)
325 (let ((n (length s
)) i
)
328 ((and (or (eql (aref s
(- n
2)) #\D
) (eql (aref s
(- n
2)) #\d
)) (eql (aref s
(- n
1)) #\
0))
329 (subseq s
0 (- n
2)))
330 ((setq i
(position #\D s
))
331 (setf (aref s i
) #\E
)
333 ((setq i
(position #\d s
))
334 (setf (aref s i
) #\e
)
339 ;; Replace "nnnn.Ennn" or "nnn.ennn" with "nnn.0Ennn" or nnn.0ennn", respectively.
340 ;; (Decimal immediately before exponent without intervening digits is
341 ;; explicitly allowed by CLHS; see Section 2.3.1, "Numbers as Tokens".)
343 (defun insert-zero-before-exponent (s)
344 (let ((n (length s
)) (i (position #\. s
)))
345 (if (and i
(< i
(1- n
)))
346 (let ((c (aref s
(1+ i
))))
347 (if (or (eql c
#\E
) (eql c
#\e
))
348 (concatenate 'string
(subseq s
0 (1+ i
)) "0" (subseq s
(1+ i
) n
))
352 (defun exploden-format-float-pretty (symb)
353 (let ((a (abs symb
)) string
)
354 ;; When printing out something for Fortran, we want to be
355 ;; sure to print the exponent marker so that Fortran
356 ;; knows what kind of number it is. It turns out that
357 ;; Fortran's exponent markers are the same as Lisp's so
358 ;; we just need to make sure the exponent marker is
362 ;; Strings for non-finite numbers as specified for input in Fortran 2003 spec;
363 ;; they apparently did not exist in earlier versions.
364 ((float-nan-p symb
) "NAN")
365 ((float-inf-p symb
) (if (< symb
0) "-INF" "INF"))
366 (t (format nil
"~e" symb
))))
367 (multiple-value-bind (form digits
)
373 ((integer-log10 (floor (/ (log a
) #.
(log 10.0))))
374 (scale (1+ integer-log10
)))
375 (if (< scale $fpprintprec
)
376 (values "~,vf" (- $fpprintprec scale
))
377 (values "~,ve" (1- $fpprintprec
)))))
378 ((or (float-inf-p symb
) (float-nan-p symb
))
379 (return-from exploden-format-float-pretty
(format nil
"~a" symb
)))
381 (values "~,ve" (1- $fpprintprec
))))
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
))
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
))))))
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
"~s" 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 (let ((ch (read-char-no-hang stream nil eof-option
)))
578 (when (and *prompt-on-read-hang
* *read-hang-prompt
*)
579 (princ *read-hang-prompt
*)
580 (finish-output *standard-output
*))
581 (read-char stream nil eof-option
)))))
583 (defun tyi (&optional
(stream *standard-input
*) eof-option
)
584 (let ((ch (tyi-raw stream eof-option
)))
585 (if (eql ch eof-option
)
587 (backslash-check ch stream eof-option
))))
589 ; The sequences of characters
590 ; <anything-except-backslash>
591 ; (<backslash> <newline> | <backslash> <return> | <backslash> <return> <newline>)+
593 ; are reduced to <anything-except-backslash> <anything> .
594 ; Note that this has no effect on <backslash> <anything-but-newline-or-return> .
596 (let ((previous-tyi #\a))
597 (defun backslash-check (ch stream eof-option
)
598 (if (eql previous-tyi
#\\ )
599 (progn (setq previous-tyi
#\a) ch
)
602 (let ((next-char (peek-char nil stream nil eof-option
)))
603 (if (or (eql next-char
#\newline
) (eql next-char
#\return
))
604 (eat-continuations ch stream eof-option
)
607 ; We have just read <backslash> and we know the next character is <newline> or <return>.
608 ; Eat line continuations until we come to something which doesn't match, or we reach eof.
609 (defun eat-continuations (ch stream eof-option
)
610 (setq ch
(tyi-raw stream eof-option
))
611 (do () ((not (or (eql ch
#\newline
) (eql ch
#\return
))))
612 (let ((next-char (peek-char nil stream nil eof-option
)))
613 (if (and (eql ch
#\return
) (eql next-char
#\newline
))
614 (tyi-raw stream eof-option
)))
615 (setq ch
(tyi-raw stream eof-option
))
616 (let ((next-char (peek-char nil stream nil eof-option
)))
617 (if (and (eql ch
#\\ ) (or (eql next-char
#\return
) (eql next-char
#\newline
)))
618 (setq ch
(tyi-raw stream eof-option
))
619 (return-from eat-continuations ch
))))
622 (defmfun $timedate
(&optional
(time (get-universal-time)) tz
)
624 ((and (consp tz
) (eq (caar tz
) 'rat
))
625 (setq tz
(/ (second tz
) (third tz
))))
627 (setq tz
(rationalize tz
))))
628 (if tz
(setq tz
(/ (round tz
1/60) 60)))
630 ((time-integer (mfuncall '$floor time
))
631 (time-fraction (sub time time-integer
))
632 (time-millis (mfuncall '$round
(mul 1000 time-fraction
))))
633 (when (= time-millis
1000)
634 (setq time-integer
(1+ time-integer
))
635 (setq time-millis
0))
637 (second minute hour date month year day-of-week dst-p tz
)
638 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
639 ;; so work around null TZ here.
640 (if tz
(decode-universal-time time-integer
(- tz
))
641 (decode-universal-time time-integer
))
642 (declare (ignore day-of-week
))
643 ;; DECODE-UNIVERSAL-TIME might return a timezone offset
644 ;; which is a multiple of 1/3600 but not 1/60.
645 ;; We need a multiple of 1/60 because our formatted
646 ;; timezone offset has only minutes and seconds.
647 (if (/= (mod tz
1/60) 0)
648 ($timedate time-integer
(/ (round (- tz
) 1/60) 60))
649 (let ((tz-offset (if dst-p
(- 1 tz
) (- tz
))))
651 (tz-hours tz-hour-fraction
)
654 ((tz-sign (if (<= 0 tz-offset
) #\
+ #\-
)))
655 (if (= time-millis
0)
656 (format nil
"~4,'0d-~2,'0d-~2,'0d ~2,'0d:~2,'0d:~2,'0d~a~2,'0d:~2,'0d"
657 year month date hour minute second tz-sign
(abs tz-hours
) (floor (* 60 (abs tz-hour-fraction
))))
658 (format nil
"~4,'0d-~2,'0d-~2,'0d ~2,'0d:~2,'0d:~2,'0d.~3,'0d~a~2,'0d:~2,'0d"
659 year month date hour minute second time-millis tz-sign
(abs tz-hours
) (floor (* 60 (abs tz-hour-fraction
))))))))))))
661 ;; Parse date/time strings in these formats (and only these):
663 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?([+-]hh:mm)?
664 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?([+-]hhmm)?
665 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?([+-]hh)?
666 ;; YYYY-MM-DD([ T]hh:mm:ss)?([,.]n+)?[Z]?
668 ;; where (...)? indicates an optional group (occurs zero or one times)
669 ;; ...+ indicates one or more instances of ...,
670 ;; and [...] indicates literal character alternatives.
672 ;; Trailing unparsed stuff causes the parser to fail (return NIL).
674 ;; Originally, these functions all looked like
676 ;; (defun match-date-yyyy-mm-dd (s)
677 ;; (pregexp:pregexp-match-positions
678 ;; '#.(pregexp:pregexp "^([0-9][0-9][0-9][0-9])-([0-9][0-9])-([0-9][0-9])")
681 ;; However, sbcl produces incorrect results for this. For example,
683 ;; (match-date-yyyy-mm-dd "1900-01-01 16:00:00-08:00")
685 ;; returns ((0 . 10) (0 . 4) (8 . 10) NIL). But the correct answer is
686 ;; ((0 . 10) (0 . 4) (5 . 7) (8 . 10)).
688 ;; But if you replace the '#.(pregexp:pregexp ...) with
689 ;; (pregexp:pregexp ...), sbcl works. But then we end up compiling
690 ;; the the regexp on every call. So we use a closure so the regexp is
691 ;; compiled only once.
692 (let ((pat (pregexp:pregexp
"^([0-9][0-9][0-9][0-9])-([0-9][0-9])-([0-9][0-9])")))
693 (defun match-date-yyyy-mm-dd (s)
694 (pregexp:pregexp-match-positions
698 (let ((pat (pregexp:pregexp
"^[ T]([0-9][0-9]):([0-9][0-9]):([0-9][0-9])")))
699 (defun match-time-hh-mm-ss (s)
700 (pregexp:pregexp-match-positions
704 (let ((pat (pregexp:pregexp
"^[,.]([0-9][0-9]*)")))
705 (defun match-fraction-nnn (s)
706 (pregexp:pregexp-match-positions
711 (let ((pat (pregexp:pregexp
"^([+-])([0-9][0-9]):([0-9][0-9])$")))
712 (defun match-tz-hh-mm (s)
713 (pregexp:pregexp-match-positions
717 (let ((pat (pregexp:pregexp
"^([+-])([0-9][0-9])([0-9][0-9])$")))
718 (defun match-tz-hhmm (s)
719 (pregexp:pregexp-match-positions
723 (let ((pat (pregexp:pregexp
"^([+-])([0-9][0-9])$")))
724 (defun match-tz-hh (s)
725 (pregexp:pregexp-match-positions
729 (let ((pat (pregexp:pregexp
"^Z$")))
730 (defun match-tz-Z (s)
731 (pregexp:pregexp-match-positions
735 (defmfun $parse_timedate
(s)
736 (setq s
(string-trim '(#\Space
#\Tab
#\Newline
#\Return
) s
))
739 (hours 0) (minutes 0) (seconds 0)
740 (seconds-fraction 0) seconds-fraction-numerator tz
)
741 (if (setq matches
(match-date-yyyy-mm-dd s
))
743 (multiple-value-setq (year month day
)
744 (pregexp-extract-groups-integers matches s
))
745 (setq s
(subseq s
(cdr (elt matches
0)))))
746 (return-from $parse_timedate nil
))
747 (when (setq matches
(match-time-hh-mm-ss s
))
748 (multiple-value-setq (hours minutes seconds
)
749 (pregexp-extract-groups-integers matches s
))
750 (setq s
(subseq s
(cdr (elt matches
0)))))
751 (when (setq matches
(match-fraction-nnn s
))
752 (multiple-value-setq (seconds-fraction-numerator)
753 (pregexp-extract-groups-integers matches s
))
754 (let ((group1 (elt matches
1)))
755 (setq seconds-fraction
(div seconds-fraction-numerator
(expt 10 (- (cdr group1
) (car group1
))))))
756 (setq s
(subseq s
(cdr (elt matches
0)))))
758 ((setq matches
(match-tz-hh-mm s
))
759 (multiple-value-bind (tz-sign tz-hours tz-minutes
)
760 (pregexp-extract-groups-integers matches s
)
761 (setq tz
(* tz-sign
(+ tz-hours
(/ tz-minutes
60))))))
762 ((setq matches
(match-tz-hhmm s
))
763 (multiple-value-bind (tz-sign tz-hours tz-minutes
)
764 (pregexp-extract-groups-integers matches s
)
765 (setq tz
(* tz-sign
(+ tz-hours
(/ tz-minutes
60))))))
766 ((setq matches
(match-tz-hh s
))
767 (multiple-value-bind (tz-sign tz-hours
)
768 (pregexp-extract-groups-integers matches s
)
769 (setq tz
(* tz-sign tz-hours
))))
770 ((setq matches
(match-tz-Z s
))
774 (return-from $parse_timedate nil
))))
776 (encode-time-with-all-parts year month day hours minutes seconds seconds-fraction
(if tz
(- tz
)))))
778 (defun pregexp-extract-groups-integers (matches s
)
779 (values-list (mapcar #'parse-integer-or-sign
780 (mapcar #'(lambda (ab)
781 (subseq s
(car ab
) (cdr ab
)))
784 (defun parse-integer-or-sign (s)
788 (t (parse-integer s
))))
790 ; Clisp (2.49) / Windows does have a problem with dates before 1970-01-01,
791 ; therefore add 400 years in that case and subtract 12622780800
792 ; (= parse_timedate("2300-01-01Z") (Lisp starts with 1900-01-01) in timezone
794 ; see discussion on mailing list circa 2015-04-21: "parse_timedate error"
796 ; Nota bene that this approach is correct only if the daylight saving time flag
797 ; is the same for the given date and date + 400 years. That is true for
798 ; dates before 1970-01-01 and after 2038-01-18, for Clisp at least,
799 ; which ignores daylight saving time for all dates in those ranges,
800 ; effectively making them all standard time.
803 (defun encode-time-with-all-parts (year month day hours minutes seconds-integer seconds-fraction tz
)
804 ;; Experimenting with Clisp 2.49 for Windows seems to show that the bug
805 ;; is triggered when local time zone is east of UTC, for times before
806 ;; 1970-01-01 00:00:00 UTC + the number of hours of the time zone.
807 ;; So apply the bug workaround to all times < 1970-01-02.
808 (if (or (< year
1970) (and (= year
1970) (= day
1)))
809 (sub (encode-time-with-all-parts (add year
400) month day hours minutes seconds-integer seconds-fraction tz
) 12622780800)
810 (add seconds-fraction
811 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
812 ;; so work around null TZ here.
814 (encode-universal-time seconds-integer minutes hours day month year tz
)
815 (encode-universal-time seconds-integer minutes hours day month year
)))))
818 (defun encode-time-with-all-parts (year month day hours minutes seconds-integer seconds-fraction tz
)
819 (add seconds-fraction
820 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
821 ;; so work around null TZ here.
823 (encode-universal-time seconds-integer minutes hours day month year tz
)
824 (encode-universal-time seconds-integer minutes hours day month year
))))
826 (defmfun $encode_time
(year month day hours minutes seconds
&optional tz-offset
)
828 (setq tz-offset
(sub 0 tz-offset
))
830 ((and (consp tz-offset
) (eq (caar tz-offset
) 'rat
))
831 (setq tz-offset
(/ (second tz-offset
) (third tz-offset
))))
833 (setq tz-offset
(rationalize tz-offset
))))
834 (setq tz-offset
(/ (round tz-offset
1/3600) 3600)))
836 ((seconds-integer (mfuncall '$floor seconds
))
837 (seconds-fraction (sub seconds seconds-integer
)))
838 (encode-time-with-all-parts year month day hours minutes seconds-integer seconds-fraction tz-offset
)))
840 (defmfun $decode_time
(seconds &optional tz
)
842 ((and (consp tz
) (eq (caar tz
) 'rat
))
843 (setq tz
(/ (second tz
) (third tz
))))
845 (setq tz
(rationalize tz
))))
846 (if tz
(setq tz
(/ (round tz
1/3600) 3600)))
848 ((seconds-integer (mfuncall '$floor seconds
))
849 (seconds-fraction (sub seconds seconds-integer
)))
851 (seconds minutes hours day month year day-of-week dst-p tz
)
852 ;; Some Lisps allow TZ to be null but CLHS doesn't explicitly allow it,
853 ;; so work around null TZ here.
854 (if tz
(decode-universal-time seconds-integer
(- tz
))
855 (decode-universal-time seconds-integer
))
856 (declare (ignore day-of-week
))
857 ;; HMM, CAN DECODE-UNIVERSAL-TIME RETURN TZ = NIL ??
858 (let ((tz-offset (if dst-p
(- 1 tz
) (- tz
))))
859 (list '(mlist) year month day hours minutes
(add seconds seconds-fraction
) ($ratsimp tz-offset
))))))
861 ;;Some systems make everything functionp including macros:
864 (and (not (macro-function x
))
868 ;; These symbols are shadowed because we use them also as special
870 (deff break
#'cl
:break
)