Random.st
author Claus Gittinger <cg@exept.de>
Thu, 21 Aug 1997 18:10:25 +0200
changeset 561 f00675b5531f
parent 518 f5fe8b630e4c
child 680 a7b98fdac3dc
permissions -rw-r--r--
added class protocol for random numbers

"
======================================================================
|
| Copyright (C) 1988, 1989 Free Software Foundation, Inc.
| Written by Steve Byrne.
|
| This file is part of GNU Smalltalk.
|
| GNU Smalltalk is free software; you can redistribute it and/or modify it
| under the terms of the GNU General Public License as published by the Free
| Software Foundation; either version 1, or (at your option) any later version.
| 
| GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
| ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
| FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
| details.
| 
| You should have received a copy of the GNU General Public License along with
| GNU Smalltalk; see the file LICENSE.  If not, write to the Free Software
| Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  
|
======================================================================

see notice in (Random>>documentation)
"

Stream subclass:#Random
	instanceVariableNames:'seed increment multiplier modulus'
	classVariableNames:'RandomGenerator'
	poolDictionaries:''
	category:'Magnitude-Numbers'
!

!Random class methodsFor:'documentation'!

copyright
"
======================================================================
|
| Copyright (C) 1988, 1989 Free Software Foundation, Inc.
| Written by Steve Byrne.
|
| This file is part of GNU Smalltalk.
|
| GNU Smalltalk is free software; you can redistribute it and/or modify it
| under the terms of the GNU General Public License as published by the Free
| Software Foundation; either version 1, or (at your option) any later version.
| 
| GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
| ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
| FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
| details.
| 
| You should have received a copy of the GNU General Public License along with
| GNU Smalltalk; see the file LICENSE.  If not, write to the Free Software
| Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  
|
======================================================================

see notice in (Random>>documentation)
"
!

documentation
"
    random numbers - thanks to Steves GNU Smalltalk

    Notice: although being included here,
            this file is NOT covered by the ST/X license, but by
            the FSF copyLeft (see copyright method).

            You can redistribute it under the terms stated there ...
            Also, the price you pay for ST/X does not include a charge for
            this file - it has to be considered as a separate piece of
            software, which can be copied and given away without any 
            restriction from my (CG) side.

    claus: the algorithm may need a rewrite for better numbers

    [author:]
        Steve Byrne
        Claus Gittinger
"
!

examples
"
                                                                        [exBegin]
    |rnd|

    rnd := Random new.
    10 timesRepeat:[
        Transcript showCR:(rnd next)
    ]
                                                                        [exEnd]

    rolling a dice:
                                                                        [exBegin]
    |rnd|

    rnd := Random new.
    10 timesRepeat:[
        Transcript showCR:(rnd nextIntegerBetween:1 and:6)
    ]
                                                                        [exEnd]
"
! !

!Random class methodsFor:'instance creation'!

new
    "return a new random generator"

    ^self basicNew setSeed
! !

!Random class methodsFor:'random numbers'!

nextBetween:start and:stop
    "return a random number between start and stop.
     This method behaves like the corresponding instance method,
     but allows generation of random numbers without
     a need for an instance of Random to be kept around.
     This uses a common, shared generator."

    RandomGenerator isNil ifTrue:[
        RandomGenerator := self new.
    ].
    ^ RandomGenerator nextBetween:start and:stop

    "
     Transcript showCR:(Random nextBetween:1 and:100).
     Transcript showCR:(Random nextBetween:1 and:100).
     Transcript showCR:(Random nextBetween:1 and:100).
     Transcript showCR:(Random nextBetween:1 and:100).
    "

    "Modified: 21.8.1997 / 18:08:56 / cg"
    "Created: 21.8.1997 / 18:09:36 / cg"
!

nextInteger
    "return an integral random number.
     This method behaves like the corresponding instance method,
     but allows generation of random numbers without
     a need for an instance of Random to be kept around.
     This uses a common, shared generator."

    RandomGenerator isNil ifTrue:[
        RandomGenerator := self new.
    ].
    ^ RandomGenerator nextInteger.

    "
     Transcript showCR:(Random nextInteger).
     Transcript showCR:(Random nextInteger).
     Transcript showCR:(Random nextInteger).
     Transcript showCR:(Random nextInteger).
    "

    "Created: 21.8.1997 / 18:08:23 / cg"
!

nextIntegerBetween:start and:stop
    "return an integral random number between start and stop.
     This method behaves like the corresponding instance method,
     but allows generation of random numbers without
     a need for an instance of Random to be kept around.
     This uses a common, shared generator."

    RandomGenerator isNil ifTrue:[
        RandomGenerator := self new.
    ].
    ^ RandomGenerator nextIntegerBetween:start and:stop

    "
     Transcript showCR:(Random nextIntegerBetween:1 and:10).
     Transcript showCR:(Random nextIntegerBetween:1 and:10).
     Transcript showCR:(Random nextIntegerBetween:1 and:10).
     Transcript showCR:(Random nextIntegerBetween:1 and:10).
    "

    "Created: 21.8.1997 / 18:07:00 / cg"
    "Modified: 21.8.1997 / 18:08:56 / cg"
! !

!Random class methodsFor:'testing'!

