module Level.Shuffle where import System.Random import qualified Data.Vector as V import Data.Vector ((//), (!)) data Section t = FixedSection [t] | ShuffleableSection [t] -- This intentionally is biased toward leaving some items in original order. shuffle :: StdGen -> Section t -> [t] shuffle _ (FixedSection l) = l shuffle r (ShuffleableSection l) = swap (length l) r (V.fromList l) where swap 0 _ v = V.toList v swap n g v = let range = (0, V.length v - 1) (p1, g') = randomR range g (p2, g'') = randomR range g' in swap (n - 1) g'' (v // [(p1, v ! p2), (p2, v ! p1)]) asis :: Section t -> [t] asis (FixedSection l) = l asis (ShuffleableSection l) = l