1 ;; Maxima functions for floor, ceiling, and friends
2 ;; Copyright (C) 2004, 2005, 2007 Barton Willis
5 ;; Department of Mathematics
6 ;; University of Nebraska at Kearney
10 ;; This source code is licensed under the terms of the Lisp Lesser
11 ;; GNU Public License (LLGPL). The LLGPL consists of a preamble, published
12 ;; by Franz Inc. (http://opensource.franz.com/preamble.html), and the GNU
13 ;; Library General Public License (LGPL), version 2, or (at your option)
14 ;; any later version. When the preamble conflicts with the LGPL,
15 ;; the preamble takes precedence.
17 ;; This library is distributed in the hope that it will be useful,
18 ;; but WITHOUT ANY WARRANTY; without even the implied warranty of
19 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
20 ;; Library General Public License for details.
22 ;; You should have received a copy of the GNU Library General Public
23 ;; License along with this library; if not, write to the
24 ;; Free Software Foundation, Inc., 51 Franklin St, Fifth Floor,
25 ;; Boston, MA 02110-1301, USA.
29 (macsyma-module nummod
)
31 ;; Let's have version numbers 1,2,3,...
33 (eval-when (:load-toplevel
:execute
)
34 ($put
'$nummod
3 '$version
)
35 ;; Let's remove built-in symbols from list for user-defined properties.
36 (setq $props
(remove '$nummod $props
)))
38 ;; Ideally this should be removed in favor of ftake* (in mopers.lisp),
39 ;; which is identical to what opcons used to do. But some share files
40 ;; use this, we need to keep this until those are fixed.
41 (defmacro opcons
(op &rest args
)
44 ;; charfun(pred) evaluates to 1 when the predicate 'pred' evaluates
45 ;; to true; it evaluates to 0 when 'pred' evaluates to false; otherwise,
46 ;; it evaluates to a noun form.
48 (defprop $charfun simp-charfun operators
)
49 (defprop %charfun simp-charfun operators
)
51 (defun simp-charfun (e yy z
)
54 (setq e
(take '($is
) (simplifya (specrepcheck (second e
)) z
)))
55 (let* (($prederror nil
)
59 ((op-equalp e
'$is
) `(($charfun simp
) ,(second e
)))
60 (t `(($charfun simp
) ,e
)))))
62 (defun integer-part-of-sum (e)
63 (let ((i-sum 0) (n-sum 0) (o-sum 0) (n))
66 (cond ((maxima-integerp ei
)
67 (setq i-sum
(add ei i-sum
)))
68 ((or (ratnump ei
) (floatp ei
) ($bfloatp ei
))
69 (setq n-sum
(add ei n-sum
)))
71 (setq o-sum
(add ei o-sum
)))))
72 (setq n
(ftake* '$floor n-sum
))
73 (setq i-sum
(add i-sum n
))
74 (setq o-sum
(add o-sum
(sub n-sum n
)))
75 (values i-sum o-sum
)))
77 (defprop $floor simp-floor operators
)
79 (defprop $floor tex-matchfix tex
)
80 (defprop $floor
(("\\left \\lfloor " ) " \\right \\rfloor") texsym
)
82 ;; $floor distributes over lists, matrices, and equations
83 (setf (get '$floor
'distribute_over
) '(mlist $matrix mequal
))
85 ; These defprops for $entier are copied from orthopoly/orthopoly-init.lisp.
87 (defprop $entier tex-matchfix tex
)
88 (defprop $entier
(("\\lfloor ") " \\rfloor") texsym
)
90 ;; $entier and $fix distributes over lists, matrices, and equations
91 (setf (get '$entier
'distribute_over
) '(mlist $matrix mequal
))
92 (setf (get '$fix
'distribute_over
) '(mlist $matrix mequal
))
94 ;; For an example, see pretty-good-floor-or-ceiling. Code courtesy of Stavros Macrakis.
96 (defmacro bind-fpprec
(val &body exprs
)
97 `(let (fpprec bigfloatzero bigfloatone bfhalf bfmhalf
)
98 (let (($fpprec
(fpprec1 nil
,val
)))
101 ;; Return true if the expression can be formed using rational numbers, logs, mplus, mexpt, or mtimes.
103 (defun use-radcan-p (e)
104 (or ($ratnump e
) (and (op-equalp e
'%log
'mexpt
'mplus
'mtimes
) (every 'use-radcan-p
(cdr e
)))))
106 ;; When constantp(x) is true, we use bfloat evaluation to try to determine
107 ;; the ceiling or floor. If numerical evaluation of e is ill-conditioned, this function
108 ;; can misbehave. I'm somewhat uncomfortable with this, but it is no worse
109 ;; than some other stuff. One safeguard -- the evaluation is done with three
110 ;; values for fpprec. When the floating point evaluations are
111 ;; inconsistent, bailout and return nil. I hope that this function is
112 ;; much more likely to return nil than it is to return a bogus value.
114 (defun pretty-good-floor-or-ceiling (x fn
&optional digits
)
115 (let (($float2bf t
) ($algebraic t
) (f1) (f2) (f3) (eps) (lb) (ub) (n))
117 (setq digits
(if (and (integerp digits
) (> 0 digits
)) digits
25))
120 ;; To handle ceiling(%i^%i), we need to apply rectform. If bfloat
121 ;; is improved, it might be possible to remove this call to rectform.
123 (setq x
($rectform x
))
124 (if (not ($freeof
'$%i
'$minf
'$inf
'$und
'$infinity x
)) (throw 'done nil
))
126 ;; When x doesn't evaluate to a bigfloat, bailout and return nil.
127 ;; This happens when, for example, x = asin(2). For now, bfloatp
128 ;; evaluates to nil for a complex big float. If this ever changes,
129 ;; this code might need to be repaired.
132 (setq f1
($bfloat x
))
133 (if (not ($bfloatp f1
)) (throw 'done nil
)))
136 (setq f2
(bind-fpprec digits
($bfloat x
)))
137 (if (not ($bfloatp f2
)) (throw 'done nil
))
141 (setq f3
($bfloat x
))
142 (if (not ($bfloatp f3
)) (throw 'done nil
))
144 ;; Let's say that the true value of x is in the interval
145 ;; [f3 - |f3| * eps, f3 + |f3| * eps], where eps = 10^(20 - digits).
146 ;; Define n to be the number of integers in this interval; we have
148 (setq eps
(power ($bfloat
10) (- 20 digits
)))
149 (setq lb
(sub f3
(mult (take '(mabs) f3
) eps
)))
150 (setq ub
(add f3
(mult (take '(mabs) f3
) eps
)))
152 ;; If n > 1, we're going to give up. This is true iff ceiling(ub) -
153 ;; ceiling(lb) > 1. However, we don't want to blindly try to calculate
154 ;; that: if ub and lb are enormous, we probably won't have enough
155 ;; precision in the bigfloats to calculate either ceiling. Start by
156 ;; taking the difference: if it's at least 2, then we know that n >= 2.
157 (when (fpgreaterp (cdr (sub ub lb
)) (cdr ($bfloat
2)))
160 (setq n
(sub (take '($ceiling
) ub
)
161 (take '($ceiling
) lb
))))
163 (setq f1
(take (list fn
) f1
))
164 (setq f2
(take (list fn
) f2
))
165 (setq f3
(take (list fn
) f3
))
167 ;; Provided f1 = f2 = f3 and n = 0, return f1.
168 ;; If n = 1 and (use-radcan-p e) and ($radcan e) is a $ratnump, return
169 ;; floor / ceiling of radcan(x).
171 (cond ((and (= f1 f2 f3
) (= n
0)) f1
)
172 ((and (= f1 f2 f3
) (= n
1) (use-radcan-p x
))
174 (if ($ratnump x
) (take (list fn
) x
) nil
))
178 ;; (a) The function fpentier rounds a bigfloat towards zero--we need to
181 ;; (b) Since limit(f(x))=(m)inf implies limit(floor(f(x)))=(m)inf,
182 ;; floor(inf/minf) = inf/minf. Since minf<limit(f(x))<inf implies
183 ;; minf<limit(floor(f(x)))<inf, floor(ind)=ind
185 ;; I think floor(complex number) should be undefined too. Some folks
186 ;; might like floor(a + %i b) --> floor(a) + %i floor(b). But
187 ;; this would violate the integer-valuedness of floor.
188 ;; So floor(infinity) remains unsimplified
190 (defun simp-floor (e e1 z
)
192 (setq e
(simplifya (specrepcheck (nth 1 e
)) z
))
194 (cond ((numberp e
) (floor e
))
196 ((ratnump e
) (floor (cadr e
) (caddr e
)))
199 (setq e1
(fpentier e
))
200 (if (and (minusp (cadr e
)) (not (zerop1 (sub e1 e
))))
204 ((maxima-integerp e
) e
)
206 (($orderlessp e
(neg e
))
207 (sub 0 (ftake* '$ceiling
(neg e
))))
209 ((and (setq e1
(mget e
'$numer
)) (floor e1
)))
211 ((member e
'($inf $minf $ind $und
)) e
)
212 ;; leave floor(infinity) as is
213 ((or (eq e
'$zerob
)) -
1)
214 ((or (eq e
'$zeroa
)) 0)
216 ((and ($constantp e
) (pretty-good-floor-or-ceiling e
'$floor
)))
219 (let ((i-sum) (o-sum))
220 (multiple-value-setq (i-sum o-sum
) (integer-part-of-sum e
))
221 (setq o-sum
(if (equal i-sum
0) `(($floor simp
) ,o-sum
)
222 (ftake* '$floor o-sum
)))
225 ;; handle 0 <= e < 1 implies floor(e) = 0 and
226 ;; -1 <= e < 0 implies floor(e) = -1.
228 ((and (member ($compare
0 e
) '("<" "<=") :test
#'equal
)
229 (equal ($compare e
1) "<"))
231 ((and (member ($compare -
1 e
) '("<" "<=") :test
#'equal
)
232 (equal ($compare e
0) "<"))
234 (t `(($floor simp
) ,e
))))
236 (defun floor-integral (x)
237 (let ((f (take '($floor
) x
)))
238 (mul f
(div 1 2) (add (mul 2 x
) -
1 (neg f
)))))
240 (defun ceiling-integral (x)
241 (let ((f (take '($ceiling
) x
)))
242 (mul f
(div 1 2) (add 1 (mul 2 x
) (neg f
)))))
244 (putprop '$floor
`((x) ,'floor-integral
) 'integral
)
245 (putprop '$ceiling
`((x) ,'ceiling-integral
) 'integral
)
247 (defprop $ceiling simp-ceiling operators
)
249 (defprop $floor simplim%floor simplim%function
)
251 (defun simplim%floor
(expr var val
)
252 (let* ((arg (cadr expr
))
253 (b (behavior arg var val
))
254 (arglimab (limit arg var val
'think
)) ; with $zeroa $zerob
255 (arglim (ridofab arglimab
)))
257 (maxima-integerp arglim
))
260 (maxima-integerp arglim
))
262 ((and ($constantp arglim
)
263 (not (maxima-integerp arglim
)))
264 (simplify (list '($floor
) arglim
)))
266 (throw 'limit nil
)))))
268 (defprop $ceiling tex-matchfix tex
)
269 (defprop $ceiling
(("\\left \\lceil " ) " \\right \\rceil") texsym
)
271 ;; $ceiling distributes over lists, matrices, and equations.
272 (setf (get '$ceiling
'distribute_over
) '(mlist $matrix mequal
))
274 (defun simp-ceiling (e e1 z
)
276 (setq e
(simplifya (specrepcheck (nth 1 e
)) z
))
277 (cond ((numberp e
) (ceiling e
))
279 ((ratnump e
) (ceiling (cadr e
) (caddr e
)))
282 (sub 0 (ftake* '$floor
(sub 0 e
))))
284 ((maxima-integerp e
) e
)
286 (($orderlessp e
(neg e
))
287 (sub* 0 (ftake* '$floor
(neg e
))))
289 ((and (setq e1
(mget e
'$numer
)) (ceiling e1
)))
291 ((member e
'($inf $minf $ind $und
)) e
)
292 ;; leave ceiling(infinity) as is
293 ((or (eq e
'$zerob
)) 0)
294 ((or (eq e
'$zeroa
)) 1)
296 ((and ($constantp e
) (pretty-good-floor-or-ceiling e
'$ceiling
)))
299 (let ((i-sum) (o-sum))
300 (multiple-value-setq (i-sum o-sum
) (integer-part-of-sum e
))
301 (setq o-sum
(if (equal i-sum
0) `(($ceiling simp
) ,o-sum
)
302 (ftake* '$ceiling o-sum
)))
305 ;; handle 0 < e <= 1 implies ceiling(e) = 1 and
306 ;; -1 < e <= 0 implies ceiling(e) = 0.
308 ((and (equal ($compare
0 e
) "<")
309 (member ($compare e
1) '("<" "<=") :test
#'equal
))
311 ((and (equal ($compare -
1 e
) "<")
312 (member ($compare e
0) '("<" "<=") :test
#'equal
))
314 (t `(($ceiling simp
) ,e
))))
316 (defprop $ceiling simplim%ceiling simplim%function
)
318 (defun simplim%ceiling
(expr var val
)
319 (let* ((arg (cadr expr
))
320 (b (behavior arg var val
))
321 (arglimab (limit arg var val
'think
)) ; with $zeroa $zerob
322 (arglim (ridofab arglimab
)))
324 (maxima-integerp arglim
))
327 (maxima-integerp arglim
))
329 ((and ($constantp arglim
)
330 (not (maxima-integerp arglim
)))
331 (simplify (list '($ceiling
) arglim
)))
333 (throw 'limit nil
)))))
336 (defprop $mod simp-nummod operators
)
337 (defprop $mod tex-infix tex
)
338 (defprop $mod
(" \\rm{mod} ") texsym
)
339 (defprop $mod
180. tex-lbp
)
340 (defprop $mod
180. tex-rbp
)
342 ;; $mod distributes over lists, matrices, and equations
343 (setf (get '$mod
'distribute_over
) '(mlist $matrix mequal
))
345 ;; See "Concrete Mathematics," Section 3.21.
347 (defun simp-nummod (e e1 z
)
349 (let ((x (simplifya (specrepcheck (cadr e
)) z
))
350 (y (simplifya (specrepcheck (caddr e
)) z
)))
351 (cond ((or (equal 0 y
) (equal 0 x
)) x
)
352 ((equal 1 y
) (sub x
(ftake* '$floor x
)))
353 ((and ($constantp x
) ($constantp y
))
354 (sub x
(mul y
(ftake* '$floor
(div x y
)))))
355 ((not (equal 1 (setq e1
($gcd x y
))))
356 (mul e1
(ftake* '$mod
(div x e1
) (div y e1
))))
357 (t `(($mod simp
) ,x
,y
)))))
359 ;; The function 'round' rounds a number to the nearest integer. For a tie, round to the
360 ;; nearest even integer.
362 ;; This property is important to get round(round(x)) => round(x).
363 (setf (get '%round
'integer-valued
) t
)
364 (setf (get '%round
'reflection-rule
) 'odd-function-reflect
)
365 ;; round distributes over lists, matrices, and equations.
366 (setf (get '%round
'distribute_over
) '(mlist $matrix mequal
))
368 (def-simplifier round
(e)
369 (cond (($featurep e
'$integer
)
370 ;; takes care of round(round(x)) --> round(x).
372 ((member e
'($inf $minf $und $ind
) :test
#'eq
)
379 (let* ((lb (take '($floor
) e
))
380 (ub (take '($ceiling
) e
))
381 (sgn (csign (sub (sub ub e
) (sub e lb
)))))
389 ;; For floats that are integers, this can
390 ;; happen. Maybe featurep should catch this.
392 ((and (eq sgn
'$zero
)
393 ($featurep lb
'$even
))
395 ((and (eq sgn
'$zero
)
396 ($featurep ub
'$even
))
398 ((apply-reflection-simp (mop form
) e t
))
401 (defprop %round simplim%round simplim%function
)
403 (defun simplim%round
(expr var val
)
404 (let* ((arg (cadr expr
))
405 (b (behavior arg var val
))
406 (arglimab (limit arg var val
'think
)) ; with $zeroa $zerob
407 (arglim (ridofab arglimab
)))
409 (maxima-integerp (m+ 1//2 arglim
)))
412 (maxima-integerp (m+ 1//2 arglim
)))
414 ((and ($constantp arglim
)
415 (not (maxima-integerp (m+ 1//2 arglim
))))
416 (simplify (list '(%round
) arglim
)))
418 (throw 'limit nil
)))))
420 ;; Round a number towards zero.
423 ;; This property is important to get truncate(truncate(x)) =>
425 (setf (get '%truncate
'integer-valued
) t
)
426 (setf (get '%truncate
'reflection-rule
) 'odd-function-reflect
)
428 ;; truncate distributes over lists, matrices, and equations.
429 (setf (get '%truncate
'distribute_over
) '(mlist $matrix mequal
))
431 (def-simplifier truncate
(e)
432 (cond (($featurep e
'$integer
)
433 ;; takes care of truncate(truncate(x)) --> truncate(x).
435 ((member e
'($inf $minf $und $ind
) :test
#'eq
)
442 (let ((sgn (csign e
)))
443 (cond ((member sgn
'($neg $nz
) :test
#'eq
)
444 (take '($ceiling
) e
))
445 ((member sgn
'($zero $pz $pos
) :test
#'eq
)
447 ((apply-reflection-simp (mop form
) e t
))
450 ;;; integration for signum, unit_step, and mod.
452 ;; integrate(signum(x),x) = |x|
453 (defun signum-integral (x)
456 ;; integrate(unit_step(x),x) = (x + |x|)/2
457 (defun unit-step-integral (x)
458 (div (add x
(take '(mabs) x
)) 2))
460 ;; We have mod(x,a) = x-a*floor(x/a). This gives
461 ;; integrate(mod(x,a),x) = (a^2 floor(x/a)^2 + (a^2 - 2 a x) floor(x/a) + x^2)/2
462 ;; In terms of mod(x,a), an antiderivative is
463 ;; integrate(mod(x,a),x) = (mod(x,a)^2-a*mod(x,a)+a*x)/2
464 ;; Before this function is called, Maxima checks if a explicitly depends on x. So
465 ;; this function doesn't need to do that check.
466 (defun mod-integral (x a
)
467 (let ((q (take '($mod
) x a
)))
468 (div (add (mul q q
) (mul -
1 a q
) (mul a x
)) 2)))
470 (putprop '%signum
(list (list 'x
) 'signum-integral
) 'integral
)
471 (putprop '$unit_step
(list (list 'x
) 'unit-step-integral
) 'integral
)
473 ;; integrate(mod(x,a),a) doesn't have representation in terms of functions
474 ;; known to Maxima, I think. (Barton Willis, 2020).
475 (putprop '$mod
(list (list 'x
'y
) 'mod-integral nil
) 'integral
)