1"======================================================================
2|
3|   Numerical methods - Class extensions
4|
5|
6 ======================================================================"
7
8"======================================================================
9|
10| Copyright 1999, 2002, 2007, 2010 Didier Besset.
11| Written by Didier Besset.
12|
13| This file is part of the Smalltalk Numerical Methods library.
14|
15| The Smalltalk Numerical Methods library is free software; you can
16| redistribute it and/or modify it under the terms of the GNU Lesser General
17| Public License as published by the Free Software Foundation; either version
18| 2.1, or (at your option) any later version.
19|
20| The Smalltalk Numerical Methods library is distributed in the hope that it
21| will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty
22| of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Lesser
23| General Public License for more details.
24|
25| You should have received a copy of the GNU Lesser General Public License
26| along with the Smalltalk Numerical Methods library; see the file COPYING.LIB.
27| If not, write to the Free Software Foundation, 59 Temple Place - Suite
28| 330, Boston, MA 02110-1301, USA.
29|
30 ======================================================================"
31
32Integer extend [
33
34    gamma [
35	"Compute the Gamma function for the receiver.
36	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
37	 Initial code: 11/2/99"
38
39	<category: 'numerics'>
40	self > 0
41	    ifFalse:
42		[^self
43		    error: 'Attempt to compute the Gamma function of a non-positive integer'].
44	^(self - 1) factorial
45    ]
46
47    random [
48	"Answer a random integer between 0 and the receiver.
49	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
50	 Initial code: 15/2/99"
51
52	<category: 'numerics'>
53	^Dhb.DhbMitchellMooreGenerator new integerValue: self
54    ]
55
56]
57
58
59
60Number class extend [
61
62    random [
63	"Answers a random number between 0 and 1.
64	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
65	 Initial code: 17/2/99"
66
67	<category: 'numerics'>
68	^Dhb.DhbMitchellMooreGenerator new floatValue
69    ]
70
71]
72
73
74
75Number extend [
76
77    addPolynomial: aPolynomial [
78	"(c) Copyrights Didier BESSET, 1999, all rights reserved.
79	 Initial code: 19/4/99"
80
81	<category: 'numerics'>
82	^aPolynomial addNumber: self
83    ]
84
85    asLimitedPrecisionReal [
86	"Convert the receiver to an instance of
87	 some subclass of LimitedPrecisionReal.
88	 This method defines what the default is."
89
90	<category: 'numerics'>
91	^self asFloat
92    ]
93
94    beta: aNumber [
95	"Computes the beta function of the receiver and aNumber
96	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
97	 Initial code: 1/3/99"
98
99	<category: 'numerics'>
100	^(self logBeta: aNumber) exp
101    ]
102
103    dividingPolynomial: aPolynomial [
104	"(c) Copyrights Didier BESSET, 1999, all rights reserved.
105	 Initial code: 17/4/99"
106
107	<category: 'numerics'>
108	^aPolynomial timesNumber: 1 / self
109    ]
110
111    equalsTo: aNumber [
112	"(c) Copyrights Didier BESSET, 1999, all rights reserved.
113	 Initial code: 21/4/99"
114
115	<category: 'numerics'>
116	^self relativelyEqualsTo: aNumber
117	    upTo: Dhb.DhbFloatingPointMachine new defaultNumericalPrecision
118    ]
119
120    errorFunction [
121	"Answer the error function for the receiver.
122	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
123	 Initial code: 11/2/99"
124
125	<category: 'numerics'>
126	^Dhb.DhbErfApproximation new value: self
127    ]
128
129    gamma [
130	"Compute the Gamma function for the receiver.
131	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
132	 Initial code: 11/2/99"
133
134	<category: 'numerics'>
135	^self > 1
136	    ifTrue: [^Dhb.DhbLanczosFormula new gamma: self]
137	    ifFalse:
138		[self < 0
139		    ifTrue: [Float pi / ((Float pi * self) sin * (1 - self) gamma)]
140		    ifFalse: [(Dhb.DhbLanczosFormula new gamma: self + 1) / self]]
141    ]
142
143    logBeta: aNumber [
144	"Computes the logarithm of the beta function of the receiver and aNumber
145	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
146	 Initial code: 1/3/99"
147
148	<category: 'numerics'>
149	^self logGamma + aNumber logGamma - (self + aNumber) logGamma
150    ]
151
152    logGamma [
153	"Computes the log of the Gamma function (for positive numbers only)
154	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
155	 Initial code: 1/3/99"
156
157	<category: 'numerics'>
158	^self > 1
159	    ifTrue: [Dhb.DhbLanczosFormula new logGamma: self]
160	    ifFalse:
161		[self > 0
162		    ifTrue: [(Dhb.DhbLanczosFormula new logGamma: self + 1) - self ln]
163		    ifFalse: [^self error: 'Argument for the log gamma function must be positive']]
164    ]
165
166    productWithMatrix: aMatrix [
167	"Answer a new matrix, product of aMatrix with the receiver.
168	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
169	 Initial code: 11/2/99"
170
171	<category: 'numerics'>
172	^aMatrix class rows: (aMatrix rowsCollect: [:each | each * self])
173    ]
174
175    productWithVector: aVector [
176	"Answers a new vector product of the receiver with aVector.
177	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
178	 Initial code: 11/2/99"
179
180	<category: 'numerics'>
181	^aVector collect: [:each | each * self]
182    ]
183
184    random [
185	"Answers a random number distributed between 0 and the receiver.
186	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
187	 Initial code: 17/2/99"
188
189	<category: 'numerics'>
190	^self class random * self
191    ]
192
193    relativelyEqualsTo: aNumber upTo: aSmallNumber [
194	"(c) Copyrights Didier BESSET, 1999, all rights reserved.
195	 Initial code: 21/4/99"
196
197	<category: 'numerics'>
198	| norm |
199	norm := self abs max: aNumber abs.
200	^norm <= Dhb.DhbFloatingPointMachine new defaultNumericalPrecision
201	    or: [(self - aNumber) abs < (aSmallNumber * norm)]
202    ]
203
204    subtractToPolynomial: aPolynomial [
205	"(c) Copyrights Didier BESSET, 1999, all rights reserved.
206	 Initial code: 19/4/99"
207
208	<category: 'numerics'>
209	^aPolynomial addNumber: self negated
210    ]
211
212    timesPolynomial: aPolynomial [
213	"(c) Copyrights Didier BESSET, 1999, all rights reserved.
214	 Initial code: 17/4/99"
215
216	<category: 'numerics'>
217	^aPolynomial timesNumber: self
218    ]
219
220]
221
222
223
224Point extend [
225
226    extentFromBottomLeft: aPoint [
227	"(c) Copyrights Didier BESSET, 1998, all rights reserved
228	 Initial code: 21/4/98"
229
230	<category: 'numerics'>
231	^Rectangle origin: self
232		    - (0 @ (aPoint isInteger ifTrue: [aPoint] ifFalse: [aPoint y]))
233	    extent: aPoint
234    ]
235
236    extentFromBottomRight: aPoint [
237	"(c) Copyrights Didier BESSET, 1998, all rights reserved
238	 Initial code: 21/4/98"
239
240	<category: 'numerics'>
241	^Rectangle origin: self - aPoint extent: aPoint
242    ]
243
244    extentFromCenter: aPoint [
245	"(c) Copyrights Didier BESSET, 1998, all rights reserved
246	 Initial code: 21/4/98"
247
248	<category: 'numerics'>
249	^Rectangle origin: self - (aPoint // 2) extent: aPoint
250    ]
251
252    extentFromTopLeft: aPoint [
253	"(c) Copyrights Didier BESSET, 1998, all rights reserved
254	 Initial code: 21/4/98"
255
256	<category: 'numerics'>
257	^Rectangle origin: self extent: aPoint
258    ]
259
260    extentFromTopRight: aPoint [
261	"(c) Copyrights Didier BESSET, 1998, all rights reserved
262	 Initial code: 21/4/98"
263
264	<category: 'numerics'>
265	^Rectangle origin: self
266		    - ((aPoint isInteger ifTrue: [aPoint] ifFalse: [aPoint x]) @ 0)
267	    extent: aPoint
268    ]
269
270]
271
272
273
274Rectangle extend [
275
276    positiveRectangle [
277	"(c) Copyrights Didier BESSET, 1998, all rights reserved
278	 Initial code: 21/4/98"
279
280	<category: 'numerics'>
281	^(origin min: corner) corner: (origin max: corner)
282    ]
283
284]
285
286
287
288Collection extend [
289
290    asVector [
291	<category: 'numerics'>
292	^(Dhb.DhbVector new: self size)
293	    replaceFrom: 1
294	    to: self size
295	    with: self
296	    startingAt: 1
297    ]
298
299]
300
301
302
303DhbPolynomial extend [
304
305    generality [
306	<category: 'numerics'>
307	^nil
308    ]
309
310]
311
312
313
314DhbVector extend [
315
316    generality [
317	<category: 'numerics'>
318	^nil
319    ]
320
321]
322
323