xref: /csrg-svn/lib/libc/stdlib/random.c (revision 42625)
121354Sdist /*
221354Sdist  * Copyright (c) 1983 Regents of the University of California.
334955Sbostic  * All rights reserved.
434955Sbostic  *
5*42625Sbostic  * %sccs.include.redist.c%
621354Sdist  */
721354Sdist 
826578Sdonn #if defined(LIBC_SCCS) && !defined(lint)
9*42625Sbostic static char sccsid[] = "@(#)random.c	5.7 (Berkeley) 06/01/90";
1034955Sbostic #endif /* LIBC_SCCS and not lint */
119316Smckusick 
1234955Sbostic #include <stdio.h>
139316Smckusick 
149316Smckusick /*
159316Smckusick  * random.c:
169316Smckusick  * An improved random number generation package.  In addition to the standard
179316Smckusick  * rand()/srand() like interface, this package also has a special state info
189316Smckusick  * interface.  The initstate() routine is called with a seed, an array of
199316Smckusick  * bytes, and a count of how many bytes are being passed in; this array is then
209316Smckusick  * initialized to contain information for random number generation with that
219316Smckusick  * much state information.  Good sizes for the amount of state information are
229316Smckusick  * 32, 64, 128, and 256 bytes.  The state can be switched by calling the
239316Smckusick  * setstate() routine with the same array as was initiallized with initstate().
249316Smckusick  * By default, the package runs with 128 bytes of state information and
259316Smckusick  * generates far better random numbers than a linear congruential generator.
269316Smckusick  * If the amount of state information is less than 32 bytes, a simple linear
279316Smckusick  * congruential R.N.G. is used.
289316Smckusick  * Internally, the state information is treated as an array of longs; the
299316Smckusick  * zeroeth element of the array is the type of R.N.G. being used (small
309316Smckusick  * integer); the remainder of the array is the state information for the
319316Smckusick  * R.N.G.  Thus, 32 bytes of state information will give 7 longs worth of
329316Smckusick  * state information, which will allow a degree seven polynomial.  (Note: the
339316Smckusick  * zeroeth word of state information also has some other information stored
349316Smckusick  * in it -- see setstate() for details).
359316Smckusick  * The random number generation technique is a linear feedback shift register
369316Smckusick  * approach, employing trinomials (since there are fewer terms to sum up that
379316Smckusick  * way).  In this approach, the least significant bit of all the numbers in
389316Smckusick  * the state table will act as a linear feedback shift register, and will have
399316Smckusick  * period 2^deg - 1 (where deg is the degree of the polynomial being used,
409316Smckusick  * assuming that the polynomial is irreducible and primitive).  The higher
419316Smckusick  * order bits will have longer periods, since their values are also influenced
429316Smckusick  * by pseudo-random carries out of the lower bits.  The total period of the
439316Smckusick  * generator is approximately deg*(2**deg - 1); thus doubling the amount of
449316Smckusick  * state information has a vast influence on the period of the generator.
459316Smckusick  * Note: the deg*(2**deg - 1) is an approximation only good for large deg,
469316Smckusick  * when the period of the shift register is the dominant factor.  With deg
479316Smckusick  * equal to seven, the period is actually much longer than the 7*(2**7 - 1)
489316Smckusick  * predicted by this formula.
499316Smckusick  */
509316Smckusick 
519316Smckusick 
529316Smckusick 
539316Smckusick /*
549316Smckusick  * For each of the currently supported random number generators, we have a
559316Smckusick  * break value on the amount of state information (you need at least this
569316Smckusick  * many bytes of state info to support this random number generator), a degree
579316Smckusick  * for the polynomial (actually a trinomial) that the R.N.G. is based on, and
589316Smckusick  * the separation between the two lower order coefficients of the trinomial.
599316Smckusick  */
609316Smckusick 
619316Smckusick #define		TYPE_0		0		/* linear congruential */
629316Smckusick #define		BREAK_0		8
639316Smckusick #define		DEG_0		0
649316Smckusick #define		SEP_0		0
659316Smckusick 
669316Smckusick #define		TYPE_1		1		/* x**7 + x**3 + 1 */
679316Smckusick #define		BREAK_1		32
689316Smckusick #define		DEG_1		7
699316Smckusick #define		SEP_1		3
709316Smckusick 
719316Smckusick #define		TYPE_2		2		/* x**15 + x + 1 */
729316Smckusick #define		BREAK_2		64
739316Smckusick #define		DEG_2		15
749316Smckusick #define		SEP_2		1
759316Smckusick 
769316Smckusick #define		TYPE_3		3		/* x**31 + x**3 + 1 */
779316Smckusick #define		BREAK_3		128
789316Smckusick #define		DEG_3		31
799316Smckusick #define		SEP_3		3
809316Smckusick 
819316Smckusick #define		TYPE_4		4		/* x**63 + x + 1 */
829316Smckusick #define		BREAK_4		256
839316Smckusick #define		DEG_4		63
849316Smckusick #define		SEP_4		1
859316Smckusick 
869316Smckusick 
879316Smckusick /*
889316Smckusick  * Array versions of the above information to make code run faster -- relies
899316Smckusick  * on fact that TYPE_i == i.
909316Smckusick  */
919316Smckusick 
929316Smckusick #define		MAX_TYPES	5		/* max number of types above */
939316Smckusick 
949316Smckusick static  int		degrees[ MAX_TYPES ]	= { DEG_0, DEG_1, DEG_2,
959316Smckusick 								DEG_3, DEG_4 };
969316Smckusick 
979316Smckusick static  int		seps[ MAX_TYPES ]	= { SEP_0, SEP_1, SEP_2,
989316Smckusick 								SEP_3, SEP_4 };
999316Smckusick 
1009316Smckusick 
1019316Smckusick 
1029316Smckusick /*
1039316Smckusick  * Initially, everything is set up as if from :
1049316Smckusick  *		initstate( 1, &randtbl, 128 );
1059316Smckusick  * Note that this initialization takes advantage of the fact that srandom()
1069316Smckusick  * advances the front and rear pointers 10*rand_deg times, and hence the
1079316Smckusick  * rear pointer which starts at 0 will also end up at zero; thus the zeroeth
1089316Smckusick  * element of the state information, which contains info about the current
1099316Smckusick  * position of the rear pointer is just
1109316Smckusick  *	MAX_TYPES*(rptr - state) + TYPE_3 == TYPE_3.
1119316Smckusick  */
1129316Smckusick 
1139316Smckusick static  long		randtbl[ DEG_3 + 1 ]	= { TYPE_3,
1149316Smckusick 			    0x9a319039, 0x32d9c024, 0x9b663182, 0x5da1f342,
1159316Smckusick 			    0xde3b81e0, 0xdf0a6fb5, 0xf103bc02, 0x48f340fb,
1169316Smckusick 			    0x7449e56b, 0xbeb1dbb0, 0xab5c5918, 0x946554fd,
1179316Smckusick 			    0x8c2e680f, 0xeb3d799f, 0xb11ee0b7, 0x2d436b86,
1189316Smckusick 			    0xda672e2a, 0x1588ca88, 0xe369735d, 0x904f35f7,
1199316Smckusick 			    0xd7158fd6, 0x6fa6f051, 0x616e6b96, 0xac94efdc,
1209316Smckusick 			    0x36413f93, 0xc622c298, 0xf5a42ab8, 0x8a88d77b,
1219316Smckusick 					0xf5ad9d0e, 0x8999220b, 0x27fb47b9 };
1229316Smckusick 
1239316Smckusick /*
1249316Smckusick  * fptr and rptr are two pointers into the state info, a front and a rear
1259316Smckusick  * pointer.  These two pointers are always rand_sep places aparts, as they cycle
1269316Smckusick  * cyclically through the state information.  (Yes, this does mean we could get
1279316Smckusick  * away with just one pointer, but the code for random() is more efficient this
1289316Smckusick  * way).  The pointers are left positioned as they would be from the call
1299316Smckusick  *			initstate( 1, randtbl, 128 )
1309316Smckusick  * (The position of the rear pointer, rptr, is really 0 (as explained above
1319316Smckusick  * in the initialization of randtbl) because the state table pointer is set
1329316Smckusick  * to point to randtbl[1] (as explained below).
1339316Smckusick  */
1349316Smckusick 
1359316Smckusick static  long		*fptr			= &randtbl[ SEP_3 + 1 ];
1369316Smckusick static  long		*rptr			= &randtbl[ 1 ];
1379316Smckusick 
1389316Smckusick 
1399316Smckusick 
1409316Smckusick /*
1419316Smckusick  * The following things are the pointer to the state information table,
1429316Smckusick  * the type of the current generator, the degree of the current polynomial
1439316Smckusick  * being used, and the separation between the two pointers.
1449316Smckusick  * Note that for efficiency of random(), we remember the first location of
1459316Smckusick  * the state information, not the zeroeth.  Hence it is valid to access
1469316Smckusick  * state[-1], which is used to store the type of the R.N.G.
1479316Smckusick  * Also, we remember the last location, since this is more efficient than
1489316Smckusick  * indexing every time to find the address of the last element to see if
1499316Smckusick  * the front and rear pointers have wrapped.
1509316Smckusick  */
1519316Smckusick 
15216396Searl static  long		*state			= &randtbl[ 1 ];
1539316Smckusick 
1549316Smckusick static  int		rand_type		= TYPE_3;
1559316Smckusick static  int		rand_deg		= DEG_3;
1569316Smckusick static  int		rand_sep		= SEP_3;
1579316Smckusick 
1589316Smckusick static  long		*end_ptr		= &randtbl[ DEG_3 + 1 ];
1599316Smckusick 
1609316Smckusick 
1619316Smckusick 
1629316Smckusick /*
1639316Smckusick  * srandom:
1649316Smckusick  * Initialize the random number generator based on the given seed.  If the
1659316Smckusick  * type is the trivial no-state-information type, just remember the seed.
1669316Smckusick  * Otherwise, initializes state[] based on the given "seed" via a linear
1679316Smckusick  * congruential generator.  Then, the pointers are set to known locations
1689316Smckusick  * that are exactly rand_sep places apart.  Lastly, it cycles the state
1699316Smckusick  * information a given number of times to get rid of any initial dependencies
1709316Smckusick  * introduced by the L.C.R.N.G.
1719316Smckusick  * Note that the initialization of randtbl[] for default usage relies on
1729316Smckusick  * values produced by this routine.
1739316Smckusick  */
1749316Smckusick 
1759316Smckusick srandom( x )
1769316Smckusick 
1779316Smckusick     unsigned		x;
1789316Smckusick {
1799316Smckusick     	register  int		i, j;
18034098Sbostic 	long random();
1819316Smckusick 
1829316Smckusick 	if(  rand_type  ==  TYPE_0  )  {
1839316Smckusick 	    state[ 0 ] = x;
1849316Smckusick 	}
1859316Smckusick 	else  {
1869316Smckusick 	    j = 1;
1879316Smckusick 	    state[ 0 ] = x;
1889316Smckusick 	    for( i = 1; i < rand_deg; i++ )  {
1899316Smckusick 		state[i] = 1103515245*state[i - 1] + 12345;
1909316Smckusick 	    }
1919316Smckusick 	    fptr = &state[ rand_sep ];
1929316Smckusick 	    rptr = &state[ 0 ];
1939316Smckusick 	    for( i = 0; i < 10*rand_deg; i++ )  random();
1949316Smckusick 	}
1959316Smckusick }
1969316Smckusick 
1979316Smckusick 
1989316Smckusick 
1999316Smckusick /*
2009316Smckusick  * initstate:
2019316Smckusick  * Initialize the state information in the given array of n bytes for
2029316Smckusick  * future random number generation.  Based on the number of bytes we
2039316Smckusick  * are given, and the break values for the different R.N.G.'s, we choose
2049316Smckusick  * the best (largest) one we can and set things up for it.  srandom() is
2059316Smckusick  * then called to initialize the state information.
2069316Smckusick  * Note that on return from srandom(), we set state[-1] to be the type
2079316Smckusick  * multiplexed with the current value of the rear pointer; this is so
2089316Smckusick  * successive calls to initstate() won't lose this information and will
2099316Smckusick  * be able to restart with setstate().
2109316Smckusick  * Note: the first thing we do is save the current state, if any, just like
2119316Smckusick  * setstate() so that it doesn't matter when initstate is called.
2129316Smckusick  * Returns a pointer to the old state.
2139316Smckusick  */
2149316Smckusick 
2159316Smckusick char  *
2169316Smckusick initstate( seed, arg_state, n )
2179316Smckusick 
2189316Smckusick     unsigned		seed;			/* seed for R. N. G. */
2199316Smckusick     char		*arg_state;		/* pointer to state array */
2209316Smckusick     int			n;			/* # bytes of state info */
2219316Smckusick {
2229316Smckusick 	register  char		*ostate		= (char *)( &state[ -1 ] );
2239316Smckusick 
2249316Smckusick 	if(  rand_type  ==  TYPE_0  )  state[ -1 ] = rand_type;
2259316Smckusick 	else  state[ -1 ] = MAX_TYPES*(rptr - state) + rand_type;
2269316Smckusick 	if(  n  <  BREAK_1  )  {
2279316Smckusick 	    if(  n  <  BREAK_0  )  {
22839837Smckusick 		fprintf( stderr, "initstate: not enough state (%d bytes); ignored.\n", n );
22939837Smckusick 		return 0;
2309316Smckusick 	    }
2319316Smckusick 	    rand_type = TYPE_0;
2329316Smckusick 	    rand_deg = DEG_0;
2339316Smckusick 	    rand_sep = SEP_0;
2349316Smckusick 	}
2359316Smckusick 	else  {
2369316Smckusick 	    if(  n  <  BREAK_2  )  {
2379316Smckusick 		rand_type = TYPE_1;
2389316Smckusick 		rand_deg = DEG_1;
2399316Smckusick 		rand_sep = SEP_1;
2409316Smckusick 	    }
2419316Smckusick 	    else  {
2429316Smckusick 		if(  n  <  BREAK_3  )  {
2439316Smckusick 		    rand_type = TYPE_2;
2449316Smckusick 		    rand_deg = DEG_2;
2459316Smckusick 		    rand_sep = SEP_2;
2469316Smckusick 		}
2479316Smckusick 		else  {
2489316Smckusick 		    if(  n  <  BREAK_4  )  {
2499316Smckusick 			rand_type = TYPE_3;
2509316Smckusick 			rand_deg = DEG_3;
2519316Smckusick 			rand_sep = SEP_3;
2529316Smckusick 		    }
2539316Smckusick 		    else  {
2549316Smckusick 			rand_type = TYPE_4;
2559316Smckusick 			rand_deg = DEG_4;
2569316Smckusick 			rand_sep = SEP_4;
2579316Smckusick 		    }
2589316Smckusick 		}
2599316Smckusick 	    }
2609316Smckusick 	}
2619316Smckusick 	state = &(  ( (long *)arg_state )[1]  );	/* first location */
2629316Smckusick 	end_ptr = &state[ rand_deg ];	/* must set end_ptr before srandom */
2639316Smckusick 	srandom( seed );
2649316Smckusick 	if(  rand_type  ==  TYPE_0  )  state[ -1 ] = rand_type;
2659316Smckusick 	else  state[ -1 ] = MAX_TYPES*(rptr - state) + rand_type;
2669316Smckusick 	return( ostate );
2679316Smckusick }
2689316Smckusick 
2699316Smckusick 
2709316Smckusick 
2719316Smckusick /*
2729316Smckusick  * setstate:
2739316Smckusick  * Restore the state from the given state array.
2749316Smckusick  * Note: it is important that we also remember the locations of the pointers
2759316Smckusick  * in the current state information, and restore the locations of the pointers
2769316Smckusick  * from the old state information.  This is done by multiplexing the pointer
2779316Smckusick  * location into the zeroeth word of the state information.
2789316Smckusick  * Note that due to the order in which things are done, it is OK to call
2799316Smckusick  * setstate() with the same state as the current state.
2809316Smckusick  * Returns a pointer to the old state information.
2819316Smckusick  */
2829316Smckusick 
2839316Smckusick char  *
2849316Smckusick setstate( arg_state )
2859316Smckusick 
2869316Smckusick     char		*arg_state;
2879316Smckusick {
2889316Smckusick 	register  long		*new_state	= (long *)arg_state;
2899316Smckusick 	register  int		type		= new_state[0]%MAX_TYPES;
2909316Smckusick 	register  int		rear		= new_state[0]/MAX_TYPES;
2919316Smckusick 	char			*ostate		= (char *)( &state[ -1 ] );
2929316Smckusick 
2939316Smckusick 	if(  rand_type  ==  TYPE_0  )  state[ -1 ] = rand_type;
2949316Smckusick 	else  state[ -1 ] = MAX_TYPES*(rptr - state) + rand_type;
2959316Smckusick 	switch(  type  )  {
2969316Smckusick 	    case  TYPE_0:
2979316Smckusick 	    case  TYPE_1:
2989316Smckusick 	    case  TYPE_2:
2999316Smckusick 	    case  TYPE_3:
3009316Smckusick 	    case  TYPE_4:
3019316Smckusick 		rand_type = type;
3029316Smckusick 		rand_deg = degrees[ type ];
3039316Smckusick 		rand_sep = seps[ type ];
3049316Smckusick 		break;
3059316Smckusick 
3069316Smckusick 	    default:
3079316Smckusick 		fprintf( stderr, "setstate: state info has been munged; not changed.\n" );
3089316Smckusick 	}
3099316Smckusick 	state = &new_state[ 1 ];
3109316Smckusick 	if(  rand_type  !=  TYPE_0  )  {
3119316Smckusick 	    rptr = &state[ rear ];
3129316Smckusick 	    fptr = &state[ (rear + rand_sep)%rand_deg ];
3139316Smckusick 	}
3149316Smckusick 	end_ptr = &state[ rand_deg ];		/* set end_ptr too */
3159316Smckusick 	return( ostate );
3169316Smckusick }
3179316Smckusick 
3189316Smckusick 
3199316Smckusick 
3209316Smckusick /*
3219316Smckusick  * random:
3229316Smckusick  * If we are using the trivial TYPE_0 R.N.G., just do the old linear
3239316Smckusick  * congruential bit.  Otherwise, we do our fancy trinomial stuff, which is the
3249316Smckusick  * same in all ther other cases due to all the global variables that have been
3259316Smckusick  * set up.  The basic operation is to add the number at the rear pointer into
3269316Smckusick  * the one at the front pointer.  Then both pointers are advanced to the next
3279316Smckusick  * location cyclically in the table.  The value returned is the sum generated,
3289316Smckusick  * reduced to 31 bits by throwing away the "least random" low bit.
3299316Smckusick  * Note: the code takes advantage of the fact that both the front and
3309316Smckusick  * rear pointers can't wrap on the same call by not testing the rear
3319316Smckusick  * pointer if the front one has wrapped.
3329316Smckusick  * Returns a 31-bit random number.
3339316Smckusick  */
3349316Smckusick 
3359316Smckusick long
3369316Smckusick random()
3379316Smckusick {
3389316Smckusick 	long		i;
3399316Smckusick 
3409316Smckusick 	if(  rand_type  ==  TYPE_0  )  {
3419316Smckusick 	    i = state[0] = ( state[0]*1103515245 + 12345 )&0x7fffffff;
3429316Smckusick 	}
3439316Smckusick 	else  {
3449316Smckusick 	    *fptr += *rptr;
3459316Smckusick 	    i = (*fptr >> 1)&0x7fffffff;	/* chucking least random bit */
3469316Smckusick 	    if(  ++fptr  >=  end_ptr  )  {
3479316Smckusick 		fptr = state;
3489316Smckusick 		++rptr;
3499316Smckusick 	    }
3509316Smckusick 	    else  {
3519316Smckusick 		if(  ++rptr  >=  end_ptr  )  rptr = state;
3529316Smckusick 	    }
3539316Smckusick 	}
3549316Smckusick 	return( i );
3559316Smckusick }
3569316Smckusick 
357