xref: /minix3/common/lib/libc/stdlib/random.c (revision 0a6a1f1d05b60e214de2f05a7310ddd1f0e590e7)
1*0a6a1f1dSLionel Sambuc /*	$NetBSD: random.c,v 1.4 2014/06/12 20:59:46 christos Exp $	*/
2b6cbf720SGianluca Guida 
3b6cbf720SGianluca Guida /*
4b6cbf720SGianluca Guida  * Copyright (c) 1983, 1993
5b6cbf720SGianluca Guida  *	The Regents of the University of California.  All rights reserved.
6b6cbf720SGianluca Guida  *
7b6cbf720SGianluca Guida  * Redistribution and use in source and binary forms, with or without
8b6cbf720SGianluca Guida  * modification, are permitted provided that the following conditions
9b6cbf720SGianluca Guida  * are met:
10b6cbf720SGianluca Guida  * 1. Redistributions of source code must retain the above copyright
11b6cbf720SGianluca Guida  *    notice, this list of conditions and the following disclaimer.
12b6cbf720SGianluca Guida  * 2. Redistributions in binary form must reproduce the above copyright
13b6cbf720SGianluca Guida  *    notice, this list of conditions and the following disclaimer in the
14b6cbf720SGianluca Guida  *    documentation and/or other materials provided with the distribution.
15b6cbf720SGianluca Guida  * 3. Neither the name of the University nor the names of its contributors
16b6cbf720SGianluca Guida  *    may be used to endorse or promote products derived from this software
17b6cbf720SGianluca Guida  *    without specific prior written permission.
18b6cbf720SGianluca Guida  *
19b6cbf720SGianluca Guida  * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
20b6cbf720SGianluca Guida  * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
21b6cbf720SGianluca Guida  * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
22b6cbf720SGianluca Guida  * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
23b6cbf720SGianluca Guida  * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
24b6cbf720SGianluca Guida  * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
25b6cbf720SGianluca Guida  * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
26b6cbf720SGianluca Guida  * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
27b6cbf720SGianluca Guida  * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
28b6cbf720SGianluca Guida  * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
29b6cbf720SGianluca Guida  * SUCH DAMAGE.
30b6cbf720SGianluca Guida  */
31b6cbf720SGianluca Guida 
32b6cbf720SGianluca Guida #if !defined(_KERNEL) && !defined(_STANDALONE)
33b6cbf720SGianluca Guida #include <sys/cdefs.h>
34b6cbf720SGianluca Guida #if defined(LIBC_SCCS) && !defined(lint)
35b6cbf720SGianluca Guida #if 0
36b6cbf720SGianluca Guida static char sccsid[] = "@(#)random.c	8.2 (Berkeley) 5/19/95";
37b6cbf720SGianluca Guida #else
38*0a6a1f1dSLionel Sambuc __RCSID("$NetBSD: random.c,v 1.4 2014/06/12 20:59:46 christos Exp $");
39b6cbf720SGianluca Guida #endif
40b6cbf720SGianluca Guida #endif /* LIBC_SCCS and not lint */
41b6cbf720SGianluca Guida 
42b6cbf720SGianluca Guida #include "namespace.h"
43b6cbf720SGianluca Guida 
44b6cbf720SGianluca Guida #include <assert.h>
45b6cbf720SGianluca Guida #include <errno.h>
46b6cbf720SGianluca Guida #include <stdlib.h>
47b6cbf720SGianluca Guida #include "reentrant.h"
48b6cbf720SGianluca Guida 
49b6cbf720SGianluca Guida #ifdef __weak_alias
50b6cbf720SGianluca Guida __weak_alias(initstate,_initstate)
51b6cbf720SGianluca Guida __weak_alias(random,_random)
52b6cbf720SGianluca Guida __weak_alias(setstate,_setstate)
53b6cbf720SGianluca Guida __weak_alias(srandom,_srandom)
54b6cbf720SGianluca Guida #endif
55b6cbf720SGianluca Guida 
56b6cbf720SGianluca Guida 
57b6cbf720SGianluca Guida #ifdef _REENTRANT
58b6cbf720SGianluca Guida static mutex_t random_mutex = MUTEX_INITIALIZER;
59b6cbf720SGianluca Guida #endif
60b6cbf720SGianluca Guida #else
61b6cbf720SGianluca Guida #include <lib/libkern/libkern.h>
62b6cbf720SGianluca Guida #define mutex_lock(a)	(void)0
63b6cbf720SGianluca Guida #define mutex_unlock(a) (void)0
64b6cbf720SGianluca Guida #endif
65b6cbf720SGianluca Guida 
66b6cbf720SGianluca Guida #ifndef SMALL_RANDOM
67b6cbf720SGianluca Guida static void srandom_unlocked(unsigned int);
68b6cbf720SGianluca Guida static long random_unlocked(void);
69b6cbf720SGianluca Guida 
70b6cbf720SGianluca Guida #define USE_BETTER_RANDOM
71b6cbf720SGianluca Guida 
72b6cbf720SGianluca Guida /*
73b6cbf720SGianluca Guida  * random.c:
74b6cbf720SGianluca Guida  *
75b6cbf720SGianluca Guida  * An improved random number generation package.  In addition to the standard
76b6cbf720SGianluca Guida  * rand()/srand() like interface, this package also has a special state info
77b6cbf720SGianluca Guida  * interface.  The initstate() routine is called with a seed, an array of
78b6cbf720SGianluca Guida  * bytes, and a count of how many bytes are being passed in; this array is
79b6cbf720SGianluca Guida  * then initialized to contain information for random number generation with
80b6cbf720SGianluca Guida  * that much state information.  Good sizes for the amount of state
81b6cbf720SGianluca Guida  * information are 32, 64, 128, and 256 bytes.  The state can be switched by
82b6cbf720SGianluca Guida  * calling the setstate() routine with the same array as was initiallized
83b6cbf720SGianluca Guida  * with initstate().  By default, the package runs with 128 bytes of state
84b6cbf720SGianluca Guida  * information and generates far better random numbers than a linear
85b6cbf720SGianluca Guida  * congruential generator.  If the amount of state information is less than
86b6cbf720SGianluca Guida  * 32 bytes, a simple linear congruential R.N.G. is used.
87b6cbf720SGianluca Guida  *
88b6cbf720SGianluca Guida  * Internally, the state information is treated as an array of ints; the
89b6cbf720SGianluca Guida  * zeroeth element of the array is the type of R.N.G. being used (small
90b6cbf720SGianluca Guida  * integer); the remainder of the array is the state information for the
91b6cbf720SGianluca Guida  * R.N.G.  Thus, 32 bytes of state information will give 7 ints worth of
92b6cbf720SGianluca Guida  * state information, which will allow a degree seven polynomial.  (Note:
93b6cbf720SGianluca Guida  * the zeroeth word of state information also has some other information
94b6cbf720SGianluca Guida  * stored in it -- see setstate() for details).
95b6cbf720SGianluca Guida  *
96b6cbf720SGianluca Guida  * The random number generation technique is a linear feedback shift register
97b6cbf720SGianluca Guida  * approach, employing trinomials (since there are fewer terms to sum up that
98b6cbf720SGianluca Guida  * way).  In this approach, the least significant bit of all the numbers in
99b6cbf720SGianluca Guida  * the state table will act as a linear feedback shift register, and will
100b6cbf720SGianluca Guida  * have period 2^deg - 1 (where deg is the degree of the polynomial being
101b6cbf720SGianluca Guida  * used, assuming that the polynomial is irreducible and primitive).  The
102b6cbf720SGianluca Guida  * higher order bits will have longer periods, since their values are also
103b6cbf720SGianluca Guida  * influenced by pseudo-random carries out of the lower bits.  The total
104b6cbf720SGianluca Guida  * period of the generator is approximately deg*(2**deg - 1); thus doubling
105b6cbf720SGianluca Guida  * the amount of state information has a vast influence on the period of the
106b6cbf720SGianluca Guida  * generator.  Note: the deg*(2**deg - 1) is an approximation only good for
107b6cbf720SGianluca Guida  * large deg, when the period of the shift register is the dominant factor.
108b6cbf720SGianluca Guida  * With deg equal to seven, the period is actually much longer than the
109b6cbf720SGianluca Guida  * 7*(2**7 - 1) predicted by this formula.
110b6cbf720SGianluca Guida  *
111b6cbf720SGianluca Guida  * Modified 28 December 1994 by Jacob S. Rosenberg.
112b6cbf720SGianluca Guida  * The following changes have been made:
113b6cbf720SGianluca Guida  * All references to the type u_int have been changed to unsigned long.
114b6cbf720SGianluca Guida  * All references to type int have been changed to type long.  Other
115b6cbf720SGianluca Guida  * cleanups have been made as well.  A warning for both initstate and
116b6cbf720SGianluca Guida  * setstate has been inserted to the effect that on Sparc platforms
117b6cbf720SGianluca Guida  * the 'arg_state' variable must be forced to begin on word boundaries.
118b6cbf720SGianluca Guida  * This can be easily done by casting a long integer array to char *.
119b6cbf720SGianluca Guida  * The overall logic has been left STRICTLY alone.  This software was
120b6cbf720SGianluca Guida  * tested on both a VAX and Sun SpacsStation with exactly the same
121b6cbf720SGianluca Guida  * results.  The new version and the original give IDENTICAL results.
122b6cbf720SGianluca Guida  * The new version is somewhat faster than the original.  As the
123b6cbf720SGianluca Guida  * documentation says:  "By default, the package runs with 128 bytes of
124b6cbf720SGianluca Guida  * state information and generates far better random numbers than a linear
125b6cbf720SGianluca Guida  * congruential generator.  If the amount of state information is less than
126b6cbf720SGianluca Guida  * 32 bytes, a simple linear congruential R.N.G. is used."  For a buffer of
127b6cbf720SGianluca Guida  * 128 bytes, this new version runs about 19 percent faster and for a 16
128b6cbf720SGianluca Guida  * byte buffer it is about 5 percent faster.
129b6cbf720SGianluca Guida  *
130b6cbf720SGianluca Guida  * Modified 07 January 2002 by Jason R. Thorpe.
131b6cbf720SGianluca Guida  * The following changes have been made:
132b6cbf720SGianluca Guida  * All the references to "long" have been changed back to "int".  This
133b6cbf720SGianluca Guida  * fixes memory corruption problems on LP64 platforms.
134b6cbf720SGianluca Guida  */
135b6cbf720SGianluca Guida 
136b6cbf720SGianluca Guida /*
137b6cbf720SGianluca Guida  * For each of the currently supported random number generators, we have a
138b6cbf720SGianluca Guida  * break value on the amount of state information (you need at least this
139b6cbf720SGianluca Guida  * many bytes of state info to support this random number generator), a degree
140b6cbf720SGianluca Guida  * for the polynomial (actually a trinomial) that the R.N.G. is based on, and
141b6cbf720SGianluca Guida  * the separation between the two lower order coefficients of the trinomial.
142b6cbf720SGianluca Guida  */
143b6cbf720SGianluca Guida #define	TYPE_0		0		/* linear congruential */
144b6cbf720SGianluca Guida #define	BREAK_0		8
145b6cbf720SGianluca Guida #define	DEG_0		0
146b6cbf720SGianluca Guida #define	SEP_0		0
147b6cbf720SGianluca Guida 
148b6cbf720SGianluca Guida #define	TYPE_1		1		/* x**7 + x**3 + 1 */
149b6cbf720SGianluca Guida #define	BREAK_1		32
150b6cbf720SGianluca Guida #define	DEG_1		7
151b6cbf720SGianluca Guida #define	SEP_1		3
152b6cbf720SGianluca Guida 
153b6cbf720SGianluca Guida #define	TYPE_2		2		/* x**15 + x + 1 */
154b6cbf720SGianluca Guida #define	BREAK_2		64
155b6cbf720SGianluca Guida #define	DEG_2		15
156b6cbf720SGianluca Guida #define	SEP_2		1
157b6cbf720SGianluca Guida 
158b6cbf720SGianluca Guida #define	TYPE_3		3		/* x**31 + x**3 + 1 */
159b6cbf720SGianluca Guida #define	BREAK_3		128
160b6cbf720SGianluca Guida #define	DEG_3		31
161b6cbf720SGianluca Guida #define	SEP_3		3
162b6cbf720SGianluca Guida 
163b6cbf720SGianluca Guida #define	TYPE_4		4		/* x**63 + x + 1 */
164b6cbf720SGianluca Guida #define	BREAK_4		256
165b6cbf720SGianluca Guida #define	DEG_4		63
166b6cbf720SGianluca Guida #define	SEP_4		1
167b6cbf720SGianluca Guida 
168b6cbf720SGianluca Guida /*
169b6cbf720SGianluca Guida  * Array versions of the above information to make code run faster --
170b6cbf720SGianluca Guida  * relies on fact that TYPE_i == i.
171b6cbf720SGianluca Guida  */
172b6cbf720SGianluca Guida #define	MAX_TYPES	5		/* max number of types above */
173b6cbf720SGianluca Guida 
174b6cbf720SGianluca Guida static const int degrees[MAX_TYPES] =	{ DEG_0, DEG_1, DEG_2, DEG_3, DEG_4 };
175b6cbf720SGianluca Guida static const int seps[MAX_TYPES] =	{ SEP_0, SEP_1, SEP_2, SEP_3, SEP_4 };
176b6cbf720SGianluca Guida 
177b6cbf720SGianluca Guida /*
178b6cbf720SGianluca Guida  * Initially, everything is set up as if from:
179b6cbf720SGianluca Guida  *
180b6cbf720SGianluca Guida  *	initstate(1, &randtbl, 128);
181b6cbf720SGianluca Guida  *
182b6cbf720SGianluca Guida  * Note that this initialization takes advantage of the fact that srandom()
183b6cbf720SGianluca Guida  * advances the front and rear pointers 10*rand_deg times, and hence the
184b6cbf720SGianluca Guida  * rear pointer which starts at 0 will also end up at zero; thus the zeroeth
185b6cbf720SGianluca Guida  * element of the state information, which contains info about the current
186b6cbf720SGianluca Guida  * position of the rear pointer is just
187b6cbf720SGianluca Guida  *
188b6cbf720SGianluca Guida  *	MAX_TYPES * (rptr - state) + TYPE_3 == TYPE_3.
189b6cbf720SGianluca Guida  */
190b6cbf720SGianluca Guida 
191b6cbf720SGianluca Guida /* LINTED */
192b6cbf720SGianluca Guida static int randtbl[DEG_3 + 1] = {
193b6cbf720SGianluca Guida 	TYPE_3,
194b6cbf720SGianluca Guida #ifdef USE_BETTER_RANDOM
195b6cbf720SGianluca Guida 	0x991539b1, 0x16a5bce3, 0x6774a4cd,
196b6cbf720SGianluca Guida 	0x3e01511e, 0x4e508aaa, 0x61048c05,
197b6cbf720SGianluca Guida 	0xf5500617, 0x846b7115, 0x6a19892c,
198b6cbf720SGianluca Guida 	0x896a97af, 0xdb48f936, 0x14898454,
199b6cbf720SGianluca Guida 	0x37ffd106, 0xb58bff9c, 0x59e17104,
200b6cbf720SGianluca Guida 	0xcf918a49, 0x09378c83, 0x52c7a471,
201b6cbf720SGianluca Guida 	0x8d293ea9, 0x1f4fc301, 0xc3db71be,
202b6cbf720SGianluca Guida 	0x39b44e1c, 0xf8a44ef9, 0x4c8b80b1,
203b6cbf720SGianluca Guida 	0x19edc328, 0x87bf4bdd, 0xc9b240e5,
204b6cbf720SGianluca Guida 	0xe9ee4b1b, 0x4382aee7, 0x535b6b41,
205b6cbf720SGianluca Guida 	0xf3bec5da,
206b6cbf720SGianluca Guida #else
207b6cbf720SGianluca Guida 	0x9a319039, 0x32d9c024, 0x9b663182,
208b6cbf720SGianluca Guida 	0x5da1f342, 0xde3b81e0, 0xdf0a6fb5,
209b6cbf720SGianluca Guida 	0xf103bc02, 0x48f340fb, 0x7449e56b,
210b6cbf720SGianluca Guida 	0xbeb1dbb0, 0xab5c5918, 0x946554fd,
211b6cbf720SGianluca Guida 	0x8c2e680f, 0xeb3d799f, 0xb11ee0b7,
212b6cbf720SGianluca Guida 	0x2d436b86, 0xda672e2a, 0x1588ca88,
213b6cbf720SGianluca Guida 	0xe369735d, 0x904f35f7, 0xd7158fd6,
214b6cbf720SGianluca Guida 	0x6fa6f051, 0x616e6b96, 0xac94efdc,
215b6cbf720SGianluca Guida 	0x36413f93, 0xc622c298, 0xf5a42ab8,
216b6cbf720SGianluca Guida 	0x8a88d77b, 0xf5ad9d0e, 0x8999220b,
217b6cbf720SGianluca Guida 	0x27fb47b9,
218b6cbf720SGianluca Guida #endif /* USE_BETTER_RANDOM */
219b6cbf720SGianluca Guida };
220b6cbf720SGianluca Guida 
221b6cbf720SGianluca Guida /*
222b6cbf720SGianluca Guida  * fptr and rptr are two pointers into the state info, a front and a rear
223b6cbf720SGianluca Guida  * pointer.  These two pointers are always rand_sep places aparts, as they
224b6cbf720SGianluca Guida  * cycle cyclically through the state information.  (Yes, this does mean we
225b6cbf720SGianluca Guida  * could get away with just one pointer, but the code for random() is more
226b6cbf720SGianluca Guida  * efficient this way).  The pointers are left positioned as they would be
227b6cbf720SGianluca Guida  * from the call
228b6cbf720SGianluca Guida  *
229b6cbf720SGianluca Guida  *	initstate(1, randtbl, 128);
230b6cbf720SGianluca Guida  *
231b6cbf720SGianluca Guida  * (The position of the rear pointer, rptr, is really 0 (as explained above
232b6cbf720SGianluca Guida  * in the initialization of randtbl) because the state table pointer is set
233b6cbf720SGianluca Guida  * to point to randtbl[1] (as explained below).
234b6cbf720SGianluca Guida  */
235b6cbf720SGianluca Guida static int *fptr = &randtbl[SEP_3 + 1];
236b6cbf720SGianluca Guida static int *rptr = &randtbl[1];
237b6cbf720SGianluca Guida 
238b6cbf720SGianluca Guida /*
239b6cbf720SGianluca Guida  * The following things are the pointer to the state information table, the
240b6cbf720SGianluca Guida  * type of the current generator, the degree of the current polynomial being
241b6cbf720SGianluca Guida  * used, and the separation between the two pointers.  Note that for efficiency
242b6cbf720SGianluca Guida  * of random(), we remember the first location of the state information, not
243b6cbf720SGianluca Guida  * the zeroeth.  Hence it is valid to access state[-1], which is used to
244b6cbf720SGianluca Guida  * store the type of the R.N.G.  Also, we remember the last location, since
245b6cbf720SGianluca Guida  * this is more efficient than indexing every time to find the address of
246b6cbf720SGianluca Guida  * the last element to see if the front and rear pointers have wrapped.
247b6cbf720SGianluca Guida  */
248b6cbf720SGianluca Guida static int *state = &randtbl[1];
249b6cbf720SGianluca Guida static int rand_type = TYPE_3;
250b6cbf720SGianluca Guida static int rand_deg = DEG_3;
251b6cbf720SGianluca Guida static int rand_sep = SEP_3;
252b6cbf720SGianluca Guida static int *end_ptr = &randtbl[DEG_3 + 1];
253b6cbf720SGianluca Guida 
254b6cbf720SGianluca Guida /*
255b6cbf720SGianluca Guida  * srandom:
256b6cbf720SGianluca Guida  *
257b6cbf720SGianluca Guida  * Initialize the random number generator based on the given seed.  If the
258b6cbf720SGianluca Guida  * type is the trivial no-state-information type, just remember the seed.
259b6cbf720SGianluca Guida  * Otherwise, initializes state[] based on the given "seed" via a linear
260b6cbf720SGianluca Guida  * congruential generator.  Then, the pointers are set to known locations
261b6cbf720SGianluca Guida  * that are exactly rand_sep places apart.  Lastly, it cycles the state
262b6cbf720SGianluca Guida  * information a given number of times to get rid of any initial dependencies
263b6cbf720SGianluca Guida  * introduced by the L.C.R.N.G.  Note that the initialization of randtbl[]
264b6cbf720SGianluca Guida  * for default usage relies on values produced by this routine.
265b6cbf720SGianluca Guida  */
266b6cbf720SGianluca Guida static void
srandom_unlocked(unsigned int x)267b6cbf720SGianluca Guida srandom_unlocked(unsigned int x)
268b6cbf720SGianluca Guida {
269b6cbf720SGianluca Guida 	int i;
270b6cbf720SGianluca Guida 
271b6cbf720SGianluca Guida 	if (rand_type == TYPE_0)
272b6cbf720SGianluca Guida 		state[0] = x;
273b6cbf720SGianluca Guida 	else {
274b6cbf720SGianluca Guida 		state[0] = x;
275b6cbf720SGianluca Guida 		for (i = 1; i < rand_deg; i++) {
276b6cbf720SGianluca Guida #ifdef USE_BETTER_RANDOM
277b6cbf720SGianluca Guida 			int x1, hi, lo, t;
278b6cbf720SGianluca Guida 
279b6cbf720SGianluca Guida 			/*
280b6cbf720SGianluca Guida 			 * Compute x[n + 1] = (7^5 * x[n]) mod (2^31 - 1).
281b6cbf720SGianluca Guida 			 * From "Random number generators: good ones are hard
282b6cbf720SGianluca Guida 			 * to find", Park and Miller, Communications of the ACM,
283b6cbf720SGianluca Guida 			 * vol. 31, no. 10,
284b6cbf720SGianluca Guida 			 * October 1988, p. 1195.
285b6cbf720SGianluca Guida 			 */
286b6cbf720SGianluca Guida 			x1 = state[i - 1];
287b6cbf720SGianluca Guida 			hi = x1 / 127773;
288b6cbf720SGianluca Guida 			lo = x1 % 127773;
289b6cbf720SGianluca Guida 			t = 16807 * lo - 2836 * hi;
290b6cbf720SGianluca Guida 			if (t <= 0)
291b6cbf720SGianluca Guida 				t += 0x7fffffff;
292b6cbf720SGianluca Guida 			state[i] = t;
293b6cbf720SGianluca Guida #else
294b6cbf720SGianluca Guida 			state[i] = 1103515245 * state[i - 1] + 12345;
295b6cbf720SGianluca Guida #endif /* USE_BETTER_RANDOM */
296b6cbf720SGianluca Guida 		}
297b6cbf720SGianluca Guida 		fptr = &state[rand_sep];
298b6cbf720SGianluca Guida 		rptr = &state[0];
299b6cbf720SGianluca Guida 		for (i = 0; i < 10 * rand_deg; i++)
300b6cbf720SGianluca Guida 			(void)random_unlocked();
301b6cbf720SGianluca Guida 	}
302b6cbf720SGianluca Guida }
303b6cbf720SGianluca Guida 
304b6cbf720SGianluca Guida void
srandom(unsigned int x)305*0a6a1f1dSLionel Sambuc srandom(unsigned int x)
306b6cbf720SGianluca Guida {
307b6cbf720SGianluca Guida 
308b6cbf720SGianluca Guida 	mutex_lock(&random_mutex);
309*0a6a1f1dSLionel Sambuc 	srandom_unlocked(x);
310b6cbf720SGianluca Guida 	mutex_unlock(&random_mutex);
311b6cbf720SGianluca Guida }
312b6cbf720SGianluca Guida 
313b6cbf720SGianluca Guida /*
314b6cbf720SGianluca Guida  * initstate:
315b6cbf720SGianluca Guida  *
316b6cbf720SGianluca Guida  * Initialize the state information in the given array of n bytes for future
317b6cbf720SGianluca Guida  * random number generation.  Based on the number of bytes we are given, and
318b6cbf720SGianluca Guida  * the break values for the different R.N.G.'s, we choose the best (largest)
319b6cbf720SGianluca Guida  * one we can and set things up for it.  srandom() is then called to
320b6cbf720SGianluca Guida  * initialize the state information.
321b6cbf720SGianluca Guida  *
322b6cbf720SGianluca Guida  * Note that on return from srandom(), we set state[-1] to be the type
323b6cbf720SGianluca Guida  * multiplexed with the current value of the rear pointer; this is so
324b6cbf720SGianluca Guida  * successive calls to initstate() won't lose this information and will be
325b6cbf720SGianluca Guida  * able to restart with setstate().
326b6cbf720SGianluca Guida  *
327b6cbf720SGianluca Guida  * Note: the first thing we do is save the current state, if any, just like
328b6cbf720SGianluca Guida  * setstate() so that it doesn't matter when initstate is called.
329b6cbf720SGianluca Guida  *
330b6cbf720SGianluca Guida  * Returns a pointer to the old state.
331b6cbf720SGianluca Guida  *
332b6cbf720SGianluca Guida  * Note: The Sparc platform requires that arg_state begin on an int
333b6cbf720SGianluca Guida  * word boundary; otherwise a bus error will occur. Even so, lint will
334b6cbf720SGianluca Guida  * complain about mis-alignment, but you should disregard these messages.
335b6cbf720SGianluca Guida  */
336b6cbf720SGianluca Guida char *
initstate(unsigned int seed,char * arg_state,size_t n)337b6cbf720SGianluca Guida initstate(
338*0a6a1f1dSLionel Sambuc 	unsigned int seed,		/* seed for R.N.G. */
339b6cbf720SGianluca Guida 	char *arg_state,		/* pointer to state array */
340b6cbf720SGianluca Guida 	size_t n)			/* # bytes of state info */
341b6cbf720SGianluca Guida {
342b6cbf720SGianluca Guida 	void *ostate = (void *)(&state[-1]);
343b6cbf720SGianluca Guida 	int *int_arg_state;
344b6cbf720SGianluca Guida 
345b6cbf720SGianluca Guida 	_DIAGASSERT(arg_state != NULL);
346b6cbf720SGianluca Guida 
347b6cbf720SGianluca Guida 	int_arg_state = (int *)(void *)arg_state;
348b6cbf720SGianluca Guida 
349b6cbf720SGianluca Guida 	mutex_lock(&random_mutex);
350b6cbf720SGianluca Guida 	if (rand_type == TYPE_0)
351b6cbf720SGianluca Guida 		state[-1] = rand_type;
352b6cbf720SGianluca Guida 	else
353b6cbf720SGianluca Guida 		state[-1] = MAX_TYPES * (int)(rptr - state) + rand_type;
354b6cbf720SGianluca Guida 	if (n < BREAK_0) {
355b6cbf720SGianluca Guida 		mutex_unlock(&random_mutex);
356b6cbf720SGianluca Guida 		return (NULL);
357b6cbf720SGianluca Guida 	} else if (n < BREAK_1) {
358b6cbf720SGianluca Guida 		rand_type = TYPE_0;
359b6cbf720SGianluca Guida 		rand_deg = DEG_0;
360b6cbf720SGianluca Guida 		rand_sep = SEP_0;
361b6cbf720SGianluca Guida 	} else if (n < BREAK_2) {
362b6cbf720SGianluca Guida 		rand_type = TYPE_1;
363b6cbf720SGianluca Guida 		rand_deg = DEG_1;
364b6cbf720SGianluca Guida 		rand_sep = SEP_1;
365b6cbf720SGianluca Guida 	} else if (n < BREAK_3) {
366b6cbf720SGianluca Guida 		rand_type = TYPE_2;
367b6cbf720SGianluca Guida 		rand_deg = DEG_2;
368b6cbf720SGianluca Guida 		rand_sep = SEP_2;
369b6cbf720SGianluca Guida 	} else if (n < BREAK_4) {
370b6cbf720SGianluca Guida 		rand_type = TYPE_3;
371b6cbf720SGianluca Guida 		rand_deg = DEG_3;
372b6cbf720SGianluca Guida 		rand_sep = SEP_3;
373b6cbf720SGianluca Guida 	} else {
374b6cbf720SGianluca Guida 		rand_type = TYPE_4;
375b6cbf720SGianluca Guida 		rand_deg = DEG_4;
376b6cbf720SGianluca Guida 		rand_sep = SEP_4;
377b6cbf720SGianluca Guida 	}
378b6cbf720SGianluca Guida 	state = (int *) (int_arg_state + 1); /* first location */
379b6cbf720SGianluca Guida 	end_ptr = &state[rand_deg];	/* must set end_ptr before srandom */
380*0a6a1f1dSLionel Sambuc 	srandom_unlocked(seed);
381b6cbf720SGianluca Guida 	if (rand_type == TYPE_0)
382b6cbf720SGianluca Guida 		int_arg_state[0] = rand_type;
383b6cbf720SGianluca Guida 	else
384b6cbf720SGianluca Guida 		int_arg_state[0] = MAX_TYPES * (int)(rptr - state) + rand_type;
385b6cbf720SGianluca Guida 	mutex_unlock(&random_mutex);
386b6cbf720SGianluca Guida 	return((char *)ostate);
387b6cbf720SGianluca Guida }
388b6cbf720SGianluca Guida 
389b6cbf720SGianluca Guida /*
390b6cbf720SGianluca Guida  * setstate:
391b6cbf720SGianluca Guida  *
392b6cbf720SGianluca Guida  * Restore the state from the given state array.
393b6cbf720SGianluca Guida  *
394b6cbf720SGianluca Guida  * Note: it is important that we also remember the locations of the pointers
395b6cbf720SGianluca Guida  * in the current state information, and restore the locations of the pointers
396b6cbf720SGianluca Guida  * from the old state information.  This is done by multiplexing the pointer
397b6cbf720SGianluca Guida  * location into the zeroeth word of the state information.
398b6cbf720SGianluca Guida  *
399b6cbf720SGianluca Guida  * Note that due to the order in which things are done, it is OK to call
400b6cbf720SGianluca Guida  * setstate() with the same state as the current state.
401b6cbf720SGianluca Guida  *
402b6cbf720SGianluca Guida  * Returns a pointer to the old state information.
403b6cbf720SGianluca Guida  *
404b6cbf720SGianluca Guida  * Note: The Sparc platform requires that arg_state begin on a long
405b6cbf720SGianluca Guida  * word boundary; otherwise a bus error will occur. Even so, lint will
406b6cbf720SGianluca Guida  * complain about mis-alignment, but you should disregard these messages.
407b6cbf720SGianluca Guida  */
408b6cbf720SGianluca Guida char *
setstate(char * arg_state)409b6cbf720SGianluca Guida setstate(char *arg_state)		/* pointer to state array */
410b6cbf720SGianluca Guida {
411b6cbf720SGianluca Guida 	int *new_state;
412b6cbf720SGianluca Guida 	int type;
413b6cbf720SGianluca Guida 	int rear;
414b6cbf720SGianluca Guida 	void *ostate = (void *)(&state[-1]);
415b6cbf720SGianluca Guida 
416b6cbf720SGianluca Guida 	_DIAGASSERT(arg_state != NULL);
417b6cbf720SGianluca Guida 
418b6cbf720SGianluca Guida 	new_state = (int *)(void *)arg_state;
419b6cbf720SGianluca Guida 	type = (int)(new_state[0] % MAX_TYPES);
420b6cbf720SGianluca Guida 	rear = (int)(new_state[0] / MAX_TYPES);
421b6cbf720SGianluca Guida 
422b6cbf720SGianluca Guida 	mutex_lock(&random_mutex);
423b6cbf720SGianluca Guida 	if (rand_type == TYPE_0)
424b6cbf720SGianluca Guida 		state[-1] = rand_type;
425b6cbf720SGianluca Guida 	else
426b6cbf720SGianluca Guida 		state[-1] = MAX_TYPES * (int)(rptr - state) + rand_type;
427b6cbf720SGianluca Guida 	switch(type) {
428b6cbf720SGianluca Guida 	case TYPE_0:
429b6cbf720SGianluca Guida 	case TYPE_1:
430b6cbf720SGianluca Guida 	case TYPE_2:
431b6cbf720SGianluca Guida 	case TYPE_3:
432b6cbf720SGianluca Guida 	case TYPE_4:
433b6cbf720SGianluca Guida 		rand_type = type;
434b6cbf720SGianluca Guida 		rand_deg = degrees[type];
435b6cbf720SGianluca Guida 		rand_sep = seps[type];
436b6cbf720SGianluca Guida 		break;
437b6cbf720SGianluca Guida 	default:
438b6cbf720SGianluca Guida 		mutex_unlock(&random_mutex);
439b6cbf720SGianluca Guida 		return (NULL);
440b6cbf720SGianluca Guida 	}
441b6cbf720SGianluca Guida 	state = (int *) (new_state + 1);
442b6cbf720SGianluca Guida 	if (rand_type != TYPE_0) {
443b6cbf720SGianluca Guida 		rptr = &state[rear];
444b6cbf720SGianluca Guida 		fptr = &state[(rear + rand_sep) % rand_deg];
445b6cbf720SGianluca Guida 	}
446b6cbf720SGianluca Guida 	end_ptr = &state[rand_deg];		/* set end_ptr too */
447b6cbf720SGianluca Guida 	mutex_unlock(&random_mutex);
448b6cbf720SGianluca Guida 	return((char *)ostate);
449b6cbf720SGianluca Guida }
450b6cbf720SGianluca Guida 
451b6cbf720SGianluca Guida /*
452b6cbf720SGianluca Guida  * random:
453b6cbf720SGianluca Guida  *
454b6cbf720SGianluca Guida  * If we are using the trivial TYPE_0 R.N.G., just do the old linear
455b6cbf720SGianluca Guida  * congruential bit.  Otherwise, we do our fancy trinomial stuff, which is
456b6cbf720SGianluca Guida  * the same in all the other cases due to all the global variables that have
457b6cbf720SGianluca Guida  * been set up.  The basic operation is to add the number at the rear pointer
458b6cbf720SGianluca Guida  * into the one at the front pointer.  Then both pointers are advanced to
459b6cbf720SGianluca Guida  * the next location cyclically in the table.  The value returned is the sum
460b6cbf720SGianluca Guida  * generated, reduced to 31 bits by throwing away the "least random" low bit.
461b6cbf720SGianluca Guida  *
462b6cbf720SGianluca Guida  * Note: the code takes advantage of the fact that both the front and
463b6cbf720SGianluca Guida  * rear pointers can't wrap on the same call by not testing the rear
464b6cbf720SGianluca Guida  * pointer if the front one has wrapped.
465b6cbf720SGianluca Guida  *
466b6cbf720SGianluca Guida  * Returns a 31-bit random number.
467b6cbf720SGianluca Guida  */
468b6cbf720SGianluca Guida static long
random_unlocked(void)469b6cbf720SGianluca Guida random_unlocked(void)
470b6cbf720SGianluca Guida {
471b6cbf720SGianluca Guida 	int i;
472b6cbf720SGianluca Guida 	int *f, *r;
473b6cbf720SGianluca Guida 
474b6cbf720SGianluca Guida 	if (rand_type == TYPE_0) {
475b6cbf720SGianluca Guida 		i = state[0];
476b6cbf720SGianluca Guida 		state[0] = i = (i * 1103515245 + 12345) & 0x7fffffff;
477b6cbf720SGianluca Guida 	} else {
478b6cbf720SGianluca Guida 		/*
479b6cbf720SGianluca Guida 		 * Use local variables rather than static variables for speed.
480b6cbf720SGianluca Guida 		 */
481b6cbf720SGianluca Guida 		f = fptr; r = rptr;
482b6cbf720SGianluca Guida 		*f += *r;
483b6cbf720SGianluca Guida 		/* chucking least random bit */
484b6cbf720SGianluca Guida 		i = ((unsigned int)*f >> 1) & 0x7fffffff;
485b6cbf720SGianluca Guida 		if (++f >= end_ptr) {
486b6cbf720SGianluca Guida 			f = state;
487b6cbf720SGianluca Guida 			++r;
488b6cbf720SGianluca Guida 		}
489b6cbf720SGianluca Guida 		else if (++r >= end_ptr) {
490b6cbf720SGianluca Guida 			r = state;
491b6cbf720SGianluca Guida 		}
492b6cbf720SGianluca Guida 
493b6cbf720SGianluca Guida 		fptr = f; rptr = r;
494b6cbf720SGianluca Guida 	}
495b6cbf720SGianluca Guida 	return(i);
496b6cbf720SGianluca Guida }
497b6cbf720SGianluca Guida 
498b6cbf720SGianluca Guida long
random(void)499b6cbf720SGianluca Guida random(void)
500b6cbf720SGianluca Guida {
501b6cbf720SGianluca Guida 	long r;
502b6cbf720SGianluca Guida 
503b6cbf720SGianluca Guida 	mutex_lock(&random_mutex);
504b6cbf720SGianluca Guida 	r = random_unlocked();
505b6cbf720SGianluca Guida 	mutex_unlock(&random_mutex);
506b6cbf720SGianluca Guida 	return (r);
507b6cbf720SGianluca Guida }
508b6cbf720SGianluca Guida #else
509b6cbf720SGianluca Guida long
random(void)510b6cbf720SGianluca Guida random(void)
511b6cbf720SGianluca Guida {
512b6cbf720SGianluca Guida 	static u_long randseed = 1;
513b6cbf720SGianluca Guida 	long x, hi, lo, t;
514b6cbf720SGianluca Guida 
515b6cbf720SGianluca Guida 	/*
516b6cbf720SGianluca Guida 	 * Compute x[n + 1] = (7^5 * x[n]) mod (2^31 - 1).
517b6cbf720SGianluca Guida 	 * From "Random number generators: good ones are hard to find",
518b6cbf720SGianluca Guida 	 * Park and Miller, Communications of the ACM, vol. 31, no. 10,
519b6cbf720SGianluca Guida 	 * October 1988, p. 1195.
520b6cbf720SGianluca Guida 	 */
521b6cbf720SGianluca Guida 	x = randseed;
522b6cbf720SGianluca Guida 	hi = x / 127773;
523b6cbf720SGianluca Guida 	lo = x % 127773;
524b6cbf720SGianluca Guida 	t = 16807 * lo - 2836 * hi;
525b6cbf720SGianluca Guida 	if (t <= 0)
526b6cbf720SGianluca Guida 		t += 0x7fffffff;
527b6cbf720SGianluca Guida 	randseed = t;
528b6cbf720SGianluca Guida 	return (t);
529b6cbf720SGianluca Guida }
530b6cbf720SGianluca Guida #endif /* SMALL_RANDOM */
531