{-
	Copyright (C) 2011 Dr. Alistair Ward

	This program 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 3 of the License, or
	(at your option) any later version.

	This program 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 this program.  If not, see <http://www.gnu.org/licenses/>.
-}
{- |
 [@AUTHOR@]	Dr. Alistair Ward

 [@DESCRIPTION@]	Utilities related to random-numbers.
-}

module ToolShed.System.Random(
-- * Functions
	randomGens,
	shuffle,
	generateSelection,
	generateSelectionFromBounded,
	select
) where

import qualified	Control.Arrow
import qualified	Data.List
import qualified	Data.Ord
import qualified	System.Random

-- | Constructs an infinite list of independent random-generators.
randomGens :: System.Random.RandomGen randomGen => randomGen -> [randomGen]
randomGens	= uncurry (:) . Control.Arrow.second randomGens {-recurse-} . System.Random.split

{- |
	* Shuffles the specified finite list.

	* The resulting list has the same length and constituents as the original; only the order has changed.

	* CAVEAT: the implementation /zips/ a list of integers, with the specified polymorphic list, then sorts it,
	but when identical random integers are generated, the sort-algorithm being /stable/ always return the corresponding items in their original order.
	The shuffle is therefore imperfect,
	but on a /64-bit/ machine, it would need such a large list of items, for the probability of randomly generating two identical integers, to be significant,
	that /sort/ probably wouldn't return in a reasonable time anyway.
	Ideally, it would be amended to use an /unstable/ sort-algorithm.
-}
shuffle :: System.Random.RandomGen randomGen => randomGen -> [a] -> [a]
shuffle randomGen	= map snd . Data.List.sortBy (Data.Ord.comparing fst) . zip (System.Random.randoms randomGen :: [Int])

{- |
	* Generate an infinite list of items, each randomly selected from the specified finite list.

	* CAVEAT: because the selections are made non-destructively, duplicates may be returned; cf. 'shuffle'.
-}
generateSelection :: System.Random.RandomGen randomGen => randomGen -> [a] -> [a]
generateSelection randomGen l	= map (l !!) $ System.Random.randomRs (0, pred $ length l) randomGen

-- | Return a random element from the specified list.
select :: System.Random.RandomGen randomGen => randomGen -> [a] -> a
select _ []		= error "ToolShed.System.Random.generateSelection:\tnull list"
select randomGen l	= head $ generateSelection randomGen l

{- |
	* Generate an infinite list of items, each randomly selected, from the specified finite list of /bounded/ items.

	* Because the selections are made non-destructively, duplicates may be returned.

	* E.g. @ (generateSelectionFromBounded `fmap` System.Random.getStdGen) :: IO [Bool] @.
-}
generateSelectionFromBounded :: (System.Random.RandomGen randomGen, Bounded a, System.Random.Random a) => randomGen -> [a]
generateSelectionFromBounded	= System.Random.randomRs (minBound, maxBound)