smalltalk
/
osmo-st-all
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-all/grease/GST/Core/GRGSTRandomProvider.st

61 lines
1.2 KiB
Smalltalk
Raw Blame History

This file contains invisible Unicode characters

This file contains invisible Unicode characters that are indistinguishable to humans but may be processed differently by a computer. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

GRObject subclass: GRGSTRandomProvider [
<comment: nil>
<category: 'Grease-GST-Core'>
GRGSTRandomProvider class [
| mutex generator |
]
GRGSTRandomProvider class >> initialize [
<category: 'private'>
GRPlatform current addToStartUpList: self.
self startUp
]
GRGSTRandomProvider class >> randomClass [
<category: 'private'>
^Random
]
GRGSTRandomProvider class >> unload [
<category: 'private'>
GRPlatform current removeFromStartUpList: self
]
GRGSTRandomProvider class >> nextInt: anInteger [
"Answer a random integer in the interval [1, anInteger]"
<category: 'public'>
^mutex critical: [generator nextInt: anInteger]
]
GRGSTRandomProvider class >> randomFrom: aCollection [
<category: 'public'>
| random count |
random := self nextInt: aCollection size.
^aCollection isSequenceable
ifTrue: [aCollection at: random]
ifFalse:
[count := 1.
aCollection do:
[:ea |
count = random ifTrue: [^ea].
count := count + 1]]
]
GRGSTRandomProvider class >> startUp [
<category: 'class initialization'>
generator := self randomClass new.
mutex := Semaphore forMutualExclusion
]
]
Eval [
GRGSTRandomProvider initialize
]