Fixes for errors Pierpaolo Bernardi found by reviewing the docs; also,
renamed `partition-count' to `partitions' to be consistent with `permutations', and gave better examples in `multinomial' docs * (flulp-error +inf.0 +nan.0) was returning +nan.0 instead of +inf.0 * Type of `multinomial' didn't match its docs or `flmultinomial' * Reworded docs for `diagonal-array' * Reworked/reordered quite a few things in docs for `math/bigfloat' * Fixed first identity given in `gamma-inc' docs * Fixed descrption for `+max.0', etc.
This commit is contained in:
parent
130c989888
commit
60dd8d065f
|
@ -83,17 +83,14 @@
|
|||
|
||||
(: flulp-error (Flonum Real -> Flonum))
|
||||
(define (flulp-error x r)
|
||||
(cond [(eqv? r +nan.0) (if (eqv? x +nan.0) 0.0 +nan.0)]
|
||||
[(= r +inf.0) (if (fl= x +inf.0) 0.0 +inf.0)]
|
||||
[(= r -inf.0) (if (fl= x -inf.0) 0.0 +inf.0)]
|
||||
[(zero? r) (if (zero? x) 0.0 +inf.0)]
|
||||
[(eqv? x +nan.0) +nan.0]
|
||||
[(fl= x +inf.0) +inf.0]
|
||||
[(fl= x -inf.0) +inf.0]
|
||||
[(zero? x) +inf.0]
|
||||
[else (flabs (real->double-flonum
|
||||
(cond [(eqv? x r) 0.0]
|
||||
[(and (fl= x 0.0) (zero? r)) 0.0]
|
||||
[(zero? r) +inf.0]
|
||||
[(and (rational? x) (rational? r))
|
||||
(flabs (real->double-flonum
|
||||
(/ (- (inexact->exact x) (inexact->exact r))
|
||||
(inexact->exact (flulp x)))))]))
|
||||
(inexact->exact (flulp x)))))]
|
||||
[else +inf.0]))
|
||||
|
||||
;; ===================================================================================================
|
||||
;; More floating-point functions
|
||||
|
|
|
@ -58,8 +58,8 @@
|
|||
[else (assert (/ (factorial n) (factorial (- n k)))
|
||||
exact-nonnegative-integer?)]))
|
||||
|
||||
(: multinomial (Integer Integer * -> Natural))
|
||||
(define (multinomial n . ks)
|
||||
(: multinomial (Integer (Listof Integer) -> Natural))
|
||||
(define (multinomial n ks)
|
||||
(cond [(negative? n) (raise-argument-error 'multinomial "Natural" 0 n ks)]
|
||||
[(ormap negative? ks) (raise-argument-error 'multinomial "(Listof Natural)" 1 n ks)]
|
||||
[(not (= n (apply + ks))) 0]
|
||||
|
|
|
@ -5,16 +5,16 @@
|
|||
"../vector/vector.rkt"
|
||||
"types.rkt")
|
||||
|
||||
(provide partition-count)
|
||||
(provide partitions)
|
||||
|
||||
(define num-global-ps 200)
|
||||
(: global-ps (Vectorof Natural))
|
||||
(define global-ps (make-vector num-global-ps 0))
|
||||
(vector-set! global-ps 0 1)
|
||||
|
||||
(: partition-count : Integer -> Natural)
|
||||
(: partitions : Integer -> Natural)
|
||||
; http://en.wikipedia.org/wiki/Partition_(number_theory)
|
||||
(define (partition-count n)
|
||||
(define (partitions n)
|
||||
(define: local-ps : (Vectorof Natural)
|
||||
(make-vector (max 0 (- (+ n 1) num-global-ps)) 0))
|
||||
|
||||
|
|
|
@ -639,9 +639,10 @@ Like @racket[indexes-array], this does not allocate storage for its elements, an
|
|||
|
||||
@defproc[(diagonal-array [dims Integer] [axes-length Integer] [on-value A] [off-value A])
|
||||
(Array A)]{
|
||||
Returns a square array with @racket[dims] axes, each with length @racket[axes-length]. The elements
|
||||
on the diagonal (i.e. at indexes of the form @racket[(vector j j ...)] for @racket[j < axes-length])
|
||||
have the value @racket[on-value]; the rest have the value @racket[off-value].
|
||||
Returns an array with @racket[dims] axes, each with length @racket[axes-length].
|
||||
(For example, the returned array for @racket[dims = 2] is square.)
|
||||
The elements on the diagonal (i.e. at indexes of the form @racket[(vector j j ...)] for
|
||||
@racket[j < axes-length]) have the value @racket[on-value]; the rest have @racket[off-value].
|
||||
@examples[#:eval typed-eval
|
||||
(diagonal-array 2 7 1 0)]
|
||||
Like @racket[indexes-array], this does not allocate storage for its elements, and is @tech{strict}.
|
||||
|
|
|
@ -23,8 +23,15 @@ a C library that provides
|
|||
@item{Elementary and special functions that are efficient and proved correct.}
|
||||
@item{Well-defined semantics that correspond with the latest IEEE 754 standard.}
|
||||
]
|
||||
The arbitrary-precision floating-point numbers MPFR provides and operates on are
|
||||
represented by the type @racket[Bigfloat].
|
||||
The arbitrary-precision floating-point numbers MPFR provides and operates on are represented by the
|
||||
Typed Racket type @racket[Bigfloat] and identified by the predicate @racket[bigfloat?].
|
||||
|
||||
With a few noted exceptions, bigfloat functions regard their arguments as if they were exact,
|
||||
regardless of their precision.
|
||||
Conceptually, they compute exact results using infinitely many bits, and return results with
|
||||
@racket[(bf-precision)] bits by rounding them using @racket[(bf-rounding-mode)].
|
||||
In practice, they use finite algorithms that have been painstakingly proved to be
|
||||
equivalent to that conceptual, infinite process.
|
||||
|
||||
MPFR is free and license-compatible with commercial software. It is distributed with Racket
|
||||
for Windows and Mac OS X, is installed on most Linux systems, and is
|
||||
|
@ -35,7 +42,7 @@ for Windows and Mac OS X, is installed on most Linux systems, and is
|
|||
@section[#:tag "quick"]{Quick Start}
|
||||
|
||||
@itemlist[#:style 'ordered
|
||||
@item{Set the working precision using @racket[(bf-precision <some-number-of-bits>)].}
|
||||
@item{Set the bigfloat function result precision using @racket[(bf-precision <some-number-of-bits>)].}
|
||||
@item{Use @racket[bf] to convert real values and well-formed strings to bigfloats.}
|
||||
@item{Operate on bigfloats using @racket[bf]-prefixed functions like @racket[bf+] and @racket[bfsin].}
|
||||
@item{Convert bigfloats to real values using @racket[bigfloat->real], @racket[bigfloat->flonum],
|
||||
|
@ -103,10 +110,10 @@ My new laptop computes @(racket 5.221469689764144e+173) as it should.
|
|||
IEEE 754 provides for different rounding modes for the smallest bit of
|
||||
a flonum result, such as round to even and round toward zero. We might use
|
||||
this to implement interval arithmetic correctly, by rounding lower bounds
|
||||
downward and the upper bounds upward. But there isn't a portable way to set the
|
||||
downward and upper bounds upward. But there isn't a portable way to set the
|
||||
rounding mode!
|
||||
|
||||
MPFR allows the rounding mode to be set before any operation, and
|
||||
MPFR allows the rounding mode to be different for any operation, and
|
||||
@racketmodname[math/bigfloat] exposes this capability using the parameter
|
||||
@racket[bf-rounding-mode].
|
||||
|
||||
|
@ -135,75 +142,14 @@ number, so the decimal/bit boundary never lines up except at the decimal point.
|
|||
Thus, the last decimal digit of any bigfloat must represent fewer than 3.3 bits,
|
||||
so it's wrong more often than not. But it's the last @italic{bit} that counts.
|
||||
|
||||
@section{Bigfloat Type and Accessors}
|
||||
@section{Type and Constructors}
|
||||
|
||||
@defidform[Bigfloat]{
|
||||
An opaque type that represents an arbitrary-precision floating-point number, or a @tech{bigfloat}.
|
||||
@deftogether[(@defidform[Bigfloat]
|
||||
@defproc[(bigfloat? [v Any]) Boolean])]{
|
||||
An opaque type that represents an arbitrary-precision floating-point number, or a @tech{bigfloat},
|
||||
and the opaque type's predicate.
|
||||
}
|
||||
|
||||
@defproc[(bigfloat? [v Any]) Boolean]{
|
||||
Returns @racket[#t] when @racket[v] is a bigfloat.
|
||||
}
|
||||
|
||||
@defproc[(bigfloat-precision [x Bigfloat]) Exact-Positive-Integer]{
|
||||
Returns the number of bits in the significand of @racket[x]. This is almost always
|
||||
the value of @racket[(bf-precision)] when @racket[x] was created.
|
||||
}
|
||||
|
||||
@defproc[(bigfloat-signbit [x Bigfloat]) (U 0 1)]{
|
||||
Returns the sign bit of the significand of @racket[x].
|
||||
@examples[#:eval untyped-eval
|
||||
(eval:alts
|
||||
(bigfloat-signbit -1.bf)
|
||||
(eval:result @racketresultfont{1}))
|
||||
(eval:alts
|
||||
(bigfloat-signbit 0.bf)
|
||||
(eval:result @racketresultfont{0}))
|
||||
(eval:alts
|
||||
(bigfloat-signbit -0.bf)
|
||||
(eval:result @racketresultfont{1}))
|
||||
(eval:alts
|
||||
(bigfloat-signbit -inf.bf)
|
||||
(eval:result @racketresultfont{1}))]
|
||||
}
|
||||
|
||||
@deftogether[(@defproc[(bigfloat-significand [x Bigfloat]) Integer]
|
||||
@defproc[(bigfloat-exponent [x Bigfloat]) Integer])]{
|
||||
Return the @italic{signed} significand or exponent of @racket[x].
|
||||
|
||||
To get both the significand and exponent at the same time, use @racket[bigfloat->sig+exp].
|
||||
}
|
||||
|
||||
@section{Bigfloat Parameters}
|
||||
|
||||
@defparam[bf-precision bits Integer]{
|
||||
A parameter that determines the precision of new @racket[Bigfloat] values.
|
||||
|
||||
With a few noted exceptions, bigfloat functions conceptually compute in infinite
|
||||
precision, round the answers to @racket[(bf-precision)] bits using
|
||||
@racket[(bf-rounding-mode)], and return the rounded answers. (In practice,
|
||||
they employ finite algorithms that have been painstakingly proved to be equivalent
|
||||
to the aforementioned infinite process.)
|
||||
|
||||
This parameter has a guard that ensures @racket[(bf-precision)] is between
|
||||
@racket[bf-min-precision] and @racket[bf-max-precision].
|
||||
}
|
||||
|
||||
@defparam[bf-rounding-mode mode (U 'nearest 'zero 'up 'down)]{
|
||||
A parameter that determines the rounding mode used when producing new @racket[Bigfloat] values.
|
||||
}
|
||||
|
||||
@defthing[bf-min-precision Exact-Positive-Integer]{
|
||||
Equal to @racket[2], because single-bit bigfloats can't be correctly rounded.
|
||||
}
|
||||
|
||||
@defthing[bf-max-precision Exact-Positive-Integer]{
|
||||
The largest value of @racket[(bf-precision)]. This is platform-dependent, and probably much
|
||||
larger than you'll ever need.
|
||||
}
|
||||
|
||||
@section[#:tag "construction"]{Bigfloat Construction and Conversion}
|
||||
|
||||
@defproc*[([(bf [x (U String Real)]) Bigfloat]
|
||||
[(bf [sig Integer] [exp Integer]) Bigfloat])]{
|
||||
The one-argument variant converts a string or real @racket[x] to a bigfloat.
|
||||
|
@ -260,8 +206,7 @@ the two-argument variant in this way:
|
|||
}
|
||||
|
||||
@defproc[(bfrandom) Bigfloat]{
|
||||
Returns a uniformly distributed random bigfloat @racket[x] such that
|
||||
@racket[(0.bf . bf<= . x)] and @racket[(x . bf< . 1.bf)].
|
||||
Returns a uniformly distributed random bigfloat in the interval [0,1].
|
||||
}
|
||||
|
||||
@defproc[(bfcopy [x Bigfloat]) Bigfloat]{
|
||||
|
@ -280,6 +225,48 @@ This example computes the golden ratio (@racket[phi.bf]) with 10 bits more than
|
|||
to make up for triple rounding error.
|
||||
}
|
||||
|
||||
@section{Accessors and Conversion Functions}
|
||||
|
||||
@defproc[(bigfloat-precision [x Bigfloat]) Exact-Positive-Integer]{
|
||||
Returns the number of bits in the significand of @racket[x]. This is almost always
|
||||
the value of @racket[(bf-precision)] when @racket[x] was created.
|
||||
}
|
||||
|
||||
@defproc[(bigfloat-signbit [x Bigfloat]) (U 0 1)]{
|
||||
Returns the sign bit of the significand of @racket[x].
|
||||
@examples[#:eval untyped-eval
|
||||
(eval:alts
|
||||
(bigfloat-signbit -1.bf)
|
||||
(eval:result @racketresultfont{1}))
|
||||
(eval:alts
|
||||
(bigfloat-signbit 0.bf)
|
||||
(eval:result @racketresultfont{0}))
|
||||
(eval:alts
|
||||
(bigfloat-signbit -0.bf)
|
||||
(eval:result @racketresultfont{1}))
|
||||
(eval:alts
|
||||
(bigfloat-signbit -inf.bf)
|
||||
(eval:result @racketresultfont{1}))]
|
||||
}
|
||||
|
||||
@deftogether[(@defproc[(bigfloat-significand [x Bigfloat]) Integer]
|
||||
@defproc[(bigfloat-exponent [x Bigfloat]) Integer])]{
|
||||
Return the @italic{signed} significand or exponent of @racket[x].
|
||||
|
||||
To access the significand and exponent at the same time, use @racket[bigfloat->sig+exp].
|
||||
}
|
||||
|
||||
@defproc[(bigfloat->sig+exp [x Bigfloat]) (Values Integer Integer)]{
|
||||
Returns the @italic{signed} significand and exponent of @racket[x].
|
||||
|
||||
If @racket[(values sig exp) = (bigfloat->sig+exp x)], its value as an exact rational
|
||||
is @racket[(* sig (expt 2 exp))]. In fact, @racket[bigfloat->rational] converts
|
||||
bigfloats to rationals in exactly this way, after ensuring that @racket[(bfrational? x)]
|
||||
is @racket[#t].
|
||||
|
||||
This function and the two-argument variant of @racket[bf] are mutual inverses.
|
||||
}
|
||||
|
||||
@deftogether[(@defproc[(bigfloat->integer [x Bigfloat]) Integer]
|
||||
@defproc[(bigfloat->rational [x Bigfloat]) Exact-Rational]
|
||||
@defproc[(bigfloat->real [x Bigfloat]) (U Exact-Rational Flonum)]
|
||||
|
@ -326,15 +313,6 @@ using the current value of @racket[bf-rounding-mode].
|
|||
integers or exact rationals. Worse, they might fit, but have all your RAM and swap space for lunch.
|
||||
}
|
||||
|
||||
@defproc[(bigfloat->sig+exp [x Bigfloat]) (Values Integer Integer)]{
|
||||
Returns the @italic{signed} significand and exponent of @racket[x].
|
||||
|
||||
If @racket[(values sig exp) = (bigfloat->sig+exp x)], its value as an exact rational
|
||||
is @racket[(* sig (expt 2 exp))]. In fact, @racket[bigfloat->rational] converts
|
||||
bigfloats to rationals in exactly this way, after ensuring that @racket[(bfrational? x)]
|
||||
is @racket[#t].
|
||||
}
|
||||
|
||||
@deftogether[(@defproc[(bigfloat->string [x Bigfloat]) String]
|
||||
@defproc[(string->bigfloat [s String]) (U Bigfloat False)])]{
|
||||
Convert a bigfloat @racket[x] to a string @racket[s] and back.
|
||||
|
@ -368,31 +346,36 @@ If @racket[s] isn't a well-formed decimal number with an optional exponent part,
|
|||
(eval:result @racketresultfont{(bf #e3.14159265358979323851)}))]
|
||||
}
|
||||
|
||||
@deftogether[(@defproc[(bftruncate [x Bigfloat]) Bigfloat]
|
||||
@defproc[(bffloor [x Bigfloat]) Bigfloat]
|
||||
@defproc[(bfceiling [x Bigfloat]) Bigfloat]
|
||||
@defproc[(bfround [x Bigfloat]) Bigfloat])]{
|
||||
Like @racket[truncate], @racket[floor], @racket[ceiling] and @racket[round], but
|
||||
for bigfloats.
|
||||
@section{Parameters}
|
||||
|
||||
Rounding is to the nearest integer, with ties broken by rounding to even.
|
||||
@examples[#:eval untyped-eval
|
||||
(eval:alts (bfround (bf 1.5)) (eval:result @racketresultfont{(bf 2)}))
|
||||
(eval:alts (bfround (bf 2.5)) (eval:result @racketresultfont{(bf 2)}))
|
||||
(eval:alts (bfround (bf -1.5)) (eval:result @racketresultfont{(bf -2)}))
|
||||
(eval:alts (bfround (bf -2.5)) (eval:result @racketresultfont{(bf -2)}))]
|
||||
@defparam[bf-precision bits Integer]{
|
||||
A parameter that determines the precision of bigfloats returned from most bigfloat functions.
|
||||
Exceptions are noted in the documentation for functions that do not use @racket[bf-precision].
|
||||
|
||||
For nonzero, rational bigfloats, the number of bits @racket[bits] includes the leading one bit.
|
||||
For example, to simulate 64-bit floating point, use @racket[(bf-precision 53)] even though
|
||||
flonums have a 52-bit significand, because the one bit is implicit in a flonum.
|
||||
|
||||
This parameter has a guard that ensures @racket[(bf-precision)] is between
|
||||
@racket[bf-min-precision] and @racket[bf-max-precision].
|
||||
}
|
||||
|
||||
@defproc[(bffrac [x Bigfloat]) Bigfloat]{
|
||||
Returns the fractional part of @racket[x], with the same sign as @racket[x].
|
||||
@defparam[bf-rounding-mode mode (U 'nearest 'zero 'up 'down)]{
|
||||
A parameter that determines the mode used to round the results of most bigfloat functions.
|
||||
Conceptually, rounding is applied to infinite-precision results to fit them into
|
||||
@racket[(bf-precision)] bits.
|
||||
}
|
||||
|
||||
@defproc[(bfrint [x Bigfloat]) Bigfloat]{
|
||||
Rounds @racket[x] to the nearest integer bigfloat, in the direction specified by
|
||||
@racket[(bf-rounding-mode)].
|
||||
@defthing[bf-min-precision Exact-Positive-Integer]{
|
||||
Equal to @racket[2], because single-bit bigfloats can't be correctly rounded.
|
||||
}
|
||||
|
||||
@section[#:tag "constants"]{Bigfloat Constants}
|
||||
@defthing[bf-max-precision Exact-Positive-Integer]{
|
||||
The largest value of @racket[(bf-precision)]. This is platform-dependent, and probably much
|
||||
larger than you'll ever need.
|
||||
}
|
||||
|
||||
@section[#:tag "constants"]{Constants}
|
||||
|
||||
Most bigfloat ``constants'' are actually identifier macros that expand to the application
|
||||
of a zero-argument function. This allows, for example, @racket[pi.bf] to depend on the
|
||||
|
@ -474,7 +457,7 @@ and @racket[+nan.bf] have fixed precision.
|
|||
More fixed-precision bigfloat constants.
|
||||
}
|
||||
|
||||
@section[#:tag "predicates"]{Bigfloat Predicates}
|
||||
@section[#:tag "predicates"]{Predicates}
|
||||
|
||||
@deftogether[(@defproc[(bfzero? [x Bigfloat]) Boolean]
|
||||
@defproc[(bfpositive? [x Bigfloat]) Boolean]
|
||||
|
@ -500,7 +483,33 @@ than any other bigfloat, and every comparison returns @racket[#f] when either ar
|
|||
is @racket[+nan.bf].
|
||||
}
|
||||
|
||||
@section[#:tag "ops"]{Bigfloat Operations}
|
||||
@section[#:tag "rounding"]{Rounding}
|
||||
|
||||
@deftogether[(@defproc[(bftruncate [x Bigfloat]) Bigfloat]
|
||||
@defproc[(bffloor [x Bigfloat]) Bigfloat]
|
||||
@defproc[(bfceiling [x Bigfloat]) Bigfloat]
|
||||
@defproc[(bfround [x Bigfloat]) Bigfloat])]{
|
||||
Like @racket[truncate], @racket[floor], @racket[ceiling] and @racket[round], but
|
||||
for bigfloats.
|
||||
|
||||
Rounding is to the nearest integer, with ties broken by rounding to even.
|
||||
@examples[#:eval untyped-eval
|
||||
(eval:alts (bfround (bf 1.5)) (eval:result @racketresultfont{(bf 2)}))
|
||||
(eval:alts (bfround (bf 2.5)) (eval:result @racketresultfont{(bf 2)}))
|
||||
(eval:alts (bfround (bf -1.5)) (eval:result @racketresultfont{(bf -2)}))
|
||||
(eval:alts (bfround (bf -2.5)) (eval:result @racketresultfont{(bf -2)}))]
|
||||
}
|
||||
|
||||
@defproc[(bffrac [x Bigfloat]) Bigfloat]{
|
||||
Returns the fractional part of @racket[x], with the same sign as @racket[x].
|
||||
}
|
||||
|
||||
@defproc[(bfrint [x Bigfloat]) Bigfloat]{
|
||||
Rounds @racket[x] to the nearest integer bigfloat, in the direction specified by
|
||||
@racket[(bf-rounding-mode)].
|
||||
}
|
||||
|
||||
@section[#:tag "ops"]{Mathematical Operations}
|
||||
|
||||
@deftogether[(@defproc[(bfmax [x Bigfloat] ...) Bigfloat]
|
||||
@defproc[(bfmin [x Bigfloat] ...) Bigfloat])]{
|
||||
|
@ -664,7 +673,7 @@ asymptotically fast algorithms such as the one that computes @racket[bflog].
|
|||
}
|
||||
|
||||
|
||||
@section[#:tag "misc"]{Low-level Bigfloat Functions}
|
||||
@section[#:tag "misc"]{Low-level Functions}
|
||||
|
||||
@deftogether[(@defproc[(bigfloat->ordinal [x Bigfloat]) Integer]
|
||||
@defproc[(ordinal->bigfloat [n Integer]) Bigfloat]
|
||||
|
|
|
@ -384,7 +384,7 @@ approximation is not necessarily represented by a flonum.
|
|||
@defthing[-min.0 Flonum]
|
||||
@defthing[+min.0 Flonum]
|
||||
@defthing[+max.0 Flonum])]{
|
||||
The rational flonums with maximum and minimum magnitude.
|
||||
The nonzero, rational flonums with maximum and minimum magnitude.
|
||||
@examples[#:eval untyped-eval (list -max.0 -min.0 +min.0 +max.0)]
|
||||
}
|
||||
|
||||
|
|
|
@ -701,25 +701,32 @@ Permutations}}
|
|||
|
||||
@margin-note{Wikipedia: @hyperlink["http://en.wikipedia.org/wiki/Multinomial_theorem#Multinomial_coefficients"]{Multinomial Coeffecient}}
|
||||
@defproc[(multinomial [n Integer] [ks (Listof Integer)]) Natural]{
|
||||
A generalization of @racket[binomial] to multiple sets of choices; i.e.
|
||||
@racket[(multinomial n (list k0 k1))] is the number of ways to choose a set of @racket[k0] items
|
||||
and a set of @racket[k1] items from a set of @racket[n] items. All arguments must be nonnegative.
|
||||
A generalization of @racket[binomial] to multiple sets of choices; e.g.
|
||||
@racket[(multinomial n (list k0 k1 k2))] is the number of ways to choose a set of @racket[k0] items,
|
||||
a set of @racket[k1] items, and a set of @racket[k2] items from a set of @racket[n] items.
|
||||
All arguments must be nonnegative.
|
||||
|
||||
When @racket[(apply + ks) = n], this is equivalent to
|
||||
@racket[(apply / (factorial n) (map factorial ks))]. Otherwise, it returns @racket[0].
|
||||
@racket[(apply / (factorial n) (map factorial ks))]. Otherwise, @racket[multinomial] returns @racket[0].
|
||||
@interaction[#:eval untyped-eval
|
||||
(multinomial 5 3 2)]
|
||||
(multinomial 5 '(3 2))
|
||||
(= (multinomial 8 '(5 3))
|
||||
(binomial 8 5)
|
||||
(binomial 8 3))
|
||||
(multinomial 10 '(5 3 2))
|
||||
(multinomial 0 '())
|
||||
(multinomial 4 '(1 1))]
|
||||
}
|
||||
|
||||
@margin-note{Wikipedia: @hyperlink["http://en.wikipedia.org/wiki/Partition_(number_theory)"]{Partition}}
|
||||
@defproc[(partition-count [n Integer]) Natural]{
|
||||
@defproc[(partitions [n Integer]) Natural]{
|
||||
Returns the number of partitions of @racket[n], which must be nonnegative.
|
||||
A partition of a positive integer @racket[n] is a way
|
||||
of writing @racket[n] as a sum of positive integers.
|
||||
The number 3 has the partitions @racket[(+ 1 1 1)], @racket[(+ 1 2)] and @racket[(+ 3)].
|
||||
@interaction[#:eval untyped-eval
|
||||
(partition-count 3)
|
||||
(partition-count 4)]
|
||||
(partitions 3)
|
||||
(partitions 4)]
|
||||
}
|
||||
|
||||
|
||||
|
|
|
@ -331,7 +331,7 @@ is defined in terms of @racket[gamma-inc] and is more flexible (e.g. it allows n
|
|||
|
||||
The following identities should hold:
|
||||
@itemlist[
|
||||
@item{@racket[(gamma-inc k x) = 0]}
|
||||
@item{@racket[(gamma-inc k 0) = 0]}
|
||||
@item{@racket[(gamma-inc k +inf.0) = (gamma k)]}
|
||||
@item{@racket[(+ (gamma-inc k x #f) (gamma-inc k x #t)) = (gamma k)] (approximately)}
|
||||
@item{@racket[(gamma-inc k x upper? #t) = (/ (gamma-inc k x upper? #f) (gamma k))] (approximately)}
|
||||
|
|
20
collects/math/tests/flonum-tests.rkt
Normal file
20
collects/math/tests/flonum-tests.rkt
Normal file
|
@ -0,0 +1,20 @@
|
|||
#lang racket
|
||||
|
||||
(require math/flonum
|
||||
rackunit)
|
||||
|
||||
(for* ([x '(+inf.0 +nan.0 -inf.0)]
|
||||
[y '(+inf.0 +nan.0 -inf.0)])
|
||||
(cond [(eqv? x y)
|
||||
(check-eqv? (flulp-error x y) 0.0 (format "(flulp-error ~v ~v)" x y))]
|
||||
[else
|
||||
(check-eqv? (flulp-error x y) +inf.0 (format "(flulp-error ~v ~v)" x y))]))
|
||||
|
||||
(check-equal? (flulp-error 55123.135123 55123.135123)
|
||||
0.0)
|
||||
|
||||
(check-equal? (flulp-error 1.0 (flnext 1.0))
|
||||
1.0)
|
||||
|
||||
(check-equal? (flulp-error +max.0 (flprev +max.0))
|
||||
1.0)
|
|
@ -63,7 +63,7 @@
|
|||
(build-list 20 (λ: ([n : Integer]) (modulo ((make-fibonacci a b) n) mod)))))
|
||||
|
||||
; "partitions.rkt"
|
||||
(check-equal? (map partition-count '(0 1 2 3 4 5 6 7 8 9 10))
|
||||
(check-equal? (map partitions '(0 1 2 3 4 5 6 7 8 9 10))
|
||||
'(1 1 2 3 5 7 11 15 22 30 42))
|
||||
|
||||
|
||||
|
@ -100,7 +100,9 @@
|
|||
(check-equal? (permutations 10 10) 3628800)
|
||||
(check-equal? (permutations 0 0) 1)
|
||||
|
||||
(check-equal? (multinomial 20 3 4 5 8) 3491888400)
|
||||
(check-equal? (multinomial 20 '(3 4 5 8)) 3491888400)
|
||||
(check-equal? (multinomial 0 '()) 1)
|
||||
(check-equal? (multinomial 4 '(1 1)) 0)
|
||||
|
||||
; "binomial.rkt"
|
||||
(check-equal? (binomial 10 3) 120)
|
||||
|
|
Loading…
Reference in New Issue
Block a user