RandomGenerator.st
author Stefan Vogel <sv@exept.de>
Tue, 30 Mar 2010 15:39:21 +0200
changeset 2439 8ef4ad63fb9b
parent 2438 3601d0065aff
child 2440 1460919397a4
permissions -rw-r--r--
comment/format in: #nextBoolean changed: #new #nextByte #nextBytes: #nextInteger Support for Windows builtin random generator.

"
 COPYRIGHT (c) 2007 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic2' }"

Object subclass:#RandomGenerator
	instanceVariableNames:''
	classVariableNames:'RandFile SharedGenerator'
	poolDictionaries:''
	category:'Magnitude-Numbers'
!

!RandomGenerator class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2007 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    This is a Random number generator, which uses either a OS random number generator,
    or a ST/X internal random number generator.

    [author:]
        Stefan Vogel

    [see also:]
        Random HashRandom Rc4Stream

    [instance variables:]

    [class variables:]
        RandFile        the FileStream we get random numbers from
"
! !

!RandomGenerator class methodsFor:'initialization'!

initialize
    "want to be informed when returning from snapshot"

    ObjectMemory addDependent:self.


!

openRandFile
    "try to open a random device"

    |randDevName|

    RandFile isStream ifTrue:[
        RandFile close.
    ].

    RandFile := false.              "prevent retry"

    randDevName := self randPath.
    randDevName notNil ifTrue:[
        randDevName := randDevName asFilename.
        randDevName isReadable ifTrue:[
            RandFile := randDevName readStream
        ].
    ].
! !

!RandomGenerator class methodsFor:'instance creation'!

new
    "return a new random number generator.
     Try to get system random numbers from device (e.g. in LINUX).
     If no system random nubers are available, fall back to
     a cryptographic secure PRNG (part of the extra libcrypt package). 
     As last resort fallback to the cryptographic insecure linear builtin PRNG"

    |result|

    SharedGenerator notNil ifTrue:[
        "each time, we do an new, add some entropy to the SharedGenerator"
        SharedGenerator addEntropy:OperatingSystem getMicrosecondTime.
        ^ SharedGenerator.
    ].

    [
        result := OperatingSystem randomBytesInto:(ByteArray new:1).
    ] on:PrimitiveFailure do:[:ex| ].

    result notNil ifTrue:[
        "OperatingSystem knows how to get random bytes"
        RandFile := true.
        SharedGenerator := self basicNew.
        ^ SharedGenerator.
    ] ifFalse:[
        RandFile isNil ifTrue:[
            self openRandFile.
        ].
        RandFile isStream ifTrue:[
            SharedGenerator := self basicNew.
            ^ SharedGenerator.
        ].
    ].

    Rc4Cipher notNil ifTrue:[
        SharedGenerator := Rc4Cipher random.
        ^ SharedGenerator.
    ].

    SharedGenerator := Random sharedGenerator.
    ^ SharedGenerator.
!

random
    "alias for new - protocol compatibility with StreamCiphers"

    ^ self new
! !

!RandomGenerator class methodsFor:'adding entropy'!

addEntropy:entropyBytes
    SharedGenerator notNil ifTrue:[
        SharedGenerator addEntropy:entropyBytes
    ].
! !

!RandomGenerator class methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    "handle image restarts and flush any device resource handles"

    SharedGenerator := nil.
    RandFile notNil ifTrue:[
        RandFile := nil.
        self openRandFile.
    ].
! !

!RandomGenerator class methodsFor:'queries'!

randPath
    "path to a file/device that is a source or random numbers"

    OperatingSystem isUNIXlike ifTrue:[^ '/dev/urandom'].
    ^ nil.
! !

!RandomGenerator methodsFor:'adding entropy'!

addEntropy:entropyBytes
    "add some entropy - ignored here, since I am file based"

    ^ self
! !

!RandomGenerator methodsFor:'basic reading'!