chiSquareTest   
    " Chi-Squared Test - from R.Sedgewick's 1st ed. of 'Algorithms', 
            o N = number of samples
            o r  = range of random numners is [0,r)      -- condition: N >= 10r.
            o Random number generator 'passes' if chisquare value is very close to r
            o Repeat test several times, since it may be *wrong* 1 out of 10 trials."

    | aRand frequencies n range t chisquare |

    chisquare := Array new: 10.     "Collect results from 10 trails"
    1 to: 10 do: [:k |       "k = trail number"
        aRand := Random new.  "Seeded differently each time"
        range := 100.   
        n := 1000.
        frequencies := Array new: range.
        1 to: frequencies size do: [ :i | frequencies at: i put: 0 ].
        1 to: n do: [ :i |
                t := ((aRand next) * range) truncated.
                frequencies at: (t+1) put: ((frequencies at: (t + 1)) + 1) ].
        t := 0.
        1 to: range do: [ :i |
                t := t +  ((frequencies at: i) squared) ].
        chisquare at: k put: (((range * t  / n) - n) asFloat).
    ].
    ^ chisquare

    "
     Random chiSquareTest 
    "

    "
      Sedgewick claims each chisquare number should be 100 +- 20. 
      The closer to 100, the better.
    "

    "Modified: 16.4.1997 / 16:48:26 / cg"
! !

!Random methodsFor:'accessing-reading'!

next
    "return the next random number in the range 0..1"

    ^ self nextInteger / modulus asFloat

    "|r|
     r := Random new.
     Transcript showCR:r next.
     Transcript showCR:r next.
     Transcript showCR:r next.
     Transcript showCR:r next.
    "

    "Modified: 1.4.1997 / 22:44:46 / cg"
!

nextBetween:start and:stop
    "return a random number between start and stop.
     claus: the original GNU version has a bug in returning values
     from the interval [start .. stop+1]"

    |rnd|

    rnd := self next.
    rnd := rnd * (stop asFloat - start asFloat).
    rnd := rnd + start asFloat.
    ^ rnd

    "|r|
     r := Random new.
     Transcript showCR:(r nextBetween:1 and:10).
     Transcript showCR:(r nextBetween:1 and:10).
     Transcript showCR:(r nextBetween:1 and:10).
     Transcript showCR:(r nextBetween:1 and:10).
    "

    "Modified: 21.8.1997 / 18:10:00 / cg"
!

nextBoolean
    "return true or false by random"

    ^ self nextInteger < (modulus / 2)

    "|r|
     r := Random new.
     Transcript showCR:r nextBoolean.
     Transcript showCR:r nextBoolean.
     Transcript showCR:r nextBoolean.
     Transcript showCR:r nextBoolean.
    "

    "Modified: 1.4.1997 / 22:52:19 / cg"
!

nextInteger
    "return the next integral random number,
     in the range 0 .. 16r3FFFFFFF.
     From Sedgewick's 'Algorithms', based on Lehmer's method"

    "the times: is a kludge - times does not convert to LargeInteger on overflow"
    self step.
    ^ seed

    "|r|
     r := Random new.
     Transcript showCR:r nextInteger.
     Transcript showCR:r nextInteger.
     Transcript showCR:r nextInteger.
     Transcript showCR:r nextInteger.
    "

    "Modified: 1.4.1997 / 22:42:53 / cg"
!

nextIntegerBetween:start and:stop
    "return an integral random number between start and stop"

    |rnd|

    rnd := self next.
    rnd := rnd * (stop asFloat - start asFloat + 1.0).
    ^ (rnd + start) truncated.

    "|r|
     r := Random new.
     Transcript showCR:(r nextIntegerBetween:1 and:10).
     Transcript showCR:(r nextIntegerBetween:1 and:10).
     Transcript showCR:(r nextIntegerBetween:1 and:10).
     Transcript showCR:(r nextIntegerBetween:1 and:10).
    "

    "Modified: 21.8.1997 / 18:10:08 / cg"
!

nextMatchFor: aNumber
    "generate the next random, return true iff it has the same
     value as aNumber. Redefined to avoid endless reading."

    ^self next = aNumber
! !

!Random methodsFor:'blocked methods'!

contents
    "blocked from use - contents makes no sense for random generators"

    self shouldNotImplement
!

nextPut: value
    "blocked from use - it makes no sense for randoms"

    self shouldNotImplement
! !

!Random methodsFor:'private'!

setSeed
    "set the initial seed value based on the current time"

    seed := Time millisecondClockValue bitAnd:16rFFFF.
    multiplier := 2311.
    increment := 25367.
    modulus := 120050.

"/    seed := Time secondClock bitAnd: 16r3FFFFFFF
"/    multiplier := 31415821.
"/    modulus := 16r3FFFFFFF.
"/    increment := 1.

    "Modified: 1.4.1997 / 22:44:13 / cg"
!

step
    "compute the next random integer"

    "/ seed := (seed times:31415821) + 1 bitAnd: 16r3FFFFFFF.
    seed := seed * multiplier + increment \\ modulus

    "Created: 1.4.1997 / 22:40:45 / cg"
    "Modified: 1.4.1997 / 22:43:01 / cg"
! !

!Random methodsFor:'testing'!

atEnd
    "instances of Random can always give more numbers"

    ^ false
!

isReadable
    ^ true
!

isWritable
    ^ false

    "Created: 1.4.1997 / 22:38:27 / cg"
! !

!Random class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Random.st,v 1.20 1997-08-21 16:10:25 cg Exp $'
! !