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