nextByte
    "get the next random byte"

    RandFile == true ifTrue:[
        ^ OperatingSystem randomBytesInto:1.
    ].

    ^ RandFile nextByte

    "
      RandomGenerator new nextByte
    "

    "
     Distribution should be equal:

     |r bag|
     r := RandomGenerator new.
     bag := Bag new.
     1000000 timesRepeat:[
         bag add:(r nextByte).
     ].
     bag.
     Transcript showCR:bag contents
    "

    "Created: / 11.11.1999 / 09:25:39 / stefan"
!

nextBytes:cnt
    "get the next cnt random bytes"

    RandFile == true ifTrue:[
        ^ OperatingSystem randomBytesInto:(ByteArray new:cnt).
    ].
    ^ RandFile nextBytes:cnt.

    "
      RandomGenerator new nextBytes:4
    "

    "Created: / 11.11.1999 / 09:25:39 / stefan"
    "Modified: / 11.11.1999 / 09:52:26 / stefan"
!

nextInteger
    "return the next integral random number,
     in the range 0 .. 16r3FFFFFFF."

    |res|

    RandFile == true ifTrue:[
        ^ OperatingSystem randomBytesInto:4.
    ].

    res := self nextBytes:4.
    ^ ((((((res at:1) bitAnd:16r3F) * 256) + (res at:2)) * 256) + (res at:3)) * 256 + (res at:4)



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

    "Modified: / 11.11.1999 / 10:08:10 / stefan"
! !

!RandomGenerator methodsFor:'reading'!

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

    ^ self nextInteger / 16r3fffffff asFloat

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

    "Modified: / 11.11.1999 / 10:31:35 / stefan"
!

nextBetween:start and:stop
    "return a random number between start and stop."

    |rnd|

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

    "
     |r|
     r := RandomGenerator 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).
    "

    "Created: / 11.11.1999 / 10:27:56 / stefan"
!

nextBoolean
    "return true or false by random"

    ^ self nextByte <= 127

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

    "
     Distribution should approach 50/50:

     |r bag|
     r := RandomGenerator new.
     bag := Bag new.
     1000000 timesRepeat:[
         bag add:(r nextBoolean).
     ].
     Transcript showCR:bag contents
    "

    "Created: / 11.11.1999 / 09:25:39 / stefan"
    "Modified: / 12.11.1999 / 17:22:01 / stefan"
!

nextCharacters:cnt
    "get the next cnt printable characters.
     We answer characters in the ascii range (codepoints 32 - 127)"

    |bytes string|

    bytes := self nextBytes:cnt.
    string := String new:cnt.

    bytes keysAndValuesDo:[:eachIndex :eachByte|
        string at:eachIndex put:(Character value:(eachByte \\ 95 + 32)).
    ].

    ^ string


    "
      RandomGenerator new nextCharacters:8
    "
!

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

    |rnd|

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

    "
     |r|
     r := RandomGenerator 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).
    "

    "
     |r bag|
     r := RandomGenerator new.
     bag := Bag new.
     1000000 timesRepeat:[
         bag add:(r nextIntegerBetween:-1 and:1).
     ].
     Transcript showCR:bag contents
    "

    "Created: / 11.11.1999 / 10:28:36 / stefan"
!

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

    ^ self next = aNumber

    "Created: / 11.11.1999 / 10:29:32 / stefan"
! !

!RandomGenerator methodsFor:'writing'!

nextPut:something
    "change the random pool by feeding in something.
     Something should be some unpredictable, random event.
     Ignored here"


!

nextPutAll:something
    "change the random pool by feeding in something.
     Something should be some unpredictable, random event.
     Ignored here"

! !

!RandomGenerator class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/RandomGenerator.st,v 1.7 2010-03-30 13:39:21 stefan Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic2/RandomGenerator.st,v 1.7 2010-03-30 13:39:21 stefan Exp $'
! !

RandomGenerator initialize!