1"======================================================================
2|
3|   Numerical methods - Random Number Generators
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
32
33
34Object subclass: DhbMitchellMooreGenerator [
35    | randoms lowIndex highIndex |
36
37    <category: 'DHB Numerical'>
38    <comment: nil>
39
40    UniqueInstance := nil.
41
42    DhbMitchellMooreGenerator class >> constants: anArray lowIndex: anInteger [
43	"(c) Copyrights Didier BESSET, 2000, all rights reserved.
44	 Initial code: 1/11/00"
45
46	<category: 'creation'>
47	^super new initialize: anArray lowIndex: anInteger
48    ]
49
50    DhbMitchellMooreGenerator class >> default [
51	"Private-
52	 (c) Copyrights Didier BESSET, 2000, all rights reserved.
53	 Initial code: 1/11/00"
54
55	<category: 'creation'>
56	| congruentialGenerator |
57	congruentialGenerator := DhbCongruentialRandomNumberGenerator new.
58	^self generateSeeds: congruentialGenerator
59    ]
60
61    DhbMitchellMooreGenerator class >> generateSeeds: congruentialGenerator [
62	"Private-"
63
64	<category: 'creation'>
65	^self
66	    constants: ((1 to: 55) collect: [:n | congruentialGenerator floatValue])
67	    lowIndex: 24
68    ]
69
70    DhbMitchellMooreGenerator class >> new [
71	"(c) Copyrights Didier BESSET, 2000, all rights reserved.
72	 Initial code: 1/11/00"
73
74	<category: 'creation'>
75	UniqueInstance isNil ifTrue: [UniqueInstance := self default].
76	^UniqueInstance
77    ]
78
79    DhbMitchellMooreGenerator class >> reset: anInteger [
80	"Reset the unique instance used for the default series"
81
82	<category: 'creation'>
83	UniqueInstance := self seed: anInteger
84    ]
85
86    DhbMitchellMooreGenerator class >> seed: anInteger [
87	"(c) Copyrights Didier BESSET, 2000, all rights reserved.
88	 Initial code: 1/18/00"
89
90	<category: 'creation'>
91	| congruentialGenerator |
92	congruentialGenerator := DhbCongruentialRandomNumberGenerator
93		    seed: anInteger.
94	^self generateSeeds: congruentialGenerator
95    ]
96
97    floatValue [
98	"(c) Copyrights Didier BESSET, 2000, all rights reserved.
99	 Initial code: 1/11/00"
100
101	<category: 'information'>
102	| x |
103	x := (randoms at: lowIndex) + (randoms at: highIndex).
104	x < 1.0 ifFalse: [x := x - 1.0].
105	randoms at: highIndex put: x.
106	highIndex := highIndex + 1.
107	highIndex > randoms size ifTrue: [highIndex := 1].
108	lowIndex := lowIndex + 1.
109	lowIndex > randoms size ifTrue: [lowIndex := 1].
110	^x
111    ]
112
113    integerValue: anInteger [
114	"(c) Copyrights Didier BESSET, 2000, all rights reserved.
115	 Initial code: 1/11/00"
116
117	<category: 'information'>
118	^(self floatValue * anInteger) truncated
119    ]
120
121    initialize: anArray lowIndex: anInteger [
122	"Private -
123	 (c) Copyrights Didier BESSET, 2000, all rights reserved.
124	 Initial code: 1/11/00"
125
126	<category: 'initialization'>
127	randoms := anArray.
128	lowIndex := anInteger.
129	highIndex := randoms size.
130	^self
131    ]
132]
133
134
135
136Object subclass: DhbCongruentialRandomNumberGenerator [
137    | constant modulus multiplicator seed |
138
139    <category: 'DHB Numerical'>
140    <comment: nil>
141
142    UniqueInstance := nil.
143
144    DhbCongruentialRandomNumberGenerator class >> constant: aNumber1 multiplicator: aNumber2 modulus: aNumber3 [
145	"Create a new instance of the receiver with given constants.
146	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
147	 Initial code: 15/2/99"
148
149	<category: 'creation'>
150	^super new
151	    initialize: aNumber1
152	    multiplicator: aNumber2
153	    modulus: aNumber3
154    ]
155
156    DhbCongruentialRandomNumberGenerator class >> new [
157	"Create a new instance of the receiver with D. Knuth's constants.
158	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
159	 Initial code: 15/2/99"
160
161	<category: 'creation'>
162	UniqueInstance isNil
163	    ifTrue:
164		[UniqueInstance := super new initialize.
165		UniqueInstance setSeed: 1].
166	^UniqueInstance
167    ]
168
169    DhbCongruentialRandomNumberGenerator class >> seed: aNumber [
170	"Create a new instance of the receiver with given seed
171	 using D. Knuth's constants.
172	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
173	 Initial code: 15/2/99"
174
175	<category: 'creation'>
176	^(super new)
177	    initialize;
178	    setSeed: aNumber;
179	    yourself
180    ]
181
182    floatValue [
183	"Answer the next pseudo-random value between 0 and 1.
184	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
185	 Initial code: 15/2/99"
186
187	<category: 'information'>
188	^self value asFloatD / modulus
189    ]
190
191    integerValue: anInteger [
192	"Answer a random integer between 0 and the anInteger.
193	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
194	 Initial code: 15/2/99"
195
196	<category: 'information'>
197	^self value \\ (anInteger * 1000) // 1000
198    ]
199
200    value [
201	"Answer the next pseudo-random value.
202	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
203	 Initial code: 15/2/99"
204
205	<category: 'information'>
206	seed := (seed * multiplicator + constant) \\ modulus.
207	^seed
208    ]
209
210    initialize [
211	"Private - Initializes the constants of the receiver with D. Knuth's constants.
212	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
213	 Initial code: 15/2/99"
214
215	<category: 'initialization'>
216	self
217	    initialize: 2718281829.0
218	    multiplicator: 3141592653.0
219	    modulus: 4294967296.0
220    ]
221
222    initialize: aNumber1 multiplicator: aNumber2 modulus: aNumber3 [
223	"Private - Initializes the constants needed by the receiver.
224	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
225	 Initial code: 15/2/99"
226
227	<category: 'initialization'>
228	constant := aNumber1.
229	modulus := aNumber2.
230	multiplicator := aNumber3.
231	self setSeed: 1
232    ]
233
234    setSeed: aNumber [
235	"Set the seed of the receiver to aNumber.
236	 (c) Copyrights Didier BESSET, 1999, all rights reserved.
237	 Initial code: 15/2/99"
238
239	<category: 'transformation'>
240	seed := aNumber
241    ]
242]
243
